gcov: make profile merging smarter
[official-gcc.git] / gcc / gimplify.c
blobd8e4b13934952c31005694a8aad238f51eb094b8
1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2021 Free Software Foundation, Inc.
4 Major work done by Sebastian Pop <s.pop@laposte.net>,
5 Diego Novillo <dnovillo@redhat.com> and Jason Merrill <jason@redhat.com>.
7 This file is part of GCC.
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
17 for more details.
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3. If not see
21 <http://www.gnu.org/licenses/>. */
23 #include "config.h"
24 #include "system.h"
25 #include "coretypes.h"
26 #include "backend.h"
27 #include "target.h"
28 #include "rtl.h"
29 #include "tree.h"
30 #include "memmodel.h"
31 #include "tm_p.h"
32 #include "gimple.h"
33 #include "gimple-predict.h"
34 #include "tree-pass.h" /* FIXME: only for PROP_gimple_any */
35 #include "ssa.h"
36 #include "cgraph.h"
37 #include "tree-pretty-print.h"
38 #include "diagnostic-core.h"
39 #include "alias.h"
40 #include "fold-const.h"
41 #include "calls.h"
42 #include "varasm.h"
43 #include "stmt.h"
44 #include "expr.h"
45 #include "gimple-fold.h"
46 #include "tree-eh.h"
47 #include "gimplify.h"
48 #include "gimple-iterator.h"
49 #include "stor-layout.h"
50 #include "print-tree.h"
51 #include "tree-iterator.h"
52 #include "tree-inline.h"
53 #include "langhooks.h"
54 #include "tree-cfg.h"
55 #include "tree-ssa.h"
56 #include "omp-general.h"
57 #include "omp-low.h"
58 #include "gimple-low.h"
59 #include "gomp-constants.h"
60 #include "splay-tree.h"
61 #include "gimple-walk.h"
62 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
63 #include "builtins.h"
64 #include "stringpool.h"
65 #include "attribs.h"
66 #include "asan.h"
67 #include "dbgcnt.h"
68 #include "omp-offload.h"
69 #include "context.h"
70 #include "tree-nested.h"
72 /* Hash set of poisoned variables in a bind expr. */
73 static hash_set<tree> *asan_poisoned_variables = NULL;
75 enum gimplify_omp_var_data
77 GOVD_SEEN = 0x000001,
78 GOVD_EXPLICIT = 0x000002,
79 GOVD_SHARED = 0x000004,
80 GOVD_PRIVATE = 0x000008,
81 GOVD_FIRSTPRIVATE = 0x000010,
82 GOVD_LASTPRIVATE = 0x000020,
83 GOVD_REDUCTION = 0x000040,
84 GOVD_LOCAL = 0x00080,
85 GOVD_MAP = 0x000100,
86 GOVD_DEBUG_PRIVATE = 0x000200,
87 GOVD_PRIVATE_OUTER_REF = 0x000400,
88 GOVD_LINEAR = 0x000800,
89 GOVD_ALIGNED = 0x001000,
91 /* Flag for GOVD_MAP: don't copy back. */
92 GOVD_MAP_TO_ONLY = 0x002000,
94 /* Flag for GOVD_LINEAR or GOVD_LASTPRIVATE: no outer reference. */
95 GOVD_LINEAR_LASTPRIVATE_NO_OUTER = 0x004000,
97 GOVD_MAP_0LEN_ARRAY = 0x008000,
99 /* Flag for GOVD_MAP, if it is always, to or always, tofrom mapping. */
100 GOVD_MAP_ALWAYS_TO = 0x010000,
102 /* Flag for shared vars that are or might be stored to in the region. */
103 GOVD_WRITTEN = 0x020000,
105 /* Flag for GOVD_MAP, if it is a forced mapping. */
106 GOVD_MAP_FORCE = 0x040000,
108 /* Flag for GOVD_MAP: must be present already. */
109 GOVD_MAP_FORCE_PRESENT = 0x080000,
111 /* Flag for GOVD_MAP: only allocate. */
112 GOVD_MAP_ALLOC_ONLY = 0x100000,
114 /* Flag for GOVD_MAP: only copy back. */
115 GOVD_MAP_FROM_ONLY = 0x200000,
117 GOVD_NONTEMPORAL = 0x400000,
119 /* Flag for GOVD_LASTPRIVATE: conditional modifier. */
120 GOVD_LASTPRIVATE_CONDITIONAL = 0x800000,
122 GOVD_CONDTEMP = 0x1000000,
124 /* Flag for GOVD_REDUCTION: inscan seen in {in,ex}clusive clause. */
125 GOVD_REDUCTION_INSCAN = 0x2000000,
127 /* Flag for GOVD_MAP: (struct) vars that have pointer attachments for
128 fields. */
129 GOVD_MAP_HAS_ATTACHMENTS = 0x4000000,
131 /* Flag for GOVD_FIRSTPRIVATE: OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT. */
132 GOVD_FIRSTPRIVATE_IMPLICIT = 0x8000000,
134 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
135 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
136 | GOVD_LOCAL)
140 enum omp_region_type
142 ORT_WORKSHARE = 0x00,
143 ORT_TASKGROUP = 0x01,
144 ORT_SIMD = 0x04,
146 ORT_PARALLEL = 0x08,
147 ORT_COMBINED_PARALLEL = ORT_PARALLEL | 1,
149 ORT_TASK = 0x10,
150 ORT_UNTIED_TASK = ORT_TASK | 1,
151 ORT_TASKLOOP = ORT_TASK | 2,
152 ORT_UNTIED_TASKLOOP = ORT_UNTIED_TASK | 2,
154 ORT_TEAMS = 0x20,
155 ORT_COMBINED_TEAMS = ORT_TEAMS | 1,
156 ORT_HOST_TEAMS = ORT_TEAMS | 2,
157 ORT_COMBINED_HOST_TEAMS = ORT_COMBINED_TEAMS | 2,
159 /* Data region. */
160 ORT_TARGET_DATA = 0x40,
162 /* Data region with offloading. */
163 ORT_TARGET = 0x80,
164 ORT_COMBINED_TARGET = ORT_TARGET | 1,
165 ORT_IMPLICIT_TARGET = ORT_TARGET | 2,
167 /* OpenACC variants. */
168 ORT_ACC = 0x100, /* A generic OpenACC region. */
169 ORT_ACC_DATA = ORT_ACC | ORT_TARGET_DATA, /* Data construct. */
170 ORT_ACC_PARALLEL = ORT_ACC | ORT_TARGET, /* Parallel construct */
171 ORT_ACC_KERNELS = ORT_ACC | ORT_TARGET | 2, /* Kernels construct. */
172 ORT_ACC_SERIAL = ORT_ACC | ORT_TARGET | 4, /* Serial construct. */
173 ORT_ACC_HOST_DATA = ORT_ACC | ORT_TARGET_DATA | 2, /* Host data. */
175 /* Dummy OpenMP region, used to disable expansion of
176 DECL_VALUE_EXPRs in taskloop pre body. */
177 ORT_NONE = 0x200
180 /* Gimplify hashtable helper. */
182 struct gimplify_hasher : free_ptr_hash <elt_t>
184 static inline hashval_t hash (const elt_t *);
185 static inline bool equal (const elt_t *, const elt_t *);
188 struct gimplify_ctx
190 struct gimplify_ctx *prev_context;
192 vec<gbind *> bind_expr_stack;
193 tree temps;
194 gimple_seq conditional_cleanups;
195 tree exit_label;
196 tree return_temp;
198 vec<tree> case_labels;
199 hash_set<tree> *live_switch_vars;
200 /* The formal temporary table. Should this be persistent? */
201 hash_table<gimplify_hasher> *temp_htab;
203 int conditions;
204 unsigned into_ssa : 1;
205 unsigned allow_rhs_cond_expr : 1;
206 unsigned in_cleanup_point_expr : 1;
207 unsigned keep_stack : 1;
208 unsigned save_stack : 1;
209 unsigned in_switch_expr : 1;
212 enum gimplify_defaultmap_kind
214 GDMK_SCALAR,
215 GDMK_SCALAR_TARGET, /* w/ Fortran's target attr, implicit mapping, only. */
216 GDMK_AGGREGATE,
217 GDMK_ALLOCATABLE,
218 GDMK_POINTER
221 struct gimplify_omp_ctx
223 struct gimplify_omp_ctx *outer_context;
224 splay_tree variables;
225 hash_set<tree> *privatized_types;
226 tree clauses;
227 /* Iteration variables in an OMP_FOR. */
228 vec<tree> loop_iter_var;
229 location_t location;
230 enum omp_clause_default_kind default_kind;
231 enum omp_region_type region_type;
232 enum tree_code code;
233 bool combined_loop;
234 bool distribute;
235 bool target_firstprivatize_array_bases;
236 bool add_safelen1;
237 bool order_concurrent;
238 bool has_depend;
239 bool in_for_exprs;
240 int defaultmap[5];
243 static struct gimplify_ctx *gimplify_ctxp;
244 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
245 static bool in_omp_construct;
247 /* Forward declaration. */
248 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
249 static hash_map<tree, tree> *oacc_declare_returns;
250 static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
251 bool (*) (tree), fallback_t, bool);
253 /* Shorter alias name for the above function for use in gimplify.c
254 only. */
256 static inline void
257 gimplify_seq_add_stmt (gimple_seq *seq_p, gimple *gs)
259 gimple_seq_add_stmt_without_update (seq_p, gs);
262 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
263 NULL, a new sequence is allocated. This function is
264 similar to gimple_seq_add_seq, but does not scan the operands.
265 During gimplification, we need to manipulate statement sequences
266 before the def/use vectors have been constructed. */
268 static void
269 gimplify_seq_add_seq (gimple_seq *dst_p, gimple_seq src)
271 gimple_stmt_iterator si;
273 if (src == NULL)
274 return;
276 si = gsi_last (*dst_p);
277 gsi_insert_seq_after_without_update (&si, src, GSI_NEW_STMT);
281 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
282 and popping gimplify contexts. */
284 static struct gimplify_ctx *ctx_pool = NULL;
286 /* Return a gimplify context struct from the pool. */
288 static inline struct gimplify_ctx *
289 ctx_alloc (void)
291 struct gimplify_ctx * c = ctx_pool;
293 if (c)
294 ctx_pool = c->prev_context;
295 else
296 c = XNEW (struct gimplify_ctx);
298 memset (c, '\0', sizeof (*c));
299 return c;
302 /* Put gimplify context C back into the pool. */
304 static inline void
305 ctx_free (struct gimplify_ctx *c)
307 c->prev_context = ctx_pool;
308 ctx_pool = c;
311 /* Free allocated ctx stack memory. */
313 void
314 free_gimplify_stack (void)
316 struct gimplify_ctx *c;
318 while ((c = ctx_pool))
320 ctx_pool = c->prev_context;
321 free (c);
326 /* Set up a context for the gimplifier. */
328 void
329 push_gimplify_context (bool in_ssa, bool rhs_cond_ok)
331 struct gimplify_ctx *c = ctx_alloc ();
333 c->prev_context = gimplify_ctxp;
334 gimplify_ctxp = c;
335 gimplify_ctxp->into_ssa = in_ssa;
336 gimplify_ctxp->allow_rhs_cond_expr = rhs_cond_ok;
339 /* Tear down a context for the gimplifier. If BODY is non-null, then
340 put the temporaries into the outer BIND_EXPR. Otherwise, put them
341 in the local_decls.
343 BODY is not a sequence, but the first tuple in a sequence. */
345 void
346 pop_gimplify_context (gimple *body)
348 struct gimplify_ctx *c = gimplify_ctxp;
350 gcc_assert (c
351 && (!c->bind_expr_stack.exists ()
352 || c->bind_expr_stack.is_empty ()));
353 c->bind_expr_stack.release ();
354 gimplify_ctxp = c->prev_context;
356 if (body)
357 declare_vars (c->temps, body, false);
358 else
359 record_vars (c->temps);
361 delete c->temp_htab;
362 c->temp_htab = NULL;
363 ctx_free (c);
366 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
368 static void
369 gimple_push_bind_expr (gbind *bind_stmt)
371 gimplify_ctxp->bind_expr_stack.reserve (8);
372 gimplify_ctxp->bind_expr_stack.safe_push (bind_stmt);
375 /* Pop the first element off the stack of bindings. */
377 static void
378 gimple_pop_bind_expr (void)
380 gimplify_ctxp->bind_expr_stack.pop ();
383 /* Return the first element of the stack of bindings. */
385 gbind *
386 gimple_current_bind_expr (void)
388 return gimplify_ctxp->bind_expr_stack.last ();
391 /* Return the stack of bindings created during gimplification. */
393 vec<gbind *>
394 gimple_bind_expr_stack (void)
396 return gimplify_ctxp->bind_expr_stack;
399 /* Return true iff there is a COND_EXPR between us and the innermost
400 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
402 static bool
403 gimple_conditional_context (void)
405 return gimplify_ctxp->conditions > 0;
408 /* Note that we've entered a COND_EXPR. */
410 static void
411 gimple_push_condition (void)
413 #ifdef ENABLE_GIMPLE_CHECKING
414 if (gimplify_ctxp->conditions == 0)
415 gcc_assert (gimple_seq_empty_p (gimplify_ctxp->conditional_cleanups));
416 #endif
417 ++(gimplify_ctxp->conditions);
420 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
421 now, add any conditional cleanups we've seen to the prequeue. */
423 static void
424 gimple_pop_condition (gimple_seq *pre_p)
426 int conds = --(gimplify_ctxp->conditions);
428 gcc_assert (conds >= 0);
429 if (conds == 0)
431 gimplify_seq_add_seq (pre_p, gimplify_ctxp->conditional_cleanups);
432 gimplify_ctxp->conditional_cleanups = NULL;
436 /* A stable comparison routine for use with splay trees and DECLs. */
438 static int
439 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
441 tree a = (tree) xa;
442 tree b = (tree) xb;
444 return DECL_UID (a) - DECL_UID (b);
447 /* Create a new omp construct that deals with variable remapping. */
449 static struct gimplify_omp_ctx *
450 new_omp_context (enum omp_region_type region_type)
452 struct gimplify_omp_ctx *c;
454 c = XCNEW (struct gimplify_omp_ctx);
455 c->outer_context = gimplify_omp_ctxp;
456 c->variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
457 c->privatized_types = new hash_set<tree>;
458 c->location = input_location;
459 c->region_type = region_type;
460 if ((region_type & ORT_TASK) == 0)
461 c->default_kind = OMP_CLAUSE_DEFAULT_SHARED;
462 else
463 c->default_kind = OMP_CLAUSE_DEFAULT_UNSPECIFIED;
464 c->defaultmap[GDMK_SCALAR] = GOVD_MAP;
465 c->defaultmap[GDMK_SCALAR_TARGET] = GOVD_MAP;
466 c->defaultmap[GDMK_AGGREGATE] = GOVD_MAP;
467 c->defaultmap[GDMK_ALLOCATABLE] = GOVD_MAP;
468 c->defaultmap[GDMK_POINTER] = GOVD_MAP;
470 return c;
473 /* Destroy an omp construct that deals with variable remapping. */
475 static void
476 delete_omp_context (struct gimplify_omp_ctx *c)
478 splay_tree_delete (c->variables);
479 delete c->privatized_types;
480 c->loop_iter_var.release ();
481 XDELETE (c);
484 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
485 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
487 /* Both gimplify the statement T and append it to *SEQ_P. This function
488 behaves exactly as gimplify_stmt, but you don't have to pass T as a
489 reference. */
491 void
492 gimplify_and_add (tree t, gimple_seq *seq_p)
494 gimplify_stmt (&t, seq_p);
497 /* Gimplify statement T into sequence *SEQ_P, and return the first
498 tuple in the sequence of generated tuples for this statement.
499 Return NULL if gimplifying T produced no tuples. */
501 static gimple *
502 gimplify_and_return_first (tree t, gimple_seq *seq_p)
504 gimple_stmt_iterator last = gsi_last (*seq_p);
506 gimplify_and_add (t, seq_p);
508 if (!gsi_end_p (last))
510 gsi_next (&last);
511 return gsi_stmt (last);
513 else
514 return gimple_seq_first_stmt (*seq_p);
517 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
518 LHS, or for a call argument. */
520 static bool
521 is_gimple_mem_rhs (tree t)
523 /* If we're dealing with a renamable type, either source or dest must be
524 a renamed variable. */
525 if (is_gimple_reg_type (TREE_TYPE (t)))
526 return is_gimple_val (t);
527 else
528 return is_gimple_val (t) || is_gimple_lvalue (t);
531 /* Return true if T is a CALL_EXPR or an expression that can be
532 assigned to a temporary. Note that this predicate should only be
533 used during gimplification. See the rationale for this in
534 gimplify_modify_expr. */
536 static bool
537 is_gimple_reg_rhs_or_call (tree t)
539 return (get_gimple_rhs_class (TREE_CODE (t)) != GIMPLE_INVALID_RHS
540 || TREE_CODE (t) == CALL_EXPR);
543 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
544 this predicate should only be used during gimplification. See the
545 rationale for this in gimplify_modify_expr. */
547 static bool
548 is_gimple_mem_rhs_or_call (tree t)
550 /* If we're dealing with a renamable type, either source or dest must be
551 a renamed variable. */
552 if (is_gimple_reg_type (TREE_TYPE (t)))
553 return is_gimple_val (t);
554 else
555 return (is_gimple_val (t)
556 || is_gimple_lvalue (t)
557 || TREE_CLOBBER_P (t)
558 || TREE_CODE (t) == CALL_EXPR);
561 /* Create a temporary with a name derived from VAL. Subroutine of
562 lookup_tmp_var; nobody else should call this function. */
564 static inline tree
565 create_tmp_from_val (tree val)
567 /* Drop all qualifiers and address-space information from the value type. */
568 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (val));
569 tree var = create_tmp_var (type, get_name (val));
570 return var;
573 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
574 an existing expression temporary. */
576 static tree
577 lookup_tmp_var (tree val, bool is_formal)
579 tree ret;
581 /* If not optimizing, never really reuse a temporary. local-alloc
582 won't allocate any variable that is used in more than one basic
583 block, which means it will go into memory, causing much extra
584 work in reload and final and poorer code generation, outweighing
585 the extra memory allocation here. */
586 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
587 ret = create_tmp_from_val (val);
588 else
590 elt_t elt, *elt_p;
591 elt_t **slot;
593 elt.val = val;
594 if (!gimplify_ctxp->temp_htab)
595 gimplify_ctxp->temp_htab = new hash_table<gimplify_hasher> (1000);
596 slot = gimplify_ctxp->temp_htab->find_slot (&elt, INSERT);
597 if (*slot == NULL)
599 elt_p = XNEW (elt_t);
600 elt_p->val = val;
601 elt_p->temp = ret = create_tmp_from_val (val);
602 *slot = elt_p;
604 else
606 elt_p = *slot;
607 ret = elt_p->temp;
611 return ret;
614 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
616 static tree
617 internal_get_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
618 bool is_formal, bool allow_ssa)
620 tree t, mod;
622 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
623 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
624 gimplify_expr (&val, pre_p, post_p, is_gimple_reg_rhs_or_call,
625 fb_rvalue);
627 if (allow_ssa
628 && gimplify_ctxp->into_ssa
629 && is_gimple_reg_type (TREE_TYPE (val)))
631 t = make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val)));
632 if (! gimple_in_ssa_p (cfun))
634 const char *name = get_name (val);
635 if (name)
636 SET_SSA_NAME_VAR_OR_IDENTIFIER (t, create_tmp_var_name (name));
639 else
640 t = lookup_tmp_var (val, is_formal);
642 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
644 SET_EXPR_LOCATION (mod, EXPR_LOC_OR_LOC (val, input_location));
646 /* gimplify_modify_expr might want to reduce this further. */
647 gimplify_and_add (mod, pre_p);
648 ggc_free (mod);
650 return t;
653 /* Return a formal temporary variable initialized with VAL. PRE_P is as
654 in gimplify_expr. Only use this function if:
656 1) The value of the unfactored expression represented by VAL will not
657 change between the initialization and use of the temporary, and
658 2) The temporary will not be otherwise modified.
660 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
661 and #2 means it is inappropriate for && temps.
663 For other cases, use get_initialized_tmp_var instead. */
665 tree
666 get_formal_tmp_var (tree val, gimple_seq *pre_p)
668 return internal_get_tmp_var (val, pre_p, NULL, true, true);
671 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
672 are as in gimplify_expr. */
674 tree
675 get_initialized_tmp_var (tree val, gimple_seq *pre_p,
676 gimple_seq *post_p /* = NULL */,
677 bool allow_ssa /* = true */)
679 return internal_get_tmp_var (val, pre_p, post_p, false, allow_ssa);
682 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
683 generate debug info for them; otherwise don't. */
685 void
686 declare_vars (tree vars, gimple *gs, bool debug_info)
688 tree last = vars;
689 if (last)
691 tree temps, block;
693 gbind *scope = as_a <gbind *> (gs);
695 temps = nreverse (last);
697 block = gimple_bind_block (scope);
698 gcc_assert (!block || TREE_CODE (block) == BLOCK);
699 if (!block || !debug_info)
701 DECL_CHAIN (last) = gimple_bind_vars (scope);
702 gimple_bind_set_vars (scope, temps);
704 else
706 /* We need to attach the nodes both to the BIND_EXPR and to its
707 associated BLOCK for debugging purposes. The key point here
708 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
709 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
710 if (BLOCK_VARS (block))
711 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
712 else
714 gimple_bind_set_vars (scope,
715 chainon (gimple_bind_vars (scope), temps));
716 BLOCK_VARS (block) = temps;
722 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
723 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
724 no such upper bound can be obtained. */
726 static void
727 force_constant_size (tree var)
729 /* The only attempt we make is by querying the maximum size of objects
730 of the variable's type. */
732 HOST_WIDE_INT max_size;
734 gcc_assert (VAR_P (var));
736 max_size = max_int_size_in_bytes (TREE_TYPE (var));
738 gcc_assert (max_size >= 0);
740 DECL_SIZE_UNIT (var)
741 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
742 DECL_SIZE (var)
743 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
746 /* Push the temporary variable TMP into the current binding. */
748 void
749 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
751 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
753 /* Later processing assumes that the object size is constant, which might
754 not be true at this point. Force the use of a constant upper bound in
755 this case. */
756 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
757 force_constant_size (tmp);
759 DECL_CONTEXT (tmp) = fn->decl;
760 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
762 record_vars_into (tmp, fn->decl);
765 /* Push the temporary variable TMP into the current binding. */
767 void
768 gimple_add_tmp_var (tree tmp)
770 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
772 /* Later processing assumes that the object size is constant, which might
773 not be true at this point. Force the use of a constant upper bound in
774 this case. */
775 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
776 force_constant_size (tmp);
778 DECL_CONTEXT (tmp) = current_function_decl;
779 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
781 if (gimplify_ctxp)
783 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
784 gimplify_ctxp->temps = tmp;
786 /* Mark temporaries local within the nearest enclosing parallel. */
787 if (gimplify_omp_ctxp)
789 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
790 int flag = GOVD_LOCAL | GOVD_SEEN;
791 while (ctx
792 && (ctx->region_type == ORT_WORKSHARE
793 || ctx->region_type == ORT_TASKGROUP
794 || ctx->region_type == ORT_SIMD
795 || ctx->region_type == ORT_ACC))
797 if (ctx->region_type == ORT_SIMD
798 && TREE_ADDRESSABLE (tmp)
799 && !TREE_STATIC (tmp))
801 if (TREE_CODE (DECL_SIZE_UNIT (tmp)) != INTEGER_CST)
802 ctx->add_safelen1 = true;
803 else if (ctx->in_for_exprs)
804 flag = GOVD_PRIVATE;
805 else
806 flag = GOVD_PRIVATE | GOVD_SEEN;
807 break;
809 ctx = ctx->outer_context;
811 if (ctx)
812 omp_add_variable (ctx, tmp, flag);
815 else if (cfun)
816 record_vars (tmp);
817 else
819 gimple_seq body_seq;
821 /* This case is for nested functions. We need to expose the locals
822 they create. */
823 body_seq = gimple_body (current_function_decl);
824 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
830 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
831 nodes that are referenced more than once in GENERIC functions. This is
832 necessary because gimplification (translation into GIMPLE) is performed
833 by modifying tree nodes in-place, so gimplication of a shared node in a
834 first context could generate an invalid GIMPLE form in a second context.
836 This is achieved with a simple mark/copy/unmark algorithm that walks the
837 GENERIC representation top-down, marks nodes with TREE_VISITED the first
838 time it encounters them, duplicates them if they already have TREE_VISITED
839 set, and finally removes the TREE_VISITED marks it has set.
841 The algorithm works only at the function level, i.e. it generates a GENERIC
842 representation of a function with no nodes shared within the function when
843 passed a GENERIC function (except for nodes that are allowed to be shared).
845 At the global level, it is also necessary to unshare tree nodes that are
846 referenced in more than one function, for the same aforementioned reason.
847 This requires some cooperation from the front-end. There are 2 strategies:
849 1. Manual unsharing. The front-end needs to call unshare_expr on every
850 expression that might end up being shared across functions.
852 2. Deep unsharing. This is an extension of regular unsharing. Instead
853 of calling unshare_expr on expressions that might be shared across
854 functions, the front-end pre-marks them with TREE_VISITED. This will
855 ensure that they are unshared on the first reference within functions
856 when the regular unsharing algorithm runs. The counterpart is that
857 this algorithm must look deeper than for manual unsharing, which is
858 specified by LANG_HOOKS_DEEP_UNSHARING.
860 If there are only few specific cases of node sharing across functions, it is
861 probably easier for a front-end to unshare the expressions manually. On the
862 contrary, if the expressions generated at the global level are as widespread
863 as expressions generated within functions, deep unsharing is very likely the
864 way to go. */
866 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
867 These nodes model computations that must be done once. If we were to
868 unshare something like SAVE_EXPR(i++), the gimplification process would
869 create wrong code. However, if DATA is non-null, it must hold a pointer
870 set that is used to unshare the subtrees of these nodes. */
872 static tree
873 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
875 tree t = *tp;
876 enum tree_code code = TREE_CODE (t);
878 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
879 copy their subtrees if we can make sure to do it only once. */
880 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
882 if (data && !((hash_set<tree> *)data)->add (t))
884 else
885 *walk_subtrees = 0;
888 /* Stop at types, decls, constants like copy_tree_r. */
889 else if (TREE_CODE_CLASS (code) == tcc_type
890 || TREE_CODE_CLASS (code) == tcc_declaration
891 || TREE_CODE_CLASS (code) == tcc_constant)
892 *walk_subtrees = 0;
894 /* Cope with the statement expression extension. */
895 else if (code == STATEMENT_LIST)
898 /* Leave the bulk of the work to copy_tree_r itself. */
899 else
900 copy_tree_r (tp, walk_subtrees, NULL);
902 return NULL_TREE;
905 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
906 If *TP has been visited already, then *TP is deeply copied by calling
907 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
909 static tree
910 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
912 tree t = *tp;
913 enum tree_code code = TREE_CODE (t);
915 /* Skip types, decls, and constants. But we do want to look at their
916 types and the bounds of types. Mark them as visited so we properly
917 unmark their subtrees on the unmark pass. If we've already seen them,
918 don't look down further. */
919 if (TREE_CODE_CLASS (code) == tcc_type
920 || TREE_CODE_CLASS (code) == tcc_declaration
921 || TREE_CODE_CLASS (code) == tcc_constant)
923 if (TREE_VISITED (t))
924 *walk_subtrees = 0;
925 else
926 TREE_VISITED (t) = 1;
929 /* If this node has been visited already, unshare it and don't look
930 any deeper. */
931 else if (TREE_VISITED (t))
933 walk_tree (tp, mostly_copy_tree_r, data, NULL);
934 *walk_subtrees = 0;
937 /* Otherwise, mark the node as visited and keep looking. */
938 else
939 TREE_VISITED (t) = 1;
941 return NULL_TREE;
944 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
945 copy_if_shared_r callback unmodified. */
947 void
948 copy_if_shared (tree *tp, void *data)
950 walk_tree (tp, copy_if_shared_r, data, NULL);
953 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
954 any nested functions. */
956 static void
957 unshare_body (tree fndecl)
959 struct cgraph_node *cgn = cgraph_node::get (fndecl);
960 /* If the language requires deep unsharing, we need a pointer set to make
961 sure we don't repeatedly unshare subtrees of unshareable nodes. */
962 hash_set<tree> *visited
963 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
965 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
966 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
967 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
969 delete visited;
971 if (cgn)
972 for (cgn = first_nested_function (cgn); cgn;
973 cgn = next_nested_function (cgn))
974 unshare_body (cgn->decl);
977 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
978 Subtrees are walked until the first unvisited node is encountered. */
980 static tree
981 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
983 tree t = *tp;
985 /* If this node has been visited, unmark it and keep looking. */
986 if (TREE_VISITED (t))
987 TREE_VISITED (t) = 0;
989 /* Otherwise, don't look any deeper. */
990 else
991 *walk_subtrees = 0;
993 return NULL_TREE;
996 /* Unmark the visited trees rooted at *TP. */
998 static inline void
999 unmark_visited (tree *tp)
1001 walk_tree (tp, unmark_visited_r, NULL, NULL);
1004 /* Likewise, but mark all trees as not visited. */
1006 static void
1007 unvisit_body (tree fndecl)
1009 struct cgraph_node *cgn = cgraph_node::get (fndecl);
1011 unmark_visited (&DECL_SAVED_TREE (fndecl));
1012 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
1013 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
1015 if (cgn)
1016 for (cgn = first_nested_function (cgn);
1017 cgn; cgn = next_nested_function (cgn))
1018 unvisit_body (cgn->decl);
1021 /* Unconditionally make an unshared copy of EXPR. This is used when using
1022 stored expressions which span multiple functions, such as BINFO_VTABLE,
1023 as the normal unsharing process can't tell that they're shared. */
1025 tree
1026 unshare_expr (tree expr)
1028 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1029 return expr;
1032 /* Worker for unshare_expr_without_location. */
1034 static tree
1035 prune_expr_location (tree *tp, int *walk_subtrees, void *)
1037 if (EXPR_P (*tp))
1038 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
1039 else
1040 *walk_subtrees = 0;
1041 return NULL_TREE;
1044 /* Similar to unshare_expr but also prune all expression locations
1045 from EXPR. */
1047 tree
1048 unshare_expr_without_location (tree expr)
1050 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1051 if (EXPR_P (expr))
1052 walk_tree (&expr, prune_expr_location, NULL, NULL);
1053 return expr;
1056 /* Return the EXPR_LOCATION of EXPR, if it (maybe recursively) has
1057 one, OR_ELSE otherwise. The location of a STATEMENT_LISTs
1058 comprising at least one DEBUG_BEGIN_STMT followed by exactly one
1059 EXPR is the location of the EXPR. */
1061 static location_t
1062 rexpr_location (tree expr, location_t or_else = UNKNOWN_LOCATION)
1064 if (!expr)
1065 return or_else;
1067 if (EXPR_HAS_LOCATION (expr))
1068 return EXPR_LOCATION (expr);
1070 if (TREE_CODE (expr) != STATEMENT_LIST)
1071 return or_else;
1073 tree_stmt_iterator i = tsi_start (expr);
1075 bool found = false;
1076 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
1078 found = true;
1079 tsi_next (&i);
1082 if (!found || !tsi_one_before_end_p (i))
1083 return or_else;
1085 return rexpr_location (tsi_stmt (i), or_else);
1088 /* Return TRUE iff EXPR (maybe recursively) has a location; see
1089 rexpr_location for the potential recursion. */
1091 static inline bool
1092 rexpr_has_location (tree expr)
1094 return rexpr_location (expr) != UNKNOWN_LOCATION;
1098 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
1099 contain statements and have a value. Assign its value to a temporary
1100 and give it void_type_node. Return the temporary, or NULL_TREE if
1101 WRAPPER was already void. */
1103 tree
1104 voidify_wrapper_expr (tree wrapper, tree temp)
1106 tree type = TREE_TYPE (wrapper);
1107 if (type && !VOID_TYPE_P (type))
1109 tree *p;
1111 /* Set p to point to the body of the wrapper. Loop until we find
1112 something that isn't a wrapper. */
1113 for (p = &wrapper; p && *p; )
1115 switch (TREE_CODE (*p))
1117 case BIND_EXPR:
1118 TREE_SIDE_EFFECTS (*p) = 1;
1119 TREE_TYPE (*p) = void_type_node;
1120 /* For a BIND_EXPR, the body is operand 1. */
1121 p = &BIND_EXPR_BODY (*p);
1122 break;
1124 case CLEANUP_POINT_EXPR:
1125 case TRY_FINALLY_EXPR:
1126 case TRY_CATCH_EXPR:
1127 TREE_SIDE_EFFECTS (*p) = 1;
1128 TREE_TYPE (*p) = void_type_node;
1129 p = &TREE_OPERAND (*p, 0);
1130 break;
1132 case STATEMENT_LIST:
1134 tree_stmt_iterator i = tsi_last (*p);
1135 TREE_SIDE_EFFECTS (*p) = 1;
1136 TREE_TYPE (*p) = void_type_node;
1137 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
1139 break;
1141 case COMPOUND_EXPR:
1142 /* Advance to the last statement. Set all container types to
1143 void. */
1144 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
1146 TREE_SIDE_EFFECTS (*p) = 1;
1147 TREE_TYPE (*p) = void_type_node;
1149 break;
1151 case TRANSACTION_EXPR:
1152 TREE_SIDE_EFFECTS (*p) = 1;
1153 TREE_TYPE (*p) = void_type_node;
1154 p = &TRANSACTION_EXPR_BODY (*p);
1155 break;
1157 default:
1158 /* Assume that any tree upon which voidify_wrapper_expr is
1159 directly called is a wrapper, and that its body is op0. */
1160 if (p == &wrapper)
1162 TREE_SIDE_EFFECTS (*p) = 1;
1163 TREE_TYPE (*p) = void_type_node;
1164 p = &TREE_OPERAND (*p, 0);
1165 break;
1167 goto out;
1171 out:
1172 if (p == NULL || IS_EMPTY_STMT (*p))
1173 temp = NULL_TREE;
1174 else if (temp)
1176 /* The wrapper is on the RHS of an assignment that we're pushing
1177 down. */
1178 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1179 || TREE_CODE (temp) == MODIFY_EXPR);
1180 TREE_OPERAND (temp, 1) = *p;
1181 *p = temp;
1183 else
1185 temp = create_tmp_var (type, "retval");
1186 *p = build2 (INIT_EXPR, type, temp, *p);
1189 return temp;
1192 return NULL_TREE;
1195 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1196 a temporary through which they communicate. */
1198 static void
1199 build_stack_save_restore (gcall **save, gcall **restore)
1201 tree tmp_var;
1203 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1204 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1205 gimple_call_set_lhs (*save, tmp_var);
1207 *restore
1208 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1209 1, tmp_var);
1212 /* Generate IFN_ASAN_MARK call that poisons shadow of a for DECL variable. */
1214 static tree
1215 build_asan_poison_call_expr (tree decl)
1217 /* Do not poison variables that have size equal to zero. */
1218 tree unit_size = DECL_SIZE_UNIT (decl);
1219 if (zerop (unit_size))
1220 return NULL_TREE;
1222 tree base = build_fold_addr_expr (decl);
1224 return build_call_expr_internal_loc (UNKNOWN_LOCATION, IFN_ASAN_MARK,
1225 void_type_node, 3,
1226 build_int_cst (integer_type_node,
1227 ASAN_MARK_POISON),
1228 base, unit_size);
1231 /* Generate IFN_ASAN_MARK call that would poison or unpoison, depending
1232 on POISON flag, shadow memory of a DECL variable. The call will be
1233 put on location identified by IT iterator, where BEFORE flag drives
1234 position where the stmt will be put. */
1236 static void
1237 asan_poison_variable (tree decl, bool poison, gimple_stmt_iterator *it,
1238 bool before)
1240 tree unit_size = DECL_SIZE_UNIT (decl);
1241 tree base = build_fold_addr_expr (decl);
1243 /* Do not poison variables that have size equal to zero. */
1244 if (zerop (unit_size))
1245 return;
1247 /* It's necessary to have all stack variables aligned to ASAN granularity
1248 bytes. */
1249 gcc_assert (!hwasan_sanitize_p () || hwasan_sanitize_stack_p ());
1250 unsigned shadow_granularity
1251 = hwasan_sanitize_p () ? HWASAN_TAG_GRANULE_SIZE : ASAN_SHADOW_GRANULARITY;
1252 if (DECL_ALIGN_UNIT (decl) <= shadow_granularity)
1253 SET_DECL_ALIGN (decl, BITS_PER_UNIT * shadow_granularity);
1255 HOST_WIDE_INT flags = poison ? ASAN_MARK_POISON : ASAN_MARK_UNPOISON;
1257 gimple *g
1258 = gimple_build_call_internal (IFN_ASAN_MARK, 3,
1259 build_int_cst (integer_type_node, flags),
1260 base, unit_size);
1262 if (before)
1263 gsi_insert_before (it, g, GSI_NEW_STMT);
1264 else
1265 gsi_insert_after (it, g, GSI_NEW_STMT);
1268 /* Generate IFN_ASAN_MARK internal call that depending on POISON flag
1269 either poisons or unpoisons a DECL. Created statement is appended
1270 to SEQ_P gimple sequence. */
1272 static void
1273 asan_poison_variable (tree decl, bool poison, gimple_seq *seq_p)
1275 gimple_stmt_iterator it = gsi_last (*seq_p);
1276 bool before = false;
1278 if (gsi_end_p (it))
1279 before = true;
1281 asan_poison_variable (decl, poison, &it, before);
1284 /* Sort pair of VAR_DECLs A and B by DECL_UID. */
1286 static int
1287 sort_by_decl_uid (const void *a, const void *b)
1289 const tree *t1 = (const tree *)a;
1290 const tree *t2 = (const tree *)b;
1292 int uid1 = DECL_UID (*t1);
1293 int uid2 = DECL_UID (*t2);
1295 if (uid1 < uid2)
1296 return -1;
1297 else if (uid1 > uid2)
1298 return 1;
1299 else
1300 return 0;
1303 /* Generate IFN_ASAN_MARK internal call for all VARIABLES
1304 depending on POISON flag. Created statement is appended
1305 to SEQ_P gimple sequence. */
1307 static void
1308 asan_poison_variables (hash_set<tree> *variables, bool poison, gimple_seq *seq_p)
1310 unsigned c = variables->elements ();
1311 if (c == 0)
1312 return;
1314 auto_vec<tree> sorted_variables (c);
1316 for (hash_set<tree>::iterator it = variables->begin ();
1317 it != variables->end (); ++it)
1318 sorted_variables.safe_push (*it);
1320 sorted_variables.qsort (sort_by_decl_uid);
1322 unsigned i;
1323 tree var;
1324 FOR_EACH_VEC_ELT (sorted_variables, i, var)
1326 asan_poison_variable (var, poison, seq_p);
1328 /* Add use_after_scope_memory attribute for the variable in order
1329 to prevent re-written into SSA. */
1330 if (!lookup_attribute (ASAN_USE_AFTER_SCOPE_ATTRIBUTE,
1331 DECL_ATTRIBUTES (var)))
1332 DECL_ATTRIBUTES (var)
1333 = tree_cons (get_identifier (ASAN_USE_AFTER_SCOPE_ATTRIBUTE),
1334 integer_one_node,
1335 DECL_ATTRIBUTES (var));
1339 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1341 static enum gimplify_status
1342 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1344 tree bind_expr = *expr_p;
1345 bool old_keep_stack = gimplify_ctxp->keep_stack;
1346 bool old_save_stack = gimplify_ctxp->save_stack;
1347 tree t;
1348 gbind *bind_stmt;
1349 gimple_seq body, cleanup;
1350 gcall *stack_save;
1351 location_t start_locus = 0, end_locus = 0;
1352 tree ret_clauses = NULL;
1354 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1356 /* Mark variables seen in this bind expr. */
1357 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1359 if (VAR_P (t))
1361 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1363 /* Mark variable as local. */
1364 if (ctx && ctx->region_type != ORT_NONE && !DECL_EXTERNAL (t))
1366 if (! DECL_SEEN_IN_BIND_EXPR_P (t)
1367 || splay_tree_lookup (ctx->variables,
1368 (splay_tree_key) t) == NULL)
1370 int flag = GOVD_LOCAL;
1371 if (ctx->region_type == ORT_SIMD
1372 && TREE_ADDRESSABLE (t)
1373 && !TREE_STATIC (t))
1375 if (TREE_CODE (DECL_SIZE_UNIT (t)) != INTEGER_CST)
1376 ctx->add_safelen1 = true;
1377 else
1378 flag = GOVD_PRIVATE;
1380 omp_add_variable (ctx, t, flag | GOVD_SEEN);
1382 /* Static locals inside of target construct or offloaded
1383 routines need to be "omp declare target". */
1384 if (TREE_STATIC (t))
1385 for (; ctx; ctx = ctx->outer_context)
1386 if ((ctx->region_type & ORT_TARGET) != 0)
1388 if (!lookup_attribute ("omp declare target",
1389 DECL_ATTRIBUTES (t)))
1391 tree id = get_identifier ("omp declare target");
1392 DECL_ATTRIBUTES (t)
1393 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (t));
1394 varpool_node *node = varpool_node::get (t);
1395 if (node)
1397 node->offloadable = 1;
1398 if (ENABLE_OFFLOADING && !DECL_EXTERNAL (t))
1400 g->have_offload = true;
1401 if (!in_lto_p)
1402 vec_safe_push (offload_vars, t);
1406 break;
1410 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1412 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1413 cfun->has_local_explicit_reg_vars = true;
1417 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1418 BIND_EXPR_BLOCK (bind_expr));
1419 gimple_push_bind_expr (bind_stmt);
1421 gimplify_ctxp->keep_stack = false;
1422 gimplify_ctxp->save_stack = false;
1424 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1425 body = NULL;
1426 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1427 gimple_bind_set_body (bind_stmt, body);
1429 /* Source location wise, the cleanup code (stack_restore and clobbers)
1430 belongs to the end of the block, so propagate what we have. The
1431 stack_save operation belongs to the beginning of block, which we can
1432 infer from the bind_expr directly if the block has no explicit
1433 assignment. */
1434 if (BIND_EXPR_BLOCK (bind_expr))
1436 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1437 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1439 if (start_locus == 0)
1440 start_locus = EXPR_LOCATION (bind_expr);
1442 cleanup = NULL;
1443 stack_save = NULL;
1445 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1446 the stack space allocated to the VLAs. */
1447 if (gimplify_ctxp->save_stack && !gimplify_ctxp->keep_stack)
1449 gcall *stack_restore;
1451 /* Save stack on entry and restore it on exit. Add a try_finally
1452 block to achieve this. */
1453 build_stack_save_restore (&stack_save, &stack_restore);
1455 gimple_set_location (stack_save, start_locus);
1456 gimple_set_location (stack_restore, end_locus);
1458 gimplify_seq_add_stmt (&cleanup, stack_restore);
1461 /* Add clobbers for all variables that go out of scope. */
1462 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1464 if (VAR_P (t)
1465 && !is_global_var (t)
1466 && DECL_CONTEXT (t) == current_function_decl)
1468 if (!DECL_HARD_REGISTER (t)
1469 && !TREE_THIS_VOLATILE (t)
1470 && !DECL_HAS_VALUE_EXPR_P (t)
1471 /* Only care for variables that have to be in memory. Others
1472 will be rewritten into SSA names, hence moved to the
1473 top-level. */
1474 && !is_gimple_reg (t)
1475 && flag_stack_reuse != SR_NONE)
1477 tree clobber = build_clobber (TREE_TYPE (t));
1478 gimple *clobber_stmt;
1479 clobber_stmt = gimple_build_assign (t, clobber);
1480 gimple_set_location (clobber_stmt, end_locus);
1481 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1484 if (flag_openacc && oacc_declare_returns != NULL)
1486 tree key = t;
1487 if (DECL_HAS_VALUE_EXPR_P (key))
1489 key = DECL_VALUE_EXPR (key);
1490 if (TREE_CODE (key) == INDIRECT_REF)
1491 key = TREE_OPERAND (key, 0);
1493 tree *c = oacc_declare_returns->get (key);
1494 if (c != NULL)
1496 if (ret_clauses)
1497 OMP_CLAUSE_CHAIN (*c) = ret_clauses;
1499 ret_clauses = unshare_expr (*c);
1501 oacc_declare_returns->remove (key);
1503 if (oacc_declare_returns->is_empty ())
1505 delete oacc_declare_returns;
1506 oacc_declare_returns = NULL;
1512 if (asan_poisoned_variables != NULL
1513 && asan_poisoned_variables->contains (t))
1515 asan_poisoned_variables->remove (t);
1516 asan_poison_variable (t, true, &cleanup);
1519 if (gimplify_ctxp->live_switch_vars != NULL
1520 && gimplify_ctxp->live_switch_vars->contains (t))
1521 gimplify_ctxp->live_switch_vars->remove (t);
1524 if (ret_clauses)
1526 gomp_target *stmt;
1527 gimple_stmt_iterator si = gsi_start (cleanup);
1529 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
1530 ret_clauses);
1531 gsi_insert_seq_before_without_update (&si, stmt, GSI_NEW_STMT);
1534 if (cleanup)
1536 gtry *gs;
1537 gimple_seq new_body;
1539 new_body = NULL;
1540 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1541 GIMPLE_TRY_FINALLY);
1543 if (stack_save)
1544 gimplify_seq_add_stmt (&new_body, stack_save);
1545 gimplify_seq_add_stmt (&new_body, gs);
1546 gimple_bind_set_body (bind_stmt, new_body);
1549 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1550 if (!gimplify_ctxp->keep_stack)
1551 gimplify_ctxp->keep_stack = old_keep_stack;
1552 gimplify_ctxp->save_stack = old_save_stack;
1554 gimple_pop_bind_expr ();
1556 gimplify_seq_add_stmt (pre_p, bind_stmt);
1558 if (temp)
1560 *expr_p = temp;
1561 return GS_OK;
1564 *expr_p = NULL_TREE;
1565 return GS_ALL_DONE;
1568 /* Maybe add early return predict statement to PRE_P sequence. */
1570 static void
1571 maybe_add_early_return_predict_stmt (gimple_seq *pre_p)
1573 /* If we are not in a conditional context, add PREDICT statement. */
1574 if (gimple_conditional_context ())
1576 gimple *predict = gimple_build_predict (PRED_TREE_EARLY_RETURN,
1577 NOT_TAKEN);
1578 gimplify_seq_add_stmt (pre_p, predict);
1582 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1583 GIMPLE value, it is assigned to a new temporary and the statement is
1584 re-written to return the temporary.
1586 PRE_P points to the sequence where side effects that must happen before
1587 STMT should be stored. */
1589 static enum gimplify_status
1590 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1592 greturn *ret;
1593 tree ret_expr = TREE_OPERAND (stmt, 0);
1594 tree result_decl, result;
1596 if (ret_expr == error_mark_node)
1597 return GS_ERROR;
1599 if (!ret_expr
1600 || TREE_CODE (ret_expr) == RESULT_DECL)
1602 maybe_add_early_return_predict_stmt (pre_p);
1603 greturn *ret = gimple_build_return (ret_expr);
1604 copy_warning (ret, stmt);
1605 gimplify_seq_add_stmt (pre_p, ret);
1606 return GS_ALL_DONE;
1609 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1610 result_decl = NULL_TREE;
1611 else if (TREE_CODE (ret_expr) == COMPOUND_EXPR)
1613 /* Used in C++ for handling EH cleanup of the return value if a local
1614 cleanup throws. Assume the front-end knows what it's doing. */
1615 result_decl = DECL_RESULT (current_function_decl);
1616 /* But crash if we end up trying to modify ret_expr below. */
1617 ret_expr = NULL_TREE;
1619 else
1621 result_decl = TREE_OPERAND (ret_expr, 0);
1623 /* See through a return by reference. */
1624 if (TREE_CODE (result_decl) == INDIRECT_REF)
1625 result_decl = TREE_OPERAND (result_decl, 0);
1627 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1628 || TREE_CODE (ret_expr) == INIT_EXPR)
1629 && TREE_CODE (result_decl) == RESULT_DECL);
1632 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1633 Recall that aggregate_value_p is FALSE for any aggregate type that is
1634 returned in registers. If we're returning values in registers, then
1635 we don't want to extend the lifetime of the RESULT_DECL, particularly
1636 across another call. In addition, for those aggregates for which
1637 hard_function_value generates a PARALLEL, we'll die during normal
1638 expansion of structure assignments; there's special code in expand_return
1639 to handle this case that does not exist in expand_expr. */
1640 if (!result_decl)
1641 result = NULL_TREE;
1642 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1644 if (!poly_int_tree_p (DECL_SIZE (result_decl)))
1646 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1647 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1648 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1649 should be effectively allocated by the caller, i.e. all calls to
1650 this function must be subject to the Return Slot Optimization. */
1651 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1652 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1654 result = result_decl;
1656 else if (gimplify_ctxp->return_temp)
1657 result = gimplify_ctxp->return_temp;
1658 else
1660 result = create_tmp_reg (TREE_TYPE (result_decl));
1662 /* ??? With complex control flow (usually involving abnormal edges),
1663 we can wind up warning about an uninitialized value for this. Due
1664 to how this variable is constructed and initialized, this is never
1665 true. Give up and never warn. */
1666 suppress_warning (result, OPT_Wuninitialized);
1668 gimplify_ctxp->return_temp = result;
1671 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1672 Then gimplify the whole thing. */
1673 if (result != result_decl)
1674 TREE_OPERAND (ret_expr, 0) = result;
1676 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1678 maybe_add_early_return_predict_stmt (pre_p);
1679 ret = gimple_build_return (result);
1680 copy_warning (ret, stmt);
1681 gimplify_seq_add_stmt (pre_p, ret);
1683 return GS_ALL_DONE;
1686 /* Gimplify a variable-length array DECL. */
1688 static void
1689 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1691 /* This is a variable-sized decl. Simplify its size and mark it
1692 for deferred expansion. */
1693 tree t, addr, ptr_type;
1695 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1696 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1698 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1699 if (DECL_HAS_VALUE_EXPR_P (decl))
1700 return;
1702 /* All occurrences of this decl in final gimplified code will be
1703 replaced by indirection. Setting DECL_VALUE_EXPR does two
1704 things: First, it lets the rest of the gimplifier know what
1705 replacement to use. Second, it lets the debug info know
1706 where to find the value. */
1707 ptr_type = build_pointer_type (TREE_TYPE (decl));
1708 addr = create_tmp_var (ptr_type, get_name (decl));
1709 DECL_IGNORED_P (addr) = 0;
1710 t = build_fold_indirect_ref (addr);
1711 TREE_THIS_NOTRAP (t) = 1;
1712 SET_DECL_VALUE_EXPR (decl, t);
1713 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1715 t = build_alloca_call_expr (DECL_SIZE_UNIT (decl), DECL_ALIGN (decl),
1716 max_int_size_in_bytes (TREE_TYPE (decl)));
1717 /* The call has been built for a variable-sized object. */
1718 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1719 t = fold_convert (ptr_type, t);
1720 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1722 gimplify_and_add (t, seq_p);
1724 /* Record the dynamic allocation associated with DECL if requested. */
1725 if (flag_callgraph_info & CALLGRAPH_INFO_DYNAMIC_ALLOC)
1726 record_dynamic_alloc (decl);
1729 /* A helper function to be called via walk_tree. Mark all labels under *TP
1730 as being forced. To be called for DECL_INITIAL of static variables. */
1732 static tree
1733 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1735 if (TYPE_P (*tp))
1736 *walk_subtrees = 0;
1737 if (TREE_CODE (*tp) == LABEL_DECL)
1739 FORCED_LABEL (*tp) = 1;
1740 cfun->has_forced_label_in_static = 1;
1743 return NULL_TREE;
1746 /* Generate an initialization to automatic variable DECL based on INIT_TYPE.
1747 Build a call to internal const function DEFERRED_INIT:
1748 1st argument: SIZE of the DECL;
1749 2nd argument: INIT_TYPE;
1750 3rd argument: IS_VLA, 0 NO, 1 YES;
1752 as LHS = DEFERRED_INIT (SIZE of the DECL, INIT_TYPE, IS_VLA)
1753 if IS_VLA is false, the LHS is the DECL itself,
1754 if IS_VLA is true, the LHS is a MEM_REF whose address is the pointer
1755 to this DECL. */
1756 static void
1757 gimple_add_init_for_auto_var (tree decl,
1758 enum auto_init_type init_type,
1759 bool is_vla,
1760 gimple_seq *seq_p)
1762 gcc_assert (auto_var_p (decl));
1763 gcc_assert (init_type > AUTO_INIT_UNINITIALIZED);
1764 location_t loc = EXPR_LOCATION (decl);
1765 tree decl_size = TYPE_SIZE_UNIT (TREE_TYPE (decl));
1767 tree init_type_node
1768 = build_int_cst (integer_type_node, (int) init_type);
1769 tree is_vla_node
1770 = build_int_cst (integer_type_node, (int) is_vla);
1772 tree call = build_call_expr_internal_loc (loc, IFN_DEFERRED_INIT,
1773 TREE_TYPE (decl), 3,
1774 decl_size, init_type_node,
1775 is_vla_node);
1777 gimplify_assign (decl, call, seq_p);
1780 /* Generate padding initialization for automatic vairable DECL.
1781 C guarantees that brace-init with fewer initializers than members
1782 aggregate will initialize the rest of the aggregate as-if it were
1783 static initialization. In turn static initialization guarantees
1784 that padding is initialized to zero. So, we always initialize paddings
1785 to zeroes regardless INIT_TYPE.
1786 To do the padding initialization, we insert a call to
1787 __BUILTIN_CLEAR_PADDING (&decl, 0, for_auto_init = true).
1788 Note, we add an additional dummy argument for __BUILTIN_CLEAR_PADDING,
1789 'for_auto_init' to distinguish whether this call is for automatic
1790 variable initialization or not.
1792 static void
1793 gimple_add_padding_init_for_auto_var (tree decl, bool is_vla,
1794 gimple_seq *seq_p)
1796 tree addr_of_decl = NULL_TREE;
1797 bool for_auto_init = true;
1798 tree fn = builtin_decl_explicit (BUILT_IN_CLEAR_PADDING);
1800 if (is_vla)
1802 /* The temporary address variable for this vla should be
1803 created in gimplify_vla_decl. */
1804 gcc_assert (DECL_HAS_VALUE_EXPR_P (decl));
1805 gcc_assert (TREE_CODE (DECL_VALUE_EXPR (decl)) == INDIRECT_REF);
1806 addr_of_decl = TREE_OPERAND (DECL_VALUE_EXPR (decl), 0);
1808 else
1810 mark_addressable (decl);
1811 addr_of_decl = build_fold_addr_expr (decl);
1814 gimple *call = gimple_build_call (fn,
1815 3, addr_of_decl,
1816 build_zero_cst (TREE_TYPE (addr_of_decl)),
1817 build_int_cst (integer_type_node,
1818 (int) for_auto_init));
1819 gimplify_seq_add_stmt (seq_p, call);
1822 /* Return true if the DECL need to be automaticly initialized by the
1823 compiler. */
1824 static bool
1825 is_var_need_auto_init (tree decl)
1827 if (auto_var_p (decl)
1828 && (TREE_CODE (decl) != VAR_DECL
1829 || !DECL_HARD_REGISTER (decl))
1830 && (flag_auto_var_init > AUTO_INIT_UNINITIALIZED)
1831 && (!lookup_attribute ("uninitialized", DECL_ATTRIBUTES (decl)))
1832 && !is_empty_type (TREE_TYPE (decl)))
1833 return true;
1834 return false;
1837 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1838 and initialization explicit. */
1840 static enum gimplify_status
1841 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1843 tree stmt = *stmt_p;
1844 tree decl = DECL_EXPR_DECL (stmt);
1846 *stmt_p = NULL_TREE;
1848 if (TREE_TYPE (decl) == error_mark_node)
1849 return GS_ERROR;
1851 if ((TREE_CODE (decl) == TYPE_DECL
1852 || VAR_P (decl))
1853 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1855 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1856 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
1857 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
1860 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1861 in case its size expressions contain problematic nodes like CALL_EXPR. */
1862 if (TREE_CODE (decl) == TYPE_DECL
1863 && DECL_ORIGINAL_TYPE (decl)
1864 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1866 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1867 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
1868 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
1871 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
1873 tree init = DECL_INITIAL (decl);
1874 bool is_vla = false;
1875 /* Check whether a decl has FE created VALUE_EXPR here BEFORE
1876 gimplify_vla_decl creates VALUE_EXPR for a vla decl.
1877 If the decl has VALUE_EXPR that was created by FE (usually
1878 C++FE), it's a proxy varaible, and FE already initialized
1879 the VALUE_EXPR of it, we should not initialize it anymore. */
1880 bool decl_had_value_expr_p = DECL_HAS_VALUE_EXPR_P (decl);
1882 poly_uint64 size;
1883 if (!poly_int_tree_p (DECL_SIZE_UNIT (decl), &size)
1884 || (!TREE_STATIC (decl)
1885 && flag_stack_check == GENERIC_STACK_CHECK
1886 && maybe_gt (size,
1887 (unsigned HOST_WIDE_INT) STACK_CHECK_MAX_VAR_SIZE)))
1889 gimplify_vla_decl (decl, seq_p);
1890 is_vla = true;
1893 if (asan_poisoned_variables
1894 && !is_vla
1895 && TREE_ADDRESSABLE (decl)
1896 && !TREE_STATIC (decl)
1897 && !DECL_HAS_VALUE_EXPR_P (decl)
1898 && DECL_ALIGN (decl) <= MAX_SUPPORTED_STACK_ALIGNMENT
1899 && dbg_cnt (asan_use_after_scope)
1900 && !gimplify_omp_ctxp
1901 /* GNAT introduces temporaries to hold return values of calls in
1902 initializers of variables defined in other units, so the
1903 declaration of the variable is discarded completely. We do not
1904 want to issue poison calls for such dropped variables. */
1905 && (DECL_SEEN_IN_BIND_EXPR_P (decl)
1906 || (DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)))
1908 asan_poisoned_variables->add (decl);
1909 asan_poison_variable (decl, false, seq_p);
1910 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
1911 gimplify_ctxp->live_switch_vars->add (decl);
1914 /* Some front ends do not explicitly declare all anonymous
1915 artificial variables. We compensate here by declaring the
1916 variables, though it would be better if the front ends would
1917 explicitly declare them. */
1918 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1919 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1920 gimple_add_tmp_var (decl);
1922 if (init && init != error_mark_node)
1924 if (!TREE_STATIC (decl))
1926 DECL_INITIAL (decl) = NULL_TREE;
1927 init = build2 (INIT_EXPR, void_type_node, decl, init);
1928 gimplify_and_add (init, seq_p);
1929 ggc_free (init);
1930 /* Clear TREE_READONLY if we really have an initialization. */
1931 if (!DECL_INITIAL (decl)
1932 && !omp_privatize_by_reference (decl))
1933 TREE_READONLY (decl) = 0;
1935 else
1936 /* We must still examine initializers for static variables
1937 as they may contain a label address. */
1938 walk_tree (&init, force_labels_r, NULL, NULL);
1940 /* When there is no explicit initializer, if the user requested,
1941 We should insert an artifical initializer for this automatic
1942 variable. */
1943 else if (is_var_need_auto_init (decl)
1944 && !decl_had_value_expr_p)
1946 gimple_add_init_for_auto_var (decl,
1947 flag_auto_var_init,
1948 is_vla,
1949 seq_p);
1950 /* The expanding of a call to the above .DEFERRED_INIT will apply
1951 block initialization to the whole space covered by this variable.
1952 As a result, all the paddings will be initialized to zeroes
1953 for zero initialization and 0xFE byte-repeatable patterns for
1954 pattern initialization.
1955 In order to make the paddings as zeroes for pattern init, We
1956 should add a call to __builtin_clear_padding to clear the
1957 paddings to zero in compatiple with CLANG. */
1958 if (flag_auto_var_init == AUTO_INIT_PATTERN)
1959 gimple_add_padding_init_for_auto_var (decl, is_vla, seq_p);
1963 return GS_ALL_DONE;
1966 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1967 and replacing the LOOP_EXPR with goto, but if the loop contains an
1968 EXIT_EXPR, we need to append a label for it to jump to. */
1970 static enum gimplify_status
1971 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1973 tree saved_label = gimplify_ctxp->exit_label;
1974 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1976 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1978 gimplify_ctxp->exit_label = NULL_TREE;
1980 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1982 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
1984 if (gimplify_ctxp->exit_label)
1985 gimplify_seq_add_stmt (pre_p,
1986 gimple_build_label (gimplify_ctxp->exit_label));
1988 gimplify_ctxp->exit_label = saved_label;
1990 *expr_p = NULL;
1991 return GS_ALL_DONE;
1994 /* Gimplify a statement list onto a sequence. These may be created either
1995 by an enlightened front-end, or by shortcut_cond_expr. */
1997 static enum gimplify_status
1998 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
2000 tree temp = voidify_wrapper_expr (*expr_p, NULL);
2002 tree_stmt_iterator i = tsi_start (*expr_p);
2004 while (!tsi_end_p (i))
2006 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
2007 tsi_delink (&i);
2010 if (temp)
2012 *expr_p = temp;
2013 return GS_OK;
2016 return GS_ALL_DONE;
2019 /* Callback for walk_gimple_seq. */
2021 static tree
2022 warn_switch_unreachable_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2023 struct walk_stmt_info *wi)
2025 gimple *stmt = gsi_stmt (*gsi_p);
2027 *handled_ops_p = true;
2028 switch (gimple_code (stmt))
2030 case GIMPLE_TRY:
2031 /* A compiler-generated cleanup or a user-written try block.
2032 If it's empty, don't dive into it--that would result in
2033 worse location info. */
2034 if (gimple_try_eval (stmt) == NULL)
2036 wi->info = stmt;
2037 return integer_zero_node;
2039 /* Fall through. */
2040 case GIMPLE_BIND:
2041 case GIMPLE_CATCH:
2042 case GIMPLE_EH_FILTER:
2043 case GIMPLE_TRANSACTION:
2044 /* Walk the sub-statements. */
2045 *handled_ops_p = false;
2046 break;
2048 case GIMPLE_DEBUG:
2049 /* Ignore these. We may generate them before declarations that
2050 are never executed. If there's something to warn about,
2051 there will be non-debug stmts too, and we'll catch those. */
2052 break;
2054 case GIMPLE_CALL:
2055 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2057 *handled_ops_p = false;
2058 break;
2060 /* Fall through. */
2061 default:
2062 /* Save the first "real" statement (not a decl/lexical scope/...). */
2063 wi->info = stmt;
2064 return integer_zero_node;
2066 return NULL_TREE;
2069 /* Possibly warn about unreachable statements between switch's controlling
2070 expression and the first case. SEQ is the body of a switch expression. */
2072 static void
2073 maybe_warn_switch_unreachable (gimple_seq seq)
2075 if (!warn_switch_unreachable
2076 /* This warning doesn't play well with Fortran when optimizations
2077 are on. */
2078 || lang_GNU_Fortran ()
2079 || seq == NULL)
2080 return;
2082 struct walk_stmt_info wi;
2083 memset (&wi, 0, sizeof (wi));
2084 walk_gimple_seq (seq, warn_switch_unreachable_r, NULL, &wi);
2085 gimple *stmt = (gimple *) wi.info;
2087 if (stmt && gimple_code (stmt) != GIMPLE_LABEL)
2089 if (gimple_code (stmt) == GIMPLE_GOTO
2090 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
2091 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
2092 /* Don't warn for compiler-generated gotos. These occur
2093 in Duff's devices, for example. */;
2094 else
2095 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
2096 "statement will never be executed");
2101 /* A label entry that pairs label and a location. */
2102 struct label_entry
2104 tree label;
2105 location_t loc;
2108 /* Find LABEL in vector of label entries VEC. */
2110 static struct label_entry *
2111 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
2113 unsigned int i;
2114 struct label_entry *l;
2116 FOR_EACH_VEC_ELT (*vec, i, l)
2117 if (l->label == label)
2118 return l;
2119 return NULL;
2122 /* Return true if LABEL, a LABEL_DECL, represents a case label
2123 in a vector of labels CASES. */
2125 static bool
2126 case_label_p (const vec<tree> *cases, tree label)
2128 unsigned int i;
2129 tree l;
2131 FOR_EACH_VEC_ELT (*cases, i, l)
2132 if (CASE_LABEL (l) == label)
2133 return true;
2134 return false;
2137 /* Find the last nondebug statement in a scope STMT. */
2139 static gimple *
2140 last_stmt_in_scope (gimple *stmt)
2142 if (!stmt)
2143 return NULL;
2145 switch (gimple_code (stmt))
2147 case GIMPLE_BIND:
2149 gbind *bind = as_a <gbind *> (stmt);
2150 stmt = gimple_seq_last_nondebug_stmt (gimple_bind_body (bind));
2151 return last_stmt_in_scope (stmt);
2154 case GIMPLE_TRY:
2156 gtry *try_stmt = as_a <gtry *> (stmt);
2157 stmt = gimple_seq_last_nondebug_stmt (gimple_try_eval (try_stmt));
2158 gimple *last_eval = last_stmt_in_scope (stmt);
2159 if (gimple_stmt_may_fallthru (last_eval)
2160 && (last_eval == NULL
2161 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
2162 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
2164 stmt = gimple_seq_last_nondebug_stmt (gimple_try_cleanup (try_stmt));
2165 return last_stmt_in_scope (stmt);
2167 else
2168 return last_eval;
2171 case GIMPLE_DEBUG:
2172 gcc_unreachable ();
2174 default:
2175 return stmt;
2179 /* Collect interesting labels in LABELS and return the statement preceding
2180 another case label, or a user-defined label. Store a location useful
2181 to give warnings at *PREVLOC (usually the location of the returned
2182 statement or of its surrounding scope). */
2184 static gimple *
2185 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
2186 auto_vec <struct label_entry> *labels,
2187 location_t *prevloc)
2189 gimple *prev = NULL;
2191 *prevloc = UNKNOWN_LOCATION;
2194 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND)
2196 /* Recognize the special GIMPLE_BIND added by gimplify_switch_expr,
2197 which starts on a GIMPLE_SWITCH and ends with a break label.
2198 Handle that as a single statement that can fall through. */
2199 gbind *bind = as_a <gbind *> (gsi_stmt (*gsi_p));
2200 gimple *first = gimple_seq_first_stmt (gimple_bind_body (bind));
2201 gimple *last = gimple_seq_last_stmt (gimple_bind_body (bind));
2202 if (last
2203 && gimple_code (first) == GIMPLE_SWITCH
2204 && gimple_code (last) == GIMPLE_LABEL)
2206 tree label = gimple_label_label (as_a <glabel *> (last));
2207 if (SWITCH_BREAK_LABEL_P (label))
2209 prev = bind;
2210 gsi_next (gsi_p);
2211 continue;
2215 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
2216 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
2218 /* Nested scope. Only look at the last statement of
2219 the innermost scope. */
2220 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
2221 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
2222 if (last)
2224 prev = last;
2225 /* It might be a label without a location. Use the
2226 location of the scope then. */
2227 if (!gimple_has_location (prev))
2228 *prevloc = bind_loc;
2230 gsi_next (gsi_p);
2231 continue;
2234 /* Ifs are tricky. */
2235 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
2237 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
2238 tree false_lab = gimple_cond_false_label (cond_stmt);
2239 location_t if_loc = gimple_location (cond_stmt);
2241 /* If we have e.g.
2242 if (i > 1) goto <D.2259>; else goto D;
2243 we can't do much with the else-branch. */
2244 if (!DECL_ARTIFICIAL (false_lab))
2245 break;
2247 /* Go on until the false label, then one step back. */
2248 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
2250 gimple *stmt = gsi_stmt (*gsi_p);
2251 if (gimple_code (stmt) == GIMPLE_LABEL
2252 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
2253 break;
2256 /* Not found? Oops. */
2257 if (gsi_end_p (*gsi_p))
2258 break;
2260 struct label_entry l = { false_lab, if_loc };
2261 labels->safe_push (l);
2263 /* Go to the last statement of the then branch. */
2264 gsi_prev (gsi_p);
2266 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
2267 <D.1759>:
2268 <stmt>;
2269 goto <D.1761>;
2270 <D.1760>:
2272 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
2273 && !gimple_has_location (gsi_stmt (*gsi_p)))
2275 /* Look at the statement before, it might be
2276 attribute fallthrough, in which case don't warn. */
2277 gsi_prev (gsi_p);
2278 bool fallthru_before_dest
2279 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
2280 gsi_next (gsi_p);
2281 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
2282 if (!fallthru_before_dest)
2284 struct label_entry l = { goto_dest, if_loc };
2285 labels->safe_push (l);
2288 /* And move back. */
2289 gsi_next (gsi_p);
2292 /* Remember the last statement. Skip labels that are of no interest
2293 to us. */
2294 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2296 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
2297 if (find_label_entry (labels, label))
2298 prev = gsi_stmt (*gsi_p);
2300 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
2302 else if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_PREDICT)
2304 else if (!is_gimple_debug (gsi_stmt (*gsi_p)))
2305 prev = gsi_stmt (*gsi_p);
2306 gsi_next (gsi_p);
2308 while (!gsi_end_p (*gsi_p)
2309 /* Stop if we find a case or a user-defined label. */
2310 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
2311 || !gimple_has_location (gsi_stmt (*gsi_p))));
2313 if (prev && gimple_has_location (prev))
2314 *prevloc = gimple_location (prev);
2315 return prev;
2318 /* Return true if the switch fallthough warning should occur. LABEL is
2319 the label statement that we're falling through to. */
2321 static bool
2322 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
2324 gimple_stmt_iterator gsi = *gsi_p;
2326 /* Don't warn if the label is marked with a "falls through" comment. */
2327 if (FALLTHROUGH_LABEL_P (label))
2328 return false;
2330 /* Don't warn for non-case labels followed by a statement:
2331 case 0:
2332 foo ();
2333 label:
2334 bar ();
2335 as these are likely intentional. */
2336 if (!case_label_p (&gimplify_ctxp->case_labels, label))
2338 tree l;
2339 while (!gsi_end_p (gsi)
2340 && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2341 && (l = gimple_label_label (as_a <glabel *> (gsi_stmt (gsi))))
2342 && !case_label_p (&gimplify_ctxp->case_labels, l))
2343 gsi_next_nondebug (&gsi);
2344 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
2345 return false;
2348 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2349 immediately breaks. */
2350 gsi = *gsi_p;
2352 /* Skip all immediately following labels. */
2353 while (!gsi_end_p (gsi)
2354 && (gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2355 || gimple_code (gsi_stmt (gsi)) == GIMPLE_PREDICT))
2356 gsi_next_nondebug (&gsi);
2358 /* { ... something; default:; } */
2359 if (gsi_end_p (gsi)
2360 /* { ... something; default: break; } or
2361 { ... something; default: goto L; } */
2362 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2363 /* { ... something; default: return; } */
2364 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2365 return false;
2367 return true;
2370 /* Callback for walk_gimple_seq. */
2372 static tree
2373 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2374 struct walk_stmt_info *)
2376 gimple *stmt = gsi_stmt (*gsi_p);
2378 *handled_ops_p = true;
2379 switch (gimple_code (stmt))
2381 case GIMPLE_TRY:
2382 case GIMPLE_BIND:
2383 case GIMPLE_CATCH:
2384 case GIMPLE_EH_FILTER:
2385 case GIMPLE_TRANSACTION:
2386 /* Walk the sub-statements. */
2387 *handled_ops_p = false;
2388 break;
2390 /* Find a sequence of form:
2392 GIMPLE_LABEL
2393 [...]
2394 <may fallthru stmt>
2395 GIMPLE_LABEL
2397 and possibly warn. */
2398 case GIMPLE_LABEL:
2400 /* Found a label. Skip all immediately following labels. */
2401 while (!gsi_end_p (*gsi_p)
2402 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2403 gsi_next_nondebug (gsi_p);
2405 /* There might be no more statements. */
2406 if (gsi_end_p (*gsi_p))
2407 return integer_zero_node;
2409 /* Vector of labels that fall through. */
2410 auto_vec <struct label_entry> labels;
2411 location_t prevloc;
2412 gimple *prev = collect_fallthrough_labels (gsi_p, &labels, &prevloc);
2414 /* There might be no more statements. */
2415 if (gsi_end_p (*gsi_p))
2416 return integer_zero_node;
2418 gimple *next = gsi_stmt (*gsi_p);
2419 tree label;
2420 /* If what follows is a label, then we may have a fallthrough. */
2421 if (gimple_code (next) == GIMPLE_LABEL
2422 && gimple_has_location (next)
2423 && (label = gimple_label_label (as_a <glabel *> (next)))
2424 && prev != NULL)
2426 struct label_entry *l;
2427 bool warned_p = false;
2428 auto_diagnostic_group d;
2429 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2430 /* Quiet. */;
2431 else if (gimple_code (prev) == GIMPLE_LABEL
2432 && (label = gimple_label_label (as_a <glabel *> (prev)))
2433 && (l = find_label_entry (&labels, label)))
2434 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2435 "this statement may fall through");
2436 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2437 /* Try to be clever and don't warn when the statement
2438 can't actually fall through. */
2439 && gimple_stmt_may_fallthru (prev)
2440 && prevloc != UNKNOWN_LOCATION)
2441 warned_p = warning_at (prevloc,
2442 OPT_Wimplicit_fallthrough_,
2443 "this statement may fall through");
2444 if (warned_p)
2445 inform (gimple_location (next), "here");
2447 /* Mark this label as processed so as to prevent multiple
2448 warnings in nested switches. */
2449 FALLTHROUGH_LABEL_P (label) = true;
2451 /* So that next warn_implicit_fallthrough_r will start looking for
2452 a new sequence starting with this label. */
2453 gsi_prev (gsi_p);
2456 break;
2457 default:
2458 break;
2460 return NULL_TREE;
2463 /* Warn when a switch case falls through. */
2465 static void
2466 maybe_warn_implicit_fallthrough (gimple_seq seq)
2468 if (!warn_implicit_fallthrough)
2469 return;
2471 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2472 if (!(lang_GNU_C ()
2473 || lang_GNU_CXX ()
2474 || lang_GNU_OBJC ()))
2475 return;
2477 struct walk_stmt_info wi;
2478 memset (&wi, 0, sizeof (wi));
2479 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2482 /* Callback for walk_gimple_seq. */
2484 static tree
2485 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2486 struct walk_stmt_info *wi)
2488 gimple *stmt = gsi_stmt (*gsi_p);
2490 *handled_ops_p = true;
2491 switch (gimple_code (stmt))
2493 case GIMPLE_TRY:
2494 case GIMPLE_BIND:
2495 case GIMPLE_CATCH:
2496 case GIMPLE_EH_FILTER:
2497 case GIMPLE_TRANSACTION:
2498 /* Walk the sub-statements. */
2499 *handled_ops_p = false;
2500 break;
2501 case GIMPLE_CALL:
2502 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2504 gsi_remove (gsi_p, true);
2505 if (gsi_end_p (*gsi_p))
2507 *static_cast<location_t *>(wi->info) = gimple_location (stmt);
2508 return integer_zero_node;
2511 bool found = false;
2512 location_t loc = gimple_location (stmt);
2514 gimple_stmt_iterator gsi2 = *gsi_p;
2515 stmt = gsi_stmt (gsi2);
2516 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2518 /* Go on until the artificial label. */
2519 tree goto_dest = gimple_goto_dest (stmt);
2520 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2522 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2523 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2524 == goto_dest)
2525 break;
2528 /* Not found? Stop. */
2529 if (gsi_end_p (gsi2))
2530 break;
2532 /* Look one past it. */
2533 gsi_next (&gsi2);
2536 /* We're looking for a case label or default label here. */
2537 while (!gsi_end_p (gsi2))
2539 stmt = gsi_stmt (gsi2);
2540 if (gimple_code (stmt) == GIMPLE_LABEL)
2542 tree label = gimple_label_label (as_a <glabel *> (stmt));
2543 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2545 found = true;
2546 break;
2549 else if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2551 else if (!is_gimple_debug (stmt))
2552 /* Anything else is not expected. */
2553 break;
2554 gsi_next (&gsi2);
2556 if (!found)
2557 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2558 "a case label or default label");
2560 break;
2561 default:
2562 break;
2564 return NULL_TREE;
2567 /* Expand all FALLTHROUGH () calls in SEQ. */
2569 static void
2570 expand_FALLTHROUGH (gimple_seq *seq_p)
2572 struct walk_stmt_info wi;
2573 location_t loc;
2574 memset (&wi, 0, sizeof (wi));
2575 wi.info = (void *) &loc;
2576 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2577 if (wi.callback_result == integer_zero_node)
2578 /* We've found [[fallthrough]]; at the end of a switch, which the C++
2579 standard says is ill-formed; see [dcl.attr.fallthrough]. */
2580 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2581 "a case label or default label");
2585 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2586 branch to. */
2588 static enum gimplify_status
2589 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2591 tree switch_expr = *expr_p;
2592 gimple_seq switch_body_seq = NULL;
2593 enum gimplify_status ret;
2594 tree index_type = TREE_TYPE (switch_expr);
2595 if (index_type == NULL_TREE)
2596 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2598 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2599 fb_rvalue);
2600 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2601 return ret;
2603 if (SWITCH_BODY (switch_expr))
2605 vec<tree> labels;
2606 vec<tree> saved_labels;
2607 hash_set<tree> *saved_live_switch_vars = NULL;
2608 tree default_case = NULL_TREE;
2609 gswitch *switch_stmt;
2611 /* Save old labels, get new ones from body, then restore the old
2612 labels. Save all the things from the switch body to append after. */
2613 saved_labels = gimplify_ctxp->case_labels;
2614 gimplify_ctxp->case_labels.create (8);
2616 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2617 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2618 tree_code body_type = TREE_CODE (SWITCH_BODY (switch_expr));
2619 if (body_type == BIND_EXPR || body_type == STATEMENT_LIST)
2620 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2621 else
2622 gimplify_ctxp->live_switch_vars = NULL;
2624 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2625 gimplify_ctxp->in_switch_expr = true;
2627 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2629 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2630 maybe_warn_switch_unreachable (switch_body_seq);
2631 maybe_warn_implicit_fallthrough (switch_body_seq);
2632 /* Only do this for the outermost GIMPLE_SWITCH. */
2633 if (!gimplify_ctxp->in_switch_expr)
2634 expand_FALLTHROUGH (&switch_body_seq);
2636 labels = gimplify_ctxp->case_labels;
2637 gimplify_ctxp->case_labels = saved_labels;
2639 if (gimplify_ctxp->live_switch_vars)
2641 gcc_assert (gimplify_ctxp->live_switch_vars->is_empty ());
2642 delete gimplify_ctxp->live_switch_vars;
2644 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2646 preprocess_case_label_vec_for_gimple (labels, index_type,
2647 &default_case);
2649 bool add_bind = false;
2650 if (!default_case)
2652 glabel *new_default;
2654 default_case
2655 = build_case_label (NULL_TREE, NULL_TREE,
2656 create_artificial_label (UNKNOWN_LOCATION));
2657 if (old_in_switch_expr)
2659 SWITCH_BREAK_LABEL_P (CASE_LABEL (default_case)) = 1;
2660 add_bind = true;
2662 new_default = gimple_build_label (CASE_LABEL (default_case));
2663 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2665 else if (old_in_switch_expr)
2667 gimple *last = gimple_seq_last_stmt (switch_body_seq);
2668 if (last && gimple_code (last) == GIMPLE_LABEL)
2670 tree label = gimple_label_label (as_a <glabel *> (last));
2671 if (SWITCH_BREAK_LABEL_P (label))
2672 add_bind = true;
2676 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2677 default_case, labels);
2678 /* For the benefit of -Wimplicit-fallthrough, if switch_body_seq
2679 ends with a GIMPLE_LABEL holding SWITCH_BREAK_LABEL_P LABEL_DECL,
2680 wrap the GIMPLE_SWITCH up to that GIMPLE_LABEL into a GIMPLE_BIND,
2681 so that we can easily find the start and end of the switch
2682 statement. */
2683 if (add_bind)
2685 gimple_seq bind_body = NULL;
2686 gimplify_seq_add_stmt (&bind_body, switch_stmt);
2687 gimple_seq_add_seq (&bind_body, switch_body_seq);
2688 gbind *bind = gimple_build_bind (NULL_TREE, bind_body, NULL_TREE);
2689 gimple_set_location (bind, EXPR_LOCATION (switch_expr));
2690 gimplify_seq_add_stmt (pre_p, bind);
2692 else
2694 gimplify_seq_add_stmt (pre_p, switch_stmt);
2695 gimplify_seq_add_seq (pre_p, switch_body_seq);
2697 labels.release ();
2699 else
2700 gcc_unreachable ();
2702 return GS_ALL_DONE;
2705 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
2707 static enum gimplify_status
2708 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
2710 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
2711 == current_function_decl);
2713 tree label = LABEL_EXPR_LABEL (*expr_p);
2714 glabel *label_stmt = gimple_build_label (label);
2715 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2716 gimplify_seq_add_stmt (pre_p, label_stmt);
2718 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2719 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2720 NOT_TAKEN));
2721 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2722 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2723 TAKEN));
2725 return GS_ALL_DONE;
2728 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
2730 static enum gimplify_status
2731 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
2733 struct gimplify_ctx *ctxp;
2734 glabel *label_stmt;
2736 /* Invalid programs can play Duff's Device type games with, for example,
2737 #pragma omp parallel. At least in the C front end, we don't
2738 detect such invalid branches until after gimplification, in the
2739 diagnose_omp_blocks pass. */
2740 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
2741 if (ctxp->case_labels.exists ())
2742 break;
2744 tree label = CASE_LABEL (*expr_p);
2745 label_stmt = gimple_build_label (label);
2746 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2747 ctxp->case_labels.safe_push (*expr_p);
2748 gimplify_seq_add_stmt (pre_p, label_stmt);
2750 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2751 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2752 NOT_TAKEN));
2753 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2754 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2755 TAKEN));
2757 return GS_ALL_DONE;
2760 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
2761 if necessary. */
2763 tree
2764 build_and_jump (tree *label_p)
2766 if (label_p == NULL)
2767 /* If there's nowhere to jump, just fall through. */
2768 return NULL_TREE;
2770 if (*label_p == NULL_TREE)
2772 tree label = create_artificial_label (UNKNOWN_LOCATION);
2773 *label_p = label;
2776 return build1 (GOTO_EXPR, void_type_node, *label_p);
2779 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
2780 This also involves building a label to jump to and communicating it to
2781 gimplify_loop_expr through gimplify_ctxp->exit_label. */
2783 static enum gimplify_status
2784 gimplify_exit_expr (tree *expr_p)
2786 tree cond = TREE_OPERAND (*expr_p, 0);
2787 tree expr;
2789 expr = build_and_jump (&gimplify_ctxp->exit_label);
2790 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
2791 *expr_p = expr;
2793 return GS_OK;
2796 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
2797 different from its canonical type, wrap the whole thing inside a
2798 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
2799 type.
2801 The canonical type of a COMPONENT_REF is the type of the field being
2802 referenced--unless the field is a bit-field which can be read directly
2803 in a smaller mode, in which case the canonical type is the
2804 sign-appropriate type corresponding to that mode. */
2806 static void
2807 canonicalize_component_ref (tree *expr_p)
2809 tree expr = *expr_p;
2810 tree type;
2812 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
2814 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
2815 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
2816 else
2817 type = TREE_TYPE (TREE_OPERAND (expr, 1));
2819 /* One could argue that all the stuff below is not necessary for
2820 the non-bitfield case and declare it a FE error if type
2821 adjustment would be needed. */
2822 if (TREE_TYPE (expr) != type)
2824 #ifdef ENABLE_TYPES_CHECKING
2825 tree old_type = TREE_TYPE (expr);
2826 #endif
2827 int type_quals;
2829 /* We need to preserve qualifiers and propagate them from
2830 operand 0. */
2831 type_quals = TYPE_QUALS (type)
2832 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
2833 if (TYPE_QUALS (type) != type_quals)
2834 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
2836 /* Set the type of the COMPONENT_REF to the underlying type. */
2837 TREE_TYPE (expr) = type;
2839 #ifdef ENABLE_TYPES_CHECKING
2840 /* It is now a FE error, if the conversion from the canonical
2841 type to the original expression type is not useless. */
2842 gcc_assert (useless_type_conversion_p (old_type, type));
2843 #endif
2847 /* If a NOP conversion is changing a pointer to array of foo to a pointer
2848 to foo, embed that change in the ADDR_EXPR by converting
2849 T array[U];
2850 (T *)&array
2852 &array[L]
2853 where L is the lower bound. For simplicity, only do this for constant
2854 lower bound.
2855 The constraint is that the type of &array[L] is trivially convertible
2856 to T *. */
2858 static void
2859 canonicalize_addr_expr (tree *expr_p)
2861 tree expr = *expr_p;
2862 tree addr_expr = TREE_OPERAND (expr, 0);
2863 tree datype, ddatype, pddatype;
2865 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
2866 if (!POINTER_TYPE_P (TREE_TYPE (expr))
2867 || TREE_CODE (addr_expr) != ADDR_EXPR)
2868 return;
2870 /* The addr_expr type should be a pointer to an array. */
2871 datype = TREE_TYPE (TREE_TYPE (addr_expr));
2872 if (TREE_CODE (datype) != ARRAY_TYPE)
2873 return;
2875 /* The pointer to element type shall be trivially convertible to
2876 the expression pointer type. */
2877 ddatype = TREE_TYPE (datype);
2878 pddatype = build_pointer_type (ddatype);
2879 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
2880 pddatype))
2881 return;
2883 /* The lower bound and element sizes must be constant. */
2884 if (!TYPE_SIZE_UNIT (ddatype)
2885 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
2886 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
2887 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
2888 return;
2890 /* All checks succeeded. Build a new node to merge the cast. */
2891 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
2892 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
2893 NULL_TREE, NULL_TREE);
2894 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
2896 /* We can have stripped a required restrict qualifier above. */
2897 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
2898 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
2901 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
2902 underneath as appropriate. */
2904 static enum gimplify_status
2905 gimplify_conversion (tree *expr_p)
2907 location_t loc = EXPR_LOCATION (*expr_p);
2908 gcc_assert (CONVERT_EXPR_P (*expr_p));
2910 /* Then strip away all but the outermost conversion. */
2911 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
2913 /* And remove the outermost conversion if it's useless. */
2914 if (tree_ssa_useless_type_conversion (*expr_p))
2915 *expr_p = TREE_OPERAND (*expr_p, 0);
2917 /* If we still have a conversion at the toplevel,
2918 then canonicalize some constructs. */
2919 if (CONVERT_EXPR_P (*expr_p))
2921 tree sub = TREE_OPERAND (*expr_p, 0);
2923 /* If a NOP conversion is changing the type of a COMPONENT_REF
2924 expression, then canonicalize its type now in order to expose more
2925 redundant conversions. */
2926 if (TREE_CODE (sub) == COMPONENT_REF)
2927 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
2929 /* If a NOP conversion is changing a pointer to array of foo
2930 to a pointer to foo, embed that change in the ADDR_EXPR. */
2931 else if (TREE_CODE (sub) == ADDR_EXPR)
2932 canonicalize_addr_expr (expr_p);
2935 /* If we have a conversion to a non-register type force the
2936 use of a VIEW_CONVERT_EXPR instead. */
2937 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
2938 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
2939 TREE_OPERAND (*expr_p, 0));
2941 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
2942 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
2943 TREE_SET_CODE (*expr_p, NOP_EXPR);
2945 return GS_OK;
2948 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
2949 DECL_VALUE_EXPR, and it's worth re-examining things. */
2951 static enum gimplify_status
2952 gimplify_var_or_parm_decl (tree *expr_p)
2954 tree decl = *expr_p;
2956 /* ??? If this is a local variable, and it has not been seen in any
2957 outer BIND_EXPR, then it's probably the result of a duplicate
2958 declaration, for which we've already issued an error. It would
2959 be really nice if the front end wouldn't leak these at all.
2960 Currently the only known culprit is C++ destructors, as seen
2961 in g++.old-deja/g++.jason/binding.C. */
2962 if (VAR_P (decl)
2963 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
2964 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
2965 && decl_function_context (decl) == current_function_decl)
2967 gcc_assert (seen_error ());
2968 return GS_ERROR;
2971 /* When within an OMP context, notice uses of variables. */
2972 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
2973 return GS_ALL_DONE;
2975 /* If the decl is an alias for another expression, substitute it now. */
2976 if (DECL_HAS_VALUE_EXPR_P (decl))
2978 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
2979 return GS_OK;
2982 return GS_ALL_DONE;
2985 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
2987 static void
2988 recalculate_side_effects (tree t)
2990 enum tree_code code = TREE_CODE (t);
2991 int len = TREE_OPERAND_LENGTH (t);
2992 int i;
2994 switch (TREE_CODE_CLASS (code))
2996 case tcc_expression:
2997 switch (code)
2999 case INIT_EXPR:
3000 case MODIFY_EXPR:
3001 case VA_ARG_EXPR:
3002 case PREDECREMENT_EXPR:
3003 case PREINCREMENT_EXPR:
3004 case POSTDECREMENT_EXPR:
3005 case POSTINCREMENT_EXPR:
3006 /* All of these have side-effects, no matter what their
3007 operands are. */
3008 return;
3010 default:
3011 break;
3013 /* Fall through. */
3015 case tcc_comparison: /* a comparison expression */
3016 case tcc_unary: /* a unary arithmetic expression */
3017 case tcc_binary: /* a binary arithmetic expression */
3018 case tcc_reference: /* a reference */
3019 case tcc_vl_exp: /* a function call */
3020 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
3021 for (i = 0; i < len; ++i)
3023 tree op = TREE_OPERAND (t, i);
3024 if (op && TREE_SIDE_EFFECTS (op))
3025 TREE_SIDE_EFFECTS (t) = 1;
3027 break;
3029 case tcc_constant:
3030 /* No side-effects. */
3031 return;
3033 default:
3034 gcc_unreachable ();
3038 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
3039 node *EXPR_P.
3041 compound_lval
3042 : min_lval '[' val ']'
3043 | min_lval '.' ID
3044 | compound_lval '[' val ']'
3045 | compound_lval '.' ID
3047 This is not part of the original SIMPLE definition, which separates
3048 array and member references, but it seems reasonable to handle them
3049 together. Also, this way we don't run into problems with union
3050 aliasing; gcc requires that for accesses through a union to alias, the
3051 union reference must be explicit, which was not always the case when we
3052 were splitting up array and member refs.
3054 PRE_P points to the sequence where side effects that must happen before
3055 *EXPR_P should be stored.
3057 POST_P points to the sequence where side effects that must happen after
3058 *EXPR_P should be stored. */
3060 static enum gimplify_status
3061 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3062 fallback_t fallback)
3064 tree *p;
3065 enum gimplify_status ret = GS_ALL_DONE, tret;
3066 int i;
3067 location_t loc = EXPR_LOCATION (*expr_p);
3068 tree expr = *expr_p;
3070 /* Create a stack of the subexpressions so later we can walk them in
3071 order from inner to outer. */
3072 auto_vec<tree, 10> expr_stack;
3074 /* We can handle anything that get_inner_reference can deal with. */
3075 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
3077 restart:
3078 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
3079 if (TREE_CODE (*p) == INDIRECT_REF)
3080 *p = fold_indirect_ref_loc (loc, *p);
3082 if (handled_component_p (*p))
3084 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
3085 additional COMPONENT_REFs. */
3086 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
3087 && gimplify_var_or_parm_decl (p) == GS_OK)
3088 goto restart;
3089 else
3090 break;
3092 expr_stack.safe_push (*p);
3095 gcc_assert (expr_stack.length ());
3097 /* Now EXPR_STACK is a stack of pointers to all the refs we've
3098 walked through and P points to the innermost expression.
3100 Java requires that we elaborated nodes in source order. That
3101 means we must gimplify the inner expression followed by each of
3102 the indices, in order. But we can't gimplify the inner
3103 expression until we deal with any variable bounds, sizes, or
3104 positions in order to deal with PLACEHOLDER_EXPRs.
3106 So we do this in three steps. First we deal with the annotations
3107 for any variables in the components, then we gimplify the base,
3108 then we gimplify any indices, from left to right. */
3109 for (i = expr_stack.length () - 1; i >= 0; i--)
3111 tree t = expr_stack[i];
3113 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3115 /* Gimplify the low bound and element type size and put them into
3116 the ARRAY_REF. If these values are set, they have already been
3117 gimplified. */
3118 if (TREE_OPERAND (t, 2) == NULL_TREE)
3120 tree low = unshare_expr (array_ref_low_bound (t));
3121 if (!is_gimple_min_invariant (low))
3123 TREE_OPERAND (t, 2) = low;
3124 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
3125 post_p, is_gimple_reg,
3126 fb_rvalue);
3127 ret = MIN (ret, tret);
3130 else
3132 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3133 is_gimple_reg, fb_rvalue);
3134 ret = MIN (ret, tret);
3137 if (TREE_OPERAND (t, 3) == NULL_TREE)
3139 tree elmt_size = array_ref_element_size (t);
3140 if (!is_gimple_min_invariant (elmt_size))
3142 elmt_size = unshare_expr (elmt_size);
3143 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
3144 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
3146 /* Divide the element size by the alignment of the element
3147 type (above). */
3148 elmt_size = size_binop_loc (loc, EXACT_DIV_EXPR,
3149 elmt_size, factor);
3151 TREE_OPERAND (t, 3) = elmt_size;
3152 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
3153 post_p, is_gimple_reg,
3154 fb_rvalue);
3155 ret = MIN (ret, tret);
3158 else
3160 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
3161 is_gimple_reg, fb_rvalue);
3162 ret = MIN (ret, tret);
3165 else if (TREE_CODE (t) == COMPONENT_REF)
3167 /* Set the field offset into T and gimplify it. */
3168 if (TREE_OPERAND (t, 2) == NULL_TREE)
3170 tree offset = component_ref_field_offset (t);
3171 if (!is_gimple_min_invariant (offset))
3173 offset = unshare_expr (offset);
3174 tree field = TREE_OPERAND (t, 1);
3175 tree factor
3176 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
3178 /* Divide the offset by its alignment. */
3179 offset = size_binop_loc (loc, EXACT_DIV_EXPR,
3180 offset, factor);
3182 TREE_OPERAND (t, 2) = offset;
3183 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
3184 post_p, is_gimple_reg,
3185 fb_rvalue);
3186 ret = MIN (ret, tret);
3189 else
3191 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3192 is_gimple_reg, fb_rvalue);
3193 ret = MIN (ret, tret);
3198 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
3199 so as to match the min_lval predicate. Failure to do so may result
3200 in the creation of large aggregate temporaries. */
3201 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
3202 fallback | fb_lvalue);
3203 ret = MIN (ret, tret);
3205 /* And finally, the indices and operands of ARRAY_REF. During this
3206 loop we also remove any useless conversions. */
3207 for (; expr_stack.length () > 0; )
3209 tree t = expr_stack.pop ();
3211 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3213 /* Gimplify the dimension. */
3214 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
3216 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
3217 is_gimple_val, fb_rvalue);
3218 ret = MIN (ret, tret);
3222 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
3224 /* The innermost expression P may have originally had
3225 TREE_SIDE_EFFECTS set which would have caused all the outer
3226 expressions in *EXPR_P leading to P to also have had
3227 TREE_SIDE_EFFECTS set. */
3228 recalculate_side_effects (t);
3231 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
3232 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
3234 canonicalize_component_ref (expr_p);
3237 expr_stack.release ();
3239 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
3241 return ret;
3244 /* Gimplify the self modifying expression pointed to by EXPR_P
3245 (++, --, +=, -=).
3247 PRE_P points to the list where side effects that must happen before
3248 *EXPR_P should be stored.
3250 POST_P points to the list where side effects that must happen after
3251 *EXPR_P should be stored.
3253 WANT_VALUE is nonzero iff we want to use the value of this expression
3254 in another expression.
3256 ARITH_TYPE is the type the computation should be performed in. */
3258 enum gimplify_status
3259 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3260 bool want_value, tree arith_type)
3262 enum tree_code code;
3263 tree lhs, lvalue, rhs, t1;
3264 gimple_seq post = NULL, *orig_post_p = post_p;
3265 bool postfix;
3266 enum tree_code arith_code;
3267 enum gimplify_status ret;
3268 location_t loc = EXPR_LOCATION (*expr_p);
3270 code = TREE_CODE (*expr_p);
3272 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
3273 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
3275 /* Prefix or postfix? */
3276 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
3277 /* Faster to treat as prefix if result is not used. */
3278 postfix = want_value;
3279 else
3280 postfix = false;
3282 /* For postfix, make sure the inner expression's post side effects
3283 are executed after side effects from this expression. */
3284 if (postfix)
3285 post_p = &post;
3287 /* Add or subtract? */
3288 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
3289 arith_code = PLUS_EXPR;
3290 else
3291 arith_code = MINUS_EXPR;
3293 /* Gimplify the LHS into a GIMPLE lvalue. */
3294 lvalue = TREE_OPERAND (*expr_p, 0);
3295 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3296 if (ret == GS_ERROR)
3297 return ret;
3299 /* Extract the operands to the arithmetic operation. */
3300 lhs = lvalue;
3301 rhs = TREE_OPERAND (*expr_p, 1);
3303 /* For postfix operator, we evaluate the LHS to an rvalue and then use
3304 that as the result value and in the postqueue operation. */
3305 if (postfix)
3307 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
3308 if (ret == GS_ERROR)
3309 return ret;
3311 lhs = get_initialized_tmp_var (lhs, pre_p);
3314 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
3315 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
3317 rhs = convert_to_ptrofftype_loc (loc, rhs);
3318 if (arith_code == MINUS_EXPR)
3319 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
3320 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
3322 else
3323 t1 = fold_convert (TREE_TYPE (*expr_p),
3324 fold_build2 (arith_code, arith_type,
3325 fold_convert (arith_type, lhs),
3326 fold_convert (arith_type, rhs)));
3328 if (postfix)
3330 gimplify_assign (lvalue, t1, pre_p);
3331 gimplify_seq_add_seq (orig_post_p, post);
3332 *expr_p = lhs;
3333 return GS_ALL_DONE;
3335 else
3337 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
3338 return GS_OK;
3342 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
3344 static void
3345 maybe_with_size_expr (tree *expr_p)
3347 tree expr = *expr_p;
3348 tree type = TREE_TYPE (expr);
3349 tree size;
3351 /* If we've already wrapped this or the type is error_mark_node, we can't do
3352 anything. */
3353 if (TREE_CODE (expr) == WITH_SIZE_EXPR
3354 || type == error_mark_node)
3355 return;
3357 /* If the size isn't known or is a constant, we have nothing to do. */
3358 size = TYPE_SIZE_UNIT (type);
3359 if (!size || poly_int_tree_p (size))
3360 return;
3362 /* Otherwise, make a WITH_SIZE_EXPR. */
3363 size = unshare_expr (size);
3364 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
3365 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
3368 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
3369 Store any side-effects in PRE_P. CALL_LOCATION is the location of
3370 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
3371 gimplified to an SSA name. */
3373 enum gimplify_status
3374 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3375 bool allow_ssa)
3377 bool (*test) (tree);
3378 fallback_t fb;
3380 /* In general, we allow lvalues for function arguments to avoid
3381 extra overhead of copying large aggregates out of even larger
3382 aggregates into temporaries only to copy the temporaries to
3383 the argument list. Make optimizers happy by pulling out to
3384 temporaries those types that fit in registers. */
3385 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3386 test = is_gimple_val, fb = fb_rvalue;
3387 else
3389 test = is_gimple_lvalue, fb = fb_either;
3390 /* Also strip a TARGET_EXPR that would force an extra copy. */
3391 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3393 tree init = TARGET_EXPR_INITIAL (*arg_p);
3394 if (init
3395 && !VOID_TYPE_P (TREE_TYPE (init)))
3396 *arg_p = init;
3400 /* If this is a variable sized type, we must remember the size. */
3401 maybe_with_size_expr (arg_p);
3403 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3404 /* Make sure arguments have the same location as the function call
3405 itself. */
3406 protected_set_expr_location (*arg_p, call_location);
3408 /* There is a sequence point before a function call. Side effects in
3409 the argument list must occur before the actual call. So, when
3410 gimplifying arguments, force gimplify_expr to use an internal
3411 post queue which is then appended to the end of PRE_P. */
3412 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3415 /* Don't fold inside offloading or taskreg regions: it can break code by
3416 adding decl references that weren't in the source. We'll do it during
3417 omplower pass instead. */
3419 static bool
3420 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3422 struct gimplify_omp_ctx *ctx;
3423 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3424 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3425 return false;
3426 else if ((ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
3427 return false;
3428 /* Delay folding of builtins until the IL is in consistent state
3429 so the diagnostic machinery can do a better job. */
3430 if (gimple_call_builtin_p (gsi_stmt (*gsi)))
3431 return false;
3432 return fold_stmt (gsi);
3435 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3436 WANT_VALUE is true if the result of the call is desired. */
3438 static enum gimplify_status
3439 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3441 tree fndecl, parms, p, fnptrtype;
3442 enum gimplify_status ret;
3443 int i, nargs;
3444 gcall *call;
3445 bool builtin_va_start_p = false;
3446 location_t loc = EXPR_LOCATION (*expr_p);
3448 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3450 /* For reliable diagnostics during inlining, it is necessary that
3451 every call_expr be annotated with file and line. */
3452 if (! EXPR_HAS_LOCATION (*expr_p))
3453 SET_EXPR_LOCATION (*expr_p, input_location);
3455 /* Gimplify internal functions created in the FEs. */
3456 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3458 if (want_value)
3459 return GS_ALL_DONE;
3461 nargs = call_expr_nargs (*expr_p);
3462 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3463 auto_vec<tree> vargs (nargs);
3465 for (i = 0; i < nargs; i++)
3467 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3468 EXPR_LOCATION (*expr_p));
3469 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3472 gcall *call = gimple_build_call_internal_vec (ifn, vargs);
3473 gimple_call_set_nothrow (call, TREE_NOTHROW (*expr_p));
3474 gimplify_seq_add_stmt (pre_p, call);
3475 return GS_ALL_DONE;
3478 /* This may be a call to a builtin function.
3480 Builtin function calls may be transformed into different
3481 (and more efficient) builtin function calls under certain
3482 circumstances. Unfortunately, gimplification can muck things
3483 up enough that the builtin expanders are not aware that certain
3484 transformations are still valid.
3486 So we attempt transformation/gimplification of the call before
3487 we gimplify the CALL_EXPR. At this time we do not manage to
3488 transform all calls in the same manner as the expanders do, but
3489 we do transform most of them. */
3490 fndecl = get_callee_fndecl (*expr_p);
3491 if (fndecl && fndecl_built_in_p (fndecl, BUILT_IN_NORMAL))
3492 switch (DECL_FUNCTION_CODE (fndecl))
3494 CASE_BUILT_IN_ALLOCA:
3495 /* If the call has been built for a variable-sized object, then we
3496 want to restore the stack level when the enclosing BIND_EXPR is
3497 exited to reclaim the allocated space; otherwise, we precisely
3498 need to do the opposite and preserve the latest stack level. */
3499 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3500 gimplify_ctxp->save_stack = true;
3501 else
3502 gimplify_ctxp->keep_stack = true;
3503 break;
3505 case BUILT_IN_VA_START:
3507 builtin_va_start_p = TRUE;
3508 if (call_expr_nargs (*expr_p) < 2)
3510 error ("too few arguments to function %<va_start%>");
3511 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3512 return GS_OK;
3515 if (fold_builtin_next_arg (*expr_p, true))
3517 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3518 return GS_OK;
3520 break;
3523 case BUILT_IN_EH_RETURN:
3524 cfun->calls_eh_return = true;
3525 break;
3527 case BUILT_IN_CLEAR_PADDING:
3528 if (call_expr_nargs (*expr_p) == 1)
3530 /* Remember the original type of the argument in an internal
3531 dummy second argument, as in GIMPLE pointer conversions are
3532 useless. also mark this call as not for automatic initialization
3533 in the internal dummy third argument. */
3534 p = CALL_EXPR_ARG (*expr_p, 0);
3535 bool for_auto_init = false;
3536 *expr_p
3537 = build_call_expr_loc (EXPR_LOCATION (*expr_p), fndecl, 3, p,
3538 build_zero_cst (TREE_TYPE (p)),
3539 build_int_cst (integer_type_node,
3540 (int) for_auto_init));
3541 return GS_OK;
3543 break;
3545 default:
3548 if (fndecl && fndecl_built_in_p (fndecl))
3550 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3551 if (new_tree && new_tree != *expr_p)
3553 /* There was a transformation of this call which computes the
3554 same value, but in a more efficient way. Return and try
3555 again. */
3556 *expr_p = new_tree;
3557 return GS_OK;
3561 /* Remember the original function pointer type. */
3562 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3564 if (flag_openmp
3565 && fndecl
3566 && cfun
3567 && (cfun->curr_properties & PROP_gimple_any) == 0)
3569 tree variant = omp_resolve_declare_variant (fndecl);
3570 if (variant != fndecl)
3571 CALL_EXPR_FN (*expr_p) = build1 (ADDR_EXPR, fnptrtype, variant);
3574 /* There is a sequence point before the call, so any side effects in
3575 the calling expression must occur before the actual call. Force
3576 gimplify_expr to use an internal post queue. */
3577 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3578 is_gimple_call_addr, fb_rvalue);
3580 nargs = call_expr_nargs (*expr_p);
3582 /* Get argument types for verification. */
3583 fndecl = get_callee_fndecl (*expr_p);
3584 parms = NULL_TREE;
3585 if (fndecl)
3586 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3587 else
3588 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3590 if (fndecl && DECL_ARGUMENTS (fndecl))
3591 p = DECL_ARGUMENTS (fndecl);
3592 else if (parms)
3593 p = parms;
3594 else
3595 p = NULL_TREE;
3596 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3599 /* If the last argument is __builtin_va_arg_pack () and it is not
3600 passed as a named argument, decrease the number of CALL_EXPR
3601 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3602 if (!p
3603 && i < nargs
3604 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3606 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3607 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3609 if (last_arg_fndecl
3610 && fndecl_built_in_p (last_arg_fndecl, BUILT_IN_VA_ARG_PACK))
3612 tree call = *expr_p;
3614 --nargs;
3615 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
3616 CALL_EXPR_FN (call),
3617 nargs, CALL_EXPR_ARGP (call));
3619 /* Copy all CALL_EXPR flags, location and block, except
3620 CALL_EXPR_VA_ARG_PACK flag. */
3621 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
3622 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
3623 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
3624 = CALL_EXPR_RETURN_SLOT_OPT (call);
3625 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
3626 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
3628 /* Set CALL_EXPR_VA_ARG_PACK. */
3629 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
3633 /* If the call returns twice then after building the CFG the call
3634 argument computations will no longer dominate the call because
3635 we add an abnormal incoming edge to the call. So do not use SSA
3636 vars there. */
3637 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
3639 /* Gimplify the function arguments. */
3640 if (nargs > 0)
3642 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
3643 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
3644 PUSH_ARGS_REVERSED ? i-- : i++)
3646 enum gimplify_status t;
3648 /* Avoid gimplifying the second argument to va_start, which needs to
3649 be the plain PARM_DECL. */
3650 if ((i != 1) || !builtin_va_start_p)
3652 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3653 EXPR_LOCATION (*expr_p), ! returns_twice);
3655 if (t == GS_ERROR)
3656 ret = GS_ERROR;
3661 /* Gimplify the static chain. */
3662 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
3664 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
3665 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
3666 else
3668 enum gimplify_status t;
3669 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
3670 EXPR_LOCATION (*expr_p), ! returns_twice);
3671 if (t == GS_ERROR)
3672 ret = GS_ERROR;
3676 /* Verify the function result. */
3677 if (want_value && fndecl
3678 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
3680 error_at (loc, "using result of function returning %<void%>");
3681 ret = GS_ERROR;
3684 /* Try this again in case gimplification exposed something. */
3685 if (ret != GS_ERROR)
3687 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3689 if (new_tree && new_tree != *expr_p)
3691 /* There was a transformation of this call which computes the
3692 same value, but in a more efficient way. Return and try
3693 again. */
3694 *expr_p = new_tree;
3695 return GS_OK;
3698 else
3700 *expr_p = error_mark_node;
3701 return GS_ERROR;
3704 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
3705 decl. This allows us to eliminate redundant or useless
3706 calls to "const" functions. */
3707 if (TREE_CODE (*expr_p) == CALL_EXPR)
3709 int flags = call_expr_flags (*expr_p);
3710 if (flags & (ECF_CONST | ECF_PURE)
3711 /* An infinite loop is considered a side effect. */
3712 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
3713 TREE_SIDE_EFFECTS (*expr_p) = 0;
3716 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
3717 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
3718 form and delegate the creation of a GIMPLE_CALL to
3719 gimplify_modify_expr. This is always possible because when
3720 WANT_VALUE is true, the caller wants the result of this call into
3721 a temporary, which means that we will emit an INIT_EXPR in
3722 internal_get_tmp_var which will then be handled by
3723 gimplify_modify_expr. */
3724 if (!want_value)
3726 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
3727 have to do is replicate it as a GIMPLE_CALL tuple. */
3728 gimple_stmt_iterator gsi;
3729 call = gimple_build_call_from_tree (*expr_p, fnptrtype);
3730 notice_special_calls (call);
3731 gimplify_seq_add_stmt (pre_p, call);
3732 gsi = gsi_last (*pre_p);
3733 maybe_fold_stmt (&gsi);
3734 *expr_p = NULL_TREE;
3736 else
3737 /* Remember the original function type. */
3738 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
3739 CALL_EXPR_FN (*expr_p));
3741 return ret;
3744 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
3745 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
3747 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
3748 condition is true or false, respectively. If null, we should generate
3749 our own to skip over the evaluation of this specific expression.
3751 LOCUS is the source location of the COND_EXPR.
3753 This function is the tree equivalent of do_jump.
3755 shortcut_cond_r should only be called by shortcut_cond_expr. */
3757 static tree
3758 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
3759 location_t locus)
3761 tree local_label = NULL_TREE;
3762 tree t, expr = NULL;
3764 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
3765 retain the shortcut semantics. Just insert the gotos here;
3766 shortcut_cond_expr will append the real blocks later. */
3767 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3769 location_t new_locus;
3771 /* Turn if (a && b) into
3773 if (a); else goto no;
3774 if (b) goto yes; else goto no;
3775 (no:) */
3777 if (false_label_p == NULL)
3778 false_label_p = &local_label;
3780 /* Keep the original source location on the first 'if'. */
3781 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
3782 append_to_statement_list (t, &expr);
3784 /* Set the source location of the && on the second 'if'. */
3785 new_locus = rexpr_location (pred, locus);
3786 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3787 new_locus);
3788 append_to_statement_list (t, &expr);
3790 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3792 location_t new_locus;
3794 /* Turn if (a || b) into
3796 if (a) goto yes;
3797 if (b) goto yes; else goto no;
3798 (yes:) */
3800 if (true_label_p == NULL)
3801 true_label_p = &local_label;
3803 /* Keep the original source location on the first 'if'. */
3804 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
3805 append_to_statement_list (t, &expr);
3807 /* Set the source location of the || on the second 'if'. */
3808 new_locus = rexpr_location (pred, locus);
3809 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3810 new_locus);
3811 append_to_statement_list (t, &expr);
3813 else if (TREE_CODE (pred) == COND_EXPR
3814 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
3815 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
3817 location_t new_locus;
3819 /* As long as we're messing with gotos, turn if (a ? b : c) into
3820 if (a)
3821 if (b) goto yes; else goto no;
3822 else
3823 if (c) goto yes; else goto no;
3825 Don't do this if one of the arms has void type, which can happen
3826 in C++ when the arm is throw. */
3828 /* Keep the original source location on the first 'if'. Set the source
3829 location of the ? on the second 'if'. */
3830 new_locus = rexpr_location (pred, locus);
3831 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
3832 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
3833 false_label_p, locus),
3834 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
3835 false_label_p, new_locus));
3837 else
3839 expr = build3 (COND_EXPR, void_type_node, pred,
3840 build_and_jump (true_label_p),
3841 build_and_jump (false_label_p));
3842 SET_EXPR_LOCATION (expr, locus);
3845 if (local_label)
3847 t = build1 (LABEL_EXPR, void_type_node, local_label);
3848 append_to_statement_list (t, &expr);
3851 return expr;
3854 /* If EXPR is a GOTO_EXPR, return it. If it is a STATEMENT_LIST, skip
3855 any of its leading DEBUG_BEGIN_STMTS and recurse on the subsequent
3856 statement, if it is the last one. Otherwise, return NULL. */
3858 static tree
3859 find_goto (tree expr)
3861 if (!expr)
3862 return NULL_TREE;
3864 if (TREE_CODE (expr) == GOTO_EXPR)
3865 return expr;
3867 if (TREE_CODE (expr) != STATEMENT_LIST)
3868 return NULL_TREE;
3870 tree_stmt_iterator i = tsi_start (expr);
3872 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
3873 tsi_next (&i);
3875 if (!tsi_one_before_end_p (i))
3876 return NULL_TREE;
3878 return find_goto (tsi_stmt (i));
3881 /* Same as find_goto, except that it returns NULL if the destination
3882 is not a LABEL_DECL. */
3884 static inline tree
3885 find_goto_label (tree expr)
3887 tree dest = find_goto (expr);
3888 if (dest && TREE_CODE (GOTO_DESTINATION (dest)) == LABEL_DECL)
3889 return dest;
3890 return NULL_TREE;
3893 /* Given a conditional expression EXPR with short-circuit boolean
3894 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
3895 predicate apart into the equivalent sequence of conditionals. */
3897 static tree
3898 shortcut_cond_expr (tree expr)
3900 tree pred = TREE_OPERAND (expr, 0);
3901 tree then_ = TREE_OPERAND (expr, 1);
3902 tree else_ = TREE_OPERAND (expr, 2);
3903 tree true_label, false_label, end_label, t;
3904 tree *true_label_p;
3905 tree *false_label_p;
3906 bool emit_end, emit_false, jump_over_else;
3907 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
3908 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
3910 /* First do simple transformations. */
3911 if (!else_se)
3913 /* If there is no 'else', turn
3914 if (a && b) then c
3915 into
3916 if (a) if (b) then c. */
3917 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3919 /* Keep the original source location on the first 'if'. */
3920 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3921 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3922 /* Set the source location of the && on the second 'if'. */
3923 if (rexpr_has_location (pred))
3924 SET_EXPR_LOCATION (expr, rexpr_location (pred));
3925 then_ = shortcut_cond_expr (expr);
3926 then_se = then_ && TREE_SIDE_EFFECTS (then_);
3927 pred = TREE_OPERAND (pred, 0);
3928 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
3929 SET_EXPR_LOCATION (expr, locus);
3933 if (!then_se)
3935 /* If there is no 'then', turn
3936 if (a || b); else d
3937 into
3938 if (a); else if (b); else d. */
3939 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3941 /* Keep the original source location on the first 'if'. */
3942 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3943 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3944 /* Set the source location of the || on the second 'if'. */
3945 if (rexpr_has_location (pred))
3946 SET_EXPR_LOCATION (expr, rexpr_location (pred));
3947 else_ = shortcut_cond_expr (expr);
3948 else_se = else_ && TREE_SIDE_EFFECTS (else_);
3949 pred = TREE_OPERAND (pred, 0);
3950 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
3951 SET_EXPR_LOCATION (expr, locus);
3955 /* If we're done, great. */
3956 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
3957 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
3958 return expr;
3960 /* Otherwise we need to mess with gotos. Change
3961 if (a) c; else d;
3963 if (a); else goto no;
3964 c; goto end;
3965 no: d; end:
3966 and recursively gimplify the condition. */
3968 true_label = false_label = end_label = NULL_TREE;
3970 /* If our arms just jump somewhere, hijack those labels so we don't
3971 generate jumps to jumps. */
3973 if (tree then_goto = find_goto_label (then_))
3975 true_label = GOTO_DESTINATION (then_goto);
3976 then_ = NULL;
3977 then_se = false;
3980 if (tree else_goto = find_goto_label (else_))
3982 false_label = GOTO_DESTINATION (else_goto);
3983 else_ = NULL;
3984 else_se = false;
3987 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
3988 if (true_label)
3989 true_label_p = &true_label;
3990 else
3991 true_label_p = NULL;
3993 /* The 'else' branch also needs a label if it contains interesting code. */
3994 if (false_label || else_se)
3995 false_label_p = &false_label;
3996 else
3997 false_label_p = NULL;
3999 /* If there was nothing else in our arms, just forward the label(s). */
4000 if (!then_se && !else_se)
4001 return shortcut_cond_r (pred, true_label_p, false_label_p,
4002 EXPR_LOC_OR_LOC (expr, input_location));
4004 /* If our last subexpression already has a terminal label, reuse it. */
4005 if (else_se)
4006 t = expr_last (else_);
4007 else if (then_se)
4008 t = expr_last (then_);
4009 else
4010 t = NULL;
4011 if (t && TREE_CODE (t) == LABEL_EXPR)
4012 end_label = LABEL_EXPR_LABEL (t);
4014 /* If we don't care about jumping to the 'else' branch, jump to the end
4015 if the condition is false. */
4016 if (!false_label_p)
4017 false_label_p = &end_label;
4019 /* We only want to emit these labels if we aren't hijacking them. */
4020 emit_end = (end_label == NULL_TREE);
4021 emit_false = (false_label == NULL_TREE);
4023 /* We only emit the jump over the else clause if we have to--if the
4024 then clause may fall through. Otherwise we can wind up with a
4025 useless jump and a useless label at the end of gimplified code,
4026 which will cause us to think that this conditional as a whole
4027 falls through even if it doesn't. If we then inline a function
4028 which ends with such a condition, that can cause us to issue an
4029 inappropriate warning about control reaching the end of a
4030 non-void function. */
4031 jump_over_else = block_may_fallthru (then_);
4033 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
4034 EXPR_LOC_OR_LOC (expr, input_location));
4036 expr = NULL;
4037 append_to_statement_list (pred, &expr);
4039 append_to_statement_list (then_, &expr);
4040 if (else_se)
4042 if (jump_over_else)
4044 tree last = expr_last (expr);
4045 t = build_and_jump (&end_label);
4046 if (rexpr_has_location (last))
4047 SET_EXPR_LOCATION (t, rexpr_location (last));
4048 append_to_statement_list (t, &expr);
4050 if (emit_false)
4052 t = build1 (LABEL_EXPR, void_type_node, false_label);
4053 append_to_statement_list (t, &expr);
4055 append_to_statement_list (else_, &expr);
4057 if (emit_end && end_label)
4059 t = build1 (LABEL_EXPR, void_type_node, end_label);
4060 append_to_statement_list (t, &expr);
4063 return expr;
4066 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
4068 tree
4069 gimple_boolify (tree expr)
4071 tree type = TREE_TYPE (expr);
4072 location_t loc = EXPR_LOCATION (expr);
4074 if (TREE_CODE (expr) == NE_EXPR
4075 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
4076 && integer_zerop (TREE_OPERAND (expr, 1)))
4078 tree call = TREE_OPERAND (expr, 0);
4079 tree fn = get_callee_fndecl (call);
4081 /* For __builtin_expect ((long) (x), y) recurse into x as well
4082 if x is truth_value_p. */
4083 if (fn
4084 && fndecl_built_in_p (fn, BUILT_IN_EXPECT)
4085 && call_expr_nargs (call) == 2)
4087 tree arg = CALL_EXPR_ARG (call, 0);
4088 if (arg)
4090 if (TREE_CODE (arg) == NOP_EXPR
4091 && TREE_TYPE (arg) == TREE_TYPE (call))
4092 arg = TREE_OPERAND (arg, 0);
4093 if (truth_value_p (TREE_CODE (arg)))
4095 arg = gimple_boolify (arg);
4096 CALL_EXPR_ARG (call, 0)
4097 = fold_convert_loc (loc, TREE_TYPE (call), arg);
4103 switch (TREE_CODE (expr))
4105 case TRUTH_AND_EXPR:
4106 case TRUTH_OR_EXPR:
4107 case TRUTH_XOR_EXPR:
4108 case TRUTH_ANDIF_EXPR:
4109 case TRUTH_ORIF_EXPR:
4110 /* Also boolify the arguments of truth exprs. */
4111 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
4112 /* FALLTHRU */
4114 case TRUTH_NOT_EXPR:
4115 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4117 /* These expressions always produce boolean results. */
4118 if (TREE_CODE (type) != BOOLEAN_TYPE)
4119 TREE_TYPE (expr) = boolean_type_node;
4120 return expr;
4122 case ANNOTATE_EXPR:
4123 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
4125 case annot_expr_ivdep_kind:
4126 case annot_expr_unroll_kind:
4127 case annot_expr_no_vector_kind:
4128 case annot_expr_vector_kind:
4129 case annot_expr_parallel_kind:
4130 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4131 if (TREE_CODE (type) != BOOLEAN_TYPE)
4132 TREE_TYPE (expr) = boolean_type_node;
4133 return expr;
4134 default:
4135 gcc_unreachable ();
4138 default:
4139 if (COMPARISON_CLASS_P (expr))
4141 /* There expressions always prduce boolean results. */
4142 if (TREE_CODE (type) != BOOLEAN_TYPE)
4143 TREE_TYPE (expr) = boolean_type_node;
4144 return expr;
4146 /* Other expressions that get here must have boolean values, but
4147 might need to be converted to the appropriate mode. */
4148 if (TREE_CODE (type) == BOOLEAN_TYPE)
4149 return expr;
4150 return fold_convert_loc (loc, boolean_type_node, expr);
4154 /* Given a conditional expression *EXPR_P without side effects, gimplify
4155 its operands. New statements are inserted to PRE_P. */
4157 static enum gimplify_status
4158 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
4160 tree expr = *expr_p, cond;
4161 enum gimplify_status ret, tret;
4162 enum tree_code code;
4164 cond = gimple_boolify (COND_EXPR_COND (expr));
4166 /* We need to handle && and || specially, as their gimplification
4167 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
4168 code = TREE_CODE (cond);
4169 if (code == TRUTH_ANDIF_EXPR)
4170 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
4171 else if (code == TRUTH_ORIF_EXPR)
4172 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
4173 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_condexpr, fb_rvalue);
4174 COND_EXPR_COND (*expr_p) = cond;
4176 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
4177 is_gimple_val, fb_rvalue);
4178 ret = MIN (ret, tret);
4179 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
4180 is_gimple_val, fb_rvalue);
4182 return MIN (ret, tret);
4185 /* Return true if evaluating EXPR could trap.
4186 EXPR is GENERIC, while tree_could_trap_p can be called
4187 only on GIMPLE. */
4189 bool
4190 generic_expr_could_trap_p (tree expr)
4192 unsigned i, n;
4194 if (!expr || is_gimple_val (expr))
4195 return false;
4197 if (!EXPR_P (expr) || tree_could_trap_p (expr))
4198 return true;
4200 n = TREE_OPERAND_LENGTH (expr);
4201 for (i = 0; i < n; i++)
4202 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
4203 return true;
4205 return false;
4208 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
4209 into
4211 if (p) if (p)
4212 t1 = a; a;
4213 else or else
4214 t1 = b; b;
4217 The second form is used when *EXPR_P is of type void.
4219 PRE_P points to the list where side effects that must happen before
4220 *EXPR_P should be stored. */
4222 static enum gimplify_status
4223 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
4225 tree expr = *expr_p;
4226 tree type = TREE_TYPE (expr);
4227 location_t loc = EXPR_LOCATION (expr);
4228 tree tmp, arm1, arm2;
4229 enum gimplify_status ret;
4230 tree label_true, label_false, label_cont;
4231 bool have_then_clause_p, have_else_clause_p;
4232 gcond *cond_stmt;
4233 enum tree_code pred_code;
4234 gimple_seq seq = NULL;
4236 /* If this COND_EXPR has a value, copy the values into a temporary within
4237 the arms. */
4238 if (!VOID_TYPE_P (type))
4240 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
4241 tree result;
4243 /* If either an rvalue is ok or we do not require an lvalue, create the
4244 temporary. But we cannot do that if the type is addressable. */
4245 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
4246 && !TREE_ADDRESSABLE (type))
4248 if (gimplify_ctxp->allow_rhs_cond_expr
4249 /* If either branch has side effects or could trap, it can't be
4250 evaluated unconditionally. */
4251 && !TREE_SIDE_EFFECTS (then_)
4252 && !generic_expr_could_trap_p (then_)
4253 && !TREE_SIDE_EFFECTS (else_)
4254 && !generic_expr_could_trap_p (else_))
4255 return gimplify_pure_cond_expr (expr_p, pre_p);
4257 tmp = create_tmp_var (type, "iftmp");
4258 result = tmp;
4261 /* Otherwise, only create and copy references to the values. */
4262 else
4264 type = build_pointer_type (type);
4266 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4267 then_ = build_fold_addr_expr_loc (loc, then_);
4269 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4270 else_ = build_fold_addr_expr_loc (loc, else_);
4272 expr
4273 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
4275 tmp = create_tmp_var (type, "iftmp");
4276 result = build_simple_mem_ref_loc (loc, tmp);
4279 /* Build the new then clause, `tmp = then_;'. But don't build the
4280 assignment if the value is void; in C++ it can be if it's a throw. */
4281 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4282 TREE_OPERAND (expr, 1) = build2 (INIT_EXPR, type, tmp, then_);
4284 /* Similarly, build the new else clause, `tmp = else_;'. */
4285 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4286 TREE_OPERAND (expr, 2) = build2 (INIT_EXPR, type, tmp, else_);
4288 TREE_TYPE (expr) = void_type_node;
4289 recalculate_side_effects (expr);
4291 /* Move the COND_EXPR to the prequeue. */
4292 gimplify_stmt (&expr, pre_p);
4294 *expr_p = result;
4295 return GS_ALL_DONE;
4298 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
4299 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
4300 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
4301 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
4303 /* Make sure the condition has BOOLEAN_TYPE. */
4304 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4306 /* Break apart && and || conditions. */
4307 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
4308 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
4310 expr = shortcut_cond_expr (expr);
4312 if (expr != *expr_p)
4314 *expr_p = expr;
4316 /* We can't rely on gimplify_expr to re-gimplify the expanded
4317 form properly, as cleanups might cause the target labels to be
4318 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
4319 set up a conditional context. */
4320 gimple_push_condition ();
4321 gimplify_stmt (expr_p, &seq);
4322 gimple_pop_condition (pre_p);
4323 gimple_seq_add_seq (pre_p, seq);
4325 return GS_ALL_DONE;
4329 /* Now do the normal gimplification. */
4331 /* Gimplify condition. */
4332 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
4333 is_gimple_condexpr_for_cond, fb_rvalue);
4334 if (ret == GS_ERROR)
4335 return GS_ERROR;
4336 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
4338 gimple_push_condition ();
4340 have_then_clause_p = have_else_clause_p = false;
4341 label_true = find_goto_label (TREE_OPERAND (expr, 1));
4342 if (label_true
4343 && DECL_CONTEXT (GOTO_DESTINATION (label_true)) == current_function_decl
4344 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4345 have different locations, otherwise we end up with incorrect
4346 location information on the branches. */
4347 && (optimize
4348 || !EXPR_HAS_LOCATION (expr)
4349 || !rexpr_has_location (label_true)
4350 || EXPR_LOCATION (expr) == rexpr_location (label_true)))
4352 have_then_clause_p = true;
4353 label_true = GOTO_DESTINATION (label_true);
4355 else
4356 label_true = create_artificial_label (UNKNOWN_LOCATION);
4357 label_false = find_goto_label (TREE_OPERAND (expr, 2));
4358 if (label_false
4359 && DECL_CONTEXT (GOTO_DESTINATION (label_false)) == current_function_decl
4360 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4361 have different locations, otherwise we end up with incorrect
4362 location information on the branches. */
4363 && (optimize
4364 || !EXPR_HAS_LOCATION (expr)
4365 || !rexpr_has_location (label_false)
4366 || EXPR_LOCATION (expr) == rexpr_location (label_false)))
4368 have_else_clause_p = true;
4369 label_false = GOTO_DESTINATION (label_false);
4371 else
4372 label_false = create_artificial_label (UNKNOWN_LOCATION);
4374 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
4375 &arm2);
4376 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
4377 label_false);
4378 gimple_set_location (cond_stmt, EXPR_LOCATION (expr));
4379 copy_warning (cond_stmt, COND_EXPR_COND (expr));
4380 gimplify_seq_add_stmt (&seq, cond_stmt);
4381 gimple_stmt_iterator gsi = gsi_last (seq);
4382 maybe_fold_stmt (&gsi);
4384 label_cont = NULL_TREE;
4385 if (!have_then_clause_p)
4387 /* For if (...) {} else { code; } put label_true after
4388 the else block. */
4389 if (TREE_OPERAND (expr, 1) == NULL_TREE
4390 && !have_else_clause_p
4391 && TREE_OPERAND (expr, 2) != NULL_TREE)
4392 label_cont = label_true;
4393 else
4395 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
4396 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
4397 /* For if (...) { code; } else {} or
4398 if (...) { code; } else goto label; or
4399 if (...) { code; return; } else { ... }
4400 label_cont isn't needed. */
4401 if (!have_else_clause_p
4402 && TREE_OPERAND (expr, 2) != NULL_TREE
4403 && gimple_seq_may_fallthru (seq))
4405 gimple *g;
4406 label_cont = create_artificial_label (UNKNOWN_LOCATION);
4408 g = gimple_build_goto (label_cont);
4410 /* GIMPLE_COND's are very low level; they have embedded
4411 gotos. This particular embedded goto should not be marked
4412 with the location of the original COND_EXPR, as it would
4413 correspond to the COND_EXPR's condition, not the ELSE or the
4414 THEN arms. To avoid marking it with the wrong location, flag
4415 it as "no location". */
4416 gimple_set_do_not_emit_location (g);
4418 gimplify_seq_add_stmt (&seq, g);
4422 if (!have_else_clause_p)
4424 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
4425 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
4427 if (label_cont)
4428 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
4430 gimple_pop_condition (pre_p);
4431 gimple_seq_add_seq (pre_p, seq);
4433 if (ret == GS_ERROR)
4434 ; /* Do nothing. */
4435 else if (have_then_clause_p || have_else_clause_p)
4436 ret = GS_ALL_DONE;
4437 else
4439 /* Both arms are empty; replace the COND_EXPR with its predicate. */
4440 expr = TREE_OPERAND (expr, 0);
4441 gimplify_stmt (&expr, pre_p);
4444 *expr_p = NULL;
4445 return ret;
4448 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4449 to be marked addressable.
4451 We cannot rely on such an expression being directly markable if a temporary
4452 has been created by the gimplification. In this case, we create another
4453 temporary and initialize it with a copy, which will become a store after we
4454 mark it addressable. This can happen if the front-end passed us something
4455 that it could not mark addressable yet, like a Fortran pass-by-reference
4456 parameter (int) floatvar. */
4458 static void
4459 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4461 while (handled_component_p (*expr_p))
4462 expr_p = &TREE_OPERAND (*expr_p, 0);
4463 if (is_gimple_reg (*expr_p))
4465 /* Do not allow an SSA name as the temporary. */
4466 tree var = get_initialized_tmp_var (*expr_p, seq_p, NULL, false);
4467 DECL_NOT_GIMPLE_REG_P (var) = 1;
4468 *expr_p = var;
4472 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4473 a call to __builtin_memcpy. */
4475 static enum gimplify_status
4476 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4477 gimple_seq *seq_p)
4479 tree t, to, to_ptr, from, from_ptr;
4480 gcall *gs;
4481 location_t loc = EXPR_LOCATION (*expr_p);
4483 to = TREE_OPERAND (*expr_p, 0);
4484 from = TREE_OPERAND (*expr_p, 1);
4486 /* Mark the RHS addressable. Beware that it may not be possible to do so
4487 directly if a temporary has been created by the gimplification. */
4488 prepare_gimple_addressable (&from, seq_p);
4490 mark_addressable (from);
4491 from_ptr = build_fold_addr_expr_loc (loc, from);
4492 gimplify_arg (&from_ptr, seq_p, loc);
4494 mark_addressable (to);
4495 to_ptr = build_fold_addr_expr_loc (loc, to);
4496 gimplify_arg (&to_ptr, seq_p, loc);
4498 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4500 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4501 gimple_call_set_alloca_for_var (gs, true);
4503 if (want_value)
4505 /* tmp = memcpy() */
4506 t = create_tmp_var (TREE_TYPE (to_ptr));
4507 gimple_call_set_lhs (gs, t);
4508 gimplify_seq_add_stmt (seq_p, gs);
4510 *expr_p = build_simple_mem_ref (t);
4511 return GS_ALL_DONE;
4514 gimplify_seq_add_stmt (seq_p, gs);
4515 *expr_p = NULL;
4516 return GS_ALL_DONE;
4519 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4520 a call to __builtin_memset. In this case we know that the RHS is
4521 a CONSTRUCTOR with an empty element list. */
4523 static enum gimplify_status
4524 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4525 gimple_seq *seq_p)
4527 tree t, from, to, to_ptr;
4528 gcall *gs;
4529 location_t loc = EXPR_LOCATION (*expr_p);
4531 /* Assert our assumptions, to abort instead of producing wrong code
4532 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4533 not be immediately exposed. */
4534 from = TREE_OPERAND (*expr_p, 1);
4535 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4536 from = TREE_OPERAND (from, 0);
4538 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4539 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4541 /* Now proceed. */
4542 to = TREE_OPERAND (*expr_p, 0);
4544 to_ptr = build_fold_addr_expr_loc (loc, to);
4545 gimplify_arg (&to_ptr, seq_p, loc);
4546 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4548 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4550 if (want_value)
4552 /* tmp = memset() */
4553 t = create_tmp_var (TREE_TYPE (to_ptr));
4554 gimple_call_set_lhs (gs, t);
4555 gimplify_seq_add_stmt (seq_p, gs);
4557 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4558 return GS_ALL_DONE;
4561 gimplify_seq_add_stmt (seq_p, gs);
4562 *expr_p = NULL;
4563 return GS_ALL_DONE;
4566 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4567 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4568 assignment. Return non-null if we detect a potential overlap. */
4570 struct gimplify_init_ctor_preeval_data
4572 /* The base decl of the lhs object. May be NULL, in which case we
4573 have to assume the lhs is indirect. */
4574 tree lhs_base_decl;
4576 /* The alias set of the lhs object. */
4577 alias_set_type lhs_alias_set;
4580 static tree
4581 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4583 struct gimplify_init_ctor_preeval_data *data
4584 = (struct gimplify_init_ctor_preeval_data *) xdata;
4585 tree t = *tp;
4587 /* If we find the base object, obviously we have overlap. */
4588 if (data->lhs_base_decl == t)
4589 return t;
4591 /* If the constructor component is indirect, determine if we have a
4592 potential overlap with the lhs. The only bits of information we
4593 have to go on at this point are addressability and alias sets. */
4594 if ((INDIRECT_REF_P (t)
4595 || TREE_CODE (t) == MEM_REF)
4596 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4597 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
4598 return t;
4600 /* If the constructor component is a call, determine if it can hide a
4601 potential overlap with the lhs through an INDIRECT_REF like above.
4602 ??? Ugh - this is completely broken. In fact this whole analysis
4603 doesn't look conservative. */
4604 if (TREE_CODE (t) == CALL_EXPR)
4606 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
4608 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
4609 if (POINTER_TYPE_P (TREE_VALUE (type))
4610 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4611 && alias_sets_conflict_p (data->lhs_alias_set,
4612 get_alias_set
4613 (TREE_TYPE (TREE_VALUE (type)))))
4614 return t;
4617 if (IS_TYPE_OR_DECL_P (t))
4618 *walk_subtrees = 0;
4619 return NULL;
4622 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
4623 force values that overlap with the lhs (as described by *DATA)
4624 into temporaries. */
4626 static void
4627 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4628 struct gimplify_init_ctor_preeval_data *data)
4630 enum gimplify_status one;
4632 /* If the value is constant, then there's nothing to pre-evaluate. */
4633 if (TREE_CONSTANT (*expr_p))
4635 /* Ensure it does not have side effects, it might contain a reference to
4636 the object we're initializing. */
4637 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
4638 return;
4641 /* If the type has non-trivial constructors, we can't pre-evaluate. */
4642 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
4643 return;
4645 /* Recurse for nested constructors. */
4646 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
4648 unsigned HOST_WIDE_INT ix;
4649 constructor_elt *ce;
4650 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
4652 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
4653 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
4655 return;
4658 /* If this is a variable sized type, we must remember the size. */
4659 maybe_with_size_expr (expr_p);
4661 /* Gimplify the constructor element to something appropriate for the rhs
4662 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
4663 the gimplifier will consider this a store to memory. Doing this
4664 gimplification now means that we won't have to deal with complicated
4665 language-specific trees, nor trees like SAVE_EXPR that can induce
4666 exponential search behavior. */
4667 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
4668 if (one == GS_ERROR)
4670 *expr_p = NULL;
4671 return;
4674 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
4675 with the lhs, since "a = { .x=a }" doesn't make sense. This will
4676 always be true for all scalars, since is_gimple_mem_rhs insists on a
4677 temporary variable for them. */
4678 if (DECL_P (*expr_p))
4679 return;
4681 /* If this is of variable size, we have no choice but to assume it doesn't
4682 overlap since we can't make a temporary for it. */
4683 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
4684 return;
4686 /* Otherwise, we must search for overlap ... */
4687 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
4688 return;
4690 /* ... and if found, force the value into a temporary. */
4691 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
4694 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
4695 a RANGE_EXPR in a CONSTRUCTOR for an array.
4697 var = lower;
4698 loop_entry:
4699 object[var] = value;
4700 if (var == upper)
4701 goto loop_exit;
4702 var = var + 1;
4703 goto loop_entry;
4704 loop_exit:
4706 We increment var _after_ the loop exit check because we might otherwise
4707 fail if upper == TYPE_MAX_VALUE (type for upper).
4709 Note that we never have to deal with SAVE_EXPRs here, because this has
4710 already been taken care of for us, in gimplify_init_ctor_preeval(). */
4712 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
4713 gimple_seq *, bool);
4715 static void
4716 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
4717 tree value, tree array_elt_type,
4718 gimple_seq *pre_p, bool cleared)
4720 tree loop_entry_label, loop_exit_label, fall_thru_label;
4721 tree var, var_type, cref, tmp;
4723 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
4724 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
4725 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
4727 /* Create and initialize the index variable. */
4728 var_type = TREE_TYPE (upper);
4729 var = create_tmp_var (var_type);
4730 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
4732 /* Add the loop entry label. */
4733 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
4735 /* Build the reference. */
4736 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4737 var, NULL_TREE, NULL_TREE);
4739 /* If we are a constructor, just call gimplify_init_ctor_eval to do
4740 the store. Otherwise just assign value to the reference. */
4742 if (TREE_CODE (value) == CONSTRUCTOR)
4743 /* NB we might have to call ourself recursively through
4744 gimplify_init_ctor_eval if the value is a constructor. */
4745 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4746 pre_p, cleared);
4747 else
4749 if (gimplify_expr (&value, pre_p, NULL, is_gimple_val, fb_rvalue)
4750 != GS_ERROR)
4751 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
4754 /* We exit the loop when the index var is equal to the upper bound. */
4755 gimplify_seq_add_stmt (pre_p,
4756 gimple_build_cond (EQ_EXPR, var, upper,
4757 loop_exit_label, fall_thru_label));
4759 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
4761 /* Otherwise, increment the index var... */
4762 tmp = build2 (PLUS_EXPR, var_type, var,
4763 fold_convert (var_type, integer_one_node));
4764 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
4766 /* ...and jump back to the loop entry. */
4767 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
4769 /* Add the loop exit label. */
4770 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
4773 /* A subroutine of gimplify_init_constructor. Generate individual
4774 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
4775 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
4776 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
4777 zeroed first. */
4779 static void
4780 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
4781 gimple_seq *pre_p, bool cleared)
4783 tree array_elt_type = NULL;
4784 unsigned HOST_WIDE_INT ix;
4785 tree purpose, value;
4787 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
4788 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
4790 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
4792 tree cref;
4794 /* NULL values are created above for gimplification errors. */
4795 if (value == NULL)
4796 continue;
4798 if (cleared && initializer_zerop (value))
4799 continue;
4801 /* ??? Here's to hoping the front end fills in all of the indices,
4802 so we don't have to figure out what's missing ourselves. */
4803 gcc_assert (purpose);
4805 /* Skip zero-sized fields, unless value has side-effects. This can
4806 happen with calls to functions returning a empty type, which
4807 we shouldn't discard. As a number of downstream passes don't
4808 expect sets of empty type fields, we rely on the gimplification of
4809 the MODIFY_EXPR we make below to drop the assignment statement. */
4810 if (!TREE_SIDE_EFFECTS (value)
4811 && TREE_CODE (purpose) == FIELD_DECL
4812 && is_empty_type (TREE_TYPE (purpose)))
4813 continue;
4815 /* If we have a RANGE_EXPR, we have to build a loop to assign the
4816 whole range. */
4817 if (TREE_CODE (purpose) == RANGE_EXPR)
4819 tree lower = TREE_OPERAND (purpose, 0);
4820 tree upper = TREE_OPERAND (purpose, 1);
4822 /* If the lower bound is equal to upper, just treat it as if
4823 upper was the index. */
4824 if (simple_cst_equal (lower, upper))
4825 purpose = upper;
4826 else
4828 gimplify_init_ctor_eval_range (object, lower, upper, value,
4829 array_elt_type, pre_p, cleared);
4830 continue;
4834 if (array_elt_type)
4836 /* Do not use bitsizetype for ARRAY_REF indices. */
4837 if (TYPE_DOMAIN (TREE_TYPE (object)))
4838 purpose
4839 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
4840 purpose);
4841 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4842 purpose, NULL_TREE, NULL_TREE);
4844 else
4846 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
4847 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
4848 unshare_expr (object), purpose, NULL_TREE);
4851 if (TREE_CODE (value) == CONSTRUCTOR
4852 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
4853 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4854 pre_p, cleared);
4855 else
4857 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
4858 gimplify_and_add (init, pre_p);
4859 ggc_free (init);
4864 /* Return the appropriate RHS predicate for this LHS. */
4866 gimple_predicate
4867 rhs_predicate_for (tree lhs)
4869 if (is_gimple_reg (lhs))
4870 return is_gimple_reg_rhs_or_call;
4871 else
4872 return is_gimple_mem_rhs_or_call;
4875 /* Return the initial guess for an appropriate RHS predicate for this LHS,
4876 before the LHS has been gimplified. */
4878 static gimple_predicate
4879 initial_rhs_predicate_for (tree lhs)
4881 if (is_gimple_reg_type (TREE_TYPE (lhs)))
4882 return is_gimple_reg_rhs_or_call;
4883 else
4884 return is_gimple_mem_rhs_or_call;
4887 /* Gimplify a C99 compound literal expression. This just means adding
4888 the DECL_EXPR before the current statement and using its anonymous
4889 decl instead. */
4891 static enum gimplify_status
4892 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
4893 bool (*gimple_test_f) (tree),
4894 fallback_t fallback)
4896 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
4897 tree decl = DECL_EXPR_DECL (decl_s);
4898 tree init = DECL_INITIAL (decl);
4899 /* Mark the decl as addressable if the compound literal
4900 expression is addressable now, otherwise it is marked too late
4901 after we gimplify the initialization expression. */
4902 if (TREE_ADDRESSABLE (*expr_p))
4903 TREE_ADDRESSABLE (decl) = 1;
4904 /* Otherwise, if we don't need an lvalue and have a literal directly
4905 substitute it. Check if it matches the gimple predicate, as
4906 otherwise we'd generate a new temporary, and we can as well just
4907 use the decl we already have. */
4908 else if (!TREE_ADDRESSABLE (decl)
4909 && !TREE_THIS_VOLATILE (decl)
4910 && init
4911 && (fallback & fb_lvalue) == 0
4912 && gimple_test_f (init))
4914 *expr_p = init;
4915 return GS_OK;
4918 /* If the decl is not addressable, then it is being used in some
4919 expression or on the right hand side of a statement, and it can
4920 be put into a readonly data section. */
4921 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
4922 TREE_READONLY (decl) = 1;
4924 /* This decl isn't mentioned in the enclosing block, so add it to the
4925 list of temps. FIXME it seems a bit of a kludge to say that
4926 anonymous artificial vars aren't pushed, but everything else is. */
4927 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
4928 gimple_add_tmp_var (decl);
4930 gimplify_and_add (decl_s, pre_p);
4931 *expr_p = decl;
4932 return GS_OK;
4935 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
4936 return a new CONSTRUCTOR if something changed. */
4938 static tree
4939 optimize_compound_literals_in_ctor (tree orig_ctor)
4941 tree ctor = orig_ctor;
4942 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
4943 unsigned int idx, num = vec_safe_length (elts);
4945 for (idx = 0; idx < num; idx++)
4947 tree value = (*elts)[idx].value;
4948 tree newval = value;
4949 if (TREE_CODE (value) == CONSTRUCTOR)
4950 newval = optimize_compound_literals_in_ctor (value);
4951 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
4953 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
4954 tree decl = DECL_EXPR_DECL (decl_s);
4955 tree init = DECL_INITIAL (decl);
4957 if (!TREE_ADDRESSABLE (value)
4958 && !TREE_ADDRESSABLE (decl)
4959 && init
4960 && TREE_CODE (init) == CONSTRUCTOR)
4961 newval = optimize_compound_literals_in_ctor (init);
4963 if (newval == value)
4964 continue;
4966 if (ctor == orig_ctor)
4968 ctor = copy_node (orig_ctor);
4969 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
4970 elts = CONSTRUCTOR_ELTS (ctor);
4972 (*elts)[idx].value = newval;
4974 return ctor;
4977 /* A subroutine of gimplify_modify_expr. Break out elements of a
4978 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
4980 Note that we still need to clear any elements that don't have explicit
4981 initializers, so if not all elements are initialized we keep the
4982 original MODIFY_EXPR, we just remove all of the constructor elements.
4984 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
4985 GS_ERROR if we would have to create a temporary when gimplifying
4986 this constructor. Otherwise, return GS_OK.
4988 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
4990 static enum gimplify_status
4991 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4992 bool want_value, bool notify_temp_creation)
4994 tree object, ctor, type;
4995 enum gimplify_status ret;
4996 vec<constructor_elt, va_gc> *elts;
4997 bool cleared = false;
4998 bool is_empty_ctor = false;
4999 bool is_init_expr = (TREE_CODE (*expr_p) == INIT_EXPR);
5001 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
5003 if (!notify_temp_creation)
5005 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5006 is_gimple_lvalue, fb_lvalue);
5007 if (ret == GS_ERROR)
5008 return ret;
5011 object = TREE_OPERAND (*expr_p, 0);
5012 ctor = TREE_OPERAND (*expr_p, 1)
5013 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
5014 type = TREE_TYPE (ctor);
5015 elts = CONSTRUCTOR_ELTS (ctor);
5016 ret = GS_ALL_DONE;
5018 switch (TREE_CODE (type))
5020 case RECORD_TYPE:
5021 case UNION_TYPE:
5022 case QUAL_UNION_TYPE:
5023 case ARRAY_TYPE:
5025 /* Use readonly data for initializers of this or smaller size
5026 regardless of the num_nonzero_elements / num_unique_nonzero_elements
5027 ratio. */
5028 const HOST_WIDE_INT min_unique_size = 64;
5029 /* If num_nonzero_elements / num_unique_nonzero_elements ratio
5030 is smaller than this, use readonly data. */
5031 const int unique_nonzero_ratio = 8;
5032 /* True if a single access of the object must be ensured. This is the
5033 case if the target is volatile, the type is non-addressable and more
5034 than one field need to be assigned. */
5035 const bool ensure_single_access
5036 = TREE_THIS_VOLATILE (object)
5037 && !TREE_ADDRESSABLE (type)
5038 && vec_safe_length (elts) > 1;
5039 struct gimplify_init_ctor_preeval_data preeval_data;
5040 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
5041 HOST_WIDE_INT num_unique_nonzero_elements;
5042 bool complete_p, valid_const_initializer;
5044 /* Aggregate types must lower constructors to initialization of
5045 individual elements. The exception is that a CONSTRUCTOR node
5046 with no elements indicates zero-initialization of the whole. */
5047 if (vec_safe_is_empty (elts))
5049 if (notify_temp_creation)
5050 return GS_OK;
5051 is_empty_ctor = true;
5052 break;
5055 /* Fetch information about the constructor to direct later processing.
5056 We might want to make static versions of it in various cases, and
5057 can only do so if it known to be a valid constant initializer. */
5058 valid_const_initializer
5059 = categorize_ctor_elements (ctor, &num_nonzero_elements,
5060 &num_unique_nonzero_elements,
5061 &num_ctor_elements, &complete_p);
5063 /* If a const aggregate variable is being initialized, then it
5064 should never be a lose to promote the variable to be static. */
5065 if (valid_const_initializer
5066 && num_nonzero_elements > 1
5067 && TREE_READONLY (object)
5068 && VAR_P (object)
5069 && !DECL_REGISTER (object)
5070 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object))
5071 /* For ctors that have many repeated nonzero elements
5072 represented through RANGE_EXPRs, prefer initializing
5073 those through runtime loops over copies of large amounts
5074 of data from readonly data section. */
5075 && (num_unique_nonzero_elements
5076 > num_nonzero_elements / unique_nonzero_ratio
5077 || ((unsigned HOST_WIDE_INT) int_size_in_bytes (type)
5078 <= (unsigned HOST_WIDE_INT) min_unique_size)))
5080 if (notify_temp_creation)
5081 return GS_ERROR;
5083 DECL_INITIAL (object) = ctor;
5084 TREE_STATIC (object) = 1;
5085 if (!DECL_NAME (object))
5086 DECL_NAME (object) = create_tmp_var_name ("C");
5087 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
5089 /* ??? C++ doesn't automatically append a .<number> to the
5090 assembler name, and even when it does, it looks at FE private
5091 data structures to figure out what that number should be,
5092 which are not set for this variable. I suppose this is
5093 important for local statics for inline functions, which aren't
5094 "local" in the object file sense. So in order to get a unique
5095 TU-local symbol, we must invoke the lhd version now. */
5096 lhd_set_decl_assembler_name (object);
5098 *expr_p = NULL_TREE;
5099 break;
5102 /* If there are "lots" of initialized elements, even discounting
5103 those that are not address constants (and thus *must* be
5104 computed at runtime), then partition the constructor into
5105 constant and non-constant parts. Block copy the constant
5106 parts in, then generate code for the non-constant parts. */
5107 /* TODO. There's code in cp/typeck.c to do this. */
5109 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
5110 /* store_constructor will ignore the clearing of variable-sized
5111 objects. Initializers for such objects must explicitly set
5112 every field that needs to be set. */
5113 cleared = false;
5114 else if (!complete_p)
5115 /* If the constructor isn't complete, clear the whole object
5116 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
5118 ??? This ought not to be needed. For any element not present
5119 in the initializer, we should simply set them to zero. Except
5120 we'd need to *find* the elements that are not present, and that
5121 requires trickery to avoid quadratic compile-time behavior in
5122 large cases or excessive memory use in small cases. */
5123 cleared = !CONSTRUCTOR_NO_CLEARING (ctor);
5124 else if (num_ctor_elements - num_nonzero_elements
5125 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
5126 && num_nonzero_elements < num_ctor_elements / 4)
5127 /* If there are "lots" of zeros, it's more efficient to clear
5128 the memory and then set the nonzero elements. */
5129 cleared = true;
5130 else if (ensure_single_access && num_nonzero_elements == 0)
5131 /* If a single access to the target must be ensured and all elements
5132 are zero, then it's optimal to clear whatever their number. */
5133 cleared = true;
5134 else
5135 cleared = false;
5137 /* If there are "lots" of initialized elements, and all of them
5138 are valid address constants, then the entire initializer can
5139 be dropped to memory, and then memcpy'd out. Don't do this
5140 for sparse arrays, though, as it's more efficient to follow
5141 the standard CONSTRUCTOR behavior of memset followed by
5142 individual element initialization. Also don't do this for small
5143 all-zero initializers (which aren't big enough to merit
5144 clearing), and don't try to make bitwise copies of
5145 TREE_ADDRESSABLE types. */
5146 if (valid_const_initializer
5147 && complete_p
5148 && !(cleared || num_nonzero_elements == 0)
5149 && !TREE_ADDRESSABLE (type))
5151 HOST_WIDE_INT size = int_size_in_bytes (type);
5152 unsigned int align;
5154 /* ??? We can still get unbounded array types, at least
5155 from the C++ front end. This seems wrong, but attempt
5156 to work around it for now. */
5157 if (size < 0)
5159 size = int_size_in_bytes (TREE_TYPE (object));
5160 if (size >= 0)
5161 TREE_TYPE (ctor) = type = TREE_TYPE (object);
5164 /* Find the maximum alignment we can assume for the object. */
5165 /* ??? Make use of DECL_OFFSET_ALIGN. */
5166 if (DECL_P (object))
5167 align = DECL_ALIGN (object);
5168 else
5169 align = TYPE_ALIGN (type);
5171 /* Do a block move either if the size is so small as to make
5172 each individual move a sub-unit move on average, or if it
5173 is so large as to make individual moves inefficient. */
5174 if (size > 0
5175 && num_nonzero_elements > 1
5176 /* For ctors that have many repeated nonzero elements
5177 represented through RANGE_EXPRs, prefer initializing
5178 those through runtime loops over copies of large amounts
5179 of data from readonly data section. */
5180 && (num_unique_nonzero_elements
5181 > num_nonzero_elements / unique_nonzero_ratio
5182 || size <= min_unique_size)
5183 && (size < num_nonzero_elements
5184 || !can_move_by_pieces (size, align)))
5186 if (notify_temp_creation)
5187 return GS_ERROR;
5189 walk_tree (&ctor, force_labels_r, NULL, NULL);
5190 ctor = tree_output_constant_def (ctor);
5191 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
5192 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
5193 TREE_OPERAND (*expr_p, 1) = ctor;
5195 /* This is no longer an assignment of a CONSTRUCTOR, but
5196 we still may have processing to do on the LHS. So
5197 pretend we didn't do anything here to let that happen. */
5198 return GS_UNHANDLED;
5202 /* If a single access to the target must be ensured and there are
5203 nonzero elements or the zero elements are not assigned en masse,
5204 initialize the target from a temporary. */
5205 if (ensure_single_access && (num_nonzero_elements > 0 || !cleared))
5207 if (notify_temp_creation)
5208 return GS_ERROR;
5210 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
5211 TREE_OPERAND (*expr_p, 0) = temp;
5212 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
5213 *expr_p,
5214 build2 (MODIFY_EXPR, void_type_node,
5215 object, temp));
5216 return GS_OK;
5219 if (notify_temp_creation)
5220 return GS_OK;
5222 /* If there are nonzero elements and if needed, pre-evaluate to capture
5223 elements overlapping with the lhs into temporaries. We must do this
5224 before clearing to fetch the values before they are zeroed-out. */
5225 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
5227 preeval_data.lhs_base_decl = get_base_address (object);
5228 if (!DECL_P (preeval_data.lhs_base_decl))
5229 preeval_data.lhs_base_decl = NULL;
5230 preeval_data.lhs_alias_set = get_alias_set (object);
5232 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
5233 pre_p, post_p, &preeval_data);
5236 bool ctor_has_side_effects_p
5237 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
5239 if (cleared)
5241 /* Zap the CONSTRUCTOR element list, which simplifies this case.
5242 Note that we still have to gimplify, in order to handle the
5243 case of variable sized types. Avoid shared tree structures. */
5244 CONSTRUCTOR_ELTS (ctor) = NULL;
5245 TREE_SIDE_EFFECTS (ctor) = 0;
5246 object = unshare_expr (object);
5247 gimplify_stmt (expr_p, pre_p);
5250 /* If we have not block cleared the object, or if there are nonzero
5251 elements in the constructor, or if the constructor has side effects,
5252 add assignments to the individual scalar fields of the object. */
5253 if (!cleared
5254 || num_nonzero_elements > 0
5255 || ctor_has_side_effects_p)
5256 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
5258 *expr_p = NULL_TREE;
5260 break;
5262 case COMPLEX_TYPE:
5264 tree r, i;
5266 if (notify_temp_creation)
5267 return GS_OK;
5269 /* Extract the real and imaginary parts out of the ctor. */
5270 gcc_assert (elts->length () == 2);
5271 r = (*elts)[0].value;
5272 i = (*elts)[1].value;
5273 if (r == NULL || i == NULL)
5275 tree zero = build_zero_cst (TREE_TYPE (type));
5276 if (r == NULL)
5277 r = zero;
5278 if (i == NULL)
5279 i = zero;
5282 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
5283 represent creation of a complex value. */
5284 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
5286 ctor = build_complex (type, r, i);
5287 TREE_OPERAND (*expr_p, 1) = ctor;
5289 else
5291 ctor = build2 (COMPLEX_EXPR, type, r, i);
5292 TREE_OPERAND (*expr_p, 1) = ctor;
5293 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
5294 pre_p,
5295 post_p,
5296 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
5297 fb_rvalue);
5300 break;
5302 case VECTOR_TYPE:
5304 unsigned HOST_WIDE_INT ix;
5305 constructor_elt *ce;
5307 if (notify_temp_creation)
5308 return GS_OK;
5310 /* Go ahead and simplify constant constructors to VECTOR_CST. */
5311 if (TREE_CONSTANT (ctor))
5313 bool constant_p = true;
5314 tree value;
5316 /* Even when ctor is constant, it might contain non-*_CST
5317 elements, such as addresses or trapping values like
5318 1.0/0.0 - 1.0/0.0. Such expressions don't belong
5319 in VECTOR_CST nodes. */
5320 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
5321 if (!CONSTANT_CLASS_P (value))
5323 constant_p = false;
5324 break;
5327 if (constant_p)
5329 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
5330 break;
5333 TREE_CONSTANT (ctor) = 0;
5336 /* Vector types use CONSTRUCTOR all the way through gimple
5337 compilation as a general initializer. */
5338 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
5340 enum gimplify_status tret;
5341 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
5342 fb_rvalue);
5343 if (tret == GS_ERROR)
5344 ret = GS_ERROR;
5345 else if (TREE_STATIC (ctor)
5346 && !initializer_constant_valid_p (ce->value,
5347 TREE_TYPE (ce->value)))
5348 TREE_STATIC (ctor) = 0;
5350 recompute_constructor_flags (ctor);
5351 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
5352 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
5354 break;
5356 default:
5357 /* So how did we get a CONSTRUCTOR for a scalar type? */
5358 gcc_unreachable ();
5361 if (ret == GS_ERROR)
5362 return GS_ERROR;
5363 /* If we have gimplified both sides of the initializer but have
5364 not emitted an assignment, do so now. */
5365 if (*expr_p)
5367 tree lhs = TREE_OPERAND (*expr_p, 0);
5368 tree rhs = TREE_OPERAND (*expr_p, 1);
5369 if (want_value && object == lhs)
5370 lhs = unshare_expr (lhs);
5371 gassign *init = gimple_build_assign (lhs, rhs);
5372 gimplify_seq_add_stmt (pre_p, init);
5374 if (want_value)
5376 *expr_p = object;
5377 ret = GS_OK;
5379 else
5381 *expr_p = NULL;
5382 ret = GS_ALL_DONE;
5385 /* If the user requests to initialize automatic variables, we
5386 should initialize paddings inside the variable. Add a call to
5387 __BUILTIN_CLEAR_PADDING (&object, 0, for_auto_init = true) to
5388 initialize paddings of object always to zero regardless of
5389 INIT_TYPE. Note, we will not insert this call if the aggregate
5390 variable has be completely cleared already or it's initialized
5391 with an empty constructor. */
5392 if (is_init_expr
5393 && ((AGGREGATE_TYPE_P (type) && !cleared && !is_empty_ctor)
5394 || !AGGREGATE_TYPE_P (type))
5395 && is_var_need_auto_init (object))
5396 gimple_add_padding_init_for_auto_var (object, false, pre_p);
5398 return ret;
5401 /* Given a pointer value OP0, return a simplified version of an
5402 indirection through OP0, or NULL_TREE if no simplification is
5403 possible. This may only be applied to a rhs of an expression.
5404 Note that the resulting type may be different from the type pointed
5405 to in the sense that it is still compatible from the langhooks
5406 point of view. */
5408 static tree
5409 gimple_fold_indirect_ref_rhs (tree t)
5411 return gimple_fold_indirect_ref (t);
5414 /* Subroutine of gimplify_modify_expr to do simplifications of
5415 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
5416 something changes. */
5418 static enum gimplify_status
5419 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
5420 gimple_seq *pre_p, gimple_seq *post_p,
5421 bool want_value)
5423 enum gimplify_status ret = GS_UNHANDLED;
5424 bool changed;
5428 changed = false;
5429 switch (TREE_CODE (*from_p))
5431 case VAR_DECL:
5432 /* If we're assigning from a read-only variable initialized with
5433 a constructor and not volatile, do the direct assignment from
5434 the constructor, but only if the target is not volatile either
5435 since this latter assignment might end up being done on a per
5436 field basis. However, if the target is volatile and the type
5437 is aggregate and non-addressable, gimplify_init_constructor
5438 knows that it needs to ensure a single access to the target
5439 and it will return GS_OK only in this case. */
5440 if (TREE_READONLY (*from_p)
5441 && DECL_INITIAL (*from_p)
5442 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR
5443 && !TREE_THIS_VOLATILE (*from_p)
5444 && (!TREE_THIS_VOLATILE (*to_p)
5445 || (AGGREGATE_TYPE_P (TREE_TYPE (*to_p))
5446 && !TREE_ADDRESSABLE (TREE_TYPE (*to_p)))))
5448 tree old_from = *from_p;
5449 enum gimplify_status subret;
5451 /* Move the constructor into the RHS. */
5452 *from_p = unshare_expr (DECL_INITIAL (*from_p));
5454 /* Let's see if gimplify_init_constructor will need to put
5455 it in memory. */
5456 subret = gimplify_init_constructor (expr_p, NULL, NULL,
5457 false, true);
5458 if (subret == GS_ERROR)
5460 /* If so, revert the change. */
5461 *from_p = old_from;
5463 else
5465 ret = GS_OK;
5466 changed = true;
5469 break;
5470 case INDIRECT_REF:
5472 /* If we have code like
5474 *(const A*)(A*)&x
5476 where the type of "x" is a (possibly cv-qualified variant
5477 of "A"), treat the entire expression as identical to "x".
5478 This kind of code arises in C++ when an object is bound
5479 to a const reference, and if "x" is a TARGET_EXPR we want
5480 to take advantage of the optimization below. */
5481 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5482 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
5483 if (t)
5485 if (TREE_THIS_VOLATILE (t) != volatile_p)
5487 if (DECL_P (t))
5488 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5489 build_fold_addr_expr (t));
5490 if (REFERENCE_CLASS_P (t))
5491 TREE_THIS_VOLATILE (t) = volatile_p;
5493 *from_p = t;
5494 ret = GS_OK;
5495 changed = true;
5497 break;
5500 case TARGET_EXPR:
5502 /* If we are initializing something from a TARGET_EXPR, strip the
5503 TARGET_EXPR and initialize it directly, if possible. This can't
5504 be done if the initializer is void, since that implies that the
5505 temporary is set in some non-trivial way.
5507 ??? What about code that pulls out the temp and uses it
5508 elsewhere? I think that such code never uses the TARGET_EXPR as
5509 an initializer. If I'm wrong, we'll die because the temp won't
5510 have any RTL. In that case, I guess we'll need to replace
5511 references somehow. */
5512 tree init = TARGET_EXPR_INITIAL (*from_p);
5514 if (init
5515 && (TREE_CODE (*expr_p) != MODIFY_EXPR
5516 || !TARGET_EXPR_NO_ELIDE (*from_p))
5517 && !VOID_TYPE_P (TREE_TYPE (init)))
5519 *from_p = init;
5520 ret = GS_OK;
5521 changed = true;
5524 break;
5526 case COMPOUND_EXPR:
5527 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5528 caught. */
5529 gimplify_compound_expr (from_p, pre_p, true);
5530 ret = GS_OK;
5531 changed = true;
5532 break;
5534 case CONSTRUCTOR:
5535 /* If we already made some changes, let the front end have a
5536 crack at this before we break it down. */
5537 if (ret != GS_UNHANDLED)
5538 break;
5540 /* If we're initializing from a CONSTRUCTOR, break this into
5541 individual MODIFY_EXPRs. */
5542 ret = gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5543 false);
5544 return ret;
5546 case COND_EXPR:
5547 /* If we're assigning to a non-register type, push the assignment
5548 down into the branches. This is mandatory for ADDRESSABLE types,
5549 since we cannot generate temporaries for such, but it saves a
5550 copy in other cases as well. */
5551 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5553 /* This code should mirror the code in gimplify_cond_expr. */
5554 enum tree_code code = TREE_CODE (*expr_p);
5555 tree cond = *from_p;
5556 tree result = *to_p;
5558 ret = gimplify_expr (&result, pre_p, post_p,
5559 is_gimple_lvalue, fb_lvalue);
5560 if (ret != GS_ERROR)
5561 ret = GS_OK;
5563 /* If we are going to write RESULT more than once, clear
5564 TREE_READONLY flag, otherwise we might incorrectly promote
5565 the variable to static const and initialize it at compile
5566 time in one of the branches. */
5567 if (VAR_P (result)
5568 && TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node
5569 && TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5570 TREE_READONLY (result) = 0;
5571 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
5572 TREE_OPERAND (cond, 1)
5573 = build2 (code, void_type_node, result,
5574 TREE_OPERAND (cond, 1));
5575 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5576 TREE_OPERAND (cond, 2)
5577 = build2 (code, void_type_node, unshare_expr (result),
5578 TREE_OPERAND (cond, 2));
5580 TREE_TYPE (cond) = void_type_node;
5581 recalculate_side_effects (cond);
5583 if (want_value)
5585 gimplify_and_add (cond, pre_p);
5586 *expr_p = unshare_expr (result);
5588 else
5589 *expr_p = cond;
5590 return ret;
5592 break;
5594 case CALL_EXPR:
5595 /* For calls that return in memory, give *to_p as the CALL_EXPR's
5596 return slot so that we don't generate a temporary. */
5597 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
5598 && aggregate_value_p (*from_p, *from_p))
5600 bool use_target;
5602 if (!(rhs_predicate_for (*to_p))(*from_p))
5603 /* If we need a temporary, *to_p isn't accurate. */
5604 use_target = false;
5605 /* It's OK to use the return slot directly unless it's an NRV. */
5606 else if (TREE_CODE (*to_p) == RESULT_DECL
5607 && DECL_NAME (*to_p) == NULL_TREE
5608 && needs_to_live_in_memory (*to_p))
5609 use_target = true;
5610 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
5611 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
5612 /* Don't force regs into memory. */
5613 use_target = false;
5614 else if (TREE_CODE (*expr_p) == INIT_EXPR)
5615 /* It's OK to use the target directly if it's being
5616 initialized. */
5617 use_target = true;
5618 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
5619 != INTEGER_CST)
5620 /* Always use the target and thus RSO for variable-sized types.
5621 GIMPLE cannot deal with a variable-sized assignment
5622 embedded in a call statement. */
5623 use_target = true;
5624 else if (TREE_CODE (*to_p) != SSA_NAME
5625 && (!is_gimple_variable (*to_p)
5626 || needs_to_live_in_memory (*to_p)))
5627 /* Don't use the original target if it's already addressable;
5628 if its address escapes, and the called function uses the
5629 NRV optimization, a conforming program could see *to_p
5630 change before the called function returns; see c++/19317.
5631 When optimizing, the return_slot pass marks more functions
5632 as safe after we have escape info. */
5633 use_target = false;
5634 else
5635 use_target = true;
5637 if (use_target)
5639 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
5640 mark_addressable (*to_p);
5643 break;
5645 case WITH_SIZE_EXPR:
5646 /* Likewise for calls that return an aggregate of non-constant size,
5647 since we would not be able to generate a temporary at all. */
5648 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
5650 *from_p = TREE_OPERAND (*from_p, 0);
5651 /* We don't change ret in this case because the
5652 WITH_SIZE_EXPR might have been added in
5653 gimplify_modify_expr, so returning GS_OK would lead to an
5654 infinite loop. */
5655 changed = true;
5657 break;
5659 /* If we're initializing from a container, push the initialization
5660 inside it. */
5661 case CLEANUP_POINT_EXPR:
5662 case BIND_EXPR:
5663 case STATEMENT_LIST:
5665 tree wrap = *from_p;
5666 tree t;
5668 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
5669 fb_lvalue);
5670 if (ret != GS_ERROR)
5671 ret = GS_OK;
5673 t = voidify_wrapper_expr (wrap, *expr_p);
5674 gcc_assert (t == *expr_p);
5676 if (want_value)
5678 gimplify_and_add (wrap, pre_p);
5679 *expr_p = unshare_expr (*to_p);
5681 else
5682 *expr_p = wrap;
5683 return GS_OK;
5686 case NOP_EXPR:
5687 /* Pull out compound literal expressions from a NOP_EXPR.
5688 Those are created in the C FE to drop qualifiers during
5689 lvalue conversion. */
5690 if ((TREE_CODE (TREE_OPERAND (*from_p, 0)) == COMPOUND_LITERAL_EXPR)
5691 && tree_ssa_useless_type_conversion (*from_p))
5693 *from_p = TREE_OPERAND (*from_p, 0);
5694 ret = GS_OK;
5695 changed = true;
5697 break;
5699 case COMPOUND_LITERAL_EXPR:
5701 tree complit = TREE_OPERAND (*expr_p, 1);
5702 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
5703 tree decl = DECL_EXPR_DECL (decl_s);
5704 tree init = DECL_INITIAL (decl);
5706 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
5707 into struct T x = { 0, 1, 2 } if the address of the
5708 compound literal has never been taken. */
5709 if (!TREE_ADDRESSABLE (complit)
5710 && !TREE_ADDRESSABLE (decl)
5711 && init)
5713 *expr_p = copy_node (*expr_p);
5714 TREE_OPERAND (*expr_p, 1) = init;
5715 return GS_OK;
5719 default:
5720 break;
5723 while (changed);
5725 return ret;
5729 /* Return true if T looks like a valid GIMPLE statement. */
5731 static bool
5732 is_gimple_stmt (tree t)
5734 const enum tree_code code = TREE_CODE (t);
5736 switch (code)
5738 case NOP_EXPR:
5739 /* The only valid NOP_EXPR is the empty statement. */
5740 return IS_EMPTY_STMT (t);
5742 case BIND_EXPR:
5743 case COND_EXPR:
5744 /* These are only valid if they're void. */
5745 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
5747 case SWITCH_EXPR:
5748 case GOTO_EXPR:
5749 case RETURN_EXPR:
5750 case LABEL_EXPR:
5751 case CASE_LABEL_EXPR:
5752 case TRY_CATCH_EXPR:
5753 case TRY_FINALLY_EXPR:
5754 case EH_FILTER_EXPR:
5755 case CATCH_EXPR:
5756 case ASM_EXPR:
5757 case STATEMENT_LIST:
5758 case OACC_PARALLEL:
5759 case OACC_KERNELS:
5760 case OACC_SERIAL:
5761 case OACC_DATA:
5762 case OACC_HOST_DATA:
5763 case OACC_DECLARE:
5764 case OACC_UPDATE:
5765 case OACC_ENTER_DATA:
5766 case OACC_EXIT_DATA:
5767 case OACC_CACHE:
5768 case OMP_PARALLEL:
5769 case OMP_FOR:
5770 case OMP_SIMD:
5771 case OMP_DISTRIBUTE:
5772 case OMP_LOOP:
5773 case OACC_LOOP:
5774 case OMP_SCAN:
5775 case OMP_SCOPE:
5776 case OMP_SECTIONS:
5777 case OMP_SECTION:
5778 case OMP_SINGLE:
5779 case OMP_MASTER:
5780 case OMP_MASKED:
5781 case OMP_TASKGROUP:
5782 case OMP_ORDERED:
5783 case OMP_CRITICAL:
5784 case OMP_TASK:
5785 case OMP_TARGET:
5786 case OMP_TARGET_DATA:
5787 case OMP_TARGET_UPDATE:
5788 case OMP_TARGET_ENTER_DATA:
5789 case OMP_TARGET_EXIT_DATA:
5790 case OMP_TASKLOOP:
5791 case OMP_TEAMS:
5792 /* These are always void. */
5793 return true;
5795 case CALL_EXPR:
5796 case MODIFY_EXPR:
5797 case PREDICT_EXPR:
5798 /* These are valid regardless of their type. */
5799 return true;
5801 default:
5802 return false;
5807 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
5808 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a gimple register.
5810 IMPORTANT NOTE: This promotion is performed by introducing a load of the
5811 other, unmodified part of the complex object just before the total store.
5812 As a consequence, if the object is still uninitialized, an undefined value
5813 will be loaded into a register, which may result in a spurious exception
5814 if the register is floating-point and the value happens to be a signaling
5815 NaN for example. Then the fully-fledged complex operations lowering pass
5816 followed by a DCE pass are necessary in order to fix things up. */
5818 static enum gimplify_status
5819 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
5820 bool want_value)
5822 enum tree_code code, ocode;
5823 tree lhs, rhs, new_rhs, other, realpart, imagpart;
5825 lhs = TREE_OPERAND (*expr_p, 0);
5826 rhs = TREE_OPERAND (*expr_p, 1);
5827 code = TREE_CODE (lhs);
5828 lhs = TREE_OPERAND (lhs, 0);
5830 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
5831 other = build1 (ocode, TREE_TYPE (rhs), lhs);
5832 suppress_warning (other);
5833 other = get_formal_tmp_var (other, pre_p);
5835 realpart = code == REALPART_EXPR ? rhs : other;
5836 imagpart = code == REALPART_EXPR ? other : rhs;
5838 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
5839 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
5840 else
5841 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
5843 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
5844 *expr_p = (want_value) ? rhs : NULL_TREE;
5846 return GS_ALL_DONE;
5849 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
5851 modify_expr
5852 : varname '=' rhs
5853 | '*' ID '=' rhs
5855 PRE_P points to the list where side effects that must happen before
5856 *EXPR_P should be stored.
5858 POST_P points to the list where side effects that must happen after
5859 *EXPR_P should be stored.
5861 WANT_VALUE is nonzero iff we want to use the value of this expression
5862 in another expression. */
5864 static enum gimplify_status
5865 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5866 bool want_value)
5868 tree *from_p = &TREE_OPERAND (*expr_p, 1);
5869 tree *to_p = &TREE_OPERAND (*expr_p, 0);
5870 enum gimplify_status ret = GS_UNHANDLED;
5871 gimple *assign;
5872 location_t loc = EXPR_LOCATION (*expr_p);
5873 gimple_stmt_iterator gsi;
5875 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
5876 || TREE_CODE (*expr_p) == INIT_EXPR);
5878 /* Trying to simplify a clobber using normal logic doesn't work,
5879 so handle it here. */
5880 if (TREE_CLOBBER_P (*from_p))
5882 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5883 if (ret == GS_ERROR)
5884 return ret;
5885 gcc_assert (!want_value);
5886 if (!VAR_P (*to_p) && TREE_CODE (*to_p) != MEM_REF)
5888 tree addr = get_initialized_tmp_var (build_fold_addr_expr (*to_p),
5889 pre_p, post_p);
5890 *to_p = build_simple_mem_ref_loc (EXPR_LOCATION (*to_p), addr);
5892 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
5893 *expr_p = NULL;
5894 return GS_ALL_DONE;
5897 /* Insert pointer conversions required by the middle-end that are not
5898 required by the frontend. This fixes middle-end type checking for
5899 for example gcc.dg/redecl-6.c. */
5900 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
5902 STRIP_USELESS_TYPE_CONVERSION (*from_p);
5903 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
5904 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
5907 /* See if any simplifications can be done based on what the RHS is. */
5908 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5909 want_value);
5910 if (ret != GS_UNHANDLED)
5911 return ret;
5913 /* For empty types only gimplify the left hand side and right hand
5914 side as statements and throw away the assignment. Do this after
5915 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
5916 types properly. */
5917 if (is_empty_type (TREE_TYPE (*from_p))
5918 && !want_value
5919 /* Don't do this for calls that return addressable types, expand_call
5920 relies on those having a lhs. */
5921 && !(TREE_ADDRESSABLE (TREE_TYPE (*from_p))
5922 && TREE_CODE (*from_p) == CALL_EXPR))
5924 gimplify_stmt (from_p, pre_p);
5925 gimplify_stmt (to_p, pre_p);
5926 *expr_p = NULL_TREE;
5927 return GS_ALL_DONE;
5930 /* If the value being copied is of variable width, compute the length
5931 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
5932 before gimplifying any of the operands so that we can resolve any
5933 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
5934 the size of the expression to be copied, not of the destination, so
5935 that is what we must do here. */
5936 maybe_with_size_expr (from_p);
5938 /* As a special case, we have to temporarily allow for assignments
5939 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
5940 a toplevel statement, when gimplifying the GENERIC expression
5941 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
5942 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
5944 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
5945 prevent gimplify_expr from trying to create a new temporary for
5946 foo's LHS, we tell it that it should only gimplify until it
5947 reaches the CALL_EXPR. On return from gimplify_expr, the newly
5948 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
5949 and all we need to do here is set 'a' to be its LHS. */
5951 /* Gimplify the RHS first for C++17 and bug 71104. */
5952 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
5953 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
5954 if (ret == GS_ERROR)
5955 return ret;
5957 /* Then gimplify the LHS. */
5958 /* If we gimplified the RHS to a CALL_EXPR and that call may return
5959 twice we have to make sure to gimplify into non-SSA as otherwise
5960 the abnormal edge added later will make those defs not dominate
5961 their uses.
5962 ??? Technically this applies only to the registers used in the
5963 resulting non-register *TO_P. */
5964 bool saved_into_ssa = gimplify_ctxp->into_ssa;
5965 if (saved_into_ssa
5966 && TREE_CODE (*from_p) == CALL_EXPR
5967 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
5968 gimplify_ctxp->into_ssa = false;
5969 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5970 gimplify_ctxp->into_ssa = saved_into_ssa;
5971 if (ret == GS_ERROR)
5972 return ret;
5974 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
5975 guess for the predicate was wrong. */
5976 gimple_predicate final_pred = rhs_predicate_for (*to_p);
5977 if (final_pred != initial_pred)
5979 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
5980 if (ret == GS_ERROR)
5981 return ret;
5984 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
5985 size as argument to the call. */
5986 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5988 tree call = TREE_OPERAND (*from_p, 0);
5989 tree vlasize = TREE_OPERAND (*from_p, 1);
5991 if (TREE_CODE (call) == CALL_EXPR
5992 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
5994 int nargs = call_expr_nargs (call);
5995 tree type = TREE_TYPE (call);
5996 tree ap = CALL_EXPR_ARG (call, 0);
5997 tree tag = CALL_EXPR_ARG (call, 1);
5998 tree aptag = CALL_EXPR_ARG (call, 2);
5999 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
6000 IFN_VA_ARG, type,
6001 nargs + 1, ap, tag,
6002 aptag, vlasize);
6003 TREE_OPERAND (*from_p, 0) = newcall;
6007 /* Now see if the above changed *from_p to something we handle specially. */
6008 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
6009 want_value);
6010 if (ret != GS_UNHANDLED)
6011 return ret;
6013 /* If we've got a variable sized assignment between two lvalues (i.e. does
6014 not involve a call), then we can make things a bit more straightforward
6015 by converting the assignment to memcpy or memset. */
6016 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
6018 tree from = TREE_OPERAND (*from_p, 0);
6019 tree size = TREE_OPERAND (*from_p, 1);
6021 if (TREE_CODE (from) == CONSTRUCTOR)
6022 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
6024 if (is_gimple_addressable (from))
6026 *from_p = from;
6027 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
6028 pre_p);
6032 /* Transform partial stores to non-addressable complex variables into
6033 total stores. This allows us to use real instead of virtual operands
6034 for these variables, which improves optimization. */
6035 if ((TREE_CODE (*to_p) == REALPART_EXPR
6036 || TREE_CODE (*to_p) == IMAGPART_EXPR)
6037 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
6038 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
6040 /* Try to alleviate the effects of the gimplification creating artificial
6041 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
6042 make sure not to create DECL_DEBUG_EXPR links across functions. */
6043 if (!gimplify_ctxp->into_ssa
6044 && VAR_P (*from_p)
6045 && DECL_IGNORED_P (*from_p)
6046 && DECL_P (*to_p)
6047 && !DECL_IGNORED_P (*to_p)
6048 && decl_function_context (*to_p) == current_function_decl
6049 && decl_function_context (*from_p) == current_function_decl)
6051 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
6052 DECL_NAME (*from_p)
6053 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
6054 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
6055 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
6058 if (want_value && TREE_THIS_VOLATILE (*to_p))
6059 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
6061 if (TREE_CODE (*from_p) == CALL_EXPR)
6063 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
6064 instead of a GIMPLE_ASSIGN. */
6065 gcall *call_stmt;
6066 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
6068 /* Gimplify internal functions created in the FEs. */
6069 int nargs = call_expr_nargs (*from_p), i;
6070 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
6071 auto_vec<tree> vargs (nargs);
6073 for (i = 0; i < nargs; i++)
6075 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
6076 EXPR_LOCATION (*from_p));
6077 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
6079 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
6080 gimple_call_set_nothrow (call_stmt, TREE_NOTHROW (*from_p));
6081 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
6083 else
6085 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
6086 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
6087 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
6088 tree fndecl = get_callee_fndecl (*from_p);
6089 if (fndecl
6090 && fndecl_built_in_p (fndecl, BUILT_IN_EXPECT)
6091 && call_expr_nargs (*from_p) == 3)
6092 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
6093 CALL_EXPR_ARG (*from_p, 0),
6094 CALL_EXPR_ARG (*from_p, 1),
6095 CALL_EXPR_ARG (*from_p, 2));
6096 else
6098 call_stmt = gimple_build_call_from_tree (*from_p, fnptrtype);
6101 notice_special_calls (call_stmt);
6102 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
6103 gimple_call_set_lhs (call_stmt, *to_p);
6104 else if (TREE_CODE (*to_p) == SSA_NAME)
6105 /* The above is somewhat premature, avoid ICEing later for a
6106 SSA name w/o a definition. We may have uses in the GIMPLE IL.
6107 ??? This doesn't make it a default-def. */
6108 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
6110 assign = call_stmt;
6112 else
6114 assign = gimple_build_assign (*to_p, *from_p);
6115 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
6116 if (COMPARISON_CLASS_P (*from_p))
6117 copy_warning (assign, *from_p);
6120 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
6122 /* We should have got an SSA name from the start. */
6123 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
6124 || ! gimple_in_ssa_p (cfun));
6127 gimplify_seq_add_stmt (pre_p, assign);
6128 gsi = gsi_last (*pre_p);
6129 maybe_fold_stmt (&gsi);
6131 if (want_value)
6133 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
6134 return GS_OK;
6136 else
6137 *expr_p = NULL;
6139 return GS_ALL_DONE;
6142 /* Gimplify a comparison between two variable-sized objects. Do this
6143 with a call to BUILT_IN_MEMCMP. */
6145 static enum gimplify_status
6146 gimplify_variable_sized_compare (tree *expr_p)
6148 location_t loc = EXPR_LOCATION (*expr_p);
6149 tree op0 = TREE_OPERAND (*expr_p, 0);
6150 tree op1 = TREE_OPERAND (*expr_p, 1);
6151 tree t, arg, dest, src, expr;
6153 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
6154 arg = unshare_expr (arg);
6155 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
6156 src = build_fold_addr_expr_loc (loc, op1);
6157 dest = build_fold_addr_expr_loc (loc, op0);
6158 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
6159 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
6161 expr
6162 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
6163 SET_EXPR_LOCATION (expr, loc);
6164 *expr_p = expr;
6166 return GS_OK;
6169 /* Gimplify a comparison between two aggregate objects of integral scalar
6170 mode as a comparison between the bitwise equivalent scalar values. */
6172 static enum gimplify_status
6173 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
6175 location_t loc = EXPR_LOCATION (*expr_p);
6176 tree op0 = TREE_OPERAND (*expr_p, 0);
6177 tree op1 = TREE_OPERAND (*expr_p, 1);
6179 tree type = TREE_TYPE (op0);
6180 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
6182 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
6183 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
6185 *expr_p
6186 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
6188 return GS_OK;
6191 /* Gimplify an expression sequence. This function gimplifies each
6192 expression and rewrites the original expression with the last
6193 expression of the sequence in GIMPLE form.
6195 PRE_P points to the list where the side effects for all the
6196 expressions in the sequence will be emitted.
6198 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
6200 static enum gimplify_status
6201 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
6203 tree t = *expr_p;
6207 tree *sub_p = &TREE_OPERAND (t, 0);
6209 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
6210 gimplify_compound_expr (sub_p, pre_p, false);
6211 else
6212 gimplify_stmt (sub_p, pre_p);
6214 t = TREE_OPERAND (t, 1);
6216 while (TREE_CODE (t) == COMPOUND_EXPR);
6218 *expr_p = t;
6219 if (want_value)
6220 return GS_OK;
6221 else
6223 gimplify_stmt (expr_p, pre_p);
6224 return GS_ALL_DONE;
6228 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
6229 gimplify. After gimplification, EXPR_P will point to a new temporary
6230 that holds the original value of the SAVE_EXPR node.
6232 PRE_P points to the list where side effects that must happen before
6233 *EXPR_P should be stored. */
6235 static enum gimplify_status
6236 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6238 enum gimplify_status ret = GS_ALL_DONE;
6239 tree val;
6241 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
6242 val = TREE_OPERAND (*expr_p, 0);
6244 if (TREE_TYPE (val) == error_mark_node)
6245 return GS_ERROR;
6247 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
6248 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
6250 /* The operand may be a void-valued expression. It is
6251 being executed only for its side-effects. */
6252 if (TREE_TYPE (val) == void_type_node)
6254 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
6255 is_gimple_stmt, fb_none);
6256 val = NULL;
6258 else
6259 /* The temporary may not be an SSA name as later abnormal and EH
6260 control flow may invalidate use/def domination. When in SSA
6261 form then assume there are no such issues and SAVE_EXPRs only
6262 appear via GENERIC foldings. */
6263 val = get_initialized_tmp_var (val, pre_p, post_p,
6264 gimple_in_ssa_p (cfun));
6266 TREE_OPERAND (*expr_p, 0) = val;
6267 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
6270 *expr_p = val;
6272 return ret;
6275 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
6277 unary_expr
6278 : ...
6279 | '&' varname
6282 PRE_P points to the list where side effects that must happen before
6283 *EXPR_P should be stored.
6285 POST_P points to the list where side effects that must happen after
6286 *EXPR_P should be stored. */
6288 static enum gimplify_status
6289 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6291 tree expr = *expr_p;
6292 tree op0 = TREE_OPERAND (expr, 0);
6293 enum gimplify_status ret;
6294 location_t loc = EXPR_LOCATION (*expr_p);
6296 switch (TREE_CODE (op0))
6298 case INDIRECT_REF:
6299 do_indirect_ref:
6300 /* Check if we are dealing with an expression of the form '&*ptr'.
6301 While the front end folds away '&*ptr' into 'ptr', these
6302 expressions may be generated internally by the compiler (e.g.,
6303 builtins like __builtin_va_end). */
6304 /* Caution: the silent array decomposition semantics we allow for
6305 ADDR_EXPR means we can't always discard the pair. */
6306 /* Gimplification of the ADDR_EXPR operand may drop
6307 cv-qualification conversions, so make sure we add them if
6308 needed. */
6310 tree op00 = TREE_OPERAND (op0, 0);
6311 tree t_expr = TREE_TYPE (expr);
6312 tree t_op00 = TREE_TYPE (op00);
6314 if (!useless_type_conversion_p (t_expr, t_op00))
6315 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
6316 *expr_p = op00;
6317 ret = GS_OK;
6319 break;
6321 case VIEW_CONVERT_EXPR:
6322 /* Take the address of our operand and then convert it to the type of
6323 this ADDR_EXPR.
6325 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
6326 all clear. The impact of this transformation is even less clear. */
6328 /* If the operand is a useless conversion, look through it. Doing so
6329 guarantees that the ADDR_EXPR and its operand will remain of the
6330 same type. */
6331 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
6332 op0 = TREE_OPERAND (op0, 0);
6334 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
6335 build_fold_addr_expr_loc (loc,
6336 TREE_OPERAND (op0, 0)));
6337 ret = GS_OK;
6338 break;
6340 case MEM_REF:
6341 if (integer_zerop (TREE_OPERAND (op0, 1)))
6342 goto do_indirect_ref;
6344 /* fall through */
6346 default:
6347 /* If we see a call to a declared builtin or see its address
6348 being taken (we can unify those cases here) then we can mark
6349 the builtin for implicit generation by GCC. */
6350 if (TREE_CODE (op0) == FUNCTION_DECL
6351 && fndecl_built_in_p (op0, BUILT_IN_NORMAL)
6352 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
6353 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
6355 /* We use fb_either here because the C frontend sometimes takes
6356 the address of a call that returns a struct; see
6357 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
6358 the implied temporary explicit. */
6360 /* Make the operand addressable. */
6361 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
6362 is_gimple_addressable, fb_either);
6363 if (ret == GS_ERROR)
6364 break;
6366 /* Then mark it. Beware that it may not be possible to do so directly
6367 if a temporary has been created by the gimplification. */
6368 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
6370 op0 = TREE_OPERAND (expr, 0);
6372 /* For various reasons, the gimplification of the expression
6373 may have made a new INDIRECT_REF. */
6374 if (TREE_CODE (op0) == INDIRECT_REF
6375 || (TREE_CODE (op0) == MEM_REF
6376 && integer_zerop (TREE_OPERAND (op0, 1))))
6377 goto do_indirect_ref;
6379 mark_addressable (TREE_OPERAND (expr, 0));
6381 /* The FEs may end up building ADDR_EXPRs early on a decl with
6382 an incomplete type. Re-build ADDR_EXPRs in canonical form
6383 here. */
6384 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
6385 *expr_p = build_fold_addr_expr (op0);
6387 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
6388 recompute_tree_invariant_for_addr_expr (*expr_p);
6390 /* If we re-built the ADDR_EXPR add a conversion to the original type
6391 if required. */
6392 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
6393 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
6395 break;
6398 return ret;
6401 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
6402 value; output operands should be a gimple lvalue. */
6404 static enum gimplify_status
6405 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6407 tree expr;
6408 int noutputs;
6409 const char **oconstraints;
6410 int i;
6411 tree link;
6412 const char *constraint;
6413 bool allows_mem, allows_reg, is_inout;
6414 enum gimplify_status ret, tret;
6415 gasm *stmt;
6416 vec<tree, va_gc> *inputs;
6417 vec<tree, va_gc> *outputs;
6418 vec<tree, va_gc> *clobbers;
6419 vec<tree, va_gc> *labels;
6420 tree link_next;
6422 expr = *expr_p;
6423 noutputs = list_length (ASM_OUTPUTS (expr));
6424 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
6426 inputs = NULL;
6427 outputs = NULL;
6428 clobbers = NULL;
6429 labels = NULL;
6431 ret = GS_ALL_DONE;
6432 link_next = NULL_TREE;
6433 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
6435 bool ok;
6436 size_t constraint_len;
6438 link_next = TREE_CHAIN (link);
6440 oconstraints[i]
6441 = constraint
6442 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6443 constraint_len = strlen (constraint);
6444 if (constraint_len == 0)
6445 continue;
6447 ok = parse_output_constraint (&constraint, i, 0, 0,
6448 &allows_mem, &allows_reg, &is_inout);
6449 if (!ok)
6451 ret = GS_ERROR;
6452 is_inout = false;
6455 /* If we can't make copies, we can only accept memory.
6456 Similarly for VLAs. */
6457 tree outtype = TREE_TYPE (TREE_VALUE (link));
6458 if (outtype != error_mark_node
6459 && (TREE_ADDRESSABLE (outtype)
6460 || !COMPLETE_TYPE_P (outtype)
6461 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (outtype))))
6463 if (allows_mem)
6464 allows_reg = 0;
6465 else
6467 error ("impossible constraint in %<asm%>");
6468 error ("non-memory output %d must stay in memory", i);
6469 return GS_ERROR;
6473 if (!allows_reg && allows_mem)
6474 mark_addressable (TREE_VALUE (link));
6476 tree orig = TREE_VALUE (link);
6477 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6478 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
6479 fb_lvalue | fb_mayfail);
6480 if (tret == GS_ERROR)
6482 if (orig != error_mark_node)
6483 error ("invalid lvalue in %<asm%> output %d", i);
6484 ret = tret;
6487 /* If the constraint does not allow memory make sure we gimplify
6488 it to a register if it is not already but its base is. This
6489 happens for complex and vector components. */
6490 if (!allows_mem)
6492 tree op = TREE_VALUE (link);
6493 if (! is_gimple_val (op)
6494 && is_gimple_reg_type (TREE_TYPE (op))
6495 && is_gimple_reg (get_base_address (op)))
6497 tree tem = create_tmp_reg (TREE_TYPE (op));
6498 tree ass;
6499 if (is_inout)
6501 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
6502 tem, unshare_expr (op));
6503 gimplify_and_add (ass, pre_p);
6505 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
6506 gimplify_and_add (ass, post_p);
6508 TREE_VALUE (link) = tem;
6509 tret = GS_OK;
6513 vec_safe_push (outputs, link);
6514 TREE_CHAIN (link) = NULL_TREE;
6516 if (is_inout)
6518 /* An input/output operand. To give the optimizers more
6519 flexibility, split it into separate input and output
6520 operands. */
6521 tree input;
6522 /* Buffer big enough to format a 32-bit UINT_MAX into. */
6523 char buf[11];
6525 /* Turn the in/out constraint into an output constraint. */
6526 char *p = xstrdup (constraint);
6527 p[0] = '=';
6528 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
6530 /* And add a matching input constraint. */
6531 if (allows_reg)
6533 sprintf (buf, "%u", i);
6535 /* If there are multiple alternatives in the constraint,
6536 handle each of them individually. Those that allow register
6537 will be replaced with operand number, the others will stay
6538 unchanged. */
6539 if (strchr (p, ',') != NULL)
6541 size_t len = 0, buflen = strlen (buf);
6542 char *beg, *end, *str, *dst;
6544 for (beg = p + 1;;)
6546 end = strchr (beg, ',');
6547 if (end == NULL)
6548 end = strchr (beg, '\0');
6549 if ((size_t) (end - beg) < buflen)
6550 len += buflen + 1;
6551 else
6552 len += end - beg + 1;
6553 if (*end)
6554 beg = end + 1;
6555 else
6556 break;
6559 str = (char *) alloca (len);
6560 for (beg = p + 1, dst = str;;)
6562 const char *tem;
6563 bool mem_p, reg_p, inout_p;
6565 end = strchr (beg, ',');
6566 if (end)
6567 *end = '\0';
6568 beg[-1] = '=';
6569 tem = beg - 1;
6570 parse_output_constraint (&tem, i, 0, 0,
6571 &mem_p, &reg_p, &inout_p);
6572 if (dst != str)
6573 *dst++ = ',';
6574 if (reg_p)
6576 memcpy (dst, buf, buflen);
6577 dst += buflen;
6579 else
6581 if (end)
6582 len = end - beg;
6583 else
6584 len = strlen (beg);
6585 memcpy (dst, beg, len);
6586 dst += len;
6588 if (end)
6589 beg = end + 1;
6590 else
6591 break;
6593 *dst = '\0';
6594 input = build_string (dst - str, str);
6596 else
6597 input = build_string (strlen (buf), buf);
6599 else
6600 input = build_string (constraint_len - 1, constraint + 1);
6602 free (p);
6604 input = build_tree_list (build_tree_list (NULL_TREE, input),
6605 unshare_expr (TREE_VALUE (link)));
6606 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
6610 link_next = NULL_TREE;
6611 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
6613 link_next = TREE_CHAIN (link);
6614 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6615 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
6616 oconstraints, &allows_mem, &allows_reg);
6618 /* If we can't make copies, we can only accept memory. */
6619 tree intype = TREE_TYPE (TREE_VALUE (link));
6620 if (intype != error_mark_node
6621 && (TREE_ADDRESSABLE (intype)
6622 || !COMPLETE_TYPE_P (intype)
6623 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (intype))))
6625 if (allows_mem)
6626 allows_reg = 0;
6627 else
6629 error ("impossible constraint in %<asm%>");
6630 error ("non-memory input %d must stay in memory", i);
6631 return GS_ERROR;
6635 /* If the operand is a memory input, it should be an lvalue. */
6636 if (!allows_reg && allows_mem)
6638 tree inputv = TREE_VALUE (link);
6639 STRIP_NOPS (inputv);
6640 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
6641 || TREE_CODE (inputv) == PREINCREMENT_EXPR
6642 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
6643 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
6644 || TREE_CODE (inputv) == MODIFY_EXPR)
6645 TREE_VALUE (link) = error_mark_node;
6646 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6647 is_gimple_lvalue, fb_lvalue | fb_mayfail);
6648 if (tret != GS_ERROR)
6650 /* Unlike output operands, memory inputs are not guaranteed
6651 to be lvalues by the FE, and while the expressions are
6652 marked addressable there, if it is e.g. a statement
6653 expression, temporaries in it might not end up being
6654 addressable. They might be already used in the IL and thus
6655 it is too late to make them addressable now though. */
6656 tree x = TREE_VALUE (link);
6657 while (handled_component_p (x))
6658 x = TREE_OPERAND (x, 0);
6659 if (TREE_CODE (x) == MEM_REF
6660 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
6661 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
6662 if ((VAR_P (x)
6663 || TREE_CODE (x) == PARM_DECL
6664 || TREE_CODE (x) == RESULT_DECL)
6665 && !TREE_ADDRESSABLE (x)
6666 && is_gimple_reg (x))
6668 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
6669 input_location), 0,
6670 "memory input %d is not directly addressable",
6672 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
6675 mark_addressable (TREE_VALUE (link));
6676 if (tret == GS_ERROR)
6678 if (inputv != error_mark_node)
6679 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
6680 "memory input %d is not directly addressable", i);
6681 ret = tret;
6684 else
6686 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6687 is_gimple_asm_val, fb_rvalue);
6688 if (tret == GS_ERROR)
6689 ret = tret;
6692 TREE_CHAIN (link) = NULL_TREE;
6693 vec_safe_push (inputs, link);
6696 link_next = NULL_TREE;
6697 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
6699 link_next = TREE_CHAIN (link);
6700 TREE_CHAIN (link) = NULL_TREE;
6701 vec_safe_push (clobbers, link);
6704 link_next = NULL_TREE;
6705 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
6707 link_next = TREE_CHAIN (link);
6708 TREE_CHAIN (link) = NULL_TREE;
6709 vec_safe_push (labels, link);
6712 /* Do not add ASMs with errors to the gimple IL stream. */
6713 if (ret != GS_ERROR)
6715 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
6716 inputs, outputs, clobbers, labels);
6718 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
6719 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
6720 gimple_asm_set_inline (stmt, ASM_INLINE_P (expr));
6722 gimplify_seq_add_stmt (pre_p, stmt);
6725 return ret;
6728 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
6729 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
6730 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
6731 return to this function.
6733 FIXME should we complexify the prequeue handling instead? Or use flags
6734 for all the cleanups and let the optimizer tighten them up? The current
6735 code seems pretty fragile; it will break on a cleanup within any
6736 non-conditional nesting. But any such nesting would be broken, anyway;
6737 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
6738 and continues out of it. We can do that at the RTL level, though, so
6739 having an optimizer to tighten up try/finally regions would be a Good
6740 Thing. */
6742 static enum gimplify_status
6743 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
6745 gimple_stmt_iterator iter;
6746 gimple_seq body_sequence = NULL;
6748 tree temp = voidify_wrapper_expr (*expr_p, NULL);
6750 /* We only care about the number of conditions between the innermost
6751 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
6752 any cleanups collected outside the CLEANUP_POINT_EXPR. */
6753 int old_conds = gimplify_ctxp->conditions;
6754 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
6755 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
6756 gimplify_ctxp->conditions = 0;
6757 gimplify_ctxp->conditional_cleanups = NULL;
6758 gimplify_ctxp->in_cleanup_point_expr = true;
6760 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
6762 gimplify_ctxp->conditions = old_conds;
6763 gimplify_ctxp->conditional_cleanups = old_cleanups;
6764 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
6766 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
6768 gimple *wce = gsi_stmt (iter);
6770 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
6772 if (gsi_one_before_end_p (iter))
6774 /* Note that gsi_insert_seq_before and gsi_remove do not
6775 scan operands, unlike some other sequence mutators. */
6776 if (!gimple_wce_cleanup_eh_only (wce))
6777 gsi_insert_seq_before_without_update (&iter,
6778 gimple_wce_cleanup (wce),
6779 GSI_SAME_STMT);
6780 gsi_remove (&iter, true);
6781 break;
6783 else
6785 gtry *gtry;
6786 gimple_seq seq;
6787 enum gimple_try_flags kind;
6789 if (gimple_wce_cleanup_eh_only (wce))
6790 kind = GIMPLE_TRY_CATCH;
6791 else
6792 kind = GIMPLE_TRY_FINALLY;
6793 seq = gsi_split_seq_after (iter);
6795 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
6796 /* Do not use gsi_replace here, as it may scan operands.
6797 We want to do a simple structural modification only. */
6798 gsi_set_stmt (&iter, gtry);
6799 iter = gsi_start (gtry->eval);
6802 else
6803 gsi_next (&iter);
6806 gimplify_seq_add_seq (pre_p, body_sequence);
6807 if (temp)
6809 *expr_p = temp;
6810 return GS_OK;
6812 else
6814 *expr_p = NULL;
6815 return GS_ALL_DONE;
6819 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
6820 is the cleanup action required. EH_ONLY is true if the cleanup should
6821 only be executed if an exception is thrown, not on normal exit.
6822 If FORCE_UNCOND is true perform the cleanup unconditionally; this is
6823 only valid for clobbers. */
6825 static void
6826 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p,
6827 bool force_uncond = false)
6829 gimple *wce;
6830 gimple_seq cleanup_stmts = NULL;
6832 /* Errors can result in improperly nested cleanups. Which results in
6833 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
6834 if (seen_error ())
6835 return;
6837 if (gimple_conditional_context ())
6839 /* If we're in a conditional context, this is more complex. We only
6840 want to run the cleanup if we actually ran the initialization that
6841 necessitates it, but we want to run it after the end of the
6842 conditional context. So we wrap the try/finally around the
6843 condition and use a flag to determine whether or not to actually
6844 run the destructor. Thus
6846 test ? f(A()) : 0
6848 becomes (approximately)
6850 flag = 0;
6851 try {
6852 if (test) { A::A(temp); flag = 1; val = f(temp); }
6853 else { val = 0; }
6854 } finally {
6855 if (flag) A::~A(temp);
6859 if (force_uncond)
6861 gimplify_stmt (&cleanup, &cleanup_stmts);
6862 wce = gimple_build_wce (cleanup_stmts);
6863 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6865 else
6867 tree flag = create_tmp_var (boolean_type_node, "cleanup");
6868 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
6869 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
6871 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
6872 gimplify_stmt (&cleanup, &cleanup_stmts);
6873 wce = gimple_build_wce (cleanup_stmts);
6875 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
6876 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6877 gimplify_seq_add_stmt (pre_p, ftrue);
6879 /* Because of this manipulation, and the EH edges that jump
6880 threading cannot redirect, the temporary (VAR) will appear
6881 to be used uninitialized. Don't warn. */
6882 suppress_warning (var, OPT_Wuninitialized);
6885 else
6887 gimplify_stmt (&cleanup, &cleanup_stmts);
6888 wce = gimple_build_wce (cleanup_stmts);
6889 gimple_wce_set_cleanup_eh_only (wce, eh_only);
6890 gimplify_seq_add_stmt (pre_p, wce);
6894 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
6896 static enum gimplify_status
6897 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6899 tree targ = *expr_p;
6900 tree temp = TARGET_EXPR_SLOT (targ);
6901 tree init = TARGET_EXPR_INITIAL (targ);
6902 enum gimplify_status ret;
6904 bool unpoison_empty_seq = false;
6905 gimple_stmt_iterator unpoison_it;
6907 if (init)
6909 tree cleanup = NULL_TREE;
6911 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
6912 to the temps list. Handle also variable length TARGET_EXPRs. */
6913 if (!poly_int_tree_p (DECL_SIZE (temp)))
6915 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
6916 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
6917 gimplify_vla_decl (temp, pre_p);
6919 else
6921 /* Save location where we need to place unpoisoning. It's possible
6922 that a variable will be converted to needs_to_live_in_memory. */
6923 unpoison_it = gsi_last (*pre_p);
6924 unpoison_empty_seq = gsi_end_p (unpoison_it);
6926 gimple_add_tmp_var (temp);
6929 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
6930 expression is supposed to initialize the slot. */
6931 if (VOID_TYPE_P (TREE_TYPE (init)))
6932 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6933 else
6935 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
6936 init = init_expr;
6937 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6938 init = NULL;
6939 ggc_free (init_expr);
6941 if (ret == GS_ERROR)
6943 /* PR c++/28266 Make sure this is expanded only once. */
6944 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6945 return GS_ERROR;
6947 if (init)
6948 gimplify_and_add (init, pre_p);
6950 /* If needed, push the cleanup for the temp. */
6951 if (TARGET_EXPR_CLEANUP (targ))
6953 if (CLEANUP_EH_ONLY (targ))
6954 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
6955 CLEANUP_EH_ONLY (targ), pre_p);
6956 else
6957 cleanup = TARGET_EXPR_CLEANUP (targ);
6960 /* Add a clobber for the temporary going out of scope, like
6961 gimplify_bind_expr. */
6962 if (gimplify_ctxp->in_cleanup_point_expr
6963 && needs_to_live_in_memory (temp))
6965 if (flag_stack_reuse == SR_ALL)
6967 tree clobber = build_clobber (TREE_TYPE (temp));
6968 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
6969 gimple_push_cleanup (temp, clobber, false, pre_p, true);
6971 if (asan_poisoned_variables
6972 && DECL_ALIGN (temp) <= MAX_SUPPORTED_STACK_ALIGNMENT
6973 && !TREE_STATIC (temp)
6974 && dbg_cnt (asan_use_after_scope)
6975 && !gimplify_omp_ctxp)
6977 tree asan_cleanup = build_asan_poison_call_expr (temp);
6978 if (asan_cleanup)
6980 if (unpoison_empty_seq)
6981 unpoison_it = gsi_start (*pre_p);
6983 asan_poison_variable (temp, false, &unpoison_it,
6984 unpoison_empty_seq);
6985 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
6989 if (cleanup)
6990 gimple_push_cleanup (temp, cleanup, false, pre_p);
6992 /* Only expand this once. */
6993 TREE_OPERAND (targ, 3) = init;
6994 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6996 else
6997 /* We should have expanded this before. */
6998 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
7000 *expr_p = temp;
7001 return GS_OK;
7004 /* Gimplification of expression trees. */
7006 /* Gimplify an expression which appears at statement context. The
7007 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
7008 NULL, a new sequence is allocated.
7010 Return true if we actually added a statement to the queue. */
7012 bool
7013 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
7015 gimple_seq_node last;
7017 last = gimple_seq_last (*seq_p);
7018 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
7019 return last != gimple_seq_last (*seq_p);
7022 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
7023 to CTX. If entries already exist, force them to be some flavor of private.
7024 If there is no enclosing parallel, do nothing. */
7026 void
7027 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
7029 splay_tree_node n;
7031 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
7032 return;
7036 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7037 if (n != NULL)
7039 if (n->value & GOVD_SHARED)
7040 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
7041 else if (n->value & GOVD_MAP)
7042 n->value |= GOVD_MAP_TO_ONLY;
7043 else
7044 return;
7046 else if ((ctx->region_type & ORT_TARGET) != 0)
7048 if (ctx->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
7049 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7050 else
7051 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
7053 else if (ctx->region_type != ORT_WORKSHARE
7054 && ctx->region_type != ORT_TASKGROUP
7055 && ctx->region_type != ORT_SIMD
7056 && ctx->region_type != ORT_ACC
7057 && !(ctx->region_type & ORT_TARGET_DATA))
7058 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7060 ctx = ctx->outer_context;
7062 while (ctx);
7065 /* Similarly for each of the type sizes of TYPE. */
7067 static void
7068 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
7070 if (type == NULL || type == error_mark_node)
7071 return;
7072 type = TYPE_MAIN_VARIANT (type);
7074 if (ctx->privatized_types->add (type))
7075 return;
7077 switch (TREE_CODE (type))
7079 case INTEGER_TYPE:
7080 case ENUMERAL_TYPE:
7081 case BOOLEAN_TYPE:
7082 case REAL_TYPE:
7083 case FIXED_POINT_TYPE:
7084 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
7085 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
7086 break;
7088 case ARRAY_TYPE:
7089 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7090 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
7091 break;
7093 case RECORD_TYPE:
7094 case UNION_TYPE:
7095 case QUAL_UNION_TYPE:
7097 tree field;
7098 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
7099 if (TREE_CODE (field) == FIELD_DECL)
7101 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
7102 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
7105 break;
7107 case POINTER_TYPE:
7108 case REFERENCE_TYPE:
7109 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7110 break;
7112 default:
7113 break;
7116 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
7117 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
7118 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
7121 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
7123 static void
7124 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
7126 splay_tree_node n;
7127 unsigned int nflags;
7128 tree t;
7130 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
7131 return;
7133 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
7134 there are constructors involved somewhere. Exception is a shared clause,
7135 there is nothing privatized in that case. */
7136 if ((flags & GOVD_SHARED) == 0
7137 && (TREE_ADDRESSABLE (TREE_TYPE (decl))
7138 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl))))
7139 flags |= GOVD_SEEN;
7141 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7142 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7144 /* We shouldn't be re-adding the decl with the same data
7145 sharing class. */
7146 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
7147 nflags = n->value | flags;
7148 /* The only combination of data sharing classes we should see is
7149 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
7150 reduction variables to be used in data sharing clauses. */
7151 gcc_assert ((ctx->region_type & ORT_ACC) != 0
7152 || ((nflags & GOVD_DATA_SHARE_CLASS)
7153 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
7154 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
7155 n->value = nflags;
7156 return;
7159 /* When adding a variable-sized variable, we have to handle all sorts
7160 of additional bits of data: the pointer replacement variable, and
7161 the parameters of the type. */
7162 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7164 /* Add the pointer replacement variable as PRIVATE if the variable
7165 replacement is private, else FIRSTPRIVATE since we'll need the
7166 address of the original variable either for SHARED, or for the
7167 copy into or out of the context. */
7168 if (!(flags & GOVD_LOCAL) && ctx->region_type != ORT_TASKGROUP)
7170 if (flags & GOVD_MAP)
7171 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
7172 else if (flags & GOVD_PRIVATE)
7173 nflags = GOVD_PRIVATE;
7174 else if (((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7175 && (flags & GOVD_FIRSTPRIVATE))
7176 || (ctx->region_type == ORT_TARGET_DATA
7177 && (flags & GOVD_DATA_SHARE_CLASS) == 0))
7178 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
7179 else
7180 nflags = GOVD_FIRSTPRIVATE;
7181 nflags |= flags & GOVD_SEEN;
7182 t = DECL_VALUE_EXPR (decl);
7183 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7184 t = TREE_OPERAND (t, 0);
7185 gcc_assert (DECL_P (t));
7186 omp_add_variable (ctx, t, nflags);
7189 /* Add all of the variable and type parameters (which should have
7190 been gimplified to a formal temporary) as FIRSTPRIVATE. */
7191 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
7192 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
7193 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7195 /* The variable-sized variable itself is never SHARED, only some form
7196 of PRIVATE. The sharing would take place via the pointer variable
7197 which we remapped above. */
7198 if (flags & GOVD_SHARED)
7199 flags = GOVD_SHARED | GOVD_DEBUG_PRIVATE
7200 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
7202 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
7203 alloca statement we generate for the variable, so make sure it
7204 is available. This isn't automatically needed for the SHARED
7205 case, since we won't be allocating local storage then.
7206 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
7207 in this case omp_notice_variable will be called later
7208 on when it is gimplified. */
7209 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
7210 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
7211 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
7213 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
7214 && omp_privatize_by_reference (decl))
7216 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7218 /* Similar to the direct variable sized case above, we'll need the
7219 size of references being privatized. */
7220 if ((flags & GOVD_SHARED) == 0)
7222 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7223 if (t && DECL_P (t))
7224 omp_notice_variable (ctx, t, true);
7228 if (n != NULL)
7229 n->value |= flags;
7230 else
7231 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
7233 /* For reductions clauses in OpenACC loop directives, by default create a
7234 copy clause on the enclosing parallel construct for carrying back the
7235 results. */
7236 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
7238 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
7239 while (outer_ctx)
7241 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
7242 if (n != NULL)
7244 /* Ignore local variables and explicitly declared clauses. */
7245 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
7246 break;
7247 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
7249 /* According to the OpenACC spec, such a reduction variable
7250 should already have a copy map on a kernels construct,
7251 verify that here. */
7252 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
7253 && (n->value & GOVD_MAP));
7255 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7257 /* Remove firstprivate and make it a copy map. */
7258 n->value &= ~GOVD_FIRSTPRIVATE;
7259 n->value |= GOVD_MAP;
7262 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7264 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
7265 GOVD_MAP | GOVD_SEEN);
7266 break;
7268 outer_ctx = outer_ctx->outer_context;
7273 /* Notice a threadprivate variable DECL used in OMP context CTX.
7274 This just prints out diagnostics about threadprivate variable uses
7275 in untied tasks. If DECL2 is non-NULL, prevent this warning
7276 on that variable. */
7278 static bool
7279 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
7280 tree decl2)
7282 splay_tree_node n;
7283 struct gimplify_omp_ctx *octx;
7285 for (octx = ctx; octx; octx = octx->outer_context)
7286 if ((octx->region_type & ORT_TARGET) != 0
7287 || octx->order_concurrent)
7289 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
7290 if (n == NULL)
7292 if (octx->order_concurrent)
7294 error ("threadprivate variable %qE used in a region with"
7295 " %<order(concurrent)%> clause", DECL_NAME (decl));
7296 inform (octx->location, "enclosing region");
7298 else
7300 error ("threadprivate variable %qE used in target region",
7301 DECL_NAME (decl));
7302 inform (octx->location, "enclosing target region");
7304 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
7306 if (decl2)
7307 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
7310 if (ctx->region_type != ORT_UNTIED_TASK)
7311 return false;
7312 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7313 if (n == NULL)
7315 error ("threadprivate variable %qE used in untied task",
7316 DECL_NAME (decl));
7317 inform (ctx->location, "enclosing task");
7318 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
7320 if (decl2)
7321 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
7322 return false;
7325 /* Return true if global var DECL is device resident. */
7327 static bool
7328 device_resident_p (tree decl)
7330 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
7332 if (!attr)
7333 return false;
7335 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
7337 tree c = TREE_VALUE (t);
7338 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
7339 return true;
7342 return false;
7345 /* Return true if DECL has an ACC DECLARE attribute. */
7347 static bool
7348 is_oacc_declared (tree decl)
7350 tree t = TREE_CODE (decl) == MEM_REF ? TREE_OPERAND (decl, 0) : decl;
7351 tree declared = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (t));
7352 return declared != NULL_TREE;
7355 /* Determine outer default flags for DECL mentioned in an OMP region
7356 but not declared in an enclosing clause.
7358 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
7359 remapped firstprivate instead of shared. To some extent this is
7360 addressed in omp_firstprivatize_type_sizes, but not
7361 effectively. */
7363 static unsigned
7364 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
7365 bool in_code, unsigned flags)
7367 enum omp_clause_default_kind default_kind = ctx->default_kind;
7368 enum omp_clause_default_kind kind;
7370 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
7371 if (ctx->region_type & ORT_TASK)
7373 tree detach_clause = omp_find_clause (ctx->clauses, OMP_CLAUSE_DETACH);
7375 /* The event-handle specified by a detach clause should always be firstprivate,
7376 regardless of the current default. */
7377 if (detach_clause && OMP_CLAUSE_DECL (detach_clause) == decl)
7378 kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
7380 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
7381 default_kind = kind;
7382 else if (VAR_P (decl) && TREE_STATIC (decl) && DECL_IN_CONSTANT_POOL (decl))
7383 default_kind = OMP_CLAUSE_DEFAULT_SHARED;
7384 /* For C/C++ default({,first}private), variables with static storage duration
7385 declared in a namespace or global scope and referenced in construct
7386 must be explicitly specified, i.e. acts as default(none). */
7387 else if ((default_kind == OMP_CLAUSE_DEFAULT_PRIVATE
7388 || default_kind == OMP_CLAUSE_DEFAULT_FIRSTPRIVATE)
7389 && VAR_P (decl)
7390 && is_global_var (decl)
7391 && (DECL_FILE_SCOPE_P (decl)
7392 || (DECL_CONTEXT (decl)
7393 && TREE_CODE (DECL_CONTEXT (decl)) == NAMESPACE_DECL))
7394 && !lang_GNU_Fortran ())
7395 default_kind = OMP_CLAUSE_DEFAULT_NONE;
7397 switch (default_kind)
7399 case OMP_CLAUSE_DEFAULT_NONE:
7401 const char *rtype;
7403 if (ctx->region_type & ORT_PARALLEL)
7404 rtype = "parallel";
7405 else if ((ctx->region_type & ORT_TASKLOOP) == ORT_TASKLOOP)
7406 rtype = "taskloop";
7407 else if (ctx->region_type & ORT_TASK)
7408 rtype = "task";
7409 else if (ctx->region_type & ORT_TEAMS)
7410 rtype = "teams";
7411 else
7412 gcc_unreachable ();
7414 error ("%qE not specified in enclosing %qs",
7415 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
7416 inform (ctx->location, "enclosing %qs", rtype);
7418 /* FALLTHRU */
7419 case OMP_CLAUSE_DEFAULT_SHARED:
7420 flags |= GOVD_SHARED;
7421 break;
7422 case OMP_CLAUSE_DEFAULT_PRIVATE:
7423 flags |= GOVD_PRIVATE;
7424 break;
7425 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
7426 flags |= GOVD_FIRSTPRIVATE;
7427 break;
7428 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
7429 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
7430 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
7431 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
7433 omp_notice_variable (octx, decl, in_code);
7434 for (; octx; octx = octx->outer_context)
7436 splay_tree_node n2;
7438 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
7439 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
7440 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
7441 continue;
7442 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
7444 flags |= GOVD_FIRSTPRIVATE;
7445 goto found_outer;
7447 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
7449 flags |= GOVD_SHARED;
7450 goto found_outer;
7455 if (TREE_CODE (decl) == PARM_DECL
7456 || (!is_global_var (decl)
7457 && DECL_CONTEXT (decl) == current_function_decl))
7458 flags |= GOVD_FIRSTPRIVATE;
7459 else
7460 flags |= GOVD_SHARED;
7461 found_outer:
7462 break;
7464 default:
7465 gcc_unreachable ();
7468 return flags;
7472 /* Determine outer default flags for DECL mentioned in an OACC region
7473 but not declared in an enclosing clause. */
7475 static unsigned
7476 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
7478 const char *rkind;
7479 bool on_device = false;
7480 bool is_private = false;
7481 bool declared = is_oacc_declared (decl);
7482 tree type = TREE_TYPE (decl);
7484 if (omp_privatize_by_reference (decl))
7485 type = TREE_TYPE (type);
7487 /* For Fortran COMMON blocks, only used variables in those blocks are
7488 transfered and remapped. The block itself will have a private clause to
7489 avoid transfering the data twice.
7490 The hook evaluates to false by default. For a variable in Fortran's COMMON
7491 or EQUIVALENCE block, returns 'true' (as we have shared=false) - as only
7492 the variables in such a COMMON/EQUIVALENCE block shall be privatized not
7493 the whole block. For C++ and Fortran, it can also be true under certain
7494 other conditions, if DECL_HAS_VALUE_EXPR. */
7495 if (RECORD_OR_UNION_TYPE_P (type))
7496 is_private = lang_hooks.decls.omp_disregard_value_expr (decl, false);
7498 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
7499 && is_global_var (decl)
7500 && device_resident_p (decl)
7501 && !is_private)
7503 on_device = true;
7504 flags |= GOVD_MAP_TO_ONLY;
7507 switch (ctx->region_type)
7509 case ORT_ACC_KERNELS:
7510 rkind = "kernels";
7512 if (is_private)
7513 flags |= GOVD_FIRSTPRIVATE;
7514 else if (AGGREGATE_TYPE_P (type))
7516 /* Aggregates default to 'present_or_copy', or 'present'. */
7517 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7518 flags |= GOVD_MAP;
7519 else
7520 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7522 else
7523 /* Scalars default to 'copy'. */
7524 flags |= GOVD_MAP | GOVD_MAP_FORCE;
7526 break;
7528 case ORT_ACC_PARALLEL:
7529 case ORT_ACC_SERIAL:
7530 rkind = ctx->region_type == ORT_ACC_PARALLEL ? "parallel" : "serial";
7532 if (is_private)
7533 flags |= GOVD_FIRSTPRIVATE;
7534 else if (on_device || declared)
7535 flags |= GOVD_MAP;
7536 else if (AGGREGATE_TYPE_P (type))
7538 /* Aggregates default to 'present_or_copy', or 'present'. */
7539 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7540 flags |= GOVD_MAP;
7541 else
7542 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7544 else
7545 /* Scalars default to 'firstprivate'. */
7546 flags |= GOVD_FIRSTPRIVATE;
7548 break;
7550 default:
7551 gcc_unreachable ();
7554 if (DECL_ARTIFICIAL (decl))
7555 ; /* We can get compiler-generated decls, and should not complain
7556 about them. */
7557 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_NONE)
7559 error ("%qE not specified in enclosing OpenACC %qs construct",
7560 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rkind);
7561 inform (ctx->location, "enclosing OpenACC %qs construct", rkind);
7563 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_PRESENT)
7564 ; /* Handled above. */
7565 else
7566 gcc_checking_assert (ctx->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
7568 return flags;
7571 /* Record the fact that DECL was used within the OMP context CTX.
7572 IN_CODE is true when real code uses DECL, and false when we should
7573 merely emit default(none) errors. Return true if DECL is going to
7574 be remapped and thus DECL shouldn't be gimplified into its
7575 DECL_VALUE_EXPR (if any). */
7577 static bool
7578 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
7580 splay_tree_node n;
7581 unsigned flags = in_code ? GOVD_SEEN : 0;
7582 bool ret = false, shared;
7584 if (error_operand_p (decl))
7585 return false;
7587 if (ctx->region_type == ORT_NONE)
7588 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
7590 if (is_global_var (decl))
7592 /* Threadprivate variables are predetermined. */
7593 if (DECL_THREAD_LOCAL_P (decl))
7594 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
7596 if (DECL_HAS_VALUE_EXPR_P (decl))
7598 if (ctx->region_type & ORT_ACC)
7599 /* For OpenACC, defer expansion of value to avoid transfering
7600 privatized common block data instead of im-/explicitly transfered
7601 variables which are in common blocks. */
7603 else
7605 tree value = get_base_address (DECL_VALUE_EXPR (decl));
7607 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
7608 return omp_notice_threadprivate_variable (ctx, decl, value);
7612 if (gimplify_omp_ctxp->outer_context == NULL
7613 && VAR_P (decl)
7614 && oacc_get_fn_attrib (current_function_decl))
7616 location_t loc = DECL_SOURCE_LOCATION (decl);
7618 if (lookup_attribute ("omp declare target link",
7619 DECL_ATTRIBUTES (decl)))
7621 error_at (loc,
7622 "%qE with %<link%> clause used in %<routine%> function",
7623 DECL_NAME (decl));
7624 return false;
7626 else if (!lookup_attribute ("omp declare target",
7627 DECL_ATTRIBUTES (decl)))
7629 error_at (loc,
7630 "%qE requires a %<declare%> directive for use "
7631 "in a %<routine%> function", DECL_NAME (decl));
7632 return false;
7637 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7638 if ((ctx->region_type & ORT_TARGET) != 0)
7640 if (ctx->region_type & ORT_ACC)
7641 /* For OpenACC, as remarked above, defer expansion. */
7642 shared = false;
7643 else
7644 shared = true;
7646 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7647 if (n == NULL)
7649 unsigned nflags = flags;
7650 if ((ctx->region_type & ORT_ACC) == 0)
7652 bool is_declare_target = false;
7653 if (is_global_var (decl)
7654 && varpool_node::get_create (decl)->offloadable)
7656 struct gimplify_omp_ctx *octx;
7657 for (octx = ctx->outer_context;
7658 octx; octx = octx->outer_context)
7660 n = splay_tree_lookup (octx->variables,
7661 (splay_tree_key)decl);
7662 if (n
7663 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
7664 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7665 break;
7667 is_declare_target = octx == NULL;
7669 if (!is_declare_target)
7671 int gdmk;
7672 enum omp_clause_defaultmap_kind kind;
7673 if (lang_hooks.decls.omp_allocatable_p (decl))
7674 gdmk = GDMK_ALLOCATABLE;
7675 else if (lang_hooks.decls.omp_scalar_target_p (decl))
7676 gdmk = GDMK_SCALAR_TARGET;
7677 else if (lang_hooks.decls.omp_scalar_p (decl, false))
7678 gdmk = GDMK_SCALAR;
7679 else if (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
7680 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
7681 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
7682 == POINTER_TYPE)))
7683 gdmk = GDMK_POINTER;
7684 else
7685 gdmk = GDMK_AGGREGATE;
7686 kind = lang_hooks.decls.omp_predetermined_mapping (decl);
7687 if (kind != OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED)
7689 if (kind == OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE)
7690 nflags |= GOVD_FIRSTPRIVATE;
7691 else if (kind == OMP_CLAUSE_DEFAULTMAP_TO)
7692 nflags |= GOVD_MAP | GOVD_MAP_TO_ONLY;
7693 else
7694 gcc_unreachable ();
7696 else if (ctx->defaultmap[gdmk] == 0)
7698 tree d = lang_hooks.decls.omp_report_decl (decl);
7699 error ("%qE not specified in enclosing %<target%>",
7700 DECL_NAME (d));
7701 inform (ctx->location, "enclosing %<target%>");
7703 else if (ctx->defaultmap[gdmk]
7704 & (GOVD_MAP_0LEN_ARRAY | GOVD_FIRSTPRIVATE))
7705 nflags |= ctx->defaultmap[gdmk];
7706 else
7708 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
7709 nflags |= ctx->defaultmap[gdmk] & ~GOVD_MAP;
7714 struct gimplify_omp_ctx *octx = ctx->outer_context;
7715 if ((ctx->region_type & ORT_ACC) && octx)
7717 /* Look in outer OpenACC contexts, to see if there's a
7718 data attribute for this variable. */
7719 omp_notice_variable (octx, decl, in_code);
7721 for (; octx; octx = octx->outer_context)
7723 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
7724 break;
7725 splay_tree_node n2
7726 = splay_tree_lookup (octx->variables,
7727 (splay_tree_key) decl);
7728 if (n2)
7730 if (octx->region_type == ORT_ACC_HOST_DATA)
7731 error ("variable %qE declared in enclosing "
7732 "%<host_data%> region", DECL_NAME (decl));
7733 nflags |= GOVD_MAP;
7734 if (octx->region_type == ORT_ACC_DATA
7735 && (n2->value & GOVD_MAP_0LEN_ARRAY))
7736 nflags |= GOVD_MAP_0LEN_ARRAY;
7737 goto found_outer;
7742 if ((nflags & ~(GOVD_MAP_TO_ONLY | GOVD_MAP_FROM_ONLY
7743 | GOVD_MAP_ALLOC_ONLY)) == flags)
7745 tree type = TREE_TYPE (decl);
7747 if (gimplify_omp_ctxp->target_firstprivatize_array_bases
7748 && omp_privatize_by_reference (decl))
7749 type = TREE_TYPE (type);
7750 if (!lang_hooks.types.omp_mappable_type (type))
7752 error ("%qD referenced in target region does not have "
7753 "a mappable type", decl);
7754 nflags |= GOVD_MAP | GOVD_EXPLICIT;
7756 else
7758 if ((ctx->region_type & ORT_ACC) != 0)
7759 nflags = oacc_default_clause (ctx, decl, flags);
7760 else
7761 nflags |= GOVD_MAP;
7764 found_outer:
7765 omp_add_variable (ctx, decl, nflags);
7767 else
7769 /* If nothing changed, there's nothing left to do. */
7770 if ((n->value & flags) == flags)
7771 return ret;
7772 flags |= n->value;
7773 n->value = flags;
7775 goto do_outer;
7778 if (n == NULL)
7780 if (ctx->region_type == ORT_WORKSHARE
7781 || ctx->region_type == ORT_TASKGROUP
7782 || ctx->region_type == ORT_SIMD
7783 || ctx->region_type == ORT_ACC
7784 || (ctx->region_type & ORT_TARGET_DATA) != 0)
7785 goto do_outer;
7787 flags = omp_default_clause (ctx, decl, in_code, flags);
7789 if ((flags & GOVD_PRIVATE)
7790 && lang_hooks.decls.omp_private_outer_ref (decl))
7791 flags |= GOVD_PRIVATE_OUTER_REF;
7793 omp_add_variable (ctx, decl, flags);
7795 shared = (flags & GOVD_SHARED) != 0;
7796 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7797 goto do_outer;
7800 /* Don't mark as GOVD_SEEN addressable temporaries seen only in simd
7801 lb, b or incr expressions, those shouldn't be turned into simd arrays. */
7802 if (ctx->region_type == ORT_SIMD
7803 && ctx->in_for_exprs
7804 && ((n->value & (GOVD_PRIVATE | GOVD_SEEN | GOVD_EXPLICIT))
7805 == GOVD_PRIVATE))
7806 flags &= ~GOVD_SEEN;
7808 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
7809 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
7810 && DECL_SIZE (decl))
7812 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7814 splay_tree_node n2;
7815 tree t = DECL_VALUE_EXPR (decl);
7816 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7817 t = TREE_OPERAND (t, 0);
7818 gcc_assert (DECL_P (t));
7819 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7820 n2->value |= GOVD_SEEN;
7822 else if (omp_privatize_by_reference (decl)
7823 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
7824 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
7825 != INTEGER_CST))
7827 splay_tree_node n2;
7828 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7829 gcc_assert (DECL_P (t));
7830 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7831 if (n2)
7832 omp_notice_variable (ctx, t, true);
7836 if (ctx->region_type & ORT_ACC)
7837 /* For OpenACC, as remarked above, defer expansion. */
7838 shared = false;
7839 else
7840 shared = ((flags | n->value) & GOVD_SHARED) != 0;
7841 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7843 /* If nothing changed, there's nothing left to do. */
7844 if ((n->value & flags) == flags)
7845 return ret;
7846 flags |= n->value;
7847 n->value = flags;
7849 do_outer:
7850 /* If the variable is private in the current context, then we don't
7851 need to propagate anything to an outer context. */
7852 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
7853 return ret;
7854 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7855 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7856 return ret;
7857 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
7858 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7859 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7860 return ret;
7861 if (ctx->outer_context
7862 && omp_notice_variable (ctx->outer_context, decl, in_code))
7863 return true;
7864 return ret;
7867 /* Verify that DECL is private within CTX. If there's specific information
7868 to the contrary in the innermost scope, generate an error. */
7870 static bool
7871 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
7873 splay_tree_node n;
7875 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7876 if (n != NULL)
7878 if (n->value & GOVD_SHARED)
7880 if (ctx == gimplify_omp_ctxp)
7882 if (simd)
7883 error ("iteration variable %qE is predetermined linear",
7884 DECL_NAME (decl));
7885 else
7886 error ("iteration variable %qE should be private",
7887 DECL_NAME (decl));
7888 n->value = GOVD_PRIVATE;
7889 return true;
7891 else
7892 return false;
7894 else if ((n->value & GOVD_EXPLICIT) != 0
7895 && (ctx == gimplify_omp_ctxp
7896 || (ctx->region_type == ORT_COMBINED_PARALLEL
7897 && gimplify_omp_ctxp->outer_context == ctx)))
7899 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
7900 error ("iteration variable %qE should not be firstprivate",
7901 DECL_NAME (decl));
7902 else if ((n->value & GOVD_REDUCTION) != 0)
7903 error ("iteration variable %qE should not be reduction",
7904 DECL_NAME (decl));
7905 else if (simd != 1 && (n->value & GOVD_LINEAR) != 0)
7906 error ("iteration variable %qE should not be linear",
7907 DECL_NAME (decl));
7909 return (ctx == gimplify_omp_ctxp
7910 || (ctx->region_type == ORT_COMBINED_PARALLEL
7911 && gimplify_omp_ctxp->outer_context == ctx));
7914 if (ctx->region_type != ORT_WORKSHARE
7915 && ctx->region_type != ORT_TASKGROUP
7916 && ctx->region_type != ORT_SIMD
7917 && ctx->region_type != ORT_ACC)
7918 return false;
7919 else if (ctx->outer_context)
7920 return omp_is_private (ctx->outer_context, decl, simd);
7921 return false;
7924 /* Return true if DECL is private within a parallel region
7925 that binds to the current construct's context or in parallel
7926 region's REDUCTION clause. */
7928 static bool
7929 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
7931 splay_tree_node n;
7935 ctx = ctx->outer_context;
7936 if (ctx == NULL)
7938 if (is_global_var (decl))
7939 return false;
7941 /* References might be private, but might be shared too,
7942 when checking for copyprivate, assume they might be
7943 private, otherwise assume they might be shared. */
7944 if (copyprivate)
7945 return true;
7947 if (omp_privatize_by_reference (decl))
7948 return false;
7950 /* Treat C++ privatized non-static data members outside
7951 of the privatization the same. */
7952 if (omp_member_access_dummy_var (decl))
7953 return false;
7955 return true;
7958 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
7960 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7961 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
7963 if ((ctx->region_type & ORT_TARGET_DATA) != 0
7964 || n == NULL
7965 || (n->value & GOVD_MAP) == 0)
7966 continue;
7967 return false;
7970 if (n != NULL)
7972 if ((n->value & GOVD_LOCAL) != 0
7973 && omp_member_access_dummy_var (decl))
7974 return false;
7975 return (n->value & GOVD_SHARED) == 0;
7978 if (ctx->region_type == ORT_WORKSHARE
7979 || ctx->region_type == ORT_TASKGROUP
7980 || ctx->region_type == ORT_SIMD
7981 || ctx->region_type == ORT_ACC)
7982 continue;
7984 break;
7986 while (1);
7987 return false;
7990 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
7992 static tree
7993 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
7995 tree t = *tp;
7997 /* If this node has been visited, unmark it and keep looking. */
7998 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
7999 return t;
8001 if (IS_TYPE_OR_DECL_P (t))
8002 *walk_subtrees = 0;
8003 return NULL_TREE;
8007 /* Gimplify the affinity clause but effectively ignore it.
8008 Generate:
8009 var = begin;
8010 if ((step > 1) ? var <= end : var > end)
8011 locatator_var_expr; */
8013 static void
8014 gimplify_omp_affinity (tree *list_p, gimple_seq *pre_p)
8016 tree last_iter = NULL_TREE;
8017 tree last_bind = NULL_TREE;
8018 tree label = NULL_TREE;
8019 tree *last_body = NULL;
8020 for (tree c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8021 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_AFFINITY)
8023 tree t = OMP_CLAUSE_DECL (c);
8024 if (TREE_CODE (t) == TREE_LIST
8025 && TREE_PURPOSE (t)
8026 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8028 if (TREE_VALUE (t) == null_pointer_node)
8029 continue;
8030 if (TREE_PURPOSE (t) != last_iter)
8032 if (last_bind)
8034 append_to_statement_list (label, last_body);
8035 gimplify_and_add (last_bind, pre_p);
8036 last_bind = NULL_TREE;
8038 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8040 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8041 is_gimple_val, fb_rvalue) == GS_ERROR
8042 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8043 is_gimple_val, fb_rvalue) == GS_ERROR
8044 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8045 is_gimple_val, fb_rvalue) == GS_ERROR
8046 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8047 is_gimple_val, fb_rvalue)
8048 == GS_ERROR))
8049 return;
8051 last_iter = TREE_PURPOSE (t);
8052 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8053 last_bind = build3 (BIND_EXPR, void_type_node, BLOCK_VARS (block),
8054 NULL, block);
8055 last_body = &BIND_EXPR_BODY (last_bind);
8056 tree cond = NULL_TREE;
8057 location_t loc = OMP_CLAUSE_LOCATION (c);
8058 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8060 tree var = TREE_VEC_ELT (it, 0);
8061 tree begin = TREE_VEC_ELT (it, 1);
8062 tree end = TREE_VEC_ELT (it, 2);
8063 tree step = TREE_VEC_ELT (it, 3);
8064 loc = DECL_SOURCE_LOCATION (var);
8065 tree tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8066 var, begin);
8067 append_to_statement_list_force (tem, last_body);
8069 tree cond1 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8070 step, build_zero_cst (TREE_TYPE (step)));
8071 tree cond2 = fold_build2_loc (loc, LE_EXPR, boolean_type_node,
8072 var, end);
8073 tree cond3 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8074 var, end);
8075 cond1 = fold_build3_loc (loc, COND_EXPR, boolean_type_node,
8076 cond1, cond2, cond3);
8077 if (cond)
8078 cond = fold_build2_loc (loc, TRUTH_AND_EXPR,
8079 boolean_type_node, cond, cond1);
8080 else
8081 cond = cond1;
8083 tree cont_label = create_artificial_label (loc);
8084 label = build1 (LABEL_EXPR, void_type_node, cont_label);
8085 tree tem = fold_build3_loc (loc, COND_EXPR, void_type_node, cond,
8086 void_node,
8087 build_and_jump (&cont_label));
8088 append_to_statement_list_force (tem, last_body);
8090 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8092 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t), 0),
8093 last_body);
8094 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8096 if (error_operand_p (TREE_VALUE (t)))
8097 return;
8098 append_to_statement_list_force (TREE_VALUE (t), last_body);
8099 TREE_VALUE (t) = null_pointer_node;
8101 else
8103 if (last_bind)
8105 append_to_statement_list (label, last_body);
8106 gimplify_and_add (last_bind, pre_p);
8107 last_bind = NULL_TREE;
8109 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8111 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8112 NULL, is_gimple_val, fb_rvalue);
8113 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8115 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8116 return;
8117 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8118 is_gimple_val, fb_rvalue) == GS_ERROR)
8119 return;
8120 gimplify_and_add (OMP_CLAUSE_DECL (c), pre_p);
8123 if (last_bind)
8125 append_to_statement_list (label, last_body);
8126 gimplify_and_add (last_bind, pre_p);
8128 return;
8131 /* If *LIST_P contains any OpenMP depend clauses with iterators,
8132 lower all the depend clauses by populating corresponding depend
8133 array. Returns 0 if there are no such depend clauses, or
8134 2 if all depend clauses should be removed, 1 otherwise. */
8136 static int
8137 gimplify_omp_depend (tree *list_p, gimple_seq *pre_p)
8139 tree c;
8140 gimple *g;
8141 size_t n[4] = { 0, 0, 0, 0 };
8142 bool unused[4];
8143 tree counts[4] = { NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE };
8144 tree last_iter = NULL_TREE, last_count = NULL_TREE;
8145 size_t i, j;
8146 location_t first_loc = UNKNOWN_LOCATION;
8148 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8149 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8151 switch (OMP_CLAUSE_DEPEND_KIND (c))
8153 case OMP_CLAUSE_DEPEND_IN:
8154 i = 2;
8155 break;
8156 case OMP_CLAUSE_DEPEND_OUT:
8157 case OMP_CLAUSE_DEPEND_INOUT:
8158 i = 0;
8159 break;
8160 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8161 i = 1;
8162 break;
8163 case OMP_CLAUSE_DEPEND_DEPOBJ:
8164 i = 3;
8165 break;
8166 case OMP_CLAUSE_DEPEND_SOURCE:
8167 case OMP_CLAUSE_DEPEND_SINK:
8168 continue;
8169 default:
8170 gcc_unreachable ();
8172 tree t = OMP_CLAUSE_DECL (c);
8173 if (first_loc == UNKNOWN_LOCATION)
8174 first_loc = OMP_CLAUSE_LOCATION (c);
8175 if (TREE_CODE (t) == TREE_LIST
8176 && TREE_PURPOSE (t)
8177 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8179 if (TREE_PURPOSE (t) != last_iter)
8181 tree tcnt = size_one_node;
8182 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8184 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8185 is_gimple_val, fb_rvalue) == GS_ERROR
8186 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8187 is_gimple_val, fb_rvalue) == GS_ERROR
8188 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8189 is_gimple_val, fb_rvalue) == GS_ERROR
8190 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8191 is_gimple_val, fb_rvalue)
8192 == GS_ERROR))
8193 return 2;
8194 tree var = TREE_VEC_ELT (it, 0);
8195 tree begin = TREE_VEC_ELT (it, 1);
8196 tree end = TREE_VEC_ELT (it, 2);
8197 tree step = TREE_VEC_ELT (it, 3);
8198 tree orig_step = TREE_VEC_ELT (it, 4);
8199 tree type = TREE_TYPE (var);
8200 tree stype = TREE_TYPE (step);
8201 location_t loc = DECL_SOURCE_LOCATION (var);
8202 tree endmbegin;
8203 /* Compute count for this iterator as
8204 orig_step > 0
8205 ? (begin < end ? (end - begin + (step - 1)) / step : 0)
8206 : (begin > end ? (end - begin + (step + 1)) / step : 0)
8207 and compute product of those for the entire depend
8208 clause. */
8209 if (POINTER_TYPE_P (type))
8210 endmbegin = fold_build2_loc (loc, POINTER_DIFF_EXPR,
8211 stype, end, begin);
8212 else
8213 endmbegin = fold_build2_loc (loc, MINUS_EXPR, type,
8214 end, begin);
8215 tree stepm1 = fold_build2_loc (loc, MINUS_EXPR, stype,
8216 step,
8217 build_int_cst (stype, 1));
8218 tree stepp1 = fold_build2_loc (loc, PLUS_EXPR, stype, step,
8219 build_int_cst (stype, 1));
8220 tree pos = fold_build2_loc (loc, PLUS_EXPR, stype,
8221 unshare_expr (endmbegin),
8222 stepm1);
8223 pos = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8224 pos, step);
8225 tree neg = fold_build2_loc (loc, PLUS_EXPR, stype,
8226 endmbegin, stepp1);
8227 if (TYPE_UNSIGNED (stype))
8229 neg = fold_build1_loc (loc, NEGATE_EXPR, stype, neg);
8230 step = fold_build1_loc (loc, NEGATE_EXPR, stype, step);
8232 neg = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8233 neg, step);
8234 step = NULL_TREE;
8235 tree cond = fold_build2_loc (loc, LT_EXPR,
8236 boolean_type_node,
8237 begin, end);
8238 pos = fold_build3_loc (loc, COND_EXPR, stype, cond, pos,
8239 build_int_cst (stype, 0));
8240 cond = fold_build2_loc (loc, LT_EXPR, boolean_type_node,
8241 end, begin);
8242 neg = fold_build3_loc (loc, COND_EXPR, stype, cond, neg,
8243 build_int_cst (stype, 0));
8244 tree osteptype = TREE_TYPE (orig_step);
8245 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8246 orig_step,
8247 build_int_cst (osteptype, 0));
8248 tree cnt = fold_build3_loc (loc, COND_EXPR, stype,
8249 cond, pos, neg);
8250 cnt = fold_convert_loc (loc, sizetype, cnt);
8251 if (gimplify_expr (&cnt, pre_p, NULL, is_gimple_val,
8252 fb_rvalue) == GS_ERROR)
8253 return 2;
8254 tcnt = size_binop_loc (loc, MULT_EXPR, tcnt, cnt);
8256 if (gimplify_expr (&tcnt, pre_p, NULL, is_gimple_val,
8257 fb_rvalue) == GS_ERROR)
8258 return 2;
8259 last_iter = TREE_PURPOSE (t);
8260 last_count = tcnt;
8262 if (counts[i] == NULL_TREE)
8263 counts[i] = last_count;
8264 else
8265 counts[i] = size_binop_loc (OMP_CLAUSE_LOCATION (c),
8266 PLUS_EXPR, counts[i], last_count);
8268 else
8269 n[i]++;
8271 for (i = 0; i < 4; i++)
8272 if (counts[i])
8273 break;
8274 if (i == 4)
8275 return 0;
8277 tree total = size_zero_node;
8278 for (i = 0; i < 4; i++)
8280 unused[i] = counts[i] == NULL_TREE && n[i] == 0;
8281 if (counts[i] == NULL_TREE)
8282 counts[i] = size_zero_node;
8283 if (n[i])
8284 counts[i] = size_binop (PLUS_EXPR, counts[i], size_int (n[i]));
8285 if (gimplify_expr (&counts[i], pre_p, NULL, is_gimple_val,
8286 fb_rvalue) == GS_ERROR)
8287 return 2;
8288 total = size_binop (PLUS_EXPR, total, counts[i]);
8291 if (gimplify_expr (&total, pre_p, NULL, is_gimple_val, fb_rvalue)
8292 == GS_ERROR)
8293 return 2;
8294 bool is_old = unused[1] && unused[3];
8295 tree totalpx = size_binop (PLUS_EXPR, unshare_expr (total),
8296 size_int (is_old ? 1 : 4));
8297 tree type = build_array_type (ptr_type_node, build_index_type (totalpx));
8298 tree array = create_tmp_var_raw (type);
8299 TREE_ADDRESSABLE (array) = 1;
8300 if (!poly_int_tree_p (totalpx))
8302 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (array)))
8303 gimplify_type_sizes (TREE_TYPE (array), pre_p);
8304 if (gimplify_omp_ctxp)
8306 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8307 while (ctx
8308 && (ctx->region_type == ORT_WORKSHARE
8309 || ctx->region_type == ORT_TASKGROUP
8310 || ctx->region_type == ORT_SIMD
8311 || ctx->region_type == ORT_ACC))
8312 ctx = ctx->outer_context;
8313 if (ctx)
8314 omp_add_variable (ctx, array, GOVD_LOCAL | GOVD_SEEN);
8316 gimplify_vla_decl (array, pre_p);
8318 else
8319 gimple_add_tmp_var (array);
8320 tree r = build4 (ARRAY_REF, ptr_type_node, array, size_int (0), NULL_TREE,
8321 NULL_TREE);
8322 tree tem;
8323 if (!is_old)
8325 tem = build2 (MODIFY_EXPR, void_type_node, r,
8326 build_int_cst (ptr_type_node, 0));
8327 gimplify_and_add (tem, pre_p);
8328 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (1), NULL_TREE,
8329 NULL_TREE);
8331 tem = build2 (MODIFY_EXPR, void_type_node, r,
8332 fold_convert (ptr_type_node, total));
8333 gimplify_and_add (tem, pre_p);
8334 for (i = 1; i < (is_old ? 2 : 4); i++)
8336 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (i + !is_old),
8337 NULL_TREE, NULL_TREE);
8338 tem = build2 (MODIFY_EXPR, void_type_node, r, counts[i - 1]);
8339 gimplify_and_add (tem, pre_p);
8342 tree cnts[4];
8343 for (j = 4; j; j--)
8344 if (!unused[j - 1])
8345 break;
8346 for (i = 0; i < 4; i++)
8348 if (i && (i >= j || unused[i - 1]))
8350 cnts[i] = cnts[i - 1];
8351 continue;
8353 cnts[i] = create_tmp_var (sizetype);
8354 if (i == 0)
8355 g = gimple_build_assign (cnts[i], size_int (is_old ? 2 : 5));
8356 else
8358 tree t;
8359 if (is_old)
8360 t = size_binop (PLUS_EXPR, counts[0], size_int (2));
8361 else
8362 t = size_binop (PLUS_EXPR, cnts[i - 1], counts[i - 1]);
8363 if (gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue)
8364 == GS_ERROR)
8365 return 2;
8366 g = gimple_build_assign (cnts[i], t);
8368 gimple_seq_add_stmt (pre_p, g);
8371 last_iter = NULL_TREE;
8372 tree last_bind = NULL_TREE;
8373 tree *last_body = NULL;
8374 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8375 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8377 switch (OMP_CLAUSE_DEPEND_KIND (c))
8379 case OMP_CLAUSE_DEPEND_IN:
8380 i = 2;
8381 break;
8382 case OMP_CLAUSE_DEPEND_OUT:
8383 case OMP_CLAUSE_DEPEND_INOUT:
8384 i = 0;
8385 break;
8386 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8387 i = 1;
8388 break;
8389 case OMP_CLAUSE_DEPEND_DEPOBJ:
8390 i = 3;
8391 break;
8392 case OMP_CLAUSE_DEPEND_SOURCE:
8393 case OMP_CLAUSE_DEPEND_SINK:
8394 continue;
8395 default:
8396 gcc_unreachable ();
8398 tree t = OMP_CLAUSE_DECL (c);
8399 if (TREE_CODE (t) == TREE_LIST
8400 && TREE_PURPOSE (t)
8401 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8403 if (TREE_PURPOSE (t) != last_iter)
8405 if (last_bind)
8406 gimplify_and_add (last_bind, pre_p);
8407 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8408 last_bind = build3 (BIND_EXPR, void_type_node,
8409 BLOCK_VARS (block), NULL, block);
8410 TREE_SIDE_EFFECTS (last_bind) = 1;
8411 SET_EXPR_LOCATION (last_bind, OMP_CLAUSE_LOCATION (c));
8412 tree *p = &BIND_EXPR_BODY (last_bind);
8413 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8415 tree var = TREE_VEC_ELT (it, 0);
8416 tree begin = TREE_VEC_ELT (it, 1);
8417 tree end = TREE_VEC_ELT (it, 2);
8418 tree step = TREE_VEC_ELT (it, 3);
8419 tree orig_step = TREE_VEC_ELT (it, 4);
8420 tree type = TREE_TYPE (var);
8421 location_t loc = DECL_SOURCE_LOCATION (var);
8422 /* Emit:
8423 var = begin;
8424 goto cond_label;
8425 beg_label:
8427 var = var + step;
8428 cond_label:
8429 if (orig_step > 0) {
8430 if (var < end) goto beg_label;
8431 } else {
8432 if (var > end) goto beg_label;
8434 for each iterator, with inner iterators added to
8435 the ... above. */
8436 tree beg_label = create_artificial_label (loc);
8437 tree cond_label = NULL_TREE;
8438 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8439 var, begin);
8440 append_to_statement_list_force (tem, p);
8441 tem = build_and_jump (&cond_label);
8442 append_to_statement_list_force (tem, p);
8443 tem = build1 (LABEL_EXPR, void_type_node, beg_label);
8444 append_to_statement_list (tem, p);
8445 tree bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
8446 NULL_TREE, NULL_TREE);
8447 TREE_SIDE_EFFECTS (bind) = 1;
8448 SET_EXPR_LOCATION (bind, loc);
8449 append_to_statement_list_force (bind, p);
8450 if (POINTER_TYPE_P (type))
8451 tem = build2_loc (loc, POINTER_PLUS_EXPR, type,
8452 var, fold_convert_loc (loc, sizetype,
8453 step));
8454 else
8455 tem = build2_loc (loc, PLUS_EXPR, type, var, step);
8456 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8457 var, tem);
8458 append_to_statement_list_force (tem, p);
8459 tem = build1 (LABEL_EXPR, void_type_node, cond_label);
8460 append_to_statement_list (tem, p);
8461 tree cond = fold_build2_loc (loc, LT_EXPR,
8462 boolean_type_node,
8463 var, end);
8464 tree pos
8465 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8466 cond, build_and_jump (&beg_label),
8467 void_node);
8468 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8469 var, end);
8470 tree neg
8471 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8472 cond, build_and_jump (&beg_label),
8473 void_node);
8474 tree osteptype = TREE_TYPE (orig_step);
8475 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8476 orig_step,
8477 build_int_cst (osteptype, 0));
8478 tem = fold_build3_loc (loc, COND_EXPR, void_type_node,
8479 cond, pos, neg);
8480 append_to_statement_list_force (tem, p);
8481 p = &BIND_EXPR_BODY (bind);
8483 last_body = p;
8485 last_iter = TREE_PURPOSE (t);
8486 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8488 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t),
8489 0), last_body);
8490 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8492 if (error_operand_p (TREE_VALUE (t)))
8493 return 2;
8494 TREE_VALUE (t) = build_fold_addr_expr (TREE_VALUE (t));
8495 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8496 NULL_TREE, NULL_TREE);
8497 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8498 void_type_node, r, TREE_VALUE (t));
8499 append_to_statement_list_force (tem, last_body);
8500 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8501 void_type_node, cnts[i],
8502 size_binop (PLUS_EXPR, cnts[i], size_int (1)));
8503 append_to_statement_list_force (tem, last_body);
8504 TREE_VALUE (t) = null_pointer_node;
8506 else
8508 if (last_bind)
8510 gimplify_and_add (last_bind, pre_p);
8511 last_bind = NULL_TREE;
8513 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8515 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8516 NULL, is_gimple_val, fb_rvalue);
8517 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8519 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8520 return 2;
8521 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
8522 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8523 is_gimple_val, fb_rvalue) == GS_ERROR)
8524 return 2;
8525 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8526 NULL_TREE, NULL_TREE);
8527 tem = build2 (MODIFY_EXPR, void_type_node, r, OMP_CLAUSE_DECL (c));
8528 gimplify_and_add (tem, pre_p);
8529 g = gimple_build_assign (cnts[i], size_binop (PLUS_EXPR, cnts[i],
8530 size_int (1)));
8531 gimple_seq_add_stmt (pre_p, g);
8534 if (last_bind)
8535 gimplify_and_add (last_bind, pre_p);
8536 tree cond = boolean_false_node;
8537 if (is_old)
8539 if (!unused[0])
8540 cond = build2_loc (first_loc, NE_EXPR, boolean_type_node, cnts[0],
8541 size_binop_loc (first_loc, PLUS_EXPR, counts[0],
8542 size_int (2)));
8543 if (!unused[2])
8544 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8545 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8546 cnts[2],
8547 size_binop_loc (first_loc, PLUS_EXPR,
8548 totalpx,
8549 size_int (1))));
8551 else
8553 tree prev = size_int (5);
8554 for (i = 0; i < 4; i++)
8556 if (unused[i])
8557 continue;
8558 prev = size_binop_loc (first_loc, PLUS_EXPR, counts[i], prev);
8559 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8560 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8561 cnts[i], unshare_expr (prev)));
8564 tem = build3_loc (first_loc, COND_EXPR, void_type_node, cond,
8565 build_call_expr_loc (first_loc,
8566 builtin_decl_explicit (BUILT_IN_TRAP),
8567 0), void_node);
8568 gimplify_and_add (tem, pre_p);
8569 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_DEPEND);
8570 OMP_CLAUSE_DEPEND_KIND (c) = OMP_CLAUSE_DEPEND_LAST;
8571 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (array);
8572 OMP_CLAUSE_CHAIN (c) = *list_p;
8573 *list_p = c;
8574 return 1;
8577 /* Insert a GOMP_MAP_ALLOC or GOMP_MAP_RELEASE node following a
8578 GOMP_MAP_STRUCT mapping. C is an always_pointer mapping. STRUCT_NODE is
8579 the struct node to insert the new mapping after (when the struct node is
8580 initially created). PREV_NODE is the first of two or three mappings for a
8581 pointer, and is either:
8582 - the node before C, when a pair of mappings is used, e.g. for a C/C++
8583 array section.
8584 - not the node before C. This is true when we have a reference-to-pointer
8585 type (with a mapping for the reference and for the pointer), or for
8586 Fortran derived-type mappings with a GOMP_MAP_TO_PSET.
8587 If SCP is non-null, the new node is inserted before *SCP.
8588 if SCP is null, the new node is inserted before PREV_NODE.
8589 The return type is:
8590 - PREV_NODE, if SCP is non-null.
8591 - The newly-created ALLOC or RELEASE node, if SCP is null.
8592 - The second newly-created ALLOC or RELEASE node, if we are mapping a
8593 reference to a pointer. */
8595 static tree
8596 insert_struct_comp_map (enum tree_code code, tree c, tree struct_node,
8597 tree prev_node, tree *scp)
8599 enum gomp_map_kind mkind
8600 = (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA)
8601 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
8603 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8604 tree cl = scp ? prev_node : c2;
8605 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
8606 OMP_CLAUSE_DECL (c2) = unshare_expr (OMP_CLAUSE_DECL (c));
8607 OMP_CLAUSE_CHAIN (c2) = scp ? *scp : prev_node;
8608 if (OMP_CLAUSE_CHAIN (prev_node) != c
8609 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8610 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8611 == GOMP_MAP_TO_PSET))
8612 OMP_CLAUSE_SIZE (c2) = OMP_CLAUSE_SIZE (OMP_CLAUSE_CHAIN (prev_node));
8613 else
8614 OMP_CLAUSE_SIZE (c2) = TYPE_SIZE_UNIT (ptr_type_node);
8615 if (struct_node)
8616 OMP_CLAUSE_CHAIN (struct_node) = c2;
8618 /* We might need to create an additional mapping if we have a reference to a
8619 pointer (in C++). Don't do this if we have something other than a
8620 GOMP_MAP_ALWAYS_POINTER though, i.e. a GOMP_MAP_TO_PSET. */
8621 if (OMP_CLAUSE_CHAIN (prev_node) != c
8622 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8623 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8624 == GOMP_MAP_ALWAYS_POINTER)
8625 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8626 == GOMP_MAP_ATTACH_DETACH)))
8628 tree c4 = OMP_CLAUSE_CHAIN (prev_node);
8629 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8630 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
8631 OMP_CLAUSE_DECL (c3) = unshare_expr (OMP_CLAUSE_DECL (c4));
8632 OMP_CLAUSE_SIZE (c3) = TYPE_SIZE_UNIT (ptr_type_node);
8633 OMP_CLAUSE_CHAIN (c3) = prev_node;
8634 if (!scp)
8635 OMP_CLAUSE_CHAIN (c2) = c3;
8636 else
8637 cl = c3;
8640 if (scp)
8641 *scp = c2;
8643 return cl;
8646 /* Strip ARRAY_REFS or an indirect ref off BASE, find the containing object,
8647 and set *BITPOSP and *POFFSETP to the bit offset of the access.
8648 If BASE_REF is non-NULL and the containing object is a reference, set
8649 *BASE_REF to that reference before dereferencing the object.
8650 If BASE_REF is NULL, check that the containing object is a COMPONENT_REF or
8651 has array type, else return NULL. */
8653 static tree
8654 extract_base_bit_offset (tree base, tree *base_ref, poly_int64 *bitposp,
8655 poly_offset_int *poffsetp)
8657 tree offset;
8658 poly_int64 bitsize, bitpos;
8659 machine_mode mode;
8660 int unsignedp, reversep, volatilep = 0;
8661 poly_offset_int poffset;
8663 if (base_ref)
8665 *base_ref = NULL_TREE;
8667 while (TREE_CODE (base) == ARRAY_REF)
8668 base = TREE_OPERAND (base, 0);
8670 if (TREE_CODE (base) == INDIRECT_REF)
8671 base = TREE_OPERAND (base, 0);
8673 else
8675 if (TREE_CODE (base) == ARRAY_REF)
8677 while (TREE_CODE (base) == ARRAY_REF)
8678 base = TREE_OPERAND (base, 0);
8679 if (TREE_CODE (base) != COMPONENT_REF
8680 || TREE_CODE (TREE_TYPE (base)) != ARRAY_TYPE)
8681 return NULL_TREE;
8683 else if (TREE_CODE (base) == INDIRECT_REF
8684 && TREE_CODE (TREE_OPERAND (base, 0)) == COMPONENT_REF
8685 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0)))
8686 == REFERENCE_TYPE))
8687 base = TREE_OPERAND (base, 0);
8690 base = get_inner_reference (base, &bitsize, &bitpos, &offset, &mode,
8691 &unsignedp, &reversep, &volatilep);
8693 tree orig_base = base;
8695 if ((TREE_CODE (base) == INDIRECT_REF
8696 || (TREE_CODE (base) == MEM_REF
8697 && integer_zerop (TREE_OPERAND (base, 1))))
8698 && DECL_P (TREE_OPERAND (base, 0))
8699 && TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0))) == REFERENCE_TYPE)
8700 base = TREE_OPERAND (base, 0);
8702 gcc_assert (offset == NULL_TREE || poly_int_tree_p (offset));
8704 if (offset)
8705 poffset = wi::to_poly_offset (offset);
8706 else
8707 poffset = 0;
8709 if (maybe_ne (bitpos, 0))
8710 poffset += bits_to_bytes_round_down (bitpos);
8712 *bitposp = bitpos;
8713 *poffsetp = poffset;
8715 /* Set *BASE_REF if BASE was a dereferenced reference variable. */
8716 if (base_ref && orig_base != base)
8717 *base_ref = orig_base;
8719 return base;
8722 /* Returns true if EXPR is or contains (as a sub-component) BASE_PTR. */
8724 static bool
8725 is_or_contains_p (tree expr, tree base_ptr)
8727 while (expr != base_ptr)
8728 if (TREE_CODE (base_ptr) == COMPONENT_REF)
8729 base_ptr = TREE_OPERAND (base_ptr, 0);
8730 else
8731 break;
8732 return expr == base_ptr;
8735 /* Implement OpenMP 5.x map ordering rules for target directives. There are
8736 several rules, and with some level of ambiguity, hopefully we can at least
8737 collect the complexity here in one place. */
8739 static void
8740 omp_target_reorder_clauses (tree *list_p)
8742 /* Collect refs to alloc/release/delete maps. */
8743 auto_vec<tree, 32> ard;
8744 tree *cp = list_p;
8745 while (*cp != NULL_TREE)
8746 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8747 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALLOC
8748 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_RELEASE
8749 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_DELETE))
8751 /* Unlink cp and push to ard. */
8752 tree c = *cp;
8753 tree nc = OMP_CLAUSE_CHAIN (c);
8754 *cp = nc;
8755 ard.safe_push (c);
8757 /* Any associated pointer type maps should also move along. */
8758 while (*cp != NULL_TREE
8759 && OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8760 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
8761 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_POINTER
8762 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ATTACH_DETACH
8763 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_POINTER
8764 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALWAYS_POINTER
8765 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_TO_PSET))
8767 c = *cp;
8768 nc = OMP_CLAUSE_CHAIN (c);
8769 *cp = nc;
8770 ard.safe_push (c);
8773 else
8774 cp = &OMP_CLAUSE_CHAIN (*cp);
8776 /* Link alloc/release/delete maps to the end of list. */
8777 for (unsigned int i = 0; i < ard.length (); i++)
8779 *cp = ard[i];
8780 cp = &OMP_CLAUSE_CHAIN (ard[i]);
8782 *cp = NULL_TREE;
8784 /* OpenMP 5.0 requires that pointer variables are mapped before
8785 its use as a base-pointer. */
8786 auto_vec<tree *, 32> atf;
8787 for (tree *cp = list_p; *cp; cp = &OMP_CLAUSE_CHAIN (*cp))
8788 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP)
8790 /* Collect alloc, to, from, to/from clause tree pointers. */
8791 gomp_map_kind k = OMP_CLAUSE_MAP_KIND (*cp);
8792 if (k == GOMP_MAP_ALLOC
8793 || k == GOMP_MAP_TO
8794 || k == GOMP_MAP_FROM
8795 || k == GOMP_MAP_TOFROM
8796 || k == GOMP_MAP_ALWAYS_TO
8797 || k == GOMP_MAP_ALWAYS_FROM
8798 || k == GOMP_MAP_ALWAYS_TOFROM)
8799 atf.safe_push (cp);
8802 for (unsigned int i = 0; i < atf.length (); i++)
8803 if (atf[i])
8805 tree *cp = atf[i];
8806 tree decl = OMP_CLAUSE_DECL (*cp);
8807 if (TREE_CODE (decl) == INDIRECT_REF || TREE_CODE (decl) == MEM_REF)
8809 tree base_ptr = TREE_OPERAND (decl, 0);
8810 STRIP_TYPE_NOPS (base_ptr);
8811 for (unsigned int j = i + 1; j < atf.length (); j++)
8813 tree *cp2 = atf[j];
8814 tree decl2 = OMP_CLAUSE_DECL (*cp2);
8815 if (is_or_contains_p (decl2, base_ptr))
8817 /* Move *cp2 to before *cp. */
8818 tree c = *cp2;
8819 *cp2 = OMP_CLAUSE_CHAIN (c);
8820 OMP_CLAUSE_CHAIN (c) = *cp;
8821 *cp = c;
8822 atf[j] = NULL;
8829 /* DECL is supposed to have lastprivate semantics in the outer contexts
8830 of combined/composite constructs, starting with OCTX.
8831 Add needed lastprivate, shared or map clause if no data sharing or
8832 mapping clause are present. IMPLICIT_P is true if it is an implicit
8833 clause (IV on simd), in which case the lastprivate will not be
8834 copied to some constructs. */
8836 static void
8837 omp_lastprivate_for_combined_outer_constructs (struct gimplify_omp_ctx *octx,
8838 tree decl, bool implicit_p)
8840 struct gimplify_omp_ctx *orig_octx = octx;
8841 for (; octx; octx = octx->outer_context)
8843 if ((octx->region_type == ORT_COMBINED_PARALLEL
8844 || (octx->region_type & ORT_COMBINED_TEAMS) == ORT_COMBINED_TEAMS)
8845 && splay_tree_lookup (octx->variables,
8846 (splay_tree_key) decl) == NULL)
8848 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
8849 continue;
8851 if ((octx->region_type & ORT_TASK) != 0
8852 && octx->combined_loop
8853 && splay_tree_lookup (octx->variables,
8854 (splay_tree_key) decl) == NULL)
8856 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8857 continue;
8859 if (implicit_p
8860 && octx->region_type == ORT_WORKSHARE
8861 && octx->combined_loop
8862 && splay_tree_lookup (octx->variables,
8863 (splay_tree_key) decl) == NULL
8864 && octx->outer_context
8865 && octx->outer_context->region_type == ORT_COMBINED_PARALLEL
8866 && splay_tree_lookup (octx->outer_context->variables,
8867 (splay_tree_key) decl) == NULL)
8869 octx = octx->outer_context;
8870 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8871 continue;
8873 if ((octx->region_type == ORT_WORKSHARE || octx->region_type == ORT_ACC)
8874 && octx->combined_loop
8875 && splay_tree_lookup (octx->variables,
8876 (splay_tree_key) decl) == NULL
8877 && !omp_check_private (octx, decl, false))
8879 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8880 continue;
8882 if (octx->region_type == ORT_COMBINED_TARGET)
8884 splay_tree_node n = splay_tree_lookup (octx->variables,
8885 (splay_tree_key) decl);
8886 if (n == NULL)
8888 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
8889 octx = octx->outer_context;
8891 else if (!implicit_p
8892 && (n->value & GOVD_FIRSTPRIVATE_IMPLICIT))
8894 n->value &= ~(GOVD_FIRSTPRIVATE
8895 | GOVD_FIRSTPRIVATE_IMPLICIT
8896 | GOVD_EXPLICIT);
8897 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
8898 octx = octx->outer_context;
8901 break;
8903 if (octx && (implicit_p || octx != orig_octx))
8904 omp_notice_variable (octx, decl, true);
8907 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
8908 and previous omp contexts. */
8910 static void
8911 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
8912 enum omp_region_type region_type,
8913 enum tree_code code)
8915 struct gimplify_omp_ctx *ctx, *outer_ctx;
8916 tree c;
8917 hash_map<tree, tree> *struct_map_to_clause = NULL;
8918 hash_set<tree> *struct_deref_set = NULL;
8919 tree *prev_list_p = NULL, *orig_list_p = list_p;
8920 int handled_depend_iterators = -1;
8921 int nowait = -1;
8923 ctx = new_omp_context (region_type);
8924 ctx->code = code;
8925 outer_ctx = ctx->outer_context;
8926 if (code == OMP_TARGET)
8928 if (!lang_GNU_Fortran ())
8929 ctx->defaultmap[GDMK_POINTER] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
8930 ctx->defaultmap[GDMK_SCALAR] = GOVD_FIRSTPRIVATE;
8931 ctx->defaultmap[GDMK_SCALAR_TARGET] = (lang_GNU_Fortran ()
8932 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
8934 if (!lang_GNU_Fortran ())
8935 switch (code)
8937 case OMP_TARGET:
8938 case OMP_TARGET_DATA:
8939 case OMP_TARGET_ENTER_DATA:
8940 case OMP_TARGET_EXIT_DATA:
8941 case OACC_DECLARE:
8942 case OACC_HOST_DATA:
8943 case OACC_PARALLEL:
8944 case OACC_KERNELS:
8945 ctx->target_firstprivatize_array_bases = true;
8946 default:
8947 break;
8950 if (code == OMP_TARGET
8951 || code == OMP_TARGET_DATA
8952 || code == OMP_TARGET_ENTER_DATA
8953 || code == OMP_TARGET_EXIT_DATA)
8954 omp_target_reorder_clauses (list_p);
8956 while ((c = *list_p) != NULL)
8958 bool remove = false;
8959 bool notice_outer = true;
8960 const char *check_non_private = NULL;
8961 unsigned int flags;
8962 tree decl;
8964 switch (OMP_CLAUSE_CODE (c))
8966 case OMP_CLAUSE_PRIVATE:
8967 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
8968 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
8970 flags |= GOVD_PRIVATE_OUTER_REF;
8971 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
8973 else
8974 notice_outer = false;
8975 goto do_add;
8976 case OMP_CLAUSE_SHARED:
8977 flags = GOVD_SHARED | GOVD_EXPLICIT;
8978 goto do_add;
8979 case OMP_CLAUSE_FIRSTPRIVATE:
8980 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
8981 check_non_private = "firstprivate";
8982 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
8984 gcc_assert (code == OMP_TARGET);
8985 flags |= GOVD_FIRSTPRIVATE_IMPLICIT;
8987 goto do_add;
8988 case OMP_CLAUSE_LASTPRIVATE:
8989 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
8990 switch (code)
8992 case OMP_DISTRIBUTE:
8993 error_at (OMP_CLAUSE_LOCATION (c),
8994 "conditional %<lastprivate%> clause on "
8995 "%qs construct", "distribute");
8996 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8997 break;
8998 case OMP_TASKLOOP:
8999 error_at (OMP_CLAUSE_LOCATION (c),
9000 "conditional %<lastprivate%> clause on "
9001 "%qs construct", "taskloop");
9002 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
9003 break;
9004 default:
9005 break;
9007 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
9008 if (code != OMP_LOOP)
9009 check_non_private = "lastprivate";
9010 decl = OMP_CLAUSE_DECL (c);
9011 if (error_operand_p (decl))
9012 goto do_add;
9013 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c)
9014 && !lang_hooks.decls.omp_scalar_p (decl, true))
9016 error_at (OMP_CLAUSE_LOCATION (c),
9017 "non-scalar variable %qD in conditional "
9018 "%<lastprivate%> clause", decl);
9019 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
9021 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
9022 flags |= GOVD_LASTPRIVATE_CONDITIONAL;
9023 omp_lastprivate_for_combined_outer_constructs (outer_ctx, decl,
9024 false);
9025 goto do_add;
9026 case OMP_CLAUSE_REDUCTION:
9027 if (OMP_CLAUSE_REDUCTION_TASK (c))
9029 if (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
9031 if (nowait == -1)
9032 nowait = omp_find_clause (*list_p,
9033 OMP_CLAUSE_NOWAIT) != NULL_TREE;
9034 if (nowait
9035 && (outer_ctx == NULL
9036 || outer_ctx->region_type != ORT_COMBINED_PARALLEL))
9038 error_at (OMP_CLAUSE_LOCATION (c),
9039 "%<task%> reduction modifier on a construct "
9040 "with a %<nowait%> clause");
9041 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
9044 else if ((region_type & ORT_PARALLEL) != ORT_PARALLEL)
9046 error_at (OMP_CLAUSE_LOCATION (c),
9047 "invalid %<task%> reduction modifier on construct "
9048 "other than %<parallel%>, %qs, %<sections%> or "
9049 "%<scope%>", lang_GNU_Fortran () ? "do" : "for");
9050 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
9053 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
9054 switch (code)
9056 case OMP_SECTIONS:
9057 error_at (OMP_CLAUSE_LOCATION (c),
9058 "%<inscan%> %<reduction%> clause on "
9059 "%qs construct", "sections");
9060 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9061 break;
9062 case OMP_PARALLEL:
9063 error_at (OMP_CLAUSE_LOCATION (c),
9064 "%<inscan%> %<reduction%> clause on "
9065 "%qs construct", "parallel");
9066 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9067 break;
9068 case OMP_TEAMS:
9069 error_at (OMP_CLAUSE_LOCATION (c),
9070 "%<inscan%> %<reduction%> clause on "
9071 "%qs construct", "teams");
9072 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9073 break;
9074 case OMP_TASKLOOP:
9075 error_at (OMP_CLAUSE_LOCATION (c),
9076 "%<inscan%> %<reduction%> clause on "
9077 "%qs construct", "taskloop");
9078 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9079 break;
9080 case OMP_SCOPE:
9081 error_at (OMP_CLAUSE_LOCATION (c),
9082 "%<inscan%> %<reduction%> clause on "
9083 "%qs construct", "scope");
9084 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9085 break;
9086 default:
9087 break;
9089 /* FALLTHRU */
9090 case OMP_CLAUSE_IN_REDUCTION:
9091 case OMP_CLAUSE_TASK_REDUCTION:
9092 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
9093 /* OpenACC permits reductions on private variables. */
9094 if (!(region_type & ORT_ACC)
9095 /* taskgroup is actually not a worksharing region. */
9096 && code != OMP_TASKGROUP)
9097 check_non_private = omp_clause_code_name[OMP_CLAUSE_CODE (c)];
9098 decl = OMP_CLAUSE_DECL (c);
9099 if (TREE_CODE (decl) == MEM_REF)
9101 tree type = TREE_TYPE (decl);
9102 bool saved_into_ssa = gimplify_ctxp->into_ssa;
9103 gimplify_ctxp->into_ssa = false;
9104 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
9105 NULL, is_gimple_val, fb_rvalue, false)
9106 == GS_ERROR)
9108 gimplify_ctxp->into_ssa = saved_into_ssa;
9109 remove = true;
9110 break;
9112 gimplify_ctxp->into_ssa = saved_into_ssa;
9113 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
9114 if (DECL_P (v))
9116 omp_firstprivatize_variable (ctx, v);
9117 omp_notice_variable (ctx, v, true);
9119 decl = TREE_OPERAND (decl, 0);
9120 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
9122 gimplify_ctxp->into_ssa = false;
9123 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
9124 NULL, is_gimple_val, fb_rvalue, false)
9125 == GS_ERROR)
9127 gimplify_ctxp->into_ssa = saved_into_ssa;
9128 remove = true;
9129 break;
9131 gimplify_ctxp->into_ssa = saved_into_ssa;
9132 v = TREE_OPERAND (decl, 1);
9133 if (DECL_P (v))
9135 omp_firstprivatize_variable (ctx, v);
9136 omp_notice_variable (ctx, v, true);
9138 decl = TREE_OPERAND (decl, 0);
9140 if (TREE_CODE (decl) == ADDR_EXPR
9141 || TREE_CODE (decl) == INDIRECT_REF)
9142 decl = TREE_OPERAND (decl, 0);
9144 goto do_add_decl;
9145 case OMP_CLAUSE_LINEAR:
9146 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
9147 is_gimple_val, fb_rvalue) == GS_ERROR)
9149 remove = true;
9150 break;
9152 else
9154 if (code == OMP_SIMD
9155 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
9157 struct gimplify_omp_ctx *octx = outer_ctx;
9158 if (octx
9159 && octx->region_type == ORT_WORKSHARE
9160 && octx->combined_loop
9161 && !octx->distribute)
9163 if (octx->outer_context
9164 && (octx->outer_context->region_type
9165 == ORT_COMBINED_PARALLEL))
9166 octx = octx->outer_context->outer_context;
9167 else
9168 octx = octx->outer_context;
9170 if (octx
9171 && octx->region_type == ORT_WORKSHARE
9172 && octx->combined_loop
9173 && octx->distribute)
9175 error_at (OMP_CLAUSE_LOCATION (c),
9176 "%<linear%> clause for variable other than "
9177 "loop iterator specified on construct "
9178 "combined with %<distribute%>");
9179 remove = true;
9180 break;
9183 /* For combined #pragma omp parallel for simd, need to put
9184 lastprivate and perhaps firstprivate too on the
9185 parallel. Similarly for #pragma omp for simd. */
9186 struct gimplify_omp_ctx *octx = outer_ctx;
9187 bool taskloop_seen = false;
9188 decl = NULL_TREE;
9191 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9192 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9193 break;
9194 decl = OMP_CLAUSE_DECL (c);
9195 if (error_operand_p (decl))
9197 decl = NULL_TREE;
9198 break;
9200 flags = GOVD_SEEN;
9201 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
9202 flags |= GOVD_FIRSTPRIVATE;
9203 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9204 flags |= GOVD_LASTPRIVATE;
9205 if (octx
9206 && octx->region_type == ORT_WORKSHARE
9207 && octx->combined_loop)
9209 if (octx->outer_context
9210 && (octx->outer_context->region_type
9211 == ORT_COMBINED_PARALLEL))
9212 octx = octx->outer_context;
9213 else if (omp_check_private (octx, decl, false))
9214 break;
9216 else if (octx
9217 && (octx->region_type & ORT_TASK) != 0
9218 && octx->combined_loop)
9219 taskloop_seen = true;
9220 else if (octx
9221 && octx->region_type == ORT_COMBINED_PARALLEL
9222 && ((ctx->region_type == ORT_WORKSHARE
9223 && octx == outer_ctx)
9224 || taskloop_seen))
9225 flags = GOVD_SEEN | GOVD_SHARED;
9226 else if (octx
9227 && ((octx->region_type & ORT_COMBINED_TEAMS)
9228 == ORT_COMBINED_TEAMS))
9229 flags = GOVD_SEEN | GOVD_SHARED;
9230 else if (octx
9231 && octx->region_type == ORT_COMBINED_TARGET)
9233 if (flags & GOVD_LASTPRIVATE)
9234 flags = GOVD_SEEN | GOVD_MAP;
9236 else
9237 break;
9238 splay_tree_node on
9239 = splay_tree_lookup (octx->variables,
9240 (splay_tree_key) decl);
9241 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
9243 octx = NULL;
9244 break;
9246 omp_add_variable (octx, decl, flags);
9247 if (octx->outer_context == NULL)
9248 break;
9249 octx = octx->outer_context;
9251 while (1);
9252 if (octx
9253 && decl
9254 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9255 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
9256 omp_notice_variable (octx, decl, true);
9258 flags = GOVD_LINEAR | GOVD_EXPLICIT;
9259 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9260 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9262 notice_outer = false;
9263 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9265 goto do_add;
9267 case OMP_CLAUSE_MAP:
9268 decl = OMP_CLAUSE_DECL (c);
9269 if (error_operand_p (decl))
9270 remove = true;
9271 switch (code)
9273 case OMP_TARGET:
9274 break;
9275 case OACC_DATA:
9276 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
9277 break;
9278 /* FALLTHRU */
9279 case OMP_TARGET_DATA:
9280 case OMP_TARGET_ENTER_DATA:
9281 case OMP_TARGET_EXIT_DATA:
9282 case OACC_ENTER_DATA:
9283 case OACC_EXIT_DATA:
9284 case OACC_HOST_DATA:
9285 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9286 || (OMP_CLAUSE_MAP_KIND (c)
9287 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
9288 /* For target {,enter ,exit }data only the array slice is
9289 mapped, but not the pointer to it. */
9290 remove = true;
9291 break;
9292 default:
9293 break;
9295 /* For Fortran, not only the pointer to the data is mapped but also
9296 the address of the pointer, the array descriptor etc.; for
9297 'exit data' - and in particular for 'delete:' - having an 'alloc:'
9298 does not make sense. Likewise, for 'update' only transferring the
9299 data itself is needed as the rest has been handled in previous
9300 directives. However, for 'exit data', the array descriptor needs
9301 to be delete; hence, we turn the MAP_TO_PSET into a MAP_DELETE.
9303 NOTE: Generally, it is not safe to perform "enter data" operations
9304 on arrays where the data *or the descriptor* may go out of scope
9305 before a corresponding "exit data" operation -- and such a
9306 descriptor may be synthesized temporarily, e.g. to pass an
9307 explicit-shape array to a function expecting an assumed-shape
9308 argument. Performing "enter data" inside the called function
9309 would thus be problematic. */
9310 if (code == OMP_TARGET_EXIT_DATA
9311 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
9312 OMP_CLAUSE_SET_MAP_KIND (c, OMP_CLAUSE_MAP_KIND (*prev_list_p)
9313 == GOMP_MAP_DELETE
9314 ? GOMP_MAP_DELETE : GOMP_MAP_RELEASE);
9315 else if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
9316 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
9317 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
9318 remove = true;
9320 if (remove)
9321 break;
9322 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
9324 struct gimplify_omp_ctx *octx;
9325 for (octx = outer_ctx; octx; octx = octx->outer_context)
9327 if (octx->region_type != ORT_ACC_HOST_DATA)
9328 break;
9329 splay_tree_node n2
9330 = splay_tree_lookup (octx->variables,
9331 (splay_tree_key) decl);
9332 if (n2)
9333 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
9334 "declared in enclosing %<host_data%> region",
9335 DECL_NAME (decl));
9338 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9339 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9340 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9341 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9342 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
9344 remove = true;
9345 break;
9347 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9348 || (OMP_CLAUSE_MAP_KIND (c)
9349 == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9350 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9351 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
9353 OMP_CLAUSE_SIZE (c)
9354 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
9355 false);
9356 if ((region_type & ORT_TARGET) != 0)
9357 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
9358 GOVD_FIRSTPRIVATE | GOVD_SEEN);
9361 if (!DECL_P (decl))
9363 tree d = decl, *pd;
9364 if (TREE_CODE (d) == ARRAY_REF)
9366 while (TREE_CODE (d) == ARRAY_REF)
9367 d = TREE_OPERAND (d, 0);
9368 if (TREE_CODE (d) == COMPONENT_REF
9369 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
9370 decl = d;
9372 pd = &OMP_CLAUSE_DECL (c);
9373 if (d == decl
9374 && TREE_CODE (decl) == INDIRECT_REF
9375 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
9376 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9377 == REFERENCE_TYPE))
9379 pd = &TREE_OPERAND (decl, 0);
9380 decl = TREE_OPERAND (decl, 0);
9382 bool indir_p = false;
9383 tree orig_decl = decl;
9384 tree decl_ref = NULL_TREE;
9385 if ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA)) != 0
9386 && TREE_CODE (*pd) == COMPONENT_REF
9387 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH
9388 && code != OACC_UPDATE)
9390 while (TREE_CODE (decl) == COMPONENT_REF)
9392 decl = TREE_OPERAND (decl, 0);
9393 if (((TREE_CODE (decl) == MEM_REF
9394 && integer_zerop (TREE_OPERAND (decl, 1)))
9395 || INDIRECT_REF_P (decl))
9396 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9397 == POINTER_TYPE))
9399 indir_p = true;
9400 decl = TREE_OPERAND (decl, 0);
9402 if (TREE_CODE (decl) == INDIRECT_REF
9403 && DECL_P (TREE_OPERAND (decl, 0))
9404 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9405 == REFERENCE_TYPE))
9407 decl_ref = decl;
9408 decl = TREE_OPERAND (decl, 0);
9412 else if (TREE_CODE (decl) == COMPONENT_REF)
9414 while (TREE_CODE (decl) == COMPONENT_REF)
9415 decl = TREE_OPERAND (decl, 0);
9416 if (TREE_CODE (decl) == INDIRECT_REF
9417 && DECL_P (TREE_OPERAND (decl, 0))
9418 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9419 == REFERENCE_TYPE))
9420 decl = TREE_OPERAND (decl, 0);
9422 if (decl != orig_decl && DECL_P (decl) && indir_p)
9424 gomp_map_kind k
9425 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9426 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9427 /* We have a dereference of a struct member. Make this an
9428 attach/detach operation, and ensure the base pointer is
9429 mapped as a FIRSTPRIVATE_POINTER. */
9430 OMP_CLAUSE_SET_MAP_KIND (c, k);
9431 flags = GOVD_MAP | GOVD_SEEN | GOVD_EXPLICIT;
9432 tree next_clause = OMP_CLAUSE_CHAIN (c);
9433 if (k == GOMP_MAP_ATTACH
9434 && code != OACC_ENTER_DATA
9435 && code != OMP_TARGET_ENTER_DATA
9436 && (!next_clause
9437 || (OMP_CLAUSE_CODE (next_clause) != OMP_CLAUSE_MAP)
9438 || (OMP_CLAUSE_MAP_KIND (next_clause)
9439 != GOMP_MAP_POINTER)
9440 || OMP_CLAUSE_DECL (next_clause) != decl)
9441 && (!struct_deref_set
9442 || !struct_deref_set->contains (decl)))
9444 if (!struct_deref_set)
9445 struct_deref_set = new hash_set<tree> ();
9446 /* As well as the attach, we also need a
9447 FIRSTPRIVATE_POINTER clause to properly map the
9448 pointer to the struct base. */
9449 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9450 OMP_CLAUSE_MAP);
9451 OMP_CLAUSE_SET_MAP_KIND (c2, GOMP_MAP_ALLOC);
9452 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (c2)
9453 = 1;
9454 tree charptr_zero
9455 = build_int_cst (build_pointer_type (char_type_node),
9457 OMP_CLAUSE_DECL (c2)
9458 = build2 (MEM_REF, char_type_node,
9459 decl_ref ? decl_ref : decl, charptr_zero);
9460 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9461 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9462 OMP_CLAUSE_MAP);
9463 OMP_CLAUSE_SET_MAP_KIND (c3,
9464 GOMP_MAP_FIRSTPRIVATE_POINTER);
9465 OMP_CLAUSE_DECL (c3) = decl;
9466 OMP_CLAUSE_SIZE (c3) = size_zero_node;
9467 tree mapgrp = *prev_list_p;
9468 *prev_list_p = c2;
9469 OMP_CLAUSE_CHAIN (c3) = mapgrp;
9470 OMP_CLAUSE_CHAIN (c2) = c3;
9472 struct_deref_set->add (decl);
9474 goto do_add_decl;
9476 /* An "attach/detach" operation on an update directive should
9477 behave as a GOMP_MAP_ALWAYS_POINTER. Beware that
9478 unlike attach or detach map kinds, GOMP_MAP_ALWAYS_POINTER
9479 depends on the previous mapping. */
9480 if (code == OACC_UPDATE
9481 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9482 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_ALWAYS_POINTER);
9483 if (DECL_P (decl)
9484 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9485 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH
9486 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_DETACH
9487 && code != OACC_UPDATE
9488 && code != OMP_TARGET_UPDATE)
9490 if (error_operand_p (decl))
9492 remove = true;
9493 break;
9496 tree stype = TREE_TYPE (decl);
9497 if (TREE_CODE (stype) == REFERENCE_TYPE)
9498 stype = TREE_TYPE (stype);
9499 if (TYPE_SIZE_UNIT (stype) == NULL
9500 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
9502 error_at (OMP_CLAUSE_LOCATION (c),
9503 "mapping field %qE of variable length "
9504 "structure", OMP_CLAUSE_DECL (c));
9505 remove = true;
9506 break;
9509 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER
9510 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9512 /* Error recovery. */
9513 if (prev_list_p == NULL)
9515 remove = true;
9516 break;
9518 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
9520 tree ch = OMP_CLAUSE_CHAIN (*prev_list_p);
9521 if (ch == NULL_TREE || OMP_CLAUSE_CHAIN (ch) != c)
9523 remove = true;
9524 break;
9529 poly_offset_int offset1;
9530 poly_int64 bitpos1;
9531 tree base_ref;
9533 tree base
9534 = extract_base_bit_offset (OMP_CLAUSE_DECL (c), &base_ref,
9535 &bitpos1, &offset1);
9537 gcc_assert (base == decl);
9539 splay_tree_node n
9540 = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
9541 bool ptr = (OMP_CLAUSE_MAP_KIND (c)
9542 == GOMP_MAP_ALWAYS_POINTER);
9543 bool attach_detach = (OMP_CLAUSE_MAP_KIND (c)
9544 == GOMP_MAP_ATTACH_DETACH);
9545 bool attach = OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
9546 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DETACH;
9547 bool has_attachments = false;
9548 /* For OpenACC, pointers in structs should trigger an
9549 attach action. */
9550 if (attach_detach
9551 && ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA))
9552 || code == OMP_TARGET_ENTER_DATA
9553 || code == OMP_TARGET_EXIT_DATA))
9556 /* Turn a GOMP_MAP_ATTACH_DETACH clause into a
9557 GOMP_MAP_ATTACH or GOMP_MAP_DETACH clause after we
9558 have detected a case that needs a GOMP_MAP_STRUCT
9559 mapping added. */
9560 gomp_map_kind k
9561 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9562 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9563 OMP_CLAUSE_SET_MAP_KIND (c, k);
9564 has_attachments = true;
9566 if (n == NULL || (n->value & GOVD_MAP) == 0)
9568 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9569 OMP_CLAUSE_MAP);
9570 gomp_map_kind k = attach ? GOMP_MAP_FORCE_PRESENT
9571 : GOMP_MAP_STRUCT;
9573 OMP_CLAUSE_SET_MAP_KIND (l, k);
9574 if (base_ref)
9575 OMP_CLAUSE_DECL (l) = unshare_expr (base_ref);
9576 else
9577 OMP_CLAUSE_DECL (l) = decl;
9578 OMP_CLAUSE_SIZE (l)
9579 = (!attach
9580 ? size_int (1)
9581 : DECL_P (OMP_CLAUSE_DECL (l))
9582 ? DECL_SIZE_UNIT (OMP_CLAUSE_DECL (l))
9583 : TYPE_SIZE_UNIT (TREE_TYPE (OMP_CLAUSE_DECL (l))));
9584 if (struct_map_to_clause == NULL)
9585 struct_map_to_clause = new hash_map<tree, tree>;
9586 struct_map_to_clause->put (decl, l);
9587 if (ptr || attach_detach)
9589 insert_struct_comp_map (code, c, l, *prev_list_p,
9590 NULL);
9591 *prev_list_p = l;
9592 prev_list_p = NULL;
9594 else
9596 OMP_CLAUSE_CHAIN (l) = c;
9597 *list_p = l;
9598 list_p = &OMP_CLAUSE_CHAIN (l);
9600 if (base_ref && code == OMP_TARGET)
9602 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9603 OMP_CLAUSE_MAP);
9604 enum gomp_map_kind mkind
9605 = GOMP_MAP_FIRSTPRIVATE_REFERENCE;
9606 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
9607 OMP_CLAUSE_DECL (c2) = decl;
9608 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9609 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
9610 OMP_CLAUSE_CHAIN (l) = c2;
9612 flags = GOVD_MAP | GOVD_EXPLICIT;
9613 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
9614 || ptr
9615 || attach_detach)
9616 flags |= GOVD_SEEN;
9617 if (has_attachments)
9618 flags |= GOVD_MAP_HAS_ATTACHMENTS;
9619 goto do_add_decl;
9621 else if (struct_map_to_clause)
9623 tree *osc = struct_map_to_clause->get (decl);
9624 tree *sc = NULL, *scp = NULL;
9625 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
9626 || ptr
9627 || attach_detach)
9628 n->value |= GOVD_SEEN;
9629 sc = &OMP_CLAUSE_CHAIN (*osc);
9630 if (*sc != c
9631 && (OMP_CLAUSE_MAP_KIND (*sc)
9632 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
9633 sc = &OMP_CLAUSE_CHAIN (*sc);
9634 /* Here "prev_list_p" is the end of the inserted
9635 alloc/release nodes after the struct node, OSC. */
9636 for (; *sc != c; sc = &OMP_CLAUSE_CHAIN (*sc))
9637 if ((ptr || attach_detach) && sc == prev_list_p)
9638 break;
9639 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9640 != COMPONENT_REF
9641 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9642 != INDIRECT_REF)
9643 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9644 != ARRAY_REF))
9645 break;
9646 else
9648 tree sc_decl = OMP_CLAUSE_DECL (*sc);
9649 poly_offset_int offsetn;
9650 poly_int64 bitposn;
9651 tree base
9652 = extract_base_bit_offset (sc_decl, NULL,
9653 &bitposn, &offsetn);
9654 if (base != decl)
9655 break;
9656 if (scp)
9657 continue;
9658 if ((region_type & ORT_ACC) != 0)
9660 /* This duplicate checking code is currently only
9661 enabled for OpenACC. */
9662 tree d1 = OMP_CLAUSE_DECL (*sc);
9663 tree d2 = OMP_CLAUSE_DECL (c);
9664 while (TREE_CODE (d1) == ARRAY_REF)
9665 d1 = TREE_OPERAND (d1, 0);
9666 while (TREE_CODE (d2) == ARRAY_REF)
9667 d2 = TREE_OPERAND (d2, 0);
9668 if (TREE_CODE (d1) == INDIRECT_REF)
9669 d1 = TREE_OPERAND (d1, 0);
9670 if (TREE_CODE (d2) == INDIRECT_REF)
9671 d2 = TREE_OPERAND (d2, 0);
9672 while (TREE_CODE (d1) == COMPONENT_REF)
9673 if (TREE_CODE (d2) == COMPONENT_REF
9674 && TREE_OPERAND (d1, 1)
9675 == TREE_OPERAND (d2, 1))
9677 d1 = TREE_OPERAND (d1, 0);
9678 d2 = TREE_OPERAND (d2, 0);
9680 else
9681 break;
9682 if (d1 == d2)
9684 error_at (OMP_CLAUSE_LOCATION (c),
9685 "%qE appears more than once in map "
9686 "clauses", OMP_CLAUSE_DECL (c));
9687 remove = true;
9688 break;
9691 if (maybe_lt (offset1, offsetn)
9692 || (known_eq (offset1, offsetn)
9693 && maybe_lt (bitpos1, bitposn)))
9695 if (ptr || attach_detach)
9696 scp = sc;
9697 else
9698 break;
9701 if (remove)
9702 break;
9703 if (!attach)
9704 OMP_CLAUSE_SIZE (*osc)
9705 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc),
9706 size_one_node);
9707 if (ptr || attach_detach)
9709 tree cl = insert_struct_comp_map (code, c, NULL,
9710 *prev_list_p, scp);
9711 if (sc == prev_list_p)
9713 *sc = cl;
9714 prev_list_p = NULL;
9716 else
9718 *prev_list_p = OMP_CLAUSE_CHAIN (c);
9719 list_p = prev_list_p;
9720 prev_list_p = NULL;
9721 OMP_CLAUSE_CHAIN (c) = *sc;
9722 *sc = cl;
9723 continue;
9726 else if (*sc != c)
9728 *list_p = OMP_CLAUSE_CHAIN (c);
9729 OMP_CLAUSE_CHAIN (c) = *sc;
9730 *sc = c;
9731 continue;
9735 else if ((code == OACC_ENTER_DATA
9736 || code == OACC_EXIT_DATA
9737 || code == OACC_DATA
9738 || code == OACC_PARALLEL
9739 || code == OACC_KERNELS
9740 || code == OACC_SERIAL)
9741 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9743 gomp_map_kind k = (code == OACC_EXIT_DATA
9744 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9745 OMP_CLAUSE_SET_MAP_KIND (c, k);
9748 if (code == OMP_TARGET && OMP_CLAUSE_MAP_IN_REDUCTION (c))
9750 /* Don't gimplify *pd fully at this point, as the base
9751 will need to be adjusted during omp lowering. */
9752 auto_vec<tree, 10> expr_stack;
9753 tree *p = pd;
9754 while (handled_component_p (*p)
9755 || TREE_CODE (*p) == INDIRECT_REF
9756 || TREE_CODE (*p) == ADDR_EXPR
9757 || TREE_CODE (*p) == MEM_REF
9758 || TREE_CODE (*p) == NON_LVALUE_EXPR)
9760 expr_stack.safe_push (*p);
9761 p = &TREE_OPERAND (*p, 0);
9763 for (int i = expr_stack.length () - 1; i >= 0; i--)
9765 tree t = expr_stack[i];
9766 if (TREE_CODE (t) == ARRAY_REF
9767 || TREE_CODE (t) == ARRAY_RANGE_REF)
9769 if (TREE_OPERAND (t, 2) == NULL_TREE)
9771 tree low = unshare_expr (array_ref_low_bound (t));
9772 if (!is_gimple_min_invariant (low))
9774 TREE_OPERAND (t, 2) = low;
9775 if (gimplify_expr (&TREE_OPERAND (t, 2),
9776 pre_p, NULL,
9777 is_gimple_reg,
9778 fb_rvalue) == GS_ERROR)
9779 remove = true;
9782 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
9783 NULL, is_gimple_reg,
9784 fb_rvalue) == GS_ERROR)
9785 remove = true;
9786 if (TREE_OPERAND (t, 3) == NULL_TREE)
9788 tree elmt_size = array_ref_element_size (t);
9789 if (!is_gimple_min_invariant (elmt_size))
9791 elmt_size = unshare_expr (elmt_size);
9792 tree elmt_type
9793 = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t,
9794 0)));
9795 tree factor
9796 = size_int (TYPE_ALIGN_UNIT (elmt_type));
9797 elmt_size
9798 = size_binop (EXACT_DIV_EXPR, elmt_size,
9799 factor);
9800 TREE_OPERAND (t, 3) = elmt_size;
9801 if (gimplify_expr (&TREE_OPERAND (t, 3),
9802 pre_p, NULL,
9803 is_gimple_reg,
9804 fb_rvalue) == GS_ERROR)
9805 remove = true;
9808 else if (gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
9809 NULL, is_gimple_reg,
9810 fb_rvalue) == GS_ERROR)
9811 remove = true;
9813 else if (TREE_CODE (t) == COMPONENT_REF)
9815 if (TREE_OPERAND (t, 2) == NULL_TREE)
9817 tree offset = component_ref_field_offset (t);
9818 if (!is_gimple_min_invariant (offset))
9820 offset = unshare_expr (offset);
9821 tree field = TREE_OPERAND (t, 1);
9822 tree factor
9823 = size_int (DECL_OFFSET_ALIGN (field)
9824 / BITS_PER_UNIT);
9825 offset = size_binop (EXACT_DIV_EXPR, offset,
9826 factor);
9827 TREE_OPERAND (t, 2) = offset;
9828 if (gimplify_expr (&TREE_OPERAND (t, 2),
9829 pre_p, NULL,
9830 is_gimple_reg,
9831 fb_rvalue) == GS_ERROR)
9832 remove = true;
9835 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
9836 NULL, is_gimple_reg,
9837 fb_rvalue) == GS_ERROR)
9838 remove = true;
9841 for (; expr_stack.length () > 0; )
9843 tree t = expr_stack.pop ();
9845 if (TREE_CODE (t) == ARRAY_REF
9846 || TREE_CODE (t) == ARRAY_RANGE_REF)
9848 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1))
9849 && gimplify_expr (&TREE_OPERAND (t, 1), pre_p,
9850 NULL, is_gimple_val,
9851 fb_rvalue) == GS_ERROR)
9852 remove = true;
9856 else if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue,
9857 fb_lvalue) == GS_ERROR)
9859 remove = true;
9860 break;
9863 if (!remove
9864 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ALWAYS_POINTER
9865 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH_DETACH
9866 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9867 && OMP_CLAUSE_CHAIN (c)
9868 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c)) == OMP_CLAUSE_MAP
9869 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9870 == GOMP_MAP_ALWAYS_POINTER)
9871 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9872 == GOMP_MAP_ATTACH_DETACH)
9873 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9874 == GOMP_MAP_TO_PSET)))
9875 prev_list_p = list_p;
9877 break;
9879 else
9881 /* DECL_P (decl) == true */
9882 tree *sc;
9883 if (struct_map_to_clause
9884 && (sc = struct_map_to_clause->get (decl)) != NULL
9885 && OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_STRUCT
9886 && decl == OMP_CLAUSE_DECL (*sc))
9888 /* We have found a map of the whole structure after a
9889 leading GOMP_MAP_STRUCT has been created, so refill the
9890 leading clause into a map of the whole structure
9891 variable, and remove the current one.
9892 TODO: we should be able to remove some maps of the
9893 following structure element maps if they are of
9894 compatible TO/FROM/ALLOC type. */
9895 OMP_CLAUSE_SET_MAP_KIND (*sc, OMP_CLAUSE_MAP_KIND (c));
9896 OMP_CLAUSE_SIZE (*sc) = unshare_expr (OMP_CLAUSE_SIZE (c));
9897 remove = true;
9898 break;
9901 flags = GOVD_MAP | GOVD_EXPLICIT;
9902 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
9903 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM)
9904 flags |= GOVD_MAP_ALWAYS_TO;
9906 if ((code == OMP_TARGET
9907 || code == OMP_TARGET_DATA
9908 || code == OMP_TARGET_ENTER_DATA
9909 || code == OMP_TARGET_EXIT_DATA)
9910 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9912 for (struct gimplify_omp_ctx *octx = outer_ctx; octx;
9913 octx = octx->outer_context)
9915 splay_tree_node n
9916 = splay_tree_lookup (octx->variables,
9917 (splay_tree_key) OMP_CLAUSE_DECL (c));
9918 /* If this is contained in an outer OpenMP region as a
9919 firstprivate value, remove the attach/detach. */
9920 if (n && (n->value & GOVD_FIRSTPRIVATE))
9922 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FIRSTPRIVATE_POINTER);
9923 goto do_add;
9927 enum gomp_map_kind map_kind = (code == OMP_TARGET_EXIT_DATA
9928 ? GOMP_MAP_DETACH
9929 : GOMP_MAP_ATTACH);
9930 OMP_CLAUSE_SET_MAP_KIND (c, map_kind);
9933 goto do_add;
9935 case OMP_CLAUSE_AFFINITY:
9936 gimplify_omp_affinity (list_p, pre_p);
9937 remove = true;
9938 break;
9939 case OMP_CLAUSE_DEPEND:
9940 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
9942 tree deps = OMP_CLAUSE_DECL (c);
9943 while (deps && TREE_CODE (deps) == TREE_LIST)
9945 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
9946 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
9947 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
9948 pre_p, NULL, is_gimple_val, fb_rvalue);
9949 deps = TREE_CHAIN (deps);
9951 break;
9953 else if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
9954 break;
9955 if (handled_depend_iterators == -1)
9956 handled_depend_iterators = gimplify_omp_depend (list_p, pre_p);
9957 if (handled_depend_iterators)
9959 if (handled_depend_iterators == 2)
9960 remove = true;
9961 break;
9963 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
9965 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
9966 NULL, is_gimple_val, fb_rvalue);
9967 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
9969 if (error_operand_p (OMP_CLAUSE_DECL (c)))
9971 remove = true;
9972 break;
9974 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
9975 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
9976 is_gimple_val, fb_rvalue) == GS_ERROR)
9978 remove = true;
9979 break;
9981 if (code == OMP_TASK)
9982 ctx->has_depend = true;
9983 break;
9985 case OMP_CLAUSE_TO:
9986 case OMP_CLAUSE_FROM:
9987 case OMP_CLAUSE__CACHE_:
9988 decl = OMP_CLAUSE_DECL (c);
9989 if (error_operand_p (decl))
9991 remove = true;
9992 break;
9994 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9995 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9996 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9997 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9998 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
10000 remove = true;
10001 break;
10003 if (!DECL_P (decl))
10005 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
10006 NULL, is_gimple_lvalue, fb_lvalue)
10007 == GS_ERROR)
10009 remove = true;
10010 break;
10012 break;
10014 goto do_notice;
10016 case OMP_CLAUSE_USE_DEVICE_PTR:
10017 case OMP_CLAUSE_USE_DEVICE_ADDR:
10018 flags = GOVD_EXPLICIT;
10019 goto do_add;
10021 case OMP_CLAUSE_IS_DEVICE_PTR:
10022 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
10023 goto do_add;
10025 do_add:
10026 decl = OMP_CLAUSE_DECL (c);
10027 do_add_decl:
10028 if (error_operand_p (decl))
10030 remove = true;
10031 break;
10033 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
10035 tree t = omp_member_access_dummy_var (decl);
10036 if (t)
10038 tree v = DECL_VALUE_EXPR (decl);
10039 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
10040 if (outer_ctx)
10041 omp_notice_variable (outer_ctx, t, true);
10044 if (code == OACC_DATA
10045 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
10046 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
10047 flags |= GOVD_MAP_0LEN_ARRAY;
10048 omp_add_variable (ctx, decl, flags);
10049 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10050 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_IN_REDUCTION
10051 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_TASK_REDUCTION)
10052 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
10054 struct gimplify_omp_ctx *pctx
10055 = code == OMP_TARGET ? outer_ctx : ctx;
10056 if (pctx)
10057 omp_add_variable (pctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
10058 GOVD_LOCAL | GOVD_SEEN);
10059 if (pctx
10060 && OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
10061 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
10062 find_decl_expr,
10063 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
10064 NULL) == NULL_TREE)
10065 omp_add_variable (pctx,
10066 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
10067 GOVD_LOCAL | GOVD_SEEN);
10068 gimplify_omp_ctxp = pctx;
10069 push_gimplify_context ();
10071 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
10072 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
10074 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
10075 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
10076 pop_gimplify_context
10077 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
10078 push_gimplify_context ();
10079 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
10080 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
10081 pop_gimplify_context
10082 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
10083 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
10084 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
10086 gimplify_omp_ctxp = outer_ctx;
10088 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10089 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
10091 gimplify_omp_ctxp = ctx;
10092 push_gimplify_context ();
10093 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
10095 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
10096 NULL, NULL);
10097 TREE_SIDE_EFFECTS (bind) = 1;
10098 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
10099 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
10101 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
10102 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
10103 pop_gimplify_context
10104 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
10105 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
10107 gimplify_omp_ctxp = outer_ctx;
10109 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
10110 && OMP_CLAUSE_LINEAR_STMT (c))
10112 gimplify_omp_ctxp = ctx;
10113 push_gimplify_context ();
10114 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
10116 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
10117 NULL, NULL);
10118 TREE_SIDE_EFFECTS (bind) = 1;
10119 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
10120 OMP_CLAUSE_LINEAR_STMT (c) = bind;
10122 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
10123 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
10124 pop_gimplify_context
10125 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
10126 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
10128 gimplify_omp_ctxp = outer_ctx;
10130 if (notice_outer)
10131 goto do_notice;
10132 break;
10134 case OMP_CLAUSE_COPYIN:
10135 case OMP_CLAUSE_COPYPRIVATE:
10136 decl = OMP_CLAUSE_DECL (c);
10137 if (error_operand_p (decl))
10139 remove = true;
10140 break;
10142 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
10143 && !remove
10144 && !omp_check_private (ctx, decl, true))
10146 remove = true;
10147 if (is_global_var (decl))
10149 if (DECL_THREAD_LOCAL_P (decl))
10150 remove = false;
10151 else if (DECL_HAS_VALUE_EXPR_P (decl))
10153 tree value = get_base_address (DECL_VALUE_EXPR (decl));
10155 if (value
10156 && DECL_P (value)
10157 && DECL_THREAD_LOCAL_P (value))
10158 remove = false;
10161 if (remove)
10162 error_at (OMP_CLAUSE_LOCATION (c),
10163 "copyprivate variable %qE is not threadprivate"
10164 " or private in outer context", DECL_NAME (decl));
10166 do_notice:
10167 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10168 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE
10169 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
10170 && outer_ctx
10171 && ((region_type & ORT_TASKLOOP) == ORT_TASKLOOP
10172 || (region_type == ORT_WORKSHARE
10173 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10174 && (OMP_CLAUSE_REDUCTION_INSCAN (c)
10175 || code == OMP_LOOP)))
10176 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
10177 || (code == OMP_LOOP
10178 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10179 && ((outer_ctx->region_type & ORT_COMBINED_TEAMS)
10180 == ORT_COMBINED_TEAMS))))
10182 splay_tree_node on
10183 = splay_tree_lookup (outer_ctx->variables,
10184 (splay_tree_key)decl);
10185 if (on == NULL || (on->value & GOVD_DATA_SHARE_CLASS) == 0)
10187 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10188 && TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
10189 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
10190 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
10191 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
10192 == POINTER_TYPE))))
10193 omp_firstprivatize_variable (outer_ctx, decl);
10194 else
10196 omp_add_variable (outer_ctx, decl,
10197 GOVD_SEEN | GOVD_SHARED);
10198 if (outer_ctx->outer_context)
10199 omp_notice_variable (outer_ctx->outer_context, decl,
10200 true);
10204 if (outer_ctx)
10205 omp_notice_variable (outer_ctx, decl, true);
10206 if (check_non_private
10207 && (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
10208 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
10209 || decl == OMP_CLAUSE_DECL (c)
10210 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
10211 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
10212 == ADDR_EXPR
10213 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
10214 == POINTER_PLUS_EXPR
10215 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
10216 (OMP_CLAUSE_DECL (c), 0), 0))
10217 == ADDR_EXPR)))))
10218 && omp_check_private (ctx, decl, false))
10220 error ("%s variable %qE is private in outer context",
10221 check_non_private, DECL_NAME (decl));
10222 remove = true;
10224 break;
10226 case OMP_CLAUSE_DETACH:
10227 flags = GOVD_FIRSTPRIVATE | GOVD_SEEN;
10228 goto do_add;
10230 case OMP_CLAUSE_IF:
10231 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
10232 && OMP_CLAUSE_IF_MODIFIER (c) != code)
10234 const char *p[2];
10235 for (int i = 0; i < 2; i++)
10236 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
10238 case VOID_CST: p[i] = "cancel"; break;
10239 case OMP_PARALLEL: p[i] = "parallel"; break;
10240 case OMP_SIMD: p[i] = "simd"; break;
10241 case OMP_TASK: p[i] = "task"; break;
10242 case OMP_TASKLOOP: p[i] = "taskloop"; break;
10243 case OMP_TARGET_DATA: p[i] = "target data"; break;
10244 case OMP_TARGET: p[i] = "target"; break;
10245 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
10246 case OMP_TARGET_ENTER_DATA:
10247 p[i] = "target enter data"; break;
10248 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
10249 default: gcc_unreachable ();
10251 error_at (OMP_CLAUSE_LOCATION (c),
10252 "expected %qs %<if%> clause modifier rather than %qs",
10253 p[0], p[1]);
10254 remove = true;
10256 /* Fall through. */
10258 case OMP_CLAUSE_FINAL:
10259 OMP_CLAUSE_OPERAND (c, 0)
10260 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
10261 /* Fall through. */
10263 case OMP_CLAUSE_SCHEDULE:
10264 case OMP_CLAUSE_NUM_THREADS:
10265 case OMP_CLAUSE_NUM_TEAMS:
10266 case OMP_CLAUSE_THREAD_LIMIT:
10267 case OMP_CLAUSE_DIST_SCHEDULE:
10268 case OMP_CLAUSE_DEVICE:
10269 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEVICE
10270 && OMP_CLAUSE_DEVICE_ANCESTOR (c))
10272 if (code != OMP_TARGET)
10274 error_at (OMP_CLAUSE_LOCATION (c),
10275 "%<device%> clause with %<ancestor%> is only "
10276 "allowed on %<target%> construct");
10277 remove = true;
10278 break;
10281 tree clauses = *orig_list_p;
10282 for (; clauses ; clauses = OMP_CLAUSE_CHAIN (clauses))
10283 if (OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEVICE
10284 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_FIRSTPRIVATE
10285 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_PRIVATE
10286 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEFAULTMAP
10287 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_MAP
10290 error_at (OMP_CLAUSE_LOCATION (c),
10291 "with %<ancestor%>, only the %<device%>, "
10292 "%<firstprivate%>, %<private%>, %<defaultmap%>, "
10293 "and %<map%> clauses may appear on the "
10294 "construct");
10295 remove = true;
10296 break;
10299 /* Fall through. */
10301 case OMP_CLAUSE_PRIORITY:
10302 case OMP_CLAUSE_GRAINSIZE:
10303 case OMP_CLAUSE_NUM_TASKS:
10304 case OMP_CLAUSE_FILTER:
10305 case OMP_CLAUSE_HINT:
10306 case OMP_CLAUSE_ASYNC:
10307 case OMP_CLAUSE_WAIT:
10308 case OMP_CLAUSE_NUM_GANGS:
10309 case OMP_CLAUSE_NUM_WORKERS:
10310 case OMP_CLAUSE_VECTOR_LENGTH:
10311 case OMP_CLAUSE_WORKER:
10312 case OMP_CLAUSE_VECTOR:
10313 if (OMP_CLAUSE_OPERAND (c, 0)
10314 && !is_gimple_min_invariant (OMP_CLAUSE_OPERAND (c, 0)))
10316 if (error_operand_p (OMP_CLAUSE_OPERAND (c, 0)))
10318 remove = true;
10319 break;
10321 /* All these clauses care about value, not a particular decl,
10322 so try to force it into a SSA_NAME or fresh temporary. */
10323 OMP_CLAUSE_OPERAND (c, 0)
10324 = get_initialized_tmp_var (OMP_CLAUSE_OPERAND (c, 0),
10325 pre_p, NULL, true);
10327 break;
10329 case OMP_CLAUSE_GANG:
10330 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
10331 is_gimple_val, fb_rvalue) == GS_ERROR)
10332 remove = true;
10333 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
10334 is_gimple_val, fb_rvalue) == GS_ERROR)
10335 remove = true;
10336 break;
10338 case OMP_CLAUSE_NOWAIT:
10339 nowait = 1;
10340 break;
10342 case OMP_CLAUSE_ORDERED:
10343 case OMP_CLAUSE_UNTIED:
10344 case OMP_CLAUSE_COLLAPSE:
10345 case OMP_CLAUSE_TILE:
10346 case OMP_CLAUSE_AUTO:
10347 case OMP_CLAUSE_SEQ:
10348 case OMP_CLAUSE_INDEPENDENT:
10349 case OMP_CLAUSE_MERGEABLE:
10350 case OMP_CLAUSE_PROC_BIND:
10351 case OMP_CLAUSE_SAFELEN:
10352 case OMP_CLAUSE_SIMDLEN:
10353 case OMP_CLAUSE_NOGROUP:
10354 case OMP_CLAUSE_THREADS:
10355 case OMP_CLAUSE_SIMD:
10356 case OMP_CLAUSE_BIND:
10357 case OMP_CLAUSE_IF_PRESENT:
10358 case OMP_CLAUSE_FINALIZE:
10359 break;
10361 case OMP_CLAUSE_ORDER:
10362 ctx->order_concurrent = true;
10363 break;
10365 case OMP_CLAUSE_DEFAULTMAP:
10366 enum gimplify_defaultmap_kind gdmkmin, gdmkmax;
10367 switch (OMP_CLAUSE_DEFAULTMAP_CATEGORY (c))
10369 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED:
10370 gdmkmin = GDMK_SCALAR;
10371 gdmkmax = GDMK_POINTER;
10372 break;
10373 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_SCALAR:
10374 gdmkmin = GDMK_SCALAR;
10375 gdmkmax = GDMK_SCALAR_TARGET;
10376 break;
10377 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_AGGREGATE:
10378 gdmkmin = gdmkmax = GDMK_AGGREGATE;
10379 break;
10380 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALLOCATABLE:
10381 gdmkmin = gdmkmax = GDMK_ALLOCATABLE;
10382 break;
10383 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_POINTER:
10384 gdmkmin = gdmkmax = GDMK_POINTER;
10385 break;
10386 default:
10387 gcc_unreachable ();
10389 for (int gdmk = gdmkmin; gdmk <= gdmkmax; gdmk++)
10390 switch (OMP_CLAUSE_DEFAULTMAP_BEHAVIOR (c))
10392 case OMP_CLAUSE_DEFAULTMAP_ALLOC:
10393 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_ALLOC_ONLY;
10394 break;
10395 case OMP_CLAUSE_DEFAULTMAP_TO:
10396 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_TO_ONLY;
10397 break;
10398 case OMP_CLAUSE_DEFAULTMAP_FROM:
10399 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FROM_ONLY;
10400 break;
10401 case OMP_CLAUSE_DEFAULTMAP_TOFROM:
10402 ctx->defaultmap[gdmk] = GOVD_MAP;
10403 break;
10404 case OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE:
10405 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
10406 break;
10407 case OMP_CLAUSE_DEFAULTMAP_NONE:
10408 ctx->defaultmap[gdmk] = 0;
10409 break;
10410 case OMP_CLAUSE_DEFAULTMAP_DEFAULT:
10411 switch (gdmk)
10413 case GDMK_SCALAR:
10414 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
10415 break;
10416 case GDMK_SCALAR_TARGET:
10417 ctx->defaultmap[gdmk] = (lang_GNU_Fortran ()
10418 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
10419 break;
10420 case GDMK_AGGREGATE:
10421 case GDMK_ALLOCATABLE:
10422 ctx->defaultmap[gdmk] = GOVD_MAP;
10423 break;
10424 case GDMK_POINTER:
10425 ctx->defaultmap[gdmk] = GOVD_MAP;
10426 if (!lang_GNU_Fortran ())
10427 ctx->defaultmap[gdmk] |= GOVD_MAP_0LEN_ARRAY;
10428 break;
10429 default:
10430 gcc_unreachable ();
10432 break;
10433 default:
10434 gcc_unreachable ();
10436 break;
10438 case OMP_CLAUSE_ALIGNED:
10439 decl = OMP_CLAUSE_DECL (c);
10440 if (error_operand_p (decl))
10442 remove = true;
10443 break;
10445 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
10446 is_gimple_val, fb_rvalue) == GS_ERROR)
10448 remove = true;
10449 break;
10451 if (!is_global_var (decl)
10452 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
10453 omp_add_variable (ctx, decl, GOVD_ALIGNED);
10454 break;
10456 case OMP_CLAUSE_NONTEMPORAL:
10457 decl = OMP_CLAUSE_DECL (c);
10458 if (error_operand_p (decl))
10460 remove = true;
10461 break;
10463 omp_add_variable (ctx, decl, GOVD_NONTEMPORAL);
10464 break;
10466 case OMP_CLAUSE_ALLOCATE:
10467 decl = OMP_CLAUSE_DECL (c);
10468 if (error_operand_p (decl))
10470 remove = true;
10471 break;
10473 if (gimplify_expr (&OMP_CLAUSE_ALLOCATE_ALLOCATOR (c), pre_p, NULL,
10474 is_gimple_val, fb_rvalue) == GS_ERROR)
10476 remove = true;
10477 break;
10479 else if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c) == NULL_TREE
10480 || (TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c))
10481 == INTEGER_CST))
10483 else if (code == OMP_TASKLOOP
10484 || !DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
10485 OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
10486 = get_initialized_tmp_var (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
10487 pre_p, NULL, false);
10488 break;
10490 case OMP_CLAUSE_DEFAULT:
10491 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
10492 break;
10494 case OMP_CLAUSE_INCLUSIVE:
10495 case OMP_CLAUSE_EXCLUSIVE:
10496 decl = OMP_CLAUSE_DECL (c);
10498 splay_tree_node n = splay_tree_lookup (outer_ctx->variables,
10499 (splay_tree_key) decl);
10500 if (n == NULL || (n->value & GOVD_REDUCTION) == 0)
10502 error_at (OMP_CLAUSE_LOCATION (c),
10503 "%qD specified in %qs clause but not in %<inscan%> "
10504 "%<reduction%> clause on the containing construct",
10505 decl, omp_clause_code_name[OMP_CLAUSE_CODE (c)]);
10506 remove = true;
10508 else
10510 n->value |= GOVD_REDUCTION_INSCAN;
10511 if (outer_ctx->region_type == ORT_SIMD
10512 && outer_ctx->outer_context
10513 && outer_ctx->outer_context->region_type == ORT_WORKSHARE)
10515 n = splay_tree_lookup (outer_ctx->outer_context->variables,
10516 (splay_tree_key) decl);
10517 if (n && (n->value & GOVD_REDUCTION) != 0)
10518 n->value |= GOVD_REDUCTION_INSCAN;
10522 break;
10524 case OMP_CLAUSE_NOHOST:
10525 default:
10526 gcc_unreachable ();
10529 if (code == OACC_DATA
10530 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
10531 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
10532 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10533 remove = true;
10534 if (remove)
10535 *list_p = OMP_CLAUSE_CHAIN (c);
10536 else
10537 list_p = &OMP_CLAUSE_CHAIN (c);
10540 ctx->clauses = *orig_list_p;
10541 gimplify_omp_ctxp = ctx;
10542 if (struct_map_to_clause)
10543 delete struct_map_to_clause;
10544 if (struct_deref_set)
10545 delete struct_deref_set;
10548 /* Return true if DECL is a candidate for shared to firstprivate
10549 optimization. We only consider non-addressable scalars, not
10550 too big, and not references. */
10552 static bool
10553 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
10555 if (TREE_ADDRESSABLE (decl))
10556 return false;
10557 tree type = TREE_TYPE (decl);
10558 if (!is_gimple_reg_type (type)
10559 || TREE_CODE (type) == REFERENCE_TYPE
10560 || TREE_ADDRESSABLE (type))
10561 return false;
10562 /* Don't optimize too large decls, as each thread/task will have
10563 its own. */
10564 HOST_WIDE_INT len = int_size_in_bytes (type);
10565 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
10566 return false;
10567 if (omp_privatize_by_reference (decl))
10568 return false;
10569 return true;
10572 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
10573 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
10574 GOVD_WRITTEN in outer contexts. */
10576 static void
10577 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
10579 for (; ctx; ctx = ctx->outer_context)
10581 splay_tree_node n = splay_tree_lookup (ctx->variables,
10582 (splay_tree_key) decl);
10583 if (n == NULL)
10584 continue;
10585 else if (n->value & GOVD_SHARED)
10587 n->value |= GOVD_WRITTEN;
10588 return;
10590 else if (n->value & GOVD_DATA_SHARE_CLASS)
10591 return;
10595 /* Helper callback for walk_gimple_seq to discover possible stores
10596 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
10597 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
10598 for those. */
10600 static tree
10601 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
10603 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
10605 *walk_subtrees = 0;
10606 if (!wi->is_lhs)
10607 return NULL_TREE;
10609 tree op = *tp;
10612 if (handled_component_p (op))
10613 op = TREE_OPERAND (op, 0);
10614 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
10615 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
10616 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
10617 else
10618 break;
10620 while (1);
10621 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
10622 return NULL_TREE;
10624 omp_mark_stores (gimplify_omp_ctxp, op);
10625 return NULL_TREE;
10628 /* Helper callback for walk_gimple_seq to discover possible stores
10629 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
10630 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
10631 for those. */
10633 static tree
10634 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
10635 bool *handled_ops_p,
10636 struct walk_stmt_info *wi)
10638 gimple *stmt = gsi_stmt (*gsi_p);
10639 switch (gimple_code (stmt))
10641 /* Don't recurse on OpenMP constructs for which
10642 gimplify_adjust_omp_clauses already handled the bodies,
10643 except handle gimple_omp_for_pre_body. */
10644 case GIMPLE_OMP_FOR:
10645 *handled_ops_p = true;
10646 if (gimple_omp_for_pre_body (stmt))
10647 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
10648 omp_find_stores_stmt, omp_find_stores_op, wi);
10649 break;
10650 case GIMPLE_OMP_PARALLEL:
10651 case GIMPLE_OMP_TASK:
10652 case GIMPLE_OMP_SECTIONS:
10653 case GIMPLE_OMP_SINGLE:
10654 case GIMPLE_OMP_SCOPE:
10655 case GIMPLE_OMP_TARGET:
10656 case GIMPLE_OMP_TEAMS:
10657 case GIMPLE_OMP_CRITICAL:
10658 *handled_ops_p = true;
10659 break;
10660 default:
10661 break;
10663 return NULL_TREE;
10666 struct gimplify_adjust_omp_clauses_data
10668 tree *list_p;
10669 gimple_seq *pre_p;
10672 /* For all variables that were not actually used within the context,
10673 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
10675 static int
10676 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
10678 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
10679 gimple_seq *pre_p
10680 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
10681 tree decl = (tree) n->key;
10682 unsigned flags = n->value;
10683 enum omp_clause_code code;
10684 tree clause;
10685 bool private_debug;
10687 if (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
10688 && (flags & GOVD_LASTPRIVATE_CONDITIONAL) != 0)
10689 flags = GOVD_SHARED | GOVD_SEEN | GOVD_WRITTEN;
10690 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
10691 return 0;
10692 if ((flags & GOVD_SEEN) == 0)
10693 return 0;
10694 if ((flags & GOVD_MAP_HAS_ATTACHMENTS) != 0)
10695 return 0;
10696 if (flags & GOVD_DEBUG_PRIVATE)
10698 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_SHARED);
10699 private_debug = true;
10701 else if (flags & GOVD_MAP)
10702 private_debug = false;
10703 else
10704 private_debug
10705 = lang_hooks.decls.omp_private_debug_clause (decl,
10706 !!(flags & GOVD_SHARED));
10707 if (private_debug)
10708 code = OMP_CLAUSE_PRIVATE;
10709 else if (flags & GOVD_MAP)
10711 code = OMP_CLAUSE_MAP;
10712 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
10713 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
10715 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
10716 return 0;
10718 if (VAR_P (decl)
10719 && DECL_IN_CONSTANT_POOL (decl)
10720 && !lookup_attribute ("omp declare target",
10721 DECL_ATTRIBUTES (decl)))
10723 tree id = get_identifier ("omp declare target");
10724 DECL_ATTRIBUTES (decl)
10725 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (decl));
10726 varpool_node *node = varpool_node::get (decl);
10727 if (node)
10729 node->offloadable = 1;
10730 if (ENABLE_OFFLOADING)
10731 g->have_offload = true;
10735 else if (flags & GOVD_SHARED)
10737 if (is_global_var (decl))
10739 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
10740 while (ctx != NULL)
10742 splay_tree_node on
10743 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10744 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
10745 | GOVD_PRIVATE | GOVD_REDUCTION
10746 | GOVD_LINEAR | GOVD_MAP)) != 0)
10747 break;
10748 ctx = ctx->outer_context;
10750 if (ctx == NULL)
10751 return 0;
10753 code = OMP_CLAUSE_SHARED;
10754 /* Don't optimize shared into firstprivate for read-only vars
10755 on tasks with depend clause, we shouldn't try to copy them
10756 until the dependencies are satisfied. */
10757 if (gimplify_omp_ctxp->has_depend)
10758 flags |= GOVD_WRITTEN;
10760 else if (flags & GOVD_PRIVATE)
10761 code = OMP_CLAUSE_PRIVATE;
10762 else if (flags & GOVD_FIRSTPRIVATE)
10764 code = OMP_CLAUSE_FIRSTPRIVATE;
10765 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
10766 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
10767 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
10769 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
10770 "%<target%> construct", decl);
10771 return 0;
10774 else if (flags & GOVD_LASTPRIVATE)
10775 code = OMP_CLAUSE_LASTPRIVATE;
10776 else if (flags & (GOVD_ALIGNED | GOVD_NONTEMPORAL))
10777 return 0;
10778 else if (flags & GOVD_CONDTEMP)
10780 code = OMP_CLAUSE__CONDTEMP_;
10781 gimple_add_tmp_var (decl);
10783 else
10784 gcc_unreachable ();
10786 if (((flags & GOVD_LASTPRIVATE)
10787 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
10788 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10789 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10791 tree chain = *list_p;
10792 clause = build_omp_clause (input_location, code);
10793 OMP_CLAUSE_DECL (clause) = decl;
10794 OMP_CLAUSE_CHAIN (clause) = chain;
10795 if (private_debug)
10796 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
10797 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
10798 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
10799 else if (code == OMP_CLAUSE_SHARED
10800 && (flags & GOVD_WRITTEN) == 0
10801 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10802 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
10803 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
10804 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
10805 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
10807 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
10808 OMP_CLAUSE_DECL (nc) = decl;
10809 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
10810 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
10811 OMP_CLAUSE_DECL (clause)
10812 = build_simple_mem_ref_loc (input_location, decl);
10813 OMP_CLAUSE_DECL (clause)
10814 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
10815 build_int_cst (build_pointer_type (char_type_node), 0));
10816 OMP_CLAUSE_SIZE (clause) = size_zero_node;
10817 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10818 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
10819 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
10820 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
10821 OMP_CLAUSE_CHAIN (nc) = chain;
10822 OMP_CLAUSE_CHAIN (clause) = nc;
10823 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10824 gimplify_omp_ctxp = ctx->outer_context;
10825 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
10826 pre_p, NULL, is_gimple_val, fb_rvalue);
10827 gimplify_omp_ctxp = ctx;
10829 else if (code == OMP_CLAUSE_MAP)
10831 int kind;
10832 /* Not all combinations of these GOVD_MAP flags are actually valid. */
10833 switch (flags & (GOVD_MAP_TO_ONLY
10834 | GOVD_MAP_FORCE
10835 | GOVD_MAP_FORCE_PRESENT
10836 | GOVD_MAP_ALLOC_ONLY
10837 | GOVD_MAP_FROM_ONLY))
10839 case 0:
10840 kind = GOMP_MAP_TOFROM;
10841 break;
10842 case GOVD_MAP_FORCE:
10843 kind = GOMP_MAP_TOFROM | GOMP_MAP_FLAG_FORCE;
10844 break;
10845 case GOVD_MAP_TO_ONLY:
10846 kind = GOMP_MAP_TO;
10847 break;
10848 case GOVD_MAP_FROM_ONLY:
10849 kind = GOMP_MAP_FROM;
10850 break;
10851 case GOVD_MAP_ALLOC_ONLY:
10852 kind = GOMP_MAP_ALLOC;
10853 break;
10854 case GOVD_MAP_TO_ONLY | GOVD_MAP_FORCE:
10855 kind = GOMP_MAP_TO | GOMP_MAP_FLAG_FORCE;
10856 break;
10857 case GOVD_MAP_FORCE_PRESENT:
10858 kind = GOMP_MAP_FORCE_PRESENT;
10859 break;
10860 default:
10861 gcc_unreachable ();
10863 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
10864 if (DECL_SIZE (decl)
10865 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
10867 tree decl2 = DECL_VALUE_EXPR (decl);
10868 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
10869 decl2 = TREE_OPERAND (decl2, 0);
10870 gcc_assert (DECL_P (decl2));
10871 tree mem = build_simple_mem_ref (decl2);
10872 OMP_CLAUSE_DECL (clause) = mem;
10873 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
10874 if (gimplify_omp_ctxp->outer_context)
10876 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
10877 omp_notice_variable (ctx, decl2, true);
10878 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
10880 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
10881 OMP_CLAUSE_MAP);
10882 OMP_CLAUSE_DECL (nc) = decl;
10883 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10884 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
10885 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
10886 else
10887 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
10888 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
10889 OMP_CLAUSE_CHAIN (clause) = nc;
10891 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
10892 && omp_privatize_by_reference (decl))
10894 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
10895 OMP_CLAUSE_SIZE (clause)
10896 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
10897 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10898 gimplify_omp_ctxp = ctx->outer_context;
10899 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
10900 pre_p, NULL, is_gimple_val, fb_rvalue);
10901 gimplify_omp_ctxp = ctx;
10902 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
10903 OMP_CLAUSE_MAP);
10904 OMP_CLAUSE_DECL (nc) = decl;
10905 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10906 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
10907 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
10908 OMP_CLAUSE_CHAIN (clause) = nc;
10910 else
10911 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
10913 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
10915 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
10916 OMP_CLAUSE_DECL (nc) = decl;
10917 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
10918 OMP_CLAUSE_CHAIN (nc) = chain;
10919 OMP_CLAUSE_CHAIN (clause) = nc;
10920 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10921 gimplify_omp_ctxp = ctx->outer_context;
10922 lang_hooks.decls.omp_finish_clause (nc, pre_p,
10923 (ctx->region_type & ORT_ACC) != 0);
10924 gimplify_omp_ctxp = ctx;
10926 *list_p = clause;
10927 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10928 gimplify_omp_ctxp = ctx->outer_context;
10929 /* Don't call omp_finish_clause on implicitly added OMP_CLAUSE_PRIVATE
10930 in simd. Those are only added for the local vars inside of simd body
10931 and they don't need to be e.g. default constructible. */
10932 if (code != OMP_CLAUSE_PRIVATE || ctx->region_type != ORT_SIMD)
10933 lang_hooks.decls.omp_finish_clause (clause, pre_p,
10934 (ctx->region_type & ORT_ACC) != 0);
10935 if (gimplify_omp_ctxp)
10936 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
10937 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
10938 && DECL_P (OMP_CLAUSE_SIZE (clause)))
10939 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
10940 true);
10941 gimplify_omp_ctxp = ctx;
10942 return 0;
10945 static void
10946 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
10947 enum tree_code code)
10949 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10950 tree *orig_list_p = list_p;
10951 tree c, decl;
10952 bool has_inscan_reductions = false;
10954 if (body)
10956 struct gimplify_omp_ctx *octx;
10957 for (octx = ctx; octx; octx = octx->outer_context)
10958 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
10959 break;
10960 if (octx)
10962 struct walk_stmt_info wi;
10963 memset (&wi, 0, sizeof (wi));
10964 walk_gimple_seq (body, omp_find_stores_stmt,
10965 omp_find_stores_op, &wi);
10969 if (ctx->add_safelen1)
10971 /* If there are VLAs in the body of simd loop, prevent
10972 vectorization. */
10973 gcc_assert (ctx->region_type == ORT_SIMD);
10974 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_SAFELEN);
10975 OMP_CLAUSE_SAFELEN_EXPR (c) = integer_one_node;
10976 OMP_CLAUSE_CHAIN (c) = *list_p;
10977 *list_p = c;
10978 list_p = &OMP_CLAUSE_CHAIN (c);
10981 if (ctx->region_type == ORT_WORKSHARE
10982 && ctx->outer_context
10983 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL)
10985 for (c = ctx->outer_context->clauses; c; c = OMP_CLAUSE_CHAIN (c))
10986 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10987 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
10989 decl = OMP_CLAUSE_DECL (c);
10990 splay_tree_node n
10991 = splay_tree_lookup (ctx->outer_context->variables,
10992 (splay_tree_key) decl);
10993 gcc_checking_assert (!splay_tree_lookup (ctx->variables,
10994 (splay_tree_key) decl));
10995 omp_add_variable (ctx, decl, n->value);
10996 tree c2 = copy_node (c);
10997 OMP_CLAUSE_CHAIN (c2) = *list_p;
10998 *list_p = c2;
10999 if ((n->value & GOVD_FIRSTPRIVATE) == 0)
11000 continue;
11001 c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
11002 OMP_CLAUSE_FIRSTPRIVATE);
11003 OMP_CLAUSE_DECL (c2) = decl;
11004 OMP_CLAUSE_CHAIN (c2) = *list_p;
11005 *list_p = c2;
11008 while ((c = *list_p) != NULL)
11010 splay_tree_node n;
11011 bool remove = false;
11013 switch (OMP_CLAUSE_CODE (c))
11015 case OMP_CLAUSE_FIRSTPRIVATE:
11016 if ((ctx->region_type & ORT_TARGET)
11017 && (ctx->region_type & ORT_ACC) == 0
11018 && TYPE_ATOMIC (strip_array_types
11019 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
11021 error_at (OMP_CLAUSE_LOCATION (c),
11022 "%<_Atomic%> %qD in %<firstprivate%> clause on "
11023 "%<target%> construct", OMP_CLAUSE_DECL (c));
11024 remove = true;
11025 break;
11027 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
11029 decl = OMP_CLAUSE_DECL (c);
11030 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11031 if ((n->value & GOVD_MAP) != 0)
11033 remove = true;
11034 break;
11036 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT_TARGET (c) = 0;
11037 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c) = 0;
11039 /* FALLTHRU */
11040 case OMP_CLAUSE_PRIVATE:
11041 case OMP_CLAUSE_SHARED:
11042 case OMP_CLAUSE_LINEAR:
11043 decl = OMP_CLAUSE_DECL (c);
11044 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11045 remove = !(n->value & GOVD_SEEN);
11046 if ((n->value & GOVD_LASTPRIVATE_CONDITIONAL) != 0
11047 && code == OMP_PARALLEL
11048 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE)
11049 remove = true;
11050 if (! remove)
11052 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
11053 if ((n->value & GOVD_DEBUG_PRIVATE)
11054 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
11056 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
11057 || ((n->value & GOVD_DATA_SHARE_CLASS)
11058 == GOVD_SHARED));
11059 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
11060 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
11062 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11063 && ctx->has_depend
11064 && DECL_P (decl))
11065 n->value |= GOVD_WRITTEN;
11066 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11067 && (n->value & GOVD_WRITTEN) == 0
11068 && DECL_P (decl)
11069 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11070 OMP_CLAUSE_SHARED_READONLY (c) = 1;
11071 else if (DECL_P (decl)
11072 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11073 && (n->value & GOVD_WRITTEN) != 0)
11074 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11075 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
11076 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11077 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11079 else
11080 n->value &= ~GOVD_EXPLICIT;
11081 break;
11083 case OMP_CLAUSE_LASTPRIVATE:
11084 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
11085 accurately reflect the presence of a FIRSTPRIVATE clause. */
11086 decl = OMP_CLAUSE_DECL (c);
11087 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11088 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
11089 = (n->value & GOVD_FIRSTPRIVATE) != 0;
11090 if (code == OMP_DISTRIBUTE
11091 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
11093 remove = true;
11094 error_at (OMP_CLAUSE_LOCATION (c),
11095 "same variable used in %<firstprivate%> and "
11096 "%<lastprivate%> clauses on %<distribute%> "
11097 "construct");
11099 if (!remove
11100 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
11101 && DECL_P (decl)
11102 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11103 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11104 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) && code == OMP_PARALLEL)
11105 remove = true;
11106 break;
11108 case OMP_CLAUSE_ALIGNED:
11109 decl = OMP_CLAUSE_DECL (c);
11110 if (!is_global_var (decl))
11112 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11113 remove = n == NULL || !(n->value & GOVD_SEEN);
11114 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
11116 struct gimplify_omp_ctx *octx;
11117 if (n != NULL
11118 && (n->value & (GOVD_DATA_SHARE_CLASS
11119 & ~GOVD_FIRSTPRIVATE)))
11120 remove = true;
11121 else
11122 for (octx = ctx->outer_context; octx;
11123 octx = octx->outer_context)
11125 n = splay_tree_lookup (octx->variables,
11126 (splay_tree_key) decl);
11127 if (n == NULL)
11128 continue;
11129 if (n->value & GOVD_LOCAL)
11130 break;
11131 /* We have to avoid assigning a shared variable
11132 to itself when trying to add
11133 __builtin_assume_aligned. */
11134 if (n->value & GOVD_SHARED)
11136 remove = true;
11137 break;
11142 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
11144 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11145 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
11146 remove = true;
11148 break;
11150 case OMP_CLAUSE_NONTEMPORAL:
11151 decl = OMP_CLAUSE_DECL (c);
11152 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11153 remove = n == NULL || !(n->value & GOVD_SEEN);
11154 break;
11156 case OMP_CLAUSE_MAP:
11157 if (code == OMP_TARGET_EXIT_DATA
11158 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
11160 remove = true;
11161 break;
11163 decl = OMP_CLAUSE_DECL (c);
11164 /* Data clauses associated with reductions must be
11165 compatible with present_or_copy. Warn and adjust the clause
11166 if that is not the case. */
11167 if (ctx->region_type == ORT_ACC_PARALLEL
11168 || ctx->region_type == ORT_ACC_SERIAL)
11170 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
11171 n = NULL;
11173 if (DECL_P (t))
11174 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
11176 if (n && (n->value & GOVD_REDUCTION))
11178 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
11180 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
11181 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
11182 && kind != GOMP_MAP_FORCE_PRESENT
11183 && kind != GOMP_MAP_POINTER)
11185 warning_at (OMP_CLAUSE_LOCATION (c), 0,
11186 "incompatible data clause with reduction "
11187 "on %qE; promoting to %<present_or_copy%>",
11188 DECL_NAME (t));
11189 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
11193 if (!DECL_P (decl))
11195 if ((ctx->region_type & ORT_TARGET) != 0
11196 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
11198 if (TREE_CODE (decl) == INDIRECT_REF
11199 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
11200 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
11201 == REFERENCE_TYPE))
11202 decl = TREE_OPERAND (decl, 0);
11203 if (TREE_CODE (decl) == COMPONENT_REF)
11205 while (TREE_CODE (decl) == COMPONENT_REF)
11206 decl = TREE_OPERAND (decl, 0);
11207 if (DECL_P (decl))
11209 n = splay_tree_lookup (ctx->variables,
11210 (splay_tree_key) decl);
11211 if (!(n->value & GOVD_SEEN))
11212 remove = true;
11216 break;
11218 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11219 if ((ctx->region_type & ORT_TARGET) != 0
11220 && !(n->value & GOVD_SEEN)
11221 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
11222 && (!is_global_var (decl)
11223 || !lookup_attribute ("omp declare target link",
11224 DECL_ATTRIBUTES (decl))))
11226 remove = true;
11227 /* For struct element mapping, if struct is never referenced
11228 in target block and none of the mapping has always modifier,
11229 remove all the struct element mappings, which immediately
11230 follow the GOMP_MAP_STRUCT map clause. */
11231 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
11233 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
11234 while (cnt--)
11235 OMP_CLAUSE_CHAIN (c)
11236 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
11239 else if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
11240 && (code == OMP_TARGET_EXIT_DATA
11241 || code == OACC_EXIT_DATA))
11242 remove = true;
11243 else if (DECL_SIZE (decl)
11244 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
11245 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
11246 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
11247 && (OMP_CLAUSE_MAP_KIND (c)
11248 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
11250 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
11251 for these, TREE_CODE (DECL_SIZE (decl)) will always be
11252 INTEGER_CST. */
11253 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
11255 tree decl2 = DECL_VALUE_EXPR (decl);
11256 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
11257 decl2 = TREE_OPERAND (decl2, 0);
11258 gcc_assert (DECL_P (decl2));
11259 tree mem = build_simple_mem_ref (decl2);
11260 OMP_CLAUSE_DECL (c) = mem;
11261 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
11262 if (ctx->outer_context)
11264 omp_notice_variable (ctx->outer_context, decl2, true);
11265 omp_notice_variable (ctx->outer_context,
11266 OMP_CLAUSE_SIZE (c), true);
11268 if (((ctx->region_type & ORT_TARGET) != 0
11269 || !ctx->target_firstprivatize_array_bases)
11270 && ((n->value & GOVD_SEEN) == 0
11271 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
11273 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
11274 OMP_CLAUSE_MAP);
11275 OMP_CLAUSE_DECL (nc) = decl;
11276 OMP_CLAUSE_SIZE (nc) = size_zero_node;
11277 if (ctx->target_firstprivatize_array_bases)
11278 OMP_CLAUSE_SET_MAP_KIND (nc,
11279 GOMP_MAP_FIRSTPRIVATE_POINTER);
11280 else
11281 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
11282 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
11283 OMP_CLAUSE_CHAIN (c) = nc;
11284 c = nc;
11287 else
11289 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
11290 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
11291 gcc_assert ((n->value & GOVD_SEEN) == 0
11292 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
11293 == 0));
11295 break;
11297 case OMP_CLAUSE_TO:
11298 case OMP_CLAUSE_FROM:
11299 case OMP_CLAUSE__CACHE_:
11300 decl = OMP_CLAUSE_DECL (c);
11301 if (!DECL_P (decl))
11302 break;
11303 if (DECL_SIZE (decl)
11304 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
11306 tree decl2 = DECL_VALUE_EXPR (decl);
11307 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
11308 decl2 = TREE_OPERAND (decl2, 0);
11309 gcc_assert (DECL_P (decl2));
11310 tree mem = build_simple_mem_ref (decl2);
11311 OMP_CLAUSE_DECL (c) = mem;
11312 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
11313 if (ctx->outer_context)
11315 omp_notice_variable (ctx->outer_context, decl2, true);
11316 omp_notice_variable (ctx->outer_context,
11317 OMP_CLAUSE_SIZE (c), true);
11320 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
11321 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
11322 break;
11324 case OMP_CLAUSE_REDUCTION:
11325 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
11327 decl = OMP_CLAUSE_DECL (c);
11328 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11329 if ((n->value & GOVD_REDUCTION_INSCAN) == 0)
11331 remove = true;
11332 error_at (OMP_CLAUSE_LOCATION (c),
11333 "%qD specified in %<inscan%> %<reduction%> clause "
11334 "but not in %<scan%> directive clause", decl);
11335 break;
11337 has_inscan_reductions = true;
11339 /* FALLTHRU */
11340 case OMP_CLAUSE_IN_REDUCTION:
11341 case OMP_CLAUSE_TASK_REDUCTION:
11342 decl = OMP_CLAUSE_DECL (c);
11343 /* OpenACC reductions need a present_or_copy data clause.
11344 Add one if necessary. Emit error when the reduction is private. */
11345 if (ctx->region_type == ORT_ACC_PARALLEL
11346 || ctx->region_type == ORT_ACC_SERIAL)
11348 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11349 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
11351 remove = true;
11352 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
11353 "reduction on %qE", DECL_NAME (decl));
11355 else if ((n->value & GOVD_MAP) == 0)
11357 tree next = OMP_CLAUSE_CHAIN (c);
11358 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
11359 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
11360 OMP_CLAUSE_DECL (nc) = decl;
11361 OMP_CLAUSE_CHAIN (c) = nc;
11362 lang_hooks.decls.omp_finish_clause (nc, pre_p,
11363 (ctx->region_type
11364 & ORT_ACC) != 0);
11365 while (1)
11367 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
11368 if (OMP_CLAUSE_CHAIN (nc) == NULL)
11369 break;
11370 nc = OMP_CLAUSE_CHAIN (nc);
11372 OMP_CLAUSE_CHAIN (nc) = next;
11373 n->value |= GOVD_MAP;
11376 if (DECL_P (decl)
11377 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11378 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11379 break;
11381 case OMP_CLAUSE_ALLOCATE:
11382 decl = OMP_CLAUSE_DECL (c);
11383 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11384 if (n != NULL && !(n->value & GOVD_SEEN))
11386 if ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE | GOVD_LINEAR))
11387 != 0
11388 && (n->value & (GOVD_REDUCTION | GOVD_LASTPRIVATE)) == 0)
11389 remove = true;
11391 if (!remove
11392 && OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
11393 && TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)) != INTEGER_CST
11394 && ((ctx->region_type & (ORT_PARALLEL | ORT_TARGET)) != 0
11395 || (ctx->region_type & ORT_TASKLOOP) == ORT_TASK
11396 || (ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS))
11398 tree allocator = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
11399 n = splay_tree_lookup (ctx->variables, (splay_tree_key) allocator);
11400 if (n == NULL)
11402 enum omp_clause_default_kind default_kind
11403 = ctx->default_kind;
11404 ctx->default_kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
11405 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
11406 true);
11407 ctx->default_kind = default_kind;
11409 else
11410 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
11411 true);
11413 break;
11415 case OMP_CLAUSE_COPYIN:
11416 case OMP_CLAUSE_COPYPRIVATE:
11417 case OMP_CLAUSE_IF:
11418 case OMP_CLAUSE_NUM_THREADS:
11419 case OMP_CLAUSE_NUM_TEAMS:
11420 case OMP_CLAUSE_THREAD_LIMIT:
11421 case OMP_CLAUSE_DIST_SCHEDULE:
11422 case OMP_CLAUSE_DEVICE:
11423 case OMP_CLAUSE_SCHEDULE:
11424 case OMP_CLAUSE_NOWAIT:
11425 case OMP_CLAUSE_ORDERED:
11426 case OMP_CLAUSE_DEFAULT:
11427 case OMP_CLAUSE_UNTIED:
11428 case OMP_CLAUSE_COLLAPSE:
11429 case OMP_CLAUSE_FINAL:
11430 case OMP_CLAUSE_MERGEABLE:
11431 case OMP_CLAUSE_PROC_BIND:
11432 case OMP_CLAUSE_SAFELEN:
11433 case OMP_CLAUSE_SIMDLEN:
11434 case OMP_CLAUSE_DEPEND:
11435 case OMP_CLAUSE_PRIORITY:
11436 case OMP_CLAUSE_GRAINSIZE:
11437 case OMP_CLAUSE_NUM_TASKS:
11438 case OMP_CLAUSE_NOGROUP:
11439 case OMP_CLAUSE_THREADS:
11440 case OMP_CLAUSE_SIMD:
11441 case OMP_CLAUSE_FILTER:
11442 case OMP_CLAUSE_HINT:
11443 case OMP_CLAUSE_DEFAULTMAP:
11444 case OMP_CLAUSE_ORDER:
11445 case OMP_CLAUSE_BIND:
11446 case OMP_CLAUSE_DETACH:
11447 case OMP_CLAUSE_USE_DEVICE_PTR:
11448 case OMP_CLAUSE_USE_DEVICE_ADDR:
11449 case OMP_CLAUSE_IS_DEVICE_PTR:
11450 case OMP_CLAUSE_ASYNC:
11451 case OMP_CLAUSE_WAIT:
11452 case OMP_CLAUSE_INDEPENDENT:
11453 case OMP_CLAUSE_NUM_GANGS:
11454 case OMP_CLAUSE_NUM_WORKERS:
11455 case OMP_CLAUSE_VECTOR_LENGTH:
11456 case OMP_CLAUSE_GANG:
11457 case OMP_CLAUSE_WORKER:
11458 case OMP_CLAUSE_VECTOR:
11459 case OMP_CLAUSE_AUTO:
11460 case OMP_CLAUSE_SEQ:
11461 case OMP_CLAUSE_TILE:
11462 case OMP_CLAUSE_IF_PRESENT:
11463 case OMP_CLAUSE_FINALIZE:
11464 case OMP_CLAUSE_INCLUSIVE:
11465 case OMP_CLAUSE_EXCLUSIVE:
11466 break;
11468 case OMP_CLAUSE_NOHOST:
11469 default:
11470 gcc_unreachable ();
11473 if (remove)
11474 *list_p = OMP_CLAUSE_CHAIN (c);
11475 else
11476 list_p = &OMP_CLAUSE_CHAIN (c);
11479 /* Add in any implicit data sharing. */
11480 struct gimplify_adjust_omp_clauses_data data;
11481 data.list_p = list_p;
11482 data.pre_p = pre_p;
11483 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
11485 if (has_inscan_reductions)
11486 for (c = *orig_list_p; c; c = OMP_CLAUSE_CHAIN (c))
11487 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11488 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
11490 error_at (OMP_CLAUSE_LOCATION (c),
11491 "%<inscan%> %<reduction%> clause used together with "
11492 "%<linear%> clause for a variable other than loop "
11493 "iterator");
11494 break;
11497 gimplify_omp_ctxp = ctx->outer_context;
11498 delete_omp_context (ctx);
11501 /* Return 0 if CONSTRUCTS selectors don't match the OpenMP context,
11502 -1 if unknown yet (simd is involved, won't be known until vectorization)
11503 and 1 if they do. If SCORES is non-NULL, it should point to an array
11504 of at least 2*NCONSTRUCTS+2 ints, and will be filled with the positions
11505 of the CONSTRUCTS (position -1 if it will never match) followed by
11506 number of constructs in the OpenMP context construct trait. If the
11507 score depends on whether it will be in a declare simd clone or not,
11508 the function returns 2 and there will be two sets of the scores, the first
11509 one for the case that it is not in a declare simd clone, the other
11510 that it is in a declare simd clone. */
11513 omp_construct_selector_matches (enum tree_code *constructs, int nconstructs,
11514 int *scores)
11516 int matched = 0, cnt = 0;
11517 bool simd_seen = false;
11518 bool target_seen = false;
11519 int declare_simd_cnt = -1;
11520 auto_vec<enum tree_code, 16> codes;
11521 for (struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp; ctx;)
11523 if (((ctx->region_type & ORT_PARALLEL) && ctx->code == OMP_PARALLEL)
11524 || ((ctx->region_type & (ORT_TARGET | ORT_IMPLICIT_TARGET | ORT_ACC))
11525 == ORT_TARGET && ctx->code == OMP_TARGET)
11526 || ((ctx->region_type & ORT_TEAMS) && ctx->code == OMP_TEAMS)
11527 || (ctx->region_type == ORT_WORKSHARE && ctx->code == OMP_FOR)
11528 || (ctx->region_type == ORT_SIMD
11529 && ctx->code == OMP_SIMD
11530 && !omp_find_clause (ctx->clauses, OMP_CLAUSE_BIND)))
11532 ++cnt;
11533 if (scores)
11534 codes.safe_push (ctx->code);
11535 else if (matched < nconstructs && ctx->code == constructs[matched])
11537 if (ctx->code == OMP_SIMD)
11539 if (matched)
11540 return 0;
11541 simd_seen = true;
11543 ++matched;
11545 if (ctx->code == OMP_TARGET)
11547 if (scores == NULL)
11548 return matched < nconstructs ? 0 : simd_seen ? -1 : 1;
11549 target_seen = true;
11550 break;
11553 else if (ctx->region_type == ORT_WORKSHARE
11554 && ctx->code == OMP_LOOP
11555 && ctx->outer_context
11556 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL
11557 && ctx->outer_context->outer_context
11558 && ctx->outer_context->outer_context->code == OMP_LOOP
11559 && ctx->outer_context->outer_context->distribute)
11560 ctx = ctx->outer_context->outer_context;
11561 ctx = ctx->outer_context;
11563 if (!target_seen
11564 && lookup_attribute ("omp declare simd",
11565 DECL_ATTRIBUTES (current_function_decl)))
11567 /* Declare simd is a maybe case, it is supposed to be added only to the
11568 omp-simd-clone.c added clones and not to the base function. */
11569 declare_simd_cnt = cnt++;
11570 if (scores)
11571 codes.safe_push (OMP_SIMD);
11572 else if (cnt == 0
11573 && constructs[0] == OMP_SIMD)
11575 gcc_assert (matched == 0);
11576 simd_seen = true;
11577 if (++matched == nconstructs)
11578 return -1;
11581 if (tree attr = lookup_attribute ("omp declare variant variant",
11582 DECL_ATTRIBUTES (current_function_decl)))
11584 enum tree_code variant_constructs[5];
11585 int variant_nconstructs = 0;
11586 if (!target_seen)
11587 variant_nconstructs
11588 = omp_constructor_traits_to_codes (TREE_VALUE (attr),
11589 variant_constructs);
11590 for (int i = 0; i < variant_nconstructs; i++)
11592 ++cnt;
11593 if (scores)
11594 codes.safe_push (variant_constructs[i]);
11595 else if (matched < nconstructs
11596 && variant_constructs[i] == constructs[matched])
11598 if (variant_constructs[i] == OMP_SIMD)
11600 if (matched)
11601 return 0;
11602 simd_seen = true;
11604 ++matched;
11608 if (!target_seen
11609 && lookup_attribute ("omp declare target block",
11610 DECL_ATTRIBUTES (current_function_decl)))
11612 if (scores)
11613 codes.safe_push (OMP_TARGET);
11614 else if (matched < nconstructs && constructs[matched] == OMP_TARGET)
11615 ++matched;
11617 if (scores)
11619 for (int pass = 0; pass < (declare_simd_cnt == -1 ? 1 : 2); pass++)
11621 int j = codes.length () - 1;
11622 for (int i = nconstructs - 1; i >= 0; i--)
11624 while (j >= 0
11625 && (pass != 0 || declare_simd_cnt != j)
11626 && constructs[i] != codes[j])
11627 --j;
11628 if (pass == 0 && declare_simd_cnt != -1 && j > declare_simd_cnt)
11629 *scores++ = j - 1;
11630 else
11631 *scores++ = j;
11633 *scores++ = ((pass == 0 && declare_simd_cnt != -1)
11634 ? codes.length () - 1 : codes.length ());
11636 return declare_simd_cnt == -1 ? 1 : 2;
11638 if (matched == nconstructs)
11639 return simd_seen ? -1 : 1;
11640 return 0;
11643 /* Gimplify OACC_CACHE. */
11645 static void
11646 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
11648 tree expr = *expr_p;
11650 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
11651 OACC_CACHE);
11652 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
11653 OACC_CACHE);
11655 /* TODO: Do something sensible with this information. */
11657 *expr_p = NULL_TREE;
11660 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
11661 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
11662 kind. The entry kind will replace the one in CLAUSE, while the exit
11663 kind will be used in a new omp_clause and returned to the caller. */
11665 static tree
11666 gimplify_oacc_declare_1 (tree clause)
11668 HOST_WIDE_INT kind, new_op;
11669 bool ret = false;
11670 tree c = NULL;
11672 kind = OMP_CLAUSE_MAP_KIND (clause);
11674 switch (kind)
11676 case GOMP_MAP_ALLOC:
11677 new_op = GOMP_MAP_RELEASE;
11678 ret = true;
11679 break;
11681 case GOMP_MAP_FROM:
11682 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
11683 new_op = GOMP_MAP_FROM;
11684 ret = true;
11685 break;
11687 case GOMP_MAP_TOFROM:
11688 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
11689 new_op = GOMP_MAP_FROM;
11690 ret = true;
11691 break;
11693 case GOMP_MAP_DEVICE_RESIDENT:
11694 case GOMP_MAP_FORCE_DEVICEPTR:
11695 case GOMP_MAP_FORCE_PRESENT:
11696 case GOMP_MAP_LINK:
11697 case GOMP_MAP_POINTER:
11698 case GOMP_MAP_TO:
11699 break;
11701 default:
11702 gcc_unreachable ();
11703 break;
11706 if (ret)
11708 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
11709 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
11710 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
11713 return c;
11716 /* Gimplify OACC_DECLARE. */
11718 static void
11719 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
11721 tree expr = *expr_p;
11722 gomp_target *stmt;
11723 tree clauses, t, decl;
11725 clauses = OACC_DECLARE_CLAUSES (expr);
11727 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
11728 gimplify_adjust_omp_clauses (pre_p, NULL, &clauses, OACC_DECLARE);
11730 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
11732 decl = OMP_CLAUSE_DECL (t);
11734 if (TREE_CODE (decl) == MEM_REF)
11735 decl = TREE_OPERAND (decl, 0);
11737 if (VAR_P (decl) && !is_oacc_declared (decl))
11739 tree attr = get_identifier ("oacc declare target");
11740 DECL_ATTRIBUTES (decl) = tree_cons (attr, NULL_TREE,
11741 DECL_ATTRIBUTES (decl));
11744 if (VAR_P (decl)
11745 && !is_global_var (decl)
11746 && DECL_CONTEXT (decl) == current_function_decl)
11748 tree c = gimplify_oacc_declare_1 (t);
11749 if (c)
11751 if (oacc_declare_returns == NULL)
11752 oacc_declare_returns = new hash_map<tree, tree>;
11754 oacc_declare_returns->put (decl, c);
11758 if (gimplify_omp_ctxp)
11759 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
11762 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
11763 clauses);
11765 gimplify_seq_add_stmt (pre_p, stmt);
11767 *expr_p = NULL_TREE;
11770 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
11771 gimplification of the body, as well as scanning the body for used
11772 variables. We need to do this scan now, because variable-sized
11773 decls will be decomposed during gimplification. */
11775 static void
11776 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
11778 tree expr = *expr_p;
11779 gimple *g;
11780 gimple_seq body = NULL;
11782 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
11783 OMP_PARALLEL_COMBINED (expr)
11784 ? ORT_COMBINED_PARALLEL
11785 : ORT_PARALLEL, OMP_PARALLEL);
11787 push_gimplify_context ();
11789 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
11790 if (gimple_code (g) == GIMPLE_BIND)
11791 pop_gimplify_context (g);
11792 else
11793 pop_gimplify_context (NULL);
11795 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
11796 OMP_PARALLEL);
11798 g = gimple_build_omp_parallel (body,
11799 OMP_PARALLEL_CLAUSES (expr),
11800 NULL_TREE, NULL_TREE);
11801 if (OMP_PARALLEL_COMBINED (expr))
11802 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
11803 gimplify_seq_add_stmt (pre_p, g);
11804 *expr_p = NULL_TREE;
11807 /* Gimplify the contents of an OMP_TASK statement. This involves
11808 gimplification of the body, as well as scanning the body for used
11809 variables. We need to do this scan now, because variable-sized
11810 decls will be decomposed during gimplification. */
11812 static void
11813 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
11815 tree expr = *expr_p;
11816 gimple *g;
11817 gimple_seq body = NULL;
11819 if (OMP_TASK_BODY (expr) == NULL_TREE)
11820 for (tree c = OMP_TASK_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
11821 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
11822 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_MUTEXINOUTSET)
11824 error_at (OMP_CLAUSE_LOCATION (c),
11825 "%<mutexinoutset%> kind in %<depend%> clause on a "
11826 "%<taskwait%> construct");
11827 break;
11830 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
11831 omp_find_clause (OMP_TASK_CLAUSES (expr),
11832 OMP_CLAUSE_UNTIED)
11833 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
11835 if (OMP_TASK_BODY (expr))
11837 push_gimplify_context ();
11839 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
11840 if (gimple_code (g) == GIMPLE_BIND)
11841 pop_gimplify_context (g);
11842 else
11843 pop_gimplify_context (NULL);
11846 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
11847 OMP_TASK);
11849 g = gimple_build_omp_task (body,
11850 OMP_TASK_CLAUSES (expr),
11851 NULL_TREE, NULL_TREE,
11852 NULL_TREE, NULL_TREE, NULL_TREE);
11853 if (OMP_TASK_BODY (expr) == NULL_TREE)
11854 gimple_omp_task_set_taskwait_p (g, true);
11855 gimplify_seq_add_stmt (pre_p, g);
11856 *expr_p = NULL_TREE;
11859 /* Helper function for gimplify_omp_for. If *TP is not a gimple constant,
11860 force it into a temporary initialized in PRE_P and add firstprivate clause
11861 to ORIG_FOR_STMT. */
11863 static void
11864 gimplify_omp_taskloop_expr (tree type, tree *tp, gimple_seq *pre_p,
11865 tree orig_for_stmt)
11867 if (*tp == NULL || is_gimple_constant (*tp))
11868 return;
11870 *tp = get_initialized_tmp_var (*tp, pre_p, NULL, false);
11871 /* Reference to pointer conversion is considered useless,
11872 but is significant for firstprivate clause. Force it
11873 here. */
11874 if (type
11875 && TREE_CODE (type) == POINTER_TYPE
11876 && TREE_CODE (TREE_TYPE (*tp)) == REFERENCE_TYPE)
11878 tree v = create_tmp_var (TYPE_MAIN_VARIANT (type));
11879 tree m = build2 (INIT_EXPR, TREE_TYPE (v), v, *tp);
11880 gimplify_and_add (m, pre_p);
11881 *tp = v;
11884 tree c = build_omp_clause (input_location, OMP_CLAUSE_FIRSTPRIVATE);
11885 OMP_CLAUSE_DECL (c) = *tp;
11886 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
11887 OMP_FOR_CLAUSES (orig_for_stmt) = c;
11890 /* Gimplify the gross structure of an OMP_FOR statement. */
11892 static enum gimplify_status
11893 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
11895 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
11896 enum gimplify_status ret = GS_ALL_DONE;
11897 enum gimplify_status tret;
11898 gomp_for *gfor;
11899 gimple_seq for_body, for_pre_body;
11900 int i;
11901 bitmap has_decl_expr = NULL;
11902 enum omp_region_type ort = ORT_WORKSHARE;
11903 bool openacc = TREE_CODE (*expr_p) == OACC_LOOP;
11905 orig_for_stmt = for_stmt = *expr_p;
11907 bool loop_p = (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_BIND)
11908 != NULL_TREE);
11909 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
11911 tree *data[4] = { NULL, NULL, NULL, NULL };
11912 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
11913 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
11914 find_combined_omp_for, data, NULL);
11915 if (inner_for_stmt == NULL_TREE)
11917 gcc_assert (seen_error ());
11918 *expr_p = NULL_TREE;
11919 return GS_ERROR;
11921 if (data[2] && OMP_FOR_PRE_BODY (*data[2]))
11923 append_to_statement_list_force (OMP_FOR_PRE_BODY (*data[2]),
11924 &OMP_FOR_PRE_BODY (for_stmt));
11925 OMP_FOR_PRE_BODY (*data[2]) = NULL_TREE;
11927 if (OMP_FOR_PRE_BODY (inner_for_stmt))
11929 append_to_statement_list_force (OMP_FOR_PRE_BODY (inner_for_stmt),
11930 &OMP_FOR_PRE_BODY (for_stmt));
11931 OMP_FOR_PRE_BODY (inner_for_stmt) = NULL_TREE;
11934 if (data[0])
11936 /* We have some statements or variable declarations in between
11937 the composite construct directives. Move them around the
11938 inner_for_stmt. */
11939 data[0] = expr_p;
11940 for (i = 0; i < 3; i++)
11941 if (data[i])
11943 tree t = *data[i];
11944 if (i < 2 && data[i + 1] == &OMP_BODY (t))
11945 data[i + 1] = data[i];
11946 *data[i] = OMP_BODY (t);
11947 tree body = build3 (BIND_EXPR, void_type_node, NULL_TREE,
11948 NULL_TREE, make_node (BLOCK));
11949 OMP_BODY (t) = body;
11950 append_to_statement_list_force (inner_for_stmt,
11951 &BIND_EXPR_BODY (body));
11952 *data[3] = t;
11953 data[3] = tsi_stmt_ptr (tsi_start (BIND_EXPR_BODY (body)));
11954 gcc_assert (*data[3] == inner_for_stmt);
11956 return GS_OK;
11959 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
11960 if (!loop_p
11961 && OMP_FOR_ORIG_DECLS (inner_for_stmt)
11962 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11963 i)) == TREE_LIST
11964 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11965 i)))
11967 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
11968 /* Class iterators aren't allowed on OMP_SIMD, so the only
11969 case we need to solve is distribute parallel for. They are
11970 allowed on the loop construct, but that is already handled
11971 in gimplify_omp_loop. */
11972 gcc_assert (TREE_CODE (inner_for_stmt) == OMP_FOR
11973 && TREE_CODE (for_stmt) == OMP_DISTRIBUTE
11974 && data[1]);
11975 tree orig_decl = TREE_PURPOSE (orig);
11976 tree last = TREE_VALUE (orig);
11977 tree *pc;
11978 for (pc = &OMP_FOR_CLAUSES (inner_for_stmt);
11979 *pc; pc = &OMP_CLAUSE_CHAIN (*pc))
11980 if ((OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE
11981 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LASTPRIVATE)
11982 && OMP_CLAUSE_DECL (*pc) == orig_decl)
11983 break;
11984 if (*pc == NULL_TREE)
11986 tree *spc;
11987 for (spc = &OMP_PARALLEL_CLAUSES (*data[1]);
11988 *spc; spc = &OMP_CLAUSE_CHAIN (*spc))
11989 if (OMP_CLAUSE_CODE (*spc) == OMP_CLAUSE_PRIVATE
11990 && OMP_CLAUSE_DECL (*spc) == orig_decl)
11991 break;
11992 if (*spc)
11994 tree c = *spc;
11995 *spc = OMP_CLAUSE_CHAIN (c);
11996 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
11997 *pc = c;
12000 if (*pc == NULL_TREE)
12002 else if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE)
12004 /* private clause will appear only on inner_for_stmt.
12005 Change it into firstprivate, and add private clause
12006 on for_stmt. */
12007 tree c = copy_node (*pc);
12008 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12009 OMP_FOR_CLAUSES (for_stmt) = c;
12010 OMP_CLAUSE_CODE (*pc) = OMP_CLAUSE_FIRSTPRIVATE;
12011 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
12013 else
12015 /* lastprivate clause will appear on both inner_for_stmt
12016 and for_stmt. Add firstprivate clause to
12017 inner_for_stmt. */
12018 tree c = build_omp_clause (OMP_CLAUSE_LOCATION (*pc),
12019 OMP_CLAUSE_FIRSTPRIVATE);
12020 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (*pc);
12021 OMP_CLAUSE_CHAIN (c) = *pc;
12022 *pc = c;
12023 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
12025 tree c = build_omp_clause (UNKNOWN_LOCATION,
12026 OMP_CLAUSE_FIRSTPRIVATE);
12027 OMP_CLAUSE_DECL (c) = last;
12028 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12029 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12030 c = build_omp_clause (UNKNOWN_LOCATION,
12031 *pc ? OMP_CLAUSE_SHARED
12032 : OMP_CLAUSE_FIRSTPRIVATE);
12033 OMP_CLAUSE_DECL (c) = orig_decl;
12034 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12035 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12037 /* Similarly, take care of C++ range for temporaries, those should
12038 be firstprivate on OMP_PARALLEL if any. */
12039 if (data[1])
12040 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
12041 if (OMP_FOR_ORIG_DECLS (inner_for_stmt)
12042 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
12043 i)) == TREE_LIST
12044 && TREE_CHAIN (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
12045 i)))
12047 tree orig
12048 = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
12049 tree v = TREE_CHAIN (orig);
12050 tree c = build_omp_clause (UNKNOWN_LOCATION,
12051 OMP_CLAUSE_FIRSTPRIVATE);
12052 /* First add firstprivate clause for the __for_end artificial
12053 decl. */
12054 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 1);
12055 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
12056 == REFERENCE_TYPE)
12057 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
12058 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12059 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12060 if (TREE_VEC_ELT (v, 0))
12062 /* And now the same for __for_range artificial decl if it
12063 exists. */
12064 c = build_omp_clause (UNKNOWN_LOCATION,
12065 OMP_CLAUSE_FIRSTPRIVATE);
12066 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 0);
12067 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
12068 == REFERENCE_TYPE)
12069 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
12070 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12071 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12076 switch (TREE_CODE (for_stmt))
12078 case OMP_FOR:
12079 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
12081 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12082 OMP_CLAUSE_SCHEDULE))
12083 error_at (EXPR_LOCATION (for_stmt),
12084 "%qs clause may not appear on non-rectangular %qs",
12085 "schedule", "for");
12086 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED))
12087 error_at (EXPR_LOCATION (for_stmt),
12088 "%qs clause may not appear on non-rectangular %qs",
12089 "ordered", "for");
12091 break;
12092 case OMP_DISTRIBUTE:
12093 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt)
12094 && omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12095 OMP_CLAUSE_DIST_SCHEDULE))
12096 error_at (EXPR_LOCATION (for_stmt),
12097 "%qs clause may not appear on non-rectangular %qs",
12098 "dist_schedule", "distribute");
12099 break;
12100 case OACC_LOOP:
12101 ort = ORT_ACC;
12102 break;
12103 case OMP_TASKLOOP:
12104 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
12105 ort = ORT_UNTIED_TASKLOOP;
12106 else
12107 ort = ORT_TASKLOOP;
12108 break;
12109 case OMP_SIMD:
12110 ort = ORT_SIMD;
12111 break;
12112 default:
12113 gcc_unreachable ();
12116 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
12117 clause for the IV. */
12118 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
12120 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
12121 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12122 decl = TREE_OPERAND (t, 0);
12123 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
12124 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12125 && OMP_CLAUSE_DECL (c) == decl)
12127 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
12128 break;
12132 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
12133 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
12134 loop_p && TREE_CODE (for_stmt) != OMP_SIMD
12135 ? OMP_LOOP : TREE_CODE (for_stmt));
12137 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
12138 gimplify_omp_ctxp->distribute = true;
12140 /* Handle OMP_FOR_INIT. */
12141 for_pre_body = NULL;
12142 if ((ort == ORT_SIMD
12143 || (inner_for_stmt && TREE_CODE (inner_for_stmt) == OMP_SIMD))
12144 && OMP_FOR_PRE_BODY (for_stmt))
12146 has_decl_expr = BITMAP_ALLOC (NULL);
12147 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
12148 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
12149 == VAR_DECL)
12151 t = OMP_FOR_PRE_BODY (for_stmt);
12152 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
12154 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
12156 tree_stmt_iterator si;
12157 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
12158 tsi_next (&si))
12160 t = tsi_stmt (si);
12161 if (TREE_CODE (t) == DECL_EXPR
12162 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
12163 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
12167 if (OMP_FOR_PRE_BODY (for_stmt))
12169 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
12170 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
12171 else
12173 struct gimplify_omp_ctx ctx;
12174 memset (&ctx, 0, sizeof (ctx));
12175 ctx.region_type = ORT_NONE;
12176 gimplify_omp_ctxp = &ctx;
12177 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
12178 gimplify_omp_ctxp = NULL;
12181 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
12183 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
12184 for_stmt = inner_for_stmt;
12186 /* For taskloop, need to gimplify the start, end and step before the
12187 taskloop, outside of the taskloop omp context. */
12188 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12190 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12192 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12193 gimple_seq *for_pre_p = (gimple_seq_empty_p (for_pre_body)
12194 ? pre_p : &for_pre_body);
12195 tree type = TREE_TYPE (TREE_OPERAND (t, 0));
12196 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12198 tree v = TREE_OPERAND (t, 1);
12199 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
12200 for_pre_p, orig_for_stmt);
12201 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
12202 for_pre_p, orig_for_stmt);
12204 else
12205 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
12206 orig_for_stmt);
12208 /* Handle OMP_FOR_COND. */
12209 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12210 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12212 tree v = TREE_OPERAND (t, 1);
12213 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
12214 for_pre_p, orig_for_stmt);
12215 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
12216 for_pre_p, orig_for_stmt);
12218 else
12219 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
12220 orig_for_stmt);
12222 /* Handle OMP_FOR_INCR. */
12223 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12224 if (TREE_CODE (t) == MODIFY_EXPR)
12226 decl = TREE_OPERAND (t, 0);
12227 t = TREE_OPERAND (t, 1);
12228 tree *tp = &TREE_OPERAND (t, 1);
12229 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
12230 tp = &TREE_OPERAND (t, 0);
12232 gimplify_omp_taskloop_expr (NULL_TREE, tp, for_pre_p,
12233 orig_for_stmt);
12237 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
12238 OMP_TASKLOOP);
12241 if (orig_for_stmt != for_stmt)
12242 gimplify_omp_ctxp->combined_loop = true;
12244 for_body = NULL;
12245 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12246 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
12247 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12248 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
12250 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
12251 bool is_doacross = false;
12252 if (c && OMP_CLAUSE_ORDERED_EXPR (c))
12254 is_doacross = true;
12255 gimplify_omp_ctxp->loop_iter_var.create (TREE_VEC_LENGTH
12256 (OMP_FOR_INIT (for_stmt))
12257 * 2);
12259 int collapse = 1, tile = 0;
12260 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
12261 if (c)
12262 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
12263 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_TILE);
12264 if (c)
12265 tile = list_length (OMP_CLAUSE_TILE_LIST (c));
12266 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ALLOCATE);
12267 hash_set<tree> *allocate_uids = NULL;
12268 if (c)
12270 allocate_uids = new hash_set<tree>;
12271 for (; c; c = OMP_CLAUSE_CHAIN (c))
12272 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_ALLOCATE)
12273 allocate_uids->add (OMP_CLAUSE_DECL (c));
12275 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12277 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12278 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12279 decl = TREE_OPERAND (t, 0);
12280 gcc_assert (DECL_P (decl));
12281 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
12282 || POINTER_TYPE_P (TREE_TYPE (decl)));
12283 if (is_doacross)
12285 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
12287 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12288 if (TREE_CODE (orig_decl) == TREE_LIST)
12290 orig_decl = TREE_PURPOSE (orig_decl);
12291 if (!orig_decl)
12292 orig_decl = decl;
12294 gimplify_omp_ctxp->loop_iter_var.quick_push (orig_decl);
12296 else
12297 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
12298 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
12301 /* Make sure the iteration variable is private. */
12302 tree c = NULL_TREE;
12303 tree c2 = NULL_TREE;
12304 if (orig_for_stmt != for_stmt)
12306 /* Preserve this information until we gimplify the inner simd. */
12307 if (has_decl_expr
12308 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
12309 TREE_PRIVATE (t) = 1;
12311 else if (ort == ORT_SIMD)
12313 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
12314 (splay_tree_key) decl);
12315 omp_is_private (gimplify_omp_ctxp, decl,
12316 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12317 != 1));
12318 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
12320 omp_notice_variable (gimplify_omp_ctxp, decl, true);
12321 if (n->value & GOVD_LASTPRIVATE_CONDITIONAL)
12322 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12323 OMP_CLAUSE_LASTPRIVATE);
12324 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
12325 OMP_CLAUSE_LASTPRIVATE))
12326 if (OMP_CLAUSE_DECL (c3) == decl)
12328 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
12329 "conditional %<lastprivate%> on loop "
12330 "iterator %qD ignored", decl);
12331 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
12332 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
12335 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1 && !loop_p)
12337 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
12338 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
12339 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
12340 if ((has_decl_expr
12341 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
12342 || TREE_PRIVATE (t))
12344 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12345 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12347 struct gimplify_omp_ctx *outer
12348 = gimplify_omp_ctxp->outer_context;
12349 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12351 if (outer->region_type == ORT_WORKSHARE
12352 && outer->combined_loop)
12354 n = splay_tree_lookup (outer->variables,
12355 (splay_tree_key)decl);
12356 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
12358 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12359 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12361 else
12363 struct gimplify_omp_ctx *octx = outer->outer_context;
12364 if (octx
12365 && octx->region_type == ORT_COMBINED_PARALLEL
12366 && octx->outer_context
12367 && (octx->outer_context->region_type
12368 == ORT_WORKSHARE)
12369 && octx->outer_context->combined_loop)
12371 octx = octx->outer_context;
12372 n = splay_tree_lookup (octx->variables,
12373 (splay_tree_key)decl);
12374 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
12376 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12377 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12384 OMP_CLAUSE_DECL (c) = decl;
12385 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12386 OMP_FOR_CLAUSES (for_stmt) = c;
12387 omp_add_variable (gimplify_omp_ctxp, decl, flags);
12388 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12389 omp_lastprivate_for_combined_outer_constructs (outer, decl,
12390 true);
12392 else
12394 bool lastprivate
12395 = (!has_decl_expr
12396 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
12397 if (TREE_PRIVATE (t))
12398 lastprivate = false;
12399 if (loop_p && OMP_FOR_ORIG_DECLS (for_stmt))
12401 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12402 if (TREE_CODE (elt) == TREE_LIST && TREE_PURPOSE (elt))
12403 lastprivate = false;
12406 struct gimplify_omp_ctx *outer
12407 = gimplify_omp_ctxp->outer_context;
12408 if (outer && lastprivate)
12409 omp_lastprivate_for_combined_outer_constructs (outer, decl,
12410 true);
12412 c = build_omp_clause (input_location,
12413 lastprivate ? OMP_CLAUSE_LASTPRIVATE
12414 : OMP_CLAUSE_PRIVATE);
12415 OMP_CLAUSE_DECL (c) = decl;
12416 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12417 OMP_FOR_CLAUSES (for_stmt) = c;
12418 omp_add_variable (gimplify_omp_ctxp, decl,
12419 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
12420 | GOVD_EXPLICIT | GOVD_SEEN);
12421 c = NULL_TREE;
12424 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
12426 omp_notice_variable (gimplify_omp_ctxp, decl, true);
12427 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
12428 (splay_tree_key) decl);
12429 if (n && (n->value & GOVD_LASTPRIVATE_CONDITIONAL))
12430 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12431 OMP_CLAUSE_LASTPRIVATE);
12432 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
12433 OMP_CLAUSE_LASTPRIVATE))
12434 if (OMP_CLAUSE_DECL (c3) == decl)
12436 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
12437 "conditional %<lastprivate%> on loop "
12438 "iterator %qD ignored", decl);
12439 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
12440 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
12443 else
12444 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
12446 /* If DECL is not a gimple register, create a temporary variable to act
12447 as an iteration counter. This is valid, since DECL cannot be
12448 modified in the body of the loop. Similarly for any iteration vars
12449 in simd with collapse > 1 where the iterator vars must be
12450 lastprivate. And similarly for vars mentioned in allocate clauses. */
12451 if (orig_for_stmt != for_stmt)
12452 var = decl;
12453 else if (!is_gimple_reg (decl)
12454 || (ort == ORT_SIMD
12455 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
12456 || (allocate_uids && allocate_uids->contains (decl)))
12458 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12459 /* Make sure omp_add_variable is not called on it prematurely.
12460 We call it ourselves a few lines later. */
12461 gimplify_omp_ctxp = NULL;
12462 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
12463 gimplify_omp_ctxp = ctx;
12464 TREE_OPERAND (t, 0) = var;
12466 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
12468 if (ort == ORT_SIMD
12469 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
12471 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
12472 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
12473 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
12474 OMP_CLAUSE_DECL (c2) = var;
12475 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
12476 OMP_FOR_CLAUSES (for_stmt) = c2;
12477 omp_add_variable (gimplify_omp_ctxp, var,
12478 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
12479 if (c == NULL_TREE)
12481 c = c2;
12482 c2 = NULL_TREE;
12485 else
12486 omp_add_variable (gimplify_omp_ctxp, var,
12487 GOVD_PRIVATE | GOVD_SEEN);
12489 else
12490 var = decl;
12492 gimplify_omp_ctxp->in_for_exprs = true;
12493 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12495 tree lb = TREE_OPERAND (t, 1);
12496 tret = gimplify_expr (&TREE_VEC_ELT (lb, 1), &for_pre_body, NULL,
12497 is_gimple_val, fb_rvalue, false);
12498 ret = MIN (ret, tret);
12499 tret = gimplify_expr (&TREE_VEC_ELT (lb, 2), &for_pre_body, NULL,
12500 is_gimple_val, fb_rvalue, false);
12502 else
12503 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12504 is_gimple_val, fb_rvalue, false);
12505 gimplify_omp_ctxp->in_for_exprs = false;
12506 ret = MIN (ret, tret);
12507 if (ret == GS_ERROR)
12508 return ret;
12510 /* Handle OMP_FOR_COND. */
12511 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12512 gcc_assert (COMPARISON_CLASS_P (t));
12513 gcc_assert (TREE_OPERAND (t, 0) == decl);
12515 gimplify_omp_ctxp->in_for_exprs = true;
12516 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12518 tree ub = TREE_OPERAND (t, 1);
12519 tret = gimplify_expr (&TREE_VEC_ELT (ub, 1), &for_pre_body, NULL,
12520 is_gimple_val, fb_rvalue, false);
12521 ret = MIN (ret, tret);
12522 tret = gimplify_expr (&TREE_VEC_ELT (ub, 2), &for_pre_body, NULL,
12523 is_gimple_val, fb_rvalue, false);
12525 else
12526 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12527 is_gimple_val, fb_rvalue, false);
12528 gimplify_omp_ctxp->in_for_exprs = false;
12529 ret = MIN (ret, tret);
12531 /* Handle OMP_FOR_INCR. */
12532 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12533 switch (TREE_CODE (t))
12535 case PREINCREMENT_EXPR:
12536 case POSTINCREMENT_EXPR:
12538 tree decl = TREE_OPERAND (t, 0);
12539 /* c_omp_for_incr_canonicalize_ptr() should have been
12540 called to massage things appropriately. */
12541 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
12543 if (orig_for_stmt != for_stmt)
12544 break;
12545 t = build_int_cst (TREE_TYPE (decl), 1);
12546 if (c)
12547 OMP_CLAUSE_LINEAR_STEP (c) = t;
12548 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
12549 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
12550 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
12551 break;
12554 case PREDECREMENT_EXPR:
12555 case POSTDECREMENT_EXPR:
12556 /* c_omp_for_incr_canonicalize_ptr() should have been
12557 called to massage things appropriately. */
12558 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
12559 if (orig_for_stmt != for_stmt)
12560 break;
12561 t = build_int_cst (TREE_TYPE (decl), -1);
12562 if (c)
12563 OMP_CLAUSE_LINEAR_STEP (c) = t;
12564 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
12565 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
12566 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
12567 break;
12569 case MODIFY_EXPR:
12570 gcc_assert (TREE_OPERAND (t, 0) == decl);
12571 TREE_OPERAND (t, 0) = var;
12573 t = TREE_OPERAND (t, 1);
12574 switch (TREE_CODE (t))
12576 case PLUS_EXPR:
12577 if (TREE_OPERAND (t, 1) == decl)
12579 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
12580 TREE_OPERAND (t, 0) = var;
12581 break;
12584 /* Fallthru. */
12585 case MINUS_EXPR:
12586 case POINTER_PLUS_EXPR:
12587 gcc_assert (TREE_OPERAND (t, 0) == decl);
12588 TREE_OPERAND (t, 0) = var;
12589 break;
12590 default:
12591 gcc_unreachable ();
12594 gimplify_omp_ctxp->in_for_exprs = true;
12595 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12596 is_gimple_val, fb_rvalue, false);
12597 ret = MIN (ret, tret);
12598 if (c)
12600 tree step = TREE_OPERAND (t, 1);
12601 tree stept = TREE_TYPE (decl);
12602 if (POINTER_TYPE_P (stept))
12603 stept = sizetype;
12604 step = fold_convert (stept, step);
12605 if (TREE_CODE (t) == MINUS_EXPR)
12606 step = fold_build1 (NEGATE_EXPR, stept, step);
12607 OMP_CLAUSE_LINEAR_STEP (c) = step;
12608 if (step != TREE_OPERAND (t, 1))
12610 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
12611 &for_pre_body, NULL,
12612 is_gimple_val, fb_rvalue, false);
12613 ret = MIN (ret, tret);
12616 gimplify_omp_ctxp->in_for_exprs = false;
12617 break;
12619 default:
12620 gcc_unreachable ();
12623 if (c2)
12625 gcc_assert (c);
12626 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
12629 if ((var != decl || collapse > 1 || tile) && orig_for_stmt == for_stmt)
12631 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
12632 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12633 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
12634 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12635 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
12636 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
12637 && OMP_CLAUSE_DECL (c) == decl)
12639 if (is_doacross && (collapse == 1 || i >= collapse))
12640 t = var;
12641 else
12643 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12644 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12645 gcc_assert (TREE_OPERAND (t, 0) == var);
12646 t = TREE_OPERAND (t, 1);
12647 gcc_assert (TREE_CODE (t) == PLUS_EXPR
12648 || TREE_CODE (t) == MINUS_EXPR
12649 || TREE_CODE (t) == POINTER_PLUS_EXPR);
12650 gcc_assert (TREE_OPERAND (t, 0) == var);
12651 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
12652 is_doacross ? var : decl,
12653 TREE_OPERAND (t, 1));
12655 gimple_seq *seq;
12656 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
12657 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
12658 else
12659 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
12660 push_gimplify_context ();
12661 gimplify_assign (decl, t, seq);
12662 gimple *bind = NULL;
12663 if (gimplify_ctxp->temps)
12665 bind = gimple_build_bind (NULL_TREE, *seq, NULL_TREE);
12666 *seq = NULL;
12667 gimplify_seq_add_stmt (seq, bind);
12669 pop_gimplify_context (bind);
12672 if (OMP_FOR_NON_RECTANGULAR (for_stmt) && var != decl)
12673 for (int j = i + 1; j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
12675 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
12676 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12677 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12678 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12679 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12680 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
12681 gcc_assert (COMPARISON_CLASS_P (t));
12682 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12683 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12684 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12688 BITMAP_FREE (has_decl_expr);
12689 delete allocate_uids;
12691 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
12692 || (loop_p && orig_for_stmt == for_stmt))
12694 push_gimplify_context ();
12695 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
12697 OMP_FOR_BODY (orig_for_stmt)
12698 = build3 (BIND_EXPR, void_type_node, NULL,
12699 OMP_FOR_BODY (orig_for_stmt), NULL);
12700 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
12704 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
12705 &for_body);
12707 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
12708 || (loop_p && orig_for_stmt == for_stmt))
12710 if (gimple_code (g) == GIMPLE_BIND)
12711 pop_gimplify_context (g);
12712 else
12713 pop_gimplify_context (NULL);
12716 if (orig_for_stmt != for_stmt)
12717 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12719 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12720 decl = TREE_OPERAND (t, 0);
12721 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12722 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12723 gimplify_omp_ctxp = ctx->outer_context;
12724 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
12725 gimplify_omp_ctxp = ctx;
12726 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
12727 TREE_OPERAND (t, 0) = var;
12728 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12729 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12730 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
12731 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
12732 for (int j = i + 1;
12733 j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
12735 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
12736 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12737 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12738 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12740 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12741 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12743 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
12744 gcc_assert (COMPARISON_CLASS_P (t));
12745 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12746 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12748 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12749 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12754 gimplify_adjust_omp_clauses (pre_p, for_body,
12755 &OMP_FOR_CLAUSES (orig_for_stmt),
12756 TREE_CODE (orig_for_stmt));
12758 int kind;
12759 switch (TREE_CODE (orig_for_stmt))
12761 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
12762 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
12763 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
12764 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
12765 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
12766 default:
12767 gcc_unreachable ();
12769 if (loop_p && kind == GF_OMP_FOR_KIND_SIMD)
12771 gimplify_seq_add_seq (pre_p, for_pre_body);
12772 for_pre_body = NULL;
12774 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
12775 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
12776 for_pre_body);
12777 if (orig_for_stmt != for_stmt)
12778 gimple_omp_for_set_combined_p (gfor, true);
12779 if (gimplify_omp_ctxp
12780 && (gimplify_omp_ctxp->combined_loop
12781 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
12782 && gimplify_omp_ctxp->outer_context
12783 && gimplify_omp_ctxp->outer_context->combined_loop)))
12785 gimple_omp_for_set_combined_into_p (gfor, true);
12786 if (gimplify_omp_ctxp->combined_loop)
12787 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
12788 else
12789 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
12792 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12794 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12795 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
12796 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
12797 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12798 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
12799 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
12800 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12801 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
12804 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
12805 constructs with GIMPLE_OMP_TASK sandwiched in between them.
12806 The outer taskloop stands for computing the number of iterations,
12807 counts for collapsed loops and holding taskloop specific clauses.
12808 The task construct stands for the effect of data sharing on the
12809 explicit task it creates and the inner taskloop stands for expansion
12810 of the static loop inside of the explicit task construct. */
12811 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12813 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
12814 tree task_clauses = NULL_TREE;
12815 tree c = *gfor_clauses_ptr;
12816 tree *gtask_clauses_ptr = &task_clauses;
12817 tree outer_for_clauses = NULL_TREE;
12818 tree *gforo_clauses_ptr = &outer_for_clauses;
12819 bitmap lastprivate_uids = NULL;
12820 if (omp_find_clause (c, OMP_CLAUSE_ALLOCATE))
12822 c = omp_find_clause (c, OMP_CLAUSE_LASTPRIVATE);
12823 if (c)
12825 lastprivate_uids = BITMAP_ALLOC (NULL);
12826 for (; c; c = omp_find_clause (OMP_CLAUSE_CHAIN (c),
12827 OMP_CLAUSE_LASTPRIVATE))
12828 bitmap_set_bit (lastprivate_uids,
12829 DECL_UID (OMP_CLAUSE_DECL (c)));
12831 c = *gfor_clauses_ptr;
12833 for (; c; c = OMP_CLAUSE_CHAIN (c))
12834 switch (OMP_CLAUSE_CODE (c))
12836 /* These clauses are allowed on task, move them there. */
12837 case OMP_CLAUSE_SHARED:
12838 case OMP_CLAUSE_FIRSTPRIVATE:
12839 case OMP_CLAUSE_DEFAULT:
12840 case OMP_CLAUSE_IF:
12841 case OMP_CLAUSE_UNTIED:
12842 case OMP_CLAUSE_FINAL:
12843 case OMP_CLAUSE_MERGEABLE:
12844 case OMP_CLAUSE_PRIORITY:
12845 case OMP_CLAUSE_REDUCTION:
12846 case OMP_CLAUSE_IN_REDUCTION:
12847 *gtask_clauses_ptr = c;
12848 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12849 break;
12850 case OMP_CLAUSE_PRIVATE:
12851 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
12853 /* We want private on outer for and firstprivate
12854 on task. */
12855 *gtask_clauses_ptr
12856 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12857 OMP_CLAUSE_FIRSTPRIVATE);
12858 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12859 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
12860 openacc);
12861 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12862 *gforo_clauses_ptr = c;
12863 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12865 else
12867 *gtask_clauses_ptr = c;
12868 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12870 break;
12871 /* These clauses go into outer taskloop clauses. */
12872 case OMP_CLAUSE_GRAINSIZE:
12873 case OMP_CLAUSE_NUM_TASKS:
12874 case OMP_CLAUSE_NOGROUP:
12875 *gforo_clauses_ptr = c;
12876 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12877 break;
12878 /* Collapse clause we duplicate on both taskloops. */
12879 case OMP_CLAUSE_COLLAPSE:
12880 *gfor_clauses_ptr = c;
12881 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12882 *gforo_clauses_ptr = copy_node (c);
12883 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
12884 break;
12885 /* For lastprivate, keep the clause on inner taskloop, and add
12886 a shared clause on task. If the same decl is also firstprivate,
12887 add also firstprivate clause on the inner taskloop. */
12888 case OMP_CLAUSE_LASTPRIVATE:
12889 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
12891 /* For taskloop C++ lastprivate IVs, we want:
12892 1) private on outer taskloop
12893 2) firstprivate and shared on task
12894 3) lastprivate on inner taskloop */
12895 *gtask_clauses_ptr
12896 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12897 OMP_CLAUSE_FIRSTPRIVATE);
12898 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12899 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
12900 openacc);
12901 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12902 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
12903 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12904 OMP_CLAUSE_PRIVATE);
12905 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
12906 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
12907 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
12908 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
12910 *gfor_clauses_ptr = c;
12911 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12912 *gtask_clauses_ptr
12913 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
12914 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12915 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
12916 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
12917 gtask_clauses_ptr
12918 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12919 break;
12920 /* Allocate clause we duplicate on task and inner taskloop
12921 if the decl is lastprivate, otherwise just put on task. */
12922 case OMP_CLAUSE_ALLOCATE:
12923 if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
12924 && DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
12926 /* Additionally, put firstprivate clause on task
12927 for the allocator if it is not constant. */
12928 *gtask_clauses_ptr
12929 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12930 OMP_CLAUSE_FIRSTPRIVATE);
12931 OMP_CLAUSE_DECL (*gtask_clauses_ptr)
12932 = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
12933 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12935 if (lastprivate_uids
12936 && bitmap_bit_p (lastprivate_uids,
12937 DECL_UID (OMP_CLAUSE_DECL (c))))
12939 *gfor_clauses_ptr = c;
12940 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12941 *gtask_clauses_ptr = copy_node (c);
12942 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12944 else
12946 *gtask_clauses_ptr = c;
12947 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12949 break;
12950 default:
12951 gcc_unreachable ();
12953 *gfor_clauses_ptr = NULL_TREE;
12954 *gtask_clauses_ptr = NULL_TREE;
12955 *gforo_clauses_ptr = NULL_TREE;
12956 BITMAP_FREE (lastprivate_uids);
12957 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
12958 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
12959 NULL_TREE, NULL_TREE, NULL_TREE);
12960 gimple_omp_task_set_taskloop_p (g, true);
12961 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
12962 gomp_for *gforo
12963 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
12964 gimple_omp_for_collapse (gfor),
12965 gimple_omp_for_pre_body (gfor));
12966 gimple_omp_for_set_pre_body (gfor, NULL);
12967 gimple_omp_for_set_combined_p (gforo, true);
12968 gimple_omp_for_set_combined_into_p (gfor, true);
12969 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
12971 tree type = TREE_TYPE (gimple_omp_for_index (gfor, i));
12972 tree v = create_tmp_var (type);
12973 gimple_omp_for_set_index (gforo, i, v);
12974 t = unshare_expr (gimple_omp_for_initial (gfor, i));
12975 gimple_omp_for_set_initial (gforo, i, t);
12976 gimple_omp_for_set_cond (gforo, i,
12977 gimple_omp_for_cond (gfor, i));
12978 t = unshare_expr (gimple_omp_for_final (gfor, i));
12979 gimple_omp_for_set_final (gforo, i, t);
12980 t = unshare_expr (gimple_omp_for_incr (gfor, i));
12981 gcc_assert (TREE_OPERAND (t, 0) == gimple_omp_for_index (gfor, i));
12982 TREE_OPERAND (t, 0) = v;
12983 gimple_omp_for_set_incr (gforo, i, t);
12984 t = build_omp_clause (input_location, OMP_CLAUSE_PRIVATE);
12985 OMP_CLAUSE_DECL (t) = v;
12986 OMP_CLAUSE_CHAIN (t) = gimple_omp_for_clauses (gforo);
12987 gimple_omp_for_set_clauses (gforo, t);
12988 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
12990 tree *p1 = NULL, *p2 = NULL;
12991 t = gimple_omp_for_initial (gforo, i);
12992 if (TREE_CODE (t) == TREE_VEC)
12993 p1 = &TREE_VEC_ELT (t, 0);
12994 t = gimple_omp_for_final (gforo, i);
12995 if (TREE_CODE (t) == TREE_VEC)
12997 if (p1)
12998 p2 = &TREE_VEC_ELT (t, 0);
12999 else
13000 p1 = &TREE_VEC_ELT (t, 0);
13002 if (p1)
13004 int j;
13005 for (j = 0; j < i; j++)
13006 if (*p1 == gimple_omp_for_index (gfor, j))
13008 *p1 = gimple_omp_for_index (gforo, j);
13009 if (p2)
13010 *p2 = *p1;
13011 break;
13013 gcc_assert (j < i);
13017 gimplify_seq_add_stmt (pre_p, gforo);
13019 else
13020 gimplify_seq_add_stmt (pre_p, gfor);
13022 if (TREE_CODE (orig_for_stmt) == OMP_FOR)
13024 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13025 unsigned lastprivate_conditional = 0;
13026 while (ctx
13027 && (ctx->region_type == ORT_TARGET_DATA
13028 || ctx->region_type == ORT_TASKGROUP))
13029 ctx = ctx->outer_context;
13030 if (ctx && (ctx->region_type & ORT_PARALLEL) != 0)
13031 for (tree c = gimple_omp_for_clauses (gfor);
13032 c; c = OMP_CLAUSE_CHAIN (c))
13033 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13034 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
13035 ++lastprivate_conditional;
13036 if (lastprivate_conditional)
13038 struct omp_for_data fd;
13039 omp_extract_for_data (gfor, &fd, NULL);
13040 tree type = build_array_type_nelts (unsigned_type_for (fd.iter_type),
13041 lastprivate_conditional);
13042 tree var = create_tmp_var_raw (type);
13043 tree c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE__CONDTEMP_);
13044 OMP_CLAUSE_DECL (c) = var;
13045 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
13046 gimple_omp_for_set_clauses (gfor, c);
13047 omp_add_variable (ctx, var, GOVD_CONDTEMP | GOVD_SEEN);
13050 else if (TREE_CODE (orig_for_stmt) == OMP_SIMD)
13052 unsigned lastprivate_conditional = 0;
13053 for (tree c = gimple_omp_for_clauses (gfor); c; c = OMP_CLAUSE_CHAIN (c))
13054 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13055 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
13056 ++lastprivate_conditional;
13057 if (lastprivate_conditional)
13059 struct omp_for_data fd;
13060 omp_extract_for_data (gfor, &fd, NULL);
13061 tree type = unsigned_type_for (fd.iter_type);
13062 while (lastprivate_conditional--)
13064 tree c = build_omp_clause (UNKNOWN_LOCATION,
13065 OMP_CLAUSE__CONDTEMP_);
13066 OMP_CLAUSE_DECL (c) = create_tmp_var (type);
13067 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
13068 gimple_omp_for_set_clauses (gfor, c);
13073 if (ret != GS_ALL_DONE)
13074 return GS_ERROR;
13075 *expr_p = NULL_TREE;
13076 return GS_ALL_DONE;
13079 /* Helper for gimplify_omp_loop, called through walk_tree. */
13081 static tree
13082 replace_reduction_placeholders (tree *tp, int *walk_subtrees, void *data)
13084 if (DECL_P (*tp))
13086 tree *d = (tree *) data;
13087 if (*tp == OMP_CLAUSE_REDUCTION_PLACEHOLDER (d[0]))
13089 *tp = OMP_CLAUSE_REDUCTION_PLACEHOLDER (d[1]);
13090 *walk_subtrees = 0;
13092 else if (*tp == OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (d[0]))
13094 *tp = OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (d[1]);
13095 *walk_subtrees = 0;
13098 return NULL_TREE;
13101 /* Gimplify the gross structure of an OMP_LOOP statement. */
13103 static enum gimplify_status
13104 gimplify_omp_loop (tree *expr_p, gimple_seq *pre_p)
13106 tree for_stmt = *expr_p;
13107 tree clauses = OMP_FOR_CLAUSES (for_stmt);
13108 struct gimplify_omp_ctx *octx = gimplify_omp_ctxp;
13109 enum omp_clause_bind_kind kind = OMP_CLAUSE_BIND_THREAD;
13110 int i;
13112 /* If order is not present, the behavior is as if order(concurrent)
13113 appeared. */
13114 tree order = omp_find_clause (clauses, OMP_CLAUSE_ORDER);
13115 if (order == NULL_TREE)
13117 order = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_ORDER);
13118 OMP_CLAUSE_CHAIN (order) = clauses;
13119 OMP_FOR_CLAUSES (for_stmt) = clauses = order;
13122 tree bind = omp_find_clause (clauses, OMP_CLAUSE_BIND);
13123 if (bind == NULL_TREE)
13125 if (!flag_openmp) /* flag_openmp_simd */
13127 else if (octx && (octx->region_type & ORT_TEAMS) != 0)
13128 kind = OMP_CLAUSE_BIND_TEAMS;
13129 else if (octx && (octx->region_type & ORT_PARALLEL) != 0)
13130 kind = OMP_CLAUSE_BIND_PARALLEL;
13131 else
13133 for (; octx; octx = octx->outer_context)
13135 if ((octx->region_type & ORT_ACC) != 0
13136 || octx->region_type == ORT_NONE
13137 || octx->region_type == ORT_IMPLICIT_TARGET)
13138 continue;
13139 break;
13141 if (octx == NULL && !in_omp_construct)
13142 error_at (EXPR_LOCATION (for_stmt),
13143 "%<bind%> clause not specified on a %<loop%> "
13144 "construct not nested inside another OpenMP construct");
13146 bind = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_BIND);
13147 OMP_CLAUSE_CHAIN (bind) = clauses;
13148 OMP_CLAUSE_BIND_KIND (bind) = kind;
13149 OMP_FOR_CLAUSES (for_stmt) = bind;
13151 else
13152 switch (OMP_CLAUSE_BIND_KIND (bind))
13154 case OMP_CLAUSE_BIND_THREAD:
13155 break;
13156 case OMP_CLAUSE_BIND_PARALLEL:
13157 if (!flag_openmp) /* flag_openmp_simd */
13159 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13160 break;
13162 for (; octx; octx = octx->outer_context)
13163 if (octx->region_type == ORT_SIMD
13164 && omp_find_clause (octx->clauses, OMP_CLAUSE_BIND) == NULL_TREE)
13166 error_at (EXPR_LOCATION (for_stmt),
13167 "%<bind(parallel)%> on a %<loop%> construct nested "
13168 "inside %<simd%> construct");
13169 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13170 break;
13172 kind = OMP_CLAUSE_BIND_PARALLEL;
13173 break;
13174 case OMP_CLAUSE_BIND_TEAMS:
13175 if (!flag_openmp) /* flag_openmp_simd */
13177 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13178 break;
13180 if ((octx
13181 && octx->region_type != ORT_IMPLICIT_TARGET
13182 && octx->region_type != ORT_NONE
13183 && (octx->region_type & ORT_TEAMS) == 0)
13184 || in_omp_construct)
13186 error_at (EXPR_LOCATION (for_stmt),
13187 "%<bind(teams)%> on a %<loop%> region not strictly "
13188 "nested inside of a %<teams%> region");
13189 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13190 break;
13192 kind = OMP_CLAUSE_BIND_TEAMS;
13193 break;
13194 default:
13195 gcc_unreachable ();
13198 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
13199 switch (OMP_CLAUSE_CODE (*pc))
13201 case OMP_CLAUSE_REDUCTION:
13202 if (OMP_CLAUSE_REDUCTION_INSCAN (*pc))
13204 error_at (OMP_CLAUSE_LOCATION (*pc),
13205 "%<inscan%> %<reduction%> clause on "
13206 "%qs construct", "loop");
13207 OMP_CLAUSE_REDUCTION_INSCAN (*pc) = 0;
13209 if (OMP_CLAUSE_REDUCTION_TASK (*pc))
13211 error_at (OMP_CLAUSE_LOCATION (*pc),
13212 "invalid %<task%> reduction modifier on construct "
13213 "other than %<parallel%>, %qs or %<sections%>",
13214 lang_GNU_Fortran () ? "do" : "for");
13215 OMP_CLAUSE_REDUCTION_TASK (*pc) = 0;
13217 pc = &OMP_CLAUSE_CHAIN (*pc);
13218 break;
13219 case OMP_CLAUSE_LASTPRIVATE:
13220 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
13222 tree t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
13223 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
13224 if (OMP_CLAUSE_DECL (*pc) == TREE_OPERAND (t, 0))
13225 break;
13226 if (OMP_FOR_ORIG_DECLS (for_stmt)
13227 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
13228 i)) == TREE_LIST
13229 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
13230 i)))
13232 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
13233 if (OMP_CLAUSE_DECL (*pc) == TREE_PURPOSE (orig))
13234 break;
13237 if (i == TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)))
13239 error_at (OMP_CLAUSE_LOCATION (*pc),
13240 "%<lastprivate%> clause on a %<loop%> construct refers "
13241 "to a variable %qD which is not the loop iterator",
13242 OMP_CLAUSE_DECL (*pc));
13243 *pc = OMP_CLAUSE_CHAIN (*pc);
13244 break;
13246 pc = &OMP_CLAUSE_CHAIN (*pc);
13247 break;
13248 default:
13249 pc = &OMP_CLAUSE_CHAIN (*pc);
13250 break;
13253 TREE_SET_CODE (for_stmt, OMP_SIMD);
13255 int last;
13256 switch (kind)
13258 case OMP_CLAUSE_BIND_THREAD: last = 0; break;
13259 case OMP_CLAUSE_BIND_PARALLEL: last = 1; break;
13260 case OMP_CLAUSE_BIND_TEAMS: last = 2; break;
13262 for (int pass = 1; pass <= last; pass++)
13264 if (pass == 2)
13266 tree bind = build3 (BIND_EXPR, void_type_node, NULL, NULL, NULL);
13267 append_to_statement_list (*expr_p, &BIND_EXPR_BODY (bind));
13268 *expr_p = make_node (OMP_PARALLEL);
13269 TREE_TYPE (*expr_p) = void_type_node;
13270 OMP_PARALLEL_BODY (*expr_p) = bind;
13271 OMP_PARALLEL_COMBINED (*expr_p) = 1;
13272 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (for_stmt));
13273 tree *pc = &OMP_PARALLEL_CLAUSES (*expr_p);
13274 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
13275 if (OMP_FOR_ORIG_DECLS (for_stmt)
13276 && (TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i))
13277 == TREE_LIST))
13279 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
13280 if (TREE_PURPOSE (elt) && TREE_VALUE (elt))
13282 *pc = build_omp_clause (UNKNOWN_LOCATION,
13283 OMP_CLAUSE_FIRSTPRIVATE);
13284 OMP_CLAUSE_DECL (*pc) = TREE_VALUE (elt);
13285 pc = &OMP_CLAUSE_CHAIN (*pc);
13289 tree t = make_node (pass == 2 ? OMP_DISTRIBUTE : OMP_FOR);
13290 tree *pc = &OMP_FOR_CLAUSES (t);
13291 TREE_TYPE (t) = void_type_node;
13292 OMP_FOR_BODY (t) = *expr_p;
13293 SET_EXPR_LOCATION (t, EXPR_LOCATION (for_stmt));
13294 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
13295 switch (OMP_CLAUSE_CODE (c))
13297 case OMP_CLAUSE_BIND:
13298 case OMP_CLAUSE_ORDER:
13299 case OMP_CLAUSE_COLLAPSE:
13300 *pc = copy_node (c);
13301 pc = &OMP_CLAUSE_CHAIN (*pc);
13302 break;
13303 case OMP_CLAUSE_PRIVATE:
13304 case OMP_CLAUSE_FIRSTPRIVATE:
13305 /* Only needed on innermost. */
13306 break;
13307 case OMP_CLAUSE_LASTPRIVATE:
13308 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c) && pass != last)
13310 *pc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13311 OMP_CLAUSE_FIRSTPRIVATE);
13312 OMP_CLAUSE_DECL (*pc) = OMP_CLAUSE_DECL (c);
13313 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
13314 pc = &OMP_CLAUSE_CHAIN (*pc);
13316 *pc = copy_node (c);
13317 OMP_CLAUSE_LASTPRIVATE_STMT (*pc) = NULL_TREE;
13318 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
13319 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
13321 if (pass != last)
13322 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (*pc) = 1;
13323 else
13324 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
13325 OMP_CLAUSE_LASTPRIVATE_LOOP_IV (*pc) = 0;
13327 pc = &OMP_CLAUSE_CHAIN (*pc);
13328 break;
13329 case OMP_CLAUSE_REDUCTION:
13330 *pc = copy_node (c);
13331 OMP_CLAUSE_DECL (*pc) = unshare_expr (OMP_CLAUSE_DECL (c));
13332 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
13333 OMP_CLAUSE_REDUCTION_INIT (*pc)
13334 = unshare_expr (OMP_CLAUSE_REDUCTION_INIT (c));
13335 OMP_CLAUSE_REDUCTION_MERGE (*pc)
13336 = unshare_expr (OMP_CLAUSE_REDUCTION_MERGE (c));
13337 if (OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc))
13339 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc)
13340 = copy_node (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c));
13341 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
13342 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc)
13343 = copy_node (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c));
13344 tree nc = *pc;
13345 tree data[2] = { c, nc };
13346 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_INIT (nc),
13347 replace_reduction_placeholders,
13348 data);
13349 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_MERGE (nc),
13350 replace_reduction_placeholders,
13351 data);
13353 pc = &OMP_CLAUSE_CHAIN (*pc);
13354 break;
13355 default:
13356 gcc_unreachable ();
13358 *pc = NULL_TREE;
13359 *expr_p = t;
13361 return gimplify_omp_for (expr_p, pre_p);
13365 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
13366 of OMP_TARGET's body. */
13368 static tree
13369 find_omp_teams (tree *tp, int *walk_subtrees, void *)
13371 *walk_subtrees = 0;
13372 switch (TREE_CODE (*tp))
13374 case OMP_TEAMS:
13375 return *tp;
13376 case BIND_EXPR:
13377 case STATEMENT_LIST:
13378 *walk_subtrees = 1;
13379 break;
13380 default:
13381 break;
13383 return NULL_TREE;
13386 /* Helper function of optimize_target_teams, determine if the expression
13387 can be computed safely before the target construct on the host. */
13389 static tree
13390 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
13392 splay_tree_node n;
13394 if (TYPE_P (*tp))
13396 *walk_subtrees = 0;
13397 return NULL_TREE;
13399 switch (TREE_CODE (*tp))
13401 case VAR_DECL:
13402 case PARM_DECL:
13403 case RESULT_DECL:
13404 *walk_subtrees = 0;
13405 if (error_operand_p (*tp)
13406 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
13407 || DECL_HAS_VALUE_EXPR_P (*tp)
13408 || DECL_THREAD_LOCAL_P (*tp)
13409 || TREE_SIDE_EFFECTS (*tp)
13410 || TREE_THIS_VOLATILE (*tp))
13411 return *tp;
13412 if (is_global_var (*tp)
13413 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
13414 || lookup_attribute ("omp declare target link",
13415 DECL_ATTRIBUTES (*tp))))
13416 return *tp;
13417 if (VAR_P (*tp)
13418 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
13419 && !is_global_var (*tp)
13420 && decl_function_context (*tp) == current_function_decl)
13421 return *tp;
13422 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
13423 (splay_tree_key) *tp);
13424 if (n == NULL)
13426 if (gimplify_omp_ctxp->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
13427 return NULL_TREE;
13428 return *tp;
13430 else if (n->value & GOVD_LOCAL)
13431 return *tp;
13432 else if (n->value & GOVD_FIRSTPRIVATE)
13433 return NULL_TREE;
13434 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
13435 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
13436 return NULL_TREE;
13437 return *tp;
13438 case INTEGER_CST:
13439 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
13440 return *tp;
13441 return NULL_TREE;
13442 case TARGET_EXPR:
13443 if (TARGET_EXPR_INITIAL (*tp)
13444 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
13445 return *tp;
13446 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
13447 walk_subtrees, NULL);
13448 /* Allow some reasonable subset of integral arithmetics. */
13449 case PLUS_EXPR:
13450 case MINUS_EXPR:
13451 case MULT_EXPR:
13452 case TRUNC_DIV_EXPR:
13453 case CEIL_DIV_EXPR:
13454 case FLOOR_DIV_EXPR:
13455 case ROUND_DIV_EXPR:
13456 case TRUNC_MOD_EXPR:
13457 case CEIL_MOD_EXPR:
13458 case FLOOR_MOD_EXPR:
13459 case ROUND_MOD_EXPR:
13460 case RDIV_EXPR:
13461 case EXACT_DIV_EXPR:
13462 case MIN_EXPR:
13463 case MAX_EXPR:
13464 case LSHIFT_EXPR:
13465 case RSHIFT_EXPR:
13466 case BIT_IOR_EXPR:
13467 case BIT_XOR_EXPR:
13468 case BIT_AND_EXPR:
13469 case NEGATE_EXPR:
13470 case ABS_EXPR:
13471 case BIT_NOT_EXPR:
13472 case NON_LVALUE_EXPR:
13473 CASE_CONVERT:
13474 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
13475 return *tp;
13476 return NULL_TREE;
13477 /* And disallow anything else, except for comparisons. */
13478 default:
13479 if (COMPARISON_CLASS_P (*tp))
13480 return NULL_TREE;
13481 return *tp;
13485 /* Try to determine if the num_teams and/or thread_limit expressions
13486 can have their values determined already before entering the
13487 target construct.
13488 INTEGER_CSTs trivially are,
13489 integral decls that are firstprivate (explicitly or implicitly)
13490 or explicitly map(always, to:) or map(always, tofrom:) on the target
13491 region too, and expressions involving simple arithmetics on those
13492 too, function calls are not ok, dereferencing something neither etc.
13493 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
13494 EXPR based on what we find:
13495 0 stands for clause not specified at all, use implementation default
13496 -1 stands for value that can't be determined easily before entering
13497 the target construct.
13498 If teams construct is not present at all, use 1 for num_teams
13499 and 0 for thread_limit (only one team is involved, and the thread
13500 limit is implementation defined. */
13502 static void
13503 optimize_target_teams (tree target, gimple_seq *pre_p)
13505 tree body = OMP_BODY (target);
13506 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
13507 tree num_teams = integer_zero_node;
13508 tree thread_limit = integer_zero_node;
13509 location_t num_teams_loc = EXPR_LOCATION (target);
13510 location_t thread_limit_loc = EXPR_LOCATION (target);
13511 tree c, *p, expr;
13512 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
13514 if (teams == NULL_TREE)
13515 num_teams = integer_one_node;
13516 else
13517 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
13519 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
13521 p = &num_teams;
13522 num_teams_loc = OMP_CLAUSE_LOCATION (c);
13524 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
13526 p = &thread_limit;
13527 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
13529 else
13530 continue;
13531 expr = OMP_CLAUSE_OPERAND (c, 0);
13532 if (TREE_CODE (expr) == INTEGER_CST)
13534 *p = expr;
13535 continue;
13537 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
13539 *p = integer_minus_one_node;
13540 continue;
13542 *p = expr;
13543 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
13544 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
13545 == GS_ERROR)
13547 gimplify_omp_ctxp = target_ctx;
13548 *p = integer_minus_one_node;
13549 continue;
13551 gimplify_omp_ctxp = target_ctx;
13552 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
13553 OMP_CLAUSE_OPERAND (c, 0) = *p;
13555 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
13556 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
13557 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
13558 OMP_TARGET_CLAUSES (target) = c;
13559 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
13560 OMP_CLAUSE_NUM_TEAMS_EXPR (c) = num_teams;
13561 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
13562 OMP_TARGET_CLAUSES (target) = c;
13565 /* Gimplify the gross structure of several OMP constructs. */
13567 static void
13568 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
13570 tree expr = *expr_p;
13571 gimple *stmt;
13572 gimple_seq body = NULL;
13573 enum omp_region_type ort;
13575 switch (TREE_CODE (expr))
13577 case OMP_SECTIONS:
13578 case OMP_SINGLE:
13579 ort = ORT_WORKSHARE;
13580 break;
13581 case OMP_SCOPE:
13582 ort = ORT_TASKGROUP;
13583 break;
13584 case OMP_TARGET:
13585 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
13586 break;
13587 case OACC_KERNELS:
13588 ort = ORT_ACC_KERNELS;
13589 break;
13590 case OACC_PARALLEL:
13591 ort = ORT_ACC_PARALLEL;
13592 break;
13593 case OACC_SERIAL:
13594 ort = ORT_ACC_SERIAL;
13595 break;
13596 case OACC_DATA:
13597 ort = ORT_ACC_DATA;
13598 break;
13599 case OMP_TARGET_DATA:
13600 ort = ORT_TARGET_DATA;
13601 break;
13602 case OMP_TEAMS:
13603 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
13604 if (gimplify_omp_ctxp == NULL
13605 || gimplify_omp_ctxp->region_type == ORT_IMPLICIT_TARGET)
13606 ort = (enum omp_region_type) (ort | ORT_HOST_TEAMS);
13607 break;
13608 case OACC_HOST_DATA:
13609 ort = ORT_ACC_HOST_DATA;
13610 break;
13611 default:
13612 gcc_unreachable ();
13615 bool save_in_omp_construct = in_omp_construct;
13616 if ((ort & ORT_ACC) == 0)
13617 in_omp_construct = false;
13618 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
13619 TREE_CODE (expr));
13620 if (TREE_CODE (expr) == OMP_TARGET)
13621 optimize_target_teams (expr, pre_p);
13622 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0
13623 || (ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
13625 push_gimplify_context ();
13626 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
13627 if (gimple_code (g) == GIMPLE_BIND)
13628 pop_gimplify_context (g);
13629 else
13630 pop_gimplify_context (NULL);
13631 if ((ort & ORT_TARGET_DATA) != 0)
13633 enum built_in_function end_ix;
13634 switch (TREE_CODE (expr))
13636 case OACC_DATA:
13637 case OACC_HOST_DATA:
13638 end_ix = BUILT_IN_GOACC_DATA_END;
13639 break;
13640 case OMP_TARGET_DATA:
13641 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
13642 break;
13643 default:
13644 gcc_unreachable ();
13646 tree fn = builtin_decl_explicit (end_ix);
13647 g = gimple_build_call (fn, 0);
13648 gimple_seq cleanup = NULL;
13649 gimple_seq_add_stmt (&cleanup, g);
13650 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
13651 body = NULL;
13652 gimple_seq_add_stmt (&body, g);
13655 else
13656 gimplify_and_add (OMP_BODY (expr), &body);
13657 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
13658 TREE_CODE (expr));
13659 in_omp_construct = save_in_omp_construct;
13661 switch (TREE_CODE (expr))
13663 case OACC_DATA:
13664 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
13665 OMP_CLAUSES (expr));
13666 break;
13667 case OACC_HOST_DATA:
13668 if (omp_find_clause (OMP_CLAUSES (expr), OMP_CLAUSE_IF_PRESENT))
13670 for (tree c = OMP_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13671 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_USE_DEVICE_PTR)
13672 OMP_CLAUSE_USE_DEVICE_PTR_IF_PRESENT (c) = 1;
13675 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
13676 OMP_CLAUSES (expr));
13677 break;
13678 case OACC_KERNELS:
13679 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
13680 OMP_CLAUSES (expr));
13681 break;
13682 case OACC_PARALLEL:
13683 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
13684 OMP_CLAUSES (expr));
13685 break;
13686 case OACC_SERIAL:
13687 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_SERIAL,
13688 OMP_CLAUSES (expr));
13689 break;
13690 case OMP_SECTIONS:
13691 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
13692 break;
13693 case OMP_SINGLE:
13694 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
13695 break;
13696 case OMP_SCOPE:
13697 stmt = gimple_build_omp_scope (body, OMP_CLAUSES (expr));
13698 break;
13699 case OMP_TARGET:
13700 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
13701 OMP_CLAUSES (expr));
13702 break;
13703 case OMP_TARGET_DATA:
13704 /* Put use_device_{ptr,addr} clauses last, as map clauses are supposed
13705 to be evaluated before the use_device_{ptr,addr} clauses if they
13706 refer to the same variables. */
13708 tree use_device_clauses;
13709 tree *pc, *uc = &use_device_clauses;
13710 for (pc = &OMP_CLAUSES (expr); *pc; )
13711 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_PTR
13712 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_ADDR)
13714 *uc = *pc;
13715 *pc = OMP_CLAUSE_CHAIN (*pc);
13716 uc = &OMP_CLAUSE_CHAIN (*uc);
13718 else
13719 pc = &OMP_CLAUSE_CHAIN (*pc);
13720 *uc = NULL_TREE;
13721 *pc = use_device_clauses;
13722 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
13723 OMP_CLAUSES (expr));
13725 break;
13726 case OMP_TEAMS:
13727 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
13728 if ((ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
13729 gimple_omp_teams_set_host (as_a <gomp_teams *> (stmt), true);
13730 break;
13731 default:
13732 gcc_unreachable ();
13735 gimplify_seq_add_stmt (pre_p, stmt);
13736 *expr_p = NULL_TREE;
13739 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
13740 target update constructs. */
13742 static void
13743 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
13745 tree expr = *expr_p;
13746 int kind;
13747 gomp_target *stmt;
13748 enum omp_region_type ort = ORT_WORKSHARE;
13750 switch (TREE_CODE (expr))
13752 case OACC_ENTER_DATA:
13753 kind = GF_OMP_TARGET_KIND_OACC_ENTER_DATA;
13754 ort = ORT_ACC;
13755 break;
13756 case OACC_EXIT_DATA:
13757 kind = GF_OMP_TARGET_KIND_OACC_EXIT_DATA;
13758 ort = ORT_ACC;
13759 break;
13760 case OACC_UPDATE:
13761 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
13762 ort = ORT_ACC;
13763 break;
13764 case OMP_TARGET_UPDATE:
13765 kind = GF_OMP_TARGET_KIND_UPDATE;
13766 break;
13767 case OMP_TARGET_ENTER_DATA:
13768 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
13769 break;
13770 case OMP_TARGET_EXIT_DATA:
13771 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
13772 break;
13773 default:
13774 gcc_unreachable ();
13776 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
13777 ort, TREE_CODE (expr));
13778 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
13779 TREE_CODE (expr));
13780 if (TREE_CODE (expr) == OACC_UPDATE
13781 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
13782 OMP_CLAUSE_IF_PRESENT))
13784 /* The runtime uses GOMP_MAP_{TO,FROM} to denote the if_present
13785 clause. */
13786 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13787 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
13788 switch (OMP_CLAUSE_MAP_KIND (c))
13790 case GOMP_MAP_FORCE_TO:
13791 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TO);
13792 break;
13793 case GOMP_MAP_FORCE_FROM:
13794 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FROM);
13795 break;
13796 default:
13797 break;
13800 else if (TREE_CODE (expr) == OACC_EXIT_DATA
13801 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
13802 OMP_CLAUSE_FINALIZE))
13804 /* Use GOMP_MAP_DELETE/GOMP_MAP_FORCE_FROM to denote "finalize"
13805 semantics. */
13806 bool have_clause = false;
13807 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13808 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
13809 switch (OMP_CLAUSE_MAP_KIND (c))
13811 case GOMP_MAP_FROM:
13812 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_FROM);
13813 have_clause = true;
13814 break;
13815 case GOMP_MAP_RELEASE:
13816 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
13817 have_clause = true;
13818 break;
13819 case GOMP_MAP_TO_PSET:
13820 /* Fortran arrays with descriptors must map that descriptor when
13821 doing standalone "attach" operations (in OpenACC). In that
13822 case GOMP_MAP_TO_PSET appears by itself with no preceding
13823 clause (see trans-openmp.c:gfc_trans_omp_clauses). */
13824 break;
13825 case GOMP_MAP_POINTER:
13826 /* TODO PR92929: we may see these here, but they'll always follow
13827 one of the clauses above, and will be handled by libgomp as
13828 one group, so no handling required here. */
13829 gcc_assert (have_clause);
13830 break;
13831 case GOMP_MAP_DETACH:
13832 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_DETACH);
13833 have_clause = false;
13834 break;
13835 case GOMP_MAP_STRUCT:
13836 have_clause = false;
13837 break;
13838 default:
13839 gcc_unreachable ();
13842 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
13844 gimplify_seq_add_stmt (pre_p, stmt);
13845 *expr_p = NULL_TREE;
13848 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
13849 stabilized the lhs of the atomic operation as *ADDR. Return true if
13850 EXPR is this stabilized form. */
13852 static bool
13853 goa_lhs_expr_p (tree expr, tree addr)
13855 /* Also include casts to other type variants. The C front end is fond
13856 of adding these for e.g. volatile variables. This is like
13857 STRIP_TYPE_NOPS but includes the main variant lookup. */
13858 STRIP_USELESS_TYPE_CONVERSION (expr);
13860 if (TREE_CODE (expr) == INDIRECT_REF)
13862 expr = TREE_OPERAND (expr, 0);
13863 while (expr != addr
13864 && (CONVERT_EXPR_P (expr)
13865 || TREE_CODE (expr) == NON_LVALUE_EXPR)
13866 && TREE_CODE (expr) == TREE_CODE (addr)
13867 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
13869 expr = TREE_OPERAND (expr, 0);
13870 addr = TREE_OPERAND (addr, 0);
13872 if (expr == addr)
13873 return true;
13874 return (TREE_CODE (addr) == ADDR_EXPR
13875 && TREE_CODE (expr) == ADDR_EXPR
13876 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
13878 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
13879 return true;
13880 return false;
13883 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
13884 expression does not involve the lhs, evaluate it into a temporary.
13885 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
13886 or -1 if an error was encountered. */
13888 static int
13889 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
13890 tree lhs_var, tree &target_expr, bool rhs, int depth)
13892 tree expr = *expr_p;
13893 int saw_lhs = 0;
13895 if (goa_lhs_expr_p (expr, lhs_addr))
13897 if (pre_p)
13898 *expr_p = lhs_var;
13899 return 1;
13901 if (is_gimple_val (expr))
13902 return 0;
13904 /* Maximum depth of lhs in expression is for the
13905 __builtin_clear_padding (...), __builtin_clear_padding (...),
13906 __builtin_memcmp (&TARGET_EXPR <lhs, >, ...) == 0 ? ... : lhs; */
13907 if (++depth > 7)
13908 goto finish;
13910 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
13912 case tcc_binary:
13913 case tcc_comparison:
13914 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
13915 lhs_var, target_expr, true, depth);
13916 /* FALLTHRU */
13917 case tcc_unary:
13918 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
13919 lhs_var, target_expr, true, depth);
13920 break;
13921 case tcc_expression:
13922 switch (TREE_CODE (expr))
13924 case TRUTH_ANDIF_EXPR:
13925 case TRUTH_ORIF_EXPR:
13926 case TRUTH_AND_EXPR:
13927 case TRUTH_OR_EXPR:
13928 case TRUTH_XOR_EXPR:
13929 case BIT_INSERT_EXPR:
13930 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
13931 lhs_addr, lhs_var, target_expr, true,
13932 depth);
13933 /* FALLTHRU */
13934 case TRUTH_NOT_EXPR:
13935 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13936 lhs_addr, lhs_var, target_expr, true,
13937 depth);
13938 break;
13939 case MODIFY_EXPR:
13940 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
13941 target_expr, true, depth))
13942 break;
13943 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
13944 lhs_addr, lhs_var, target_expr, true,
13945 depth);
13946 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13947 lhs_addr, lhs_var, target_expr, false,
13948 depth);
13949 break;
13950 /* FALLTHRU */
13951 case ADDR_EXPR:
13952 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
13953 target_expr, true, depth))
13954 break;
13955 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13956 lhs_addr, lhs_var, target_expr, false,
13957 depth);
13958 break;
13959 case COMPOUND_EXPR:
13960 /* Break out any preevaluations from cp_build_modify_expr. */
13961 for (; TREE_CODE (expr) == COMPOUND_EXPR;
13962 expr = TREE_OPERAND (expr, 1))
13964 /* Special-case __builtin_clear_padding call before
13965 __builtin_memcmp. */
13966 if (TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR)
13968 tree fndecl = get_callee_fndecl (TREE_OPERAND (expr, 0));
13969 if (fndecl
13970 && fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING)
13971 && VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (expr, 0)))
13972 && (!pre_p
13973 || goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL,
13974 lhs_addr, lhs_var,
13975 target_expr, true, depth)))
13977 if (pre_p)
13978 *expr_p = expr;
13979 saw_lhs = goa_stabilize_expr (&TREE_OPERAND (expr, 0),
13980 pre_p, lhs_addr, lhs_var,
13981 target_expr, true, depth);
13982 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1),
13983 pre_p, lhs_addr, lhs_var,
13984 target_expr, rhs, depth);
13985 return saw_lhs;
13989 if (pre_p)
13990 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
13992 if (!pre_p)
13993 return goa_stabilize_expr (&expr, pre_p, lhs_addr, lhs_var,
13994 target_expr, rhs, depth);
13995 *expr_p = expr;
13996 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var,
13997 target_expr, rhs, depth);
13998 case COND_EXPR:
13999 if (!goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL, lhs_addr,
14000 lhs_var, target_expr, true, depth))
14001 break;
14002 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
14003 lhs_addr, lhs_var, target_expr, true,
14004 depth);
14005 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
14006 lhs_addr, lhs_var, target_expr, true,
14007 depth);
14008 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 2), pre_p,
14009 lhs_addr, lhs_var, target_expr, true,
14010 depth);
14011 break;
14012 case TARGET_EXPR:
14013 if (TARGET_EXPR_INITIAL (expr))
14015 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr,
14016 lhs_var, target_expr, true,
14017 depth))
14018 break;
14019 if (expr == target_expr)
14020 saw_lhs = 1;
14021 else
14023 saw_lhs = goa_stabilize_expr (&TARGET_EXPR_INITIAL (expr),
14024 pre_p, lhs_addr, lhs_var,
14025 target_expr, true, depth);
14026 if (saw_lhs && target_expr == NULL_TREE && pre_p)
14027 target_expr = expr;
14030 break;
14031 default:
14032 break;
14034 break;
14035 case tcc_reference:
14036 if (TREE_CODE (expr) == BIT_FIELD_REF
14037 || TREE_CODE (expr) == VIEW_CONVERT_EXPR)
14038 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
14039 lhs_addr, lhs_var, target_expr, true,
14040 depth);
14041 break;
14042 case tcc_vl_exp:
14043 if (TREE_CODE (expr) == CALL_EXPR)
14045 if (tree fndecl = get_callee_fndecl (expr))
14046 if (fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING)
14047 || fndecl_built_in_p (fndecl, BUILT_IN_MEMCMP))
14049 int nargs = call_expr_nargs (expr);
14050 for (int i = 0; i < nargs; i++)
14051 saw_lhs |= goa_stabilize_expr (&CALL_EXPR_ARG (expr, i),
14052 pre_p, lhs_addr, lhs_var,
14053 target_expr, true, depth);
14056 break;
14057 default:
14058 break;
14061 finish:
14062 if (saw_lhs == 0 && pre_p)
14064 enum gimplify_status gs;
14065 if (TREE_CODE (expr) == CALL_EXPR && VOID_TYPE_P (TREE_TYPE (expr)))
14067 gimplify_stmt (&expr, pre_p);
14068 return saw_lhs;
14070 else if (rhs)
14071 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
14072 else
14073 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_lvalue, fb_lvalue);
14074 if (gs != GS_ALL_DONE)
14075 saw_lhs = -1;
14078 return saw_lhs;
14081 /* Gimplify an OMP_ATOMIC statement. */
14083 static enum gimplify_status
14084 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
14086 tree addr = TREE_OPERAND (*expr_p, 0);
14087 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
14088 ? NULL : TREE_OPERAND (*expr_p, 1);
14089 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
14090 tree tmp_load;
14091 gomp_atomic_load *loadstmt;
14092 gomp_atomic_store *storestmt;
14093 tree target_expr = NULL_TREE;
14095 tmp_load = create_tmp_reg (type);
14096 if (rhs
14097 && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load, target_expr,
14098 true, 0) < 0)
14099 return GS_ERROR;
14101 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
14102 != GS_ALL_DONE)
14103 return GS_ERROR;
14105 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr,
14106 OMP_ATOMIC_MEMORY_ORDER (*expr_p));
14107 gimplify_seq_add_stmt (pre_p, loadstmt);
14108 if (rhs)
14110 /* BIT_INSERT_EXPR is not valid for non-integral bitfield
14111 representatives. Use BIT_FIELD_REF on the lhs instead. */
14112 tree rhsarg = rhs;
14113 if (TREE_CODE (rhs) == COND_EXPR)
14114 rhsarg = TREE_OPERAND (rhs, 1);
14115 if (TREE_CODE (rhsarg) == BIT_INSERT_EXPR
14116 && !INTEGRAL_TYPE_P (TREE_TYPE (tmp_load)))
14118 tree bitpos = TREE_OPERAND (rhsarg, 2);
14119 tree op1 = TREE_OPERAND (rhsarg, 1);
14120 tree bitsize;
14121 tree tmp_store = tmp_load;
14122 if (TREE_CODE (*expr_p) == OMP_ATOMIC_CAPTURE_OLD)
14123 tmp_store = get_initialized_tmp_var (tmp_load, pre_p);
14124 if (INTEGRAL_TYPE_P (TREE_TYPE (op1)))
14125 bitsize = bitsize_int (TYPE_PRECISION (TREE_TYPE (op1)));
14126 else
14127 bitsize = TYPE_SIZE (TREE_TYPE (op1));
14128 gcc_assert (TREE_OPERAND (rhsarg, 0) == tmp_load);
14129 tree t = build2_loc (EXPR_LOCATION (rhsarg),
14130 MODIFY_EXPR, void_type_node,
14131 build3_loc (EXPR_LOCATION (rhsarg),
14132 BIT_FIELD_REF, TREE_TYPE (op1),
14133 tmp_store, bitsize, bitpos), op1);
14134 if (TREE_CODE (rhs) == COND_EXPR)
14135 t = build3_loc (EXPR_LOCATION (rhs), COND_EXPR, void_type_node,
14136 TREE_OPERAND (rhs, 0), t, void_node);
14137 gimplify_and_add (t, pre_p);
14138 rhs = tmp_store;
14140 bool save_allow_rhs_cond_expr = gimplify_ctxp->allow_rhs_cond_expr;
14141 if (TREE_CODE (rhs) == COND_EXPR)
14142 gimplify_ctxp->allow_rhs_cond_expr = true;
14143 enum gimplify_status gs = gimplify_expr (&rhs, pre_p, NULL,
14144 is_gimple_val, fb_rvalue);
14145 gimplify_ctxp->allow_rhs_cond_expr = save_allow_rhs_cond_expr;
14146 if (gs != GS_ALL_DONE)
14147 return GS_ERROR;
14150 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
14151 rhs = tmp_load;
14152 storestmt
14153 = gimple_build_omp_atomic_store (rhs, OMP_ATOMIC_MEMORY_ORDER (*expr_p));
14154 if (TREE_CODE (*expr_p) != OMP_ATOMIC_READ && OMP_ATOMIC_WEAK (*expr_p))
14156 gimple_omp_atomic_set_weak (loadstmt);
14157 gimple_omp_atomic_set_weak (storestmt);
14159 gimplify_seq_add_stmt (pre_p, storestmt);
14160 switch (TREE_CODE (*expr_p))
14162 case OMP_ATOMIC_READ:
14163 case OMP_ATOMIC_CAPTURE_OLD:
14164 *expr_p = tmp_load;
14165 gimple_omp_atomic_set_need_value (loadstmt);
14166 break;
14167 case OMP_ATOMIC_CAPTURE_NEW:
14168 *expr_p = rhs;
14169 gimple_omp_atomic_set_need_value (storestmt);
14170 break;
14171 default:
14172 *expr_p = NULL;
14173 break;
14176 return GS_ALL_DONE;
14179 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
14180 body, and adding some EH bits. */
14182 static enum gimplify_status
14183 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
14185 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
14186 gimple *body_stmt;
14187 gtransaction *trans_stmt;
14188 gimple_seq body = NULL;
14189 int subcode = 0;
14191 /* Wrap the transaction body in a BIND_EXPR so we have a context
14192 where to put decls for OMP. */
14193 if (TREE_CODE (tbody) != BIND_EXPR)
14195 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
14196 TREE_SIDE_EFFECTS (bind) = 1;
14197 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
14198 TRANSACTION_EXPR_BODY (expr) = bind;
14201 push_gimplify_context ();
14202 temp = voidify_wrapper_expr (*expr_p, NULL);
14204 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
14205 pop_gimplify_context (body_stmt);
14207 trans_stmt = gimple_build_transaction (body);
14208 if (TRANSACTION_EXPR_OUTER (expr))
14209 subcode = GTMA_IS_OUTER;
14210 else if (TRANSACTION_EXPR_RELAXED (expr))
14211 subcode = GTMA_IS_RELAXED;
14212 gimple_transaction_set_subcode (trans_stmt, subcode);
14214 gimplify_seq_add_stmt (pre_p, trans_stmt);
14216 if (temp)
14218 *expr_p = temp;
14219 return GS_OK;
14222 *expr_p = NULL_TREE;
14223 return GS_ALL_DONE;
14226 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
14227 is the OMP_BODY of the original EXPR (which has already been
14228 gimplified so it's not present in the EXPR).
14230 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
14232 static gimple *
14233 gimplify_omp_ordered (tree expr, gimple_seq body)
14235 tree c, decls;
14236 int failures = 0;
14237 unsigned int i;
14238 tree source_c = NULL_TREE;
14239 tree sink_c = NULL_TREE;
14241 if (gimplify_omp_ctxp)
14243 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
14244 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
14245 && gimplify_omp_ctxp->loop_iter_var.is_empty ()
14246 && (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK
14247 || OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE))
14249 error_at (OMP_CLAUSE_LOCATION (c),
14250 "%<ordered%> construct with %<depend%> clause must be "
14251 "closely nested inside a loop with %<ordered%> clause "
14252 "with a parameter");
14253 failures++;
14255 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
14256 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
14258 bool fail = false;
14259 for (decls = OMP_CLAUSE_DECL (c), i = 0;
14260 decls && TREE_CODE (decls) == TREE_LIST;
14261 decls = TREE_CHAIN (decls), ++i)
14262 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
14263 continue;
14264 else if (TREE_VALUE (decls)
14265 != gimplify_omp_ctxp->loop_iter_var[2 * i])
14267 error_at (OMP_CLAUSE_LOCATION (c),
14268 "variable %qE is not an iteration "
14269 "of outermost loop %d, expected %qE",
14270 TREE_VALUE (decls), i + 1,
14271 gimplify_omp_ctxp->loop_iter_var[2 * i]);
14272 fail = true;
14273 failures++;
14275 else
14276 TREE_VALUE (decls)
14277 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
14278 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
14280 error_at (OMP_CLAUSE_LOCATION (c),
14281 "number of variables in %<depend%> clause with "
14282 "%<sink%> modifier does not match number of "
14283 "iteration variables");
14284 failures++;
14286 sink_c = c;
14288 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
14289 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
14291 if (source_c)
14293 error_at (OMP_CLAUSE_LOCATION (c),
14294 "more than one %<depend%> clause with %<source%> "
14295 "modifier on an %<ordered%> construct");
14296 failures++;
14298 else
14299 source_c = c;
14302 if (source_c && sink_c)
14304 error_at (OMP_CLAUSE_LOCATION (source_c),
14305 "%<depend%> clause with %<source%> modifier specified "
14306 "together with %<depend%> clauses with %<sink%> modifier "
14307 "on the same construct");
14308 failures++;
14311 if (failures)
14312 return gimple_build_nop ();
14313 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
14316 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
14317 expression produces a value to be used as an operand inside a GIMPLE
14318 statement, the value will be stored back in *EXPR_P. This value will
14319 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
14320 an SSA_NAME. The corresponding sequence of GIMPLE statements is
14321 emitted in PRE_P and POST_P.
14323 Additionally, this process may overwrite parts of the input
14324 expression during gimplification. Ideally, it should be
14325 possible to do non-destructive gimplification.
14327 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
14328 the expression needs to evaluate to a value to be used as
14329 an operand in a GIMPLE statement, this value will be stored in
14330 *EXPR_P on exit. This happens when the caller specifies one
14331 of fb_lvalue or fb_rvalue fallback flags.
14333 PRE_P will contain the sequence of GIMPLE statements corresponding
14334 to the evaluation of EXPR and all the side-effects that must
14335 be executed before the main expression. On exit, the last
14336 statement of PRE_P is the core statement being gimplified. For
14337 instance, when gimplifying 'if (++a)' the last statement in
14338 PRE_P will be 'if (t.1)' where t.1 is the result of
14339 pre-incrementing 'a'.
14341 POST_P will contain the sequence of GIMPLE statements corresponding
14342 to the evaluation of all the side-effects that must be executed
14343 after the main expression. If this is NULL, the post
14344 side-effects are stored at the end of PRE_P.
14346 The reason why the output is split in two is to handle post
14347 side-effects explicitly. In some cases, an expression may have
14348 inner and outer post side-effects which need to be emitted in
14349 an order different from the one given by the recursive
14350 traversal. For instance, for the expression (*p--)++ the post
14351 side-effects of '--' must actually occur *after* the post
14352 side-effects of '++'. However, gimplification will first visit
14353 the inner expression, so if a separate POST sequence was not
14354 used, the resulting sequence would be:
14356 1 t.1 = *p
14357 2 p = p - 1
14358 3 t.2 = t.1 + 1
14359 4 *p = t.2
14361 However, the post-decrement operation in line #2 must not be
14362 evaluated until after the store to *p at line #4, so the
14363 correct sequence should be:
14365 1 t.1 = *p
14366 2 t.2 = t.1 + 1
14367 3 *p = t.2
14368 4 p = p - 1
14370 So, by specifying a separate post queue, it is possible
14371 to emit the post side-effects in the correct order.
14372 If POST_P is NULL, an internal queue will be used. Before
14373 returning to the caller, the sequence POST_P is appended to
14374 the main output sequence PRE_P.
14376 GIMPLE_TEST_F points to a function that takes a tree T and
14377 returns nonzero if T is in the GIMPLE form requested by the
14378 caller. The GIMPLE predicates are in gimple.c.
14380 FALLBACK tells the function what sort of a temporary we want if
14381 gimplification cannot produce an expression that complies with
14382 GIMPLE_TEST_F.
14384 fb_none means that no temporary should be generated
14385 fb_rvalue means that an rvalue is OK to generate
14386 fb_lvalue means that an lvalue is OK to generate
14387 fb_either means that either is OK, but an lvalue is preferable.
14388 fb_mayfail means that gimplification may fail (in which case
14389 GS_ERROR will be returned)
14391 The return value is either GS_ERROR or GS_ALL_DONE, since this
14392 function iterates until EXPR is completely gimplified or an error
14393 occurs. */
14395 enum gimplify_status
14396 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
14397 bool (*gimple_test_f) (tree), fallback_t fallback)
14399 tree tmp;
14400 gimple_seq internal_pre = NULL;
14401 gimple_seq internal_post = NULL;
14402 tree save_expr;
14403 bool is_statement;
14404 location_t saved_location;
14405 enum gimplify_status ret;
14406 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
14407 tree label;
14409 save_expr = *expr_p;
14410 if (save_expr == NULL_TREE)
14411 return GS_ALL_DONE;
14413 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
14414 is_statement = gimple_test_f == is_gimple_stmt;
14415 if (is_statement)
14416 gcc_assert (pre_p);
14418 /* Consistency checks. */
14419 if (gimple_test_f == is_gimple_reg)
14420 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
14421 else if (gimple_test_f == is_gimple_val
14422 || gimple_test_f == is_gimple_call_addr
14423 || gimple_test_f == is_gimple_condexpr
14424 || gimple_test_f == is_gimple_condexpr_for_cond
14425 || gimple_test_f == is_gimple_mem_rhs
14426 || gimple_test_f == is_gimple_mem_rhs_or_call
14427 || gimple_test_f == is_gimple_reg_rhs
14428 || gimple_test_f == is_gimple_reg_rhs_or_call
14429 || gimple_test_f == is_gimple_asm_val
14430 || gimple_test_f == is_gimple_mem_ref_addr)
14431 gcc_assert (fallback & fb_rvalue);
14432 else if (gimple_test_f == is_gimple_min_lval
14433 || gimple_test_f == is_gimple_lvalue)
14434 gcc_assert (fallback & fb_lvalue);
14435 else if (gimple_test_f == is_gimple_addressable)
14436 gcc_assert (fallback & fb_either);
14437 else if (gimple_test_f == is_gimple_stmt)
14438 gcc_assert (fallback == fb_none);
14439 else
14441 /* We should have recognized the GIMPLE_TEST_F predicate to
14442 know what kind of fallback to use in case a temporary is
14443 needed to hold the value or address of *EXPR_P. */
14444 gcc_unreachable ();
14447 /* We used to check the predicate here and return immediately if it
14448 succeeds. This is wrong; the design is for gimplification to be
14449 idempotent, and for the predicates to only test for valid forms, not
14450 whether they are fully simplified. */
14451 if (pre_p == NULL)
14452 pre_p = &internal_pre;
14454 if (post_p == NULL)
14455 post_p = &internal_post;
14457 /* Remember the last statements added to PRE_P and POST_P. Every
14458 new statement added by the gimplification helpers needs to be
14459 annotated with location information. To centralize the
14460 responsibility, we remember the last statement that had been
14461 added to both queues before gimplifying *EXPR_P. If
14462 gimplification produces new statements in PRE_P and POST_P, those
14463 statements will be annotated with the same location information
14464 as *EXPR_P. */
14465 pre_last_gsi = gsi_last (*pre_p);
14466 post_last_gsi = gsi_last (*post_p);
14468 saved_location = input_location;
14469 if (save_expr != error_mark_node
14470 && EXPR_HAS_LOCATION (*expr_p))
14471 input_location = EXPR_LOCATION (*expr_p);
14473 /* Loop over the specific gimplifiers until the toplevel node
14474 remains the same. */
14477 /* Strip away as many useless type conversions as possible
14478 at the toplevel. */
14479 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
14481 /* Remember the expr. */
14482 save_expr = *expr_p;
14484 /* Die, die, die, my darling. */
14485 if (error_operand_p (save_expr))
14487 ret = GS_ERROR;
14488 break;
14491 /* Do any language-specific gimplification. */
14492 ret = ((enum gimplify_status)
14493 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
14494 if (ret == GS_OK)
14496 if (*expr_p == NULL_TREE)
14497 break;
14498 if (*expr_p != save_expr)
14499 continue;
14501 else if (ret != GS_UNHANDLED)
14502 break;
14504 /* Make sure that all the cases set 'ret' appropriately. */
14505 ret = GS_UNHANDLED;
14506 switch (TREE_CODE (*expr_p))
14508 /* First deal with the special cases. */
14510 case POSTINCREMENT_EXPR:
14511 case POSTDECREMENT_EXPR:
14512 case PREINCREMENT_EXPR:
14513 case PREDECREMENT_EXPR:
14514 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
14515 fallback != fb_none,
14516 TREE_TYPE (*expr_p));
14517 break;
14519 case VIEW_CONVERT_EXPR:
14520 if ((fallback & fb_rvalue)
14521 && is_gimple_reg_type (TREE_TYPE (*expr_p))
14522 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
14524 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14525 post_p, is_gimple_val, fb_rvalue);
14526 recalculate_side_effects (*expr_p);
14527 break;
14529 /* Fallthru. */
14531 case ARRAY_REF:
14532 case ARRAY_RANGE_REF:
14533 case REALPART_EXPR:
14534 case IMAGPART_EXPR:
14535 case COMPONENT_REF:
14536 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
14537 fallback ? fallback : fb_rvalue);
14538 break;
14540 case COND_EXPR:
14541 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
14543 /* C99 code may assign to an array in a structure value of a
14544 conditional expression, and this has undefined behavior
14545 only on execution, so create a temporary if an lvalue is
14546 required. */
14547 if (fallback == fb_lvalue)
14549 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14550 mark_addressable (*expr_p);
14551 ret = GS_OK;
14553 break;
14555 case CALL_EXPR:
14556 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
14558 /* C99 code may assign to an array in a structure returned
14559 from a function, and this has undefined behavior only on
14560 execution, so create a temporary if an lvalue is
14561 required. */
14562 if (fallback == fb_lvalue)
14564 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14565 mark_addressable (*expr_p);
14566 ret = GS_OK;
14568 break;
14570 case TREE_LIST:
14571 gcc_unreachable ();
14573 case COMPOUND_EXPR:
14574 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
14575 break;
14577 case COMPOUND_LITERAL_EXPR:
14578 ret = gimplify_compound_literal_expr (expr_p, pre_p,
14579 gimple_test_f, fallback);
14580 break;
14582 case MODIFY_EXPR:
14583 case INIT_EXPR:
14584 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
14585 fallback != fb_none);
14586 break;
14588 case TRUTH_ANDIF_EXPR:
14589 case TRUTH_ORIF_EXPR:
14591 /* Preserve the original type of the expression and the
14592 source location of the outer expression. */
14593 tree org_type = TREE_TYPE (*expr_p);
14594 *expr_p = gimple_boolify (*expr_p);
14595 *expr_p = build3_loc (input_location, COND_EXPR,
14596 org_type, *expr_p,
14597 fold_convert_loc
14598 (input_location,
14599 org_type, boolean_true_node),
14600 fold_convert_loc
14601 (input_location,
14602 org_type, boolean_false_node));
14603 ret = GS_OK;
14604 break;
14607 case TRUTH_NOT_EXPR:
14609 tree type = TREE_TYPE (*expr_p);
14610 /* The parsers are careful to generate TRUTH_NOT_EXPR
14611 only with operands that are always zero or one.
14612 We do not fold here but handle the only interesting case
14613 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
14614 *expr_p = gimple_boolify (*expr_p);
14615 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
14616 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
14617 TREE_TYPE (*expr_p),
14618 TREE_OPERAND (*expr_p, 0));
14619 else
14620 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
14621 TREE_TYPE (*expr_p),
14622 TREE_OPERAND (*expr_p, 0),
14623 build_int_cst (TREE_TYPE (*expr_p), 1));
14624 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
14625 *expr_p = fold_convert_loc (input_location, type, *expr_p);
14626 ret = GS_OK;
14627 break;
14630 case ADDR_EXPR:
14631 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
14632 break;
14634 case ANNOTATE_EXPR:
14636 tree cond = TREE_OPERAND (*expr_p, 0);
14637 tree kind = TREE_OPERAND (*expr_p, 1);
14638 tree data = TREE_OPERAND (*expr_p, 2);
14639 tree type = TREE_TYPE (cond);
14640 if (!INTEGRAL_TYPE_P (type))
14642 *expr_p = cond;
14643 ret = GS_OK;
14644 break;
14646 tree tmp = create_tmp_var (type);
14647 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
14648 gcall *call
14649 = gimple_build_call_internal (IFN_ANNOTATE, 3, cond, kind, data);
14650 gimple_call_set_lhs (call, tmp);
14651 gimplify_seq_add_stmt (pre_p, call);
14652 *expr_p = tmp;
14653 ret = GS_ALL_DONE;
14654 break;
14657 case VA_ARG_EXPR:
14658 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
14659 break;
14661 CASE_CONVERT:
14662 if (IS_EMPTY_STMT (*expr_p))
14664 ret = GS_ALL_DONE;
14665 break;
14668 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
14669 || fallback == fb_none)
14671 /* Just strip a conversion to void (or in void context) and
14672 try again. */
14673 *expr_p = TREE_OPERAND (*expr_p, 0);
14674 ret = GS_OK;
14675 break;
14678 ret = gimplify_conversion (expr_p);
14679 if (ret == GS_ERROR)
14680 break;
14681 if (*expr_p != save_expr)
14682 break;
14683 /* FALLTHRU */
14685 case FIX_TRUNC_EXPR:
14686 /* unary_expr: ... | '(' cast ')' val | ... */
14687 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14688 is_gimple_val, fb_rvalue);
14689 recalculate_side_effects (*expr_p);
14690 break;
14692 case INDIRECT_REF:
14694 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
14695 bool notrap = TREE_THIS_NOTRAP (*expr_p);
14696 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
14698 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
14699 if (*expr_p != save_expr)
14701 ret = GS_OK;
14702 break;
14705 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14706 is_gimple_reg, fb_rvalue);
14707 if (ret == GS_ERROR)
14708 break;
14710 recalculate_side_effects (*expr_p);
14711 *expr_p = fold_build2_loc (input_location, MEM_REF,
14712 TREE_TYPE (*expr_p),
14713 TREE_OPERAND (*expr_p, 0),
14714 build_int_cst (saved_ptr_type, 0));
14715 TREE_THIS_VOLATILE (*expr_p) = volatilep;
14716 TREE_THIS_NOTRAP (*expr_p) = notrap;
14717 ret = GS_OK;
14718 break;
14721 /* We arrive here through the various re-gimplifcation paths. */
14722 case MEM_REF:
14723 /* First try re-folding the whole thing. */
14724 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
14725 TREE_OPERAND (*expr_p, 0),
14726 TREE_OPERAND (*expr_p, 1));
14727 if (tmp)
14729 REF_REVERSE_STORAGE_ORDER (tmp)
14730 = REF_REVERSE_STORAGE_ORDER (*expr_p);
14731 *expr_p = tmp;
14732 recalculate_side_effects (*expr_p);
14733 ret = GS_OK;
14734 break;
14736 /* Avoid re-gimplifying the address operand if it is already
14737 in suitable form. Re-gimplifying would mark the address
14738 operand addressable. Always gimplify when not in SSA form
14739 as we still may have to gimplify decls with value-exprs. */
14740 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
14741 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
14743 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14744 is_gimple_mem_ref_addr, fb_rvalue);
14745 if (ret == GS_ERROR)
14746 break;
14748 recalculate_side_effects (*expr_p);
14749 ret = GS_ALL_DONE;
14750 break;
14752 /* Constants need not be gimplified. */
14753 case INTEGER_CST:
14754 case REAL_CST:
14755 case FIXED_CST:
14756 case STRING_CST:
14757 case COMPLEX_CST:
14758 case VECTOR_CST:
14759 /* Drop the overflow flag on constants, we do not want
14760 that in the GIMPLE IL. */
14761 if (TREE_OVERFLOW_P (*expr_p))
14762 *expr_p = drop_tree_overflow (*expr_p);
14763 ret = GS_ALL_DONE;
14764 break;
14766 case CONST_DECL:
14767 /* If we require an lvalue, such as for ADDR_EXPR, retain the
14768 CONST_DECL node. Otherwise the decl is replaceable by its
14769 value. */
14770 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
14771 if (fallback & fb_lvalue)
14772 ret = GS_ALL_DONE;
14773 else
14775 *expr_p = DECL_INITIAL (*expr_p);
14776 ret = GS_OK;
14778 break;
14780 case DECL_EXPR:
14781 ret = gimplify_decl_expr (expr_p, pre_p);
14782 break;
14784 case BIND_EXPR:
14785 ret = gimplify_bind_expr (expr_p, pre_p);
14786 break;
14788 case LOOP_EXPR:
14789 ret = gimplify_loop_expr (expr_p, pre_p);
14790 break;
14792 case SWITCH_EXPR:
14793 ret = gimplify_switch_expr (expr_p, pre_p);
14794 break;
14796 case EXIT_EXPR:
14797 ret = gimplify_exit_expr (expr_p);
14798 break;
14800 case GOTO_EXPR:
14801 /* If the target is not LABEL, then it is a computed jump
14802 and the target needs to be gimplified. */
14803 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
14805 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
14806 NULL, is_gimple_val, fb_rvalue);
14807 if (ret == GS_ERROR)
14808 break;
14810 gimplify_seq_add_stmt (pre_p,
14811 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
14812 ret = GS_ALL_DONE;
14813 break;
14815 case PREDICT_EXPR:
14816 gimplify_seq_add_stmt (pre_p,
14817 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
14818 PREDICT_EXPR_OUTCOME (*expr_p)));
14819 ret = GS_ALL_DONE;
14820 break;
14822 case LABEL_EXPR:
14823 ret = gimplify_label_expr (expr_p, pre_p);
14824 label = LABEL_EXPR_LABEL (*expr_p);
14825 gcc_assert (decl_function_context (label) == current_function_decl);
14827 /* If the label is used in a goto statement, or address of the label
14828 is taken, we need to unpoison all variables that were seen so far.
14829 Doing so would prevent us from reporting a false positives. */
14830 if (asan_poisoned_variables
14831 && asan_used_labels != NULL
14832 && asan_used_labels->contains (label)
14833 && !gimplify_omp_ctxp)
14834 asan_poison_variables (asan_poisoned_variables, false, pre_p);
14835 break;
14837 case CASE_LABEL_EXPR:
14838 ret = gimplify_case_label_expr (expr_p, pre_p);
14840 if (gimplify_ctxp->live_switch_vars)
14841 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
14842 pre_p);
14843 break;
14845 case RETURN_EXPR:
14846 ret = gimplify_return_expr (*expr_p, pre_p);
14847 break;
14849 case CONSTRUCTOR:
14850 /* Don't reduce this in place; let gimplify_init_constructor work its
14851 magic. Buf if we're just elaborating this for side effects, just
14852 gimplify any element that has side-effects. */
14853 if (fallback == fb_none)
14855 unsigned HOST_WIDE_INT ix;
14856 tree val;
14857 tree temp = NULL_TREE;
14858 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
14859 if (TREE_SIDE_EFFECTS (val))
14860 append_to_statement_list (val, &temp);
14862 *expr_p = temp;
14863 ret = temp ? GS_OK : GS_ALL_DONE;
14865 /* C99 code may assign to an array in a constructed
14866 structure or union, and this has undefined behavior only
14867 on execution, so create a temporary if an lvalue is
14868 required. */
14869 else if (fallback == fb_lvalue)
14871 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14872 mark_addressable (*expr_p);
14873 ret = GS_OK;
14875 else
14876 ret = GS_ALL_DONE;
14877 break;
14879 /* The following are special cases that are not handled by the
14880 original GIMPLE grammar. */
14882 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
14883 eliminated. */
14884 case SAVE_EXPR:
14885 ret = gimplify_save_expr (expr_p, pre_p, post_p);
14886 break;
14888 case BIT_FIELD_REF:
14889 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14890 post_p, is_gimple_lvalue, fb_either);
14891 recalculate_side_effects (*expr_p);
14892 break;
14894 case TARGET_MEM_REF:
14896 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
14898 if (TMR_BASE (*expr_p))
14899 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
14900 post_p, is_gimple_mem_ref_addr, fb_either);
14901 if (TMR_INDEX (*expr_p))
14902 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
14903 post_p, is_gimple_val, fb_rvalue);
14904 if (TMR_INDEX2 (*expr_p))
14905 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
14906 post_p, is_gimple_val, fb_rvalue);
14907 /* TMR_STEP and TMR_OFFSET are always integer constants. */
14908 ret = MIN (r0, r1);
14910 break;
14912 case NON_LVALUE_EXPR:
14913 /* This should have been stripped above. */
14914 gcc_unreachable ();
14916 case ASM_EXPR:
14917 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
14918 break;
14920 case TRY_FINALLY_EXPR:
14921 case TRY_CATCH_EXPR:
14923 gimple_seq eval, cleanup;
14924 gtry *try_;
14926 /* Calls to destructors are generated automatically in FINALLY/CATCH
14927 block. They should have location as UNKNOWN_LOCATION. However,
14928 gimplify_call_expr will reset these call stmts to input_location
14929 if it finds stmt's location is unknown. To prevent resetting for
14930 destructors, we set the input_location to unknown.
14931 Note that this only affects the destructor calls in FINALLY/CATCH
14932 block, and will automatically reset to its original value by the
14933 end of gimplify_expr. */
14934 input_location = UNKNOWN_LOCATION;
14935 eval = cleanup = NULL;
14936 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
14937 if (TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
14938 && TREE_CODE (TREE_OPERAND (*expr_p, 1)) == EH_ELSE_EXPR)
14940 gimple_seq n = NULL, e = NULL;
14941 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
14942 0), &n);
14943 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
14944 1), &e);
14945 if (!gimple_seq_empty_p (n) && !gimple_seq_empty_p (e))
14947 geh_else *stmt = gimple_build_eh_else (n, e);
14948 gimple_seq_add_stmt (&cleanup, stmt);
14951 else
14952 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
14953 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
14954 if (gimple_seq_empty_p (cleanup))
14956 gimple_seq_add_seq (pre_p, eval);
14957 ret = GS_ALL_DONE;
14958 break;
14960 try_ = gimple_build_try (eval, cleanup,
14961 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
14962 ? GIMPLE_TRY_FINALLY
14963 : GIMPLE_TRY_CATCH);
14964 if (EXPR_HAS_LOCATION (save_expr))
14965 gimple_set_location (try_, EXPR_LOCATION (save_expr));
14966 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
14967 gimple_set_location (try_, saved_location);
14968 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
14969 gimple_try_set_catch_is_cleanup (try_,
14970 TRY_CATCH_IS_CLEANUP (*expr_p));
14971 gimplify_seq_add_stmt (pre_p, try_);
14972 ret = GS_ALL_DONE;
14973 break;
14976 case CLEANUP_POINT_EXPR:
14977 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
14978 break;
14980 case TARGET_EXPR:
14981 ret = gimplify_target_expr (expr_p, pre_p, post_p);
14982 break;
14984 case CATCH_EXPR:
14986 gimple *c;
14987 gimple_seq handler = NULL;
14988 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
14989 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
14990 gimplify_seq_add_stmt (pre_p, c);
14991 ret = GS_ALL_DONE;
14992 break;
14995 case EH_FILTER_EXPR:
14997 gimple *ehf;
14998 gimple_seq failure = NULL;
15000 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
15001 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
15002 copy_warning (ehf, *expr_p);
15003 gimplify_seq_add_stmt (pre_p, ehf);
15004 ret = GS_ALL_DONE;
15005 break;
15008 case OBJ_TYPE_REF:
15010 enum gimplify_status r0, r1;
15011 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
15012 post_p, is_gimple_val, fb_rvalue);
15013 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
15014 post_p, is_gimple_val, fb_rvalue);
15015 TREE_SIDE_EFFECTS (*expr_p) = 0;
15016 ret = MIN (r0, r1);
15018 break;
15020 case LABEL_DECL:
15021 /* We get here when taking the address of a label. We mark
15022 the label as "forced"; meaning it can never be removed and
15023 it is a potential target for any computed goto. */
15024 FORCED_LABEL (*expr_p) = 1;
15025 ret = GS_ALL_DONE;
15026 break;
15028 case STATEMENT_LIST:
15029 ret = gimplify_statement_list (expr_p, pre_p);
15030 break;
15032 case WITH_SIZE_EXPR:
15034 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15035 post_p == &internal_post ? NULL : post_p,
15036 gimple_test_f, fallback);
15037 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
15038 is_gimple_val, fb_rvalue);
15039 ret = GS_ALL_DONE;
15041 break;
15043 case VAR_DECL:
15044 case PARM_DECL:
15045 ret = gimplify_var_or_parm_decl (expr_p);
15046 break;
15048 case RESULT_DECL:
15049 /* When within an OMP context, notice uses of variables. */
15050 if (gimplify_omp_ctxp)
15051 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
15052 ret = GS_ALL_DONE;
15053 break;
15055 case DEBUG_EXPR_DECL:
15056 gcc_unreachable ();
15058 case DEBUG_BEGIN_STMT:
15059 gimplify_seq_add_stmt (pre_p,
15060 gimple_build_debug_begin_stmt
15061 (TREE_BLOCK (*expr_p),
15062 EXPR_LOCATION (*expr_p)));
15063 ret = GS_ALL_DONE;
15064 *expr_p = NULL;
15065 break;
15067 case SSA_NAME:
15068 /* Allow callbacks into the gimplifier during optimization. */
15069 ret = GS_ALL_DONE;
15070 break;
15072 case OMP_PARALLEL:
15073 gimplify_omp_parallel (expr_p, pre_p);
15074 ret = GS_ALL_DONE;
15075 break;
15077 case OMP_TASK:
15078 gimplify_omp_task (expr_p, pre_p);
15079 ret = GS_ALL_DONE;
15080 break;
15082 case OMP_FOR:
15083 case OMP_SIMD:
15084 case OMP_DISTRIBUTE:
15085 case OMP_TASKLOOP:
15086 case OACC_LOOP:
15087 ret = gimplify_omp_for (expr_p, pre_p);
15088 break;
15090 case OMP_LOOP:
15091 ret = gimplify_omp_loop (expr_p, pre_p);
15092 break;
15094 case OACC_CACHE:
15095 gimplify_oacc_cache (expr_p, pre_p);
15096 ret = GS_ALL_DONE;
15097 break;
15099 case OACC_DECLARE:
15100 gimplify_oacc_declare (expr_p, pre_p);
15101 ret = GS_ALL_DONE;
15102 break;
15104 case OACC_HOST_DATA:
15105 case OACC_DATA:
15106 case OACC_KERNELS:
15107 case OACC_PARALLEL:
15108 case OACC_SERIAL:
15109 case OMP_SCOPE:
15110 case OMP_SECTIONS:
15111 case OMP_SINGLE:
15112 case OMP_TARGET:
15113 case OMP_TARGET_DATA:
15114 case OMP_TEAMS:
15115 gimplify_omp_workshare (expr_p, pre_p);
15116 ret = GS_ALL_DONE;
15117 break;
15119 case OACC_ENTER_DATA:
15120 case OACC_EXIT_DATA:
15121 case OACC_UPDATE:
15122 case OMP_TARGET_UPDATE:
15123 case OMP_TARGET_ENTER_DATA:
15124 case OMP_TARGET_EXIT_DATA:
15125 gimplify_omp_target_update (expr_p, pre_p);
15126 ret = GS_ALL_DONE;
15127 break;
15129 case OMP_SECTION:
15130 case OMP_MASTER:
15131 case OMP_MASKED:
15132 case OMP_ORDERED:
15133 case OMP_CRITICAL:
15134 case OMP_SCAN:
15136 gimple_seq body = NULL;
15137 gimple *g;
15138 bool saved_in_omp_construct = in_omp_construct;
15140 in_omp_construct = true;
15141 gimplify_and_add (OMP_BODY (*expr_p), &body);
15142 in_omp_construct = saved_in_omp_construct;
15143 switch (TREE_CODE (*expr_p))
15145 case OMP_SECTION:
15146 g = gimple_build_omp_section (body);
15147 break;
15148 case OMP_MASTER:
15149 g = gimple_build_omp_master (body);
15150 break;
15151 case OMP_ORDERED:
15152 g = gimplify_omp_ordered (*expr_p, body);
15153 break;
15154 case OMP_MASKED:
15155 gimplify_scan_omp_clauses (&OMP_MASKED_CLAUSES (*expr_p),
15156 pre_p, ORT_WORKSHARE, OMP_MASKED);
15157 gimplify_adjust_omp_clauses (pre_p, body,
15158 &OMP_MASKED_CLAUSES (*expr_p),
15159 OMP_MASKED);
15160 g = gimple_build_omp_masked (body,
15161 OMP_MASKED_CLAUSES (*expr_p));
15162 break;
15163 case OMP_CRITICAL:
15164 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
15165 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
15166 gimplify_adjust_omp_clauses (pre_p, body,
15167 &OMP_CRITICAL_CLAUSES (*expr_p),
15168 OMP_CRITICAL);
15169 g = gimple_build_omp_critical (body,
15170 OMP_CRITICAL_NAME (*expr_p),
15171 OMP_CRITICAL_CLAUSES (*expr_p));
15172 break;
15173 case OMP_SCAN:
15174 gimplify_scan_omp_clauses (&OMP_SCAN_CLAUSES (*expr_p),
15175 pre_p, ORT_WORKSHARE, OMP_SCAN);
15176 gimplify_adjust_omp_clauses (pre_p, body,
15177 &OMP_SCAN_CLAUSES (*expr_p),
15178 OMP_SCAN);
15179 g = gimple_build_omp_scan (body, OMP_SCAN_CLAUSES (*expr_p));
15180 break;
15181 default:
15182 gcc_unreachable ();
15184 gimplify_seq_add_stmt (pre_p, g);
15185 ret = GS_ALL_DONE;
15186 break;
15189 case OMP_TASKGROUP:
15191 gimple_seq body = NULL;
15193 tree *pclauses = &OMP_TASKGROUP_CLAUSES (*expr_p);
15194 bool saved_in_omp_construct = in_omp_construct;
15195 gimplify_scan_omp_clauses (pclauses, pre_p, ORT_TASKGROUP,
15196 OMP_TASKGROUP);
15197 gimplify_adjust_omp_clauses (pre_p, NULL, pclauses, OMP_TASKGROUP);
15199 in_omp_construct = true;
15200 gimplify_and_add (OMP_BODY (*expr_p), &body);
15201 in_omp_construct = saved_in_omp_construct;
15202 gimple_seq cleanup = NULL;
15203 tree fn = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
15204 gimple *g = gimple_build_call (fn, 0);
15205 gimple_seq_add_stmt (&cleanup, g);
15206 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
15207 body = NULL;
15208 gimple_seq_add_stmt (&body, g);
15209 g = gimple_build_omp_taskgroup (body, *pclauses);
15210 gimplify_seq_add_stmt (pre_p, g);
15211 ret = GS_ALL_DONE;
15212 break;
15215 case OMP_ATOMIC:
15216 case OMP_ATOMIC_READ:
15217 case OMP_ATOMIC_CAPTURE_OLD:
15218 case OMP_ATOMIC_CAPTURE_NEW:
15219 ret = gimplify_omp_atomic (expr_p, pre_p);
15220 break;
15222 case TRANSACTION_EXPR:
15223 ret = gimplify_transaction (expr_p, pre_p);
15224 break;
15226 case TRUTH_AND_EXPR:
15227 case TRUTH_OR_EXPR:
15228 case TRUTH_XOR_EXPR:
15230 tree orig_type = TREE_TYPE (*expr_p);
15231 tree new_type, xop0, xop1;
15232 *expr_p = gimple_boolify (*expr_p);
15233 new_type = TREE_TYPE (*expr_p);
15234 if (!useless_type_conversion_p (orig_type, new_type))
15236 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
15237 ret = GS_OK;
15238 break;
15241 /* Boolified binary truth expressions are semantically equivalent
15242 to bitwise binary expressions. Canonicalize them to the
15243 bitwise variant. */
15244 switch (TREE_CODE (*expr_p))
15246 case TRUTH_AND_EXPR:
15247 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
15248 break;
15249 case TRUTH_OR_EXPR:
15250 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
15251 break;
15252 case TRUTH_XOR_EXPR:
15253 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
15254 break;
15255 default:
15256 break;
15258 /* Now make sure that operands have compatible type to
15259 expression's new_type. */
15260 xop0 = TREE_OPERAND (*expr_p, 0);
15261 xop1 = TREE_OPERAND (*expr_p, 1);
15262 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
15263 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
15264 new_type,
15265 xop0);
15266 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
15267 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
15268 new_type,
15269 xop1);
15270 /* Continue classified as tcc_binary. */
15271 goto expr_2;
15274 case VEC_COND_EXPR:
15275 goto expr_3;
15277 case VEC_PERM_EXPR:
15278 /* Classified as tcc_expression. */
15279 goto expr_3;
15281 case BIT_INSERT_EXPR:
15282 /* Argument 3 is a constant. */
15283 goto expr_2;
15285 case POINTER_PLUS_EXPR:
15287 enum gimplify_status r0, r1;
15288 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15289 post_p, is_gimple_val, fb_rvalue);
15290 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
15291 post_p, is_gimple_val, fb_rvalue);
15292 recalculate_side_effects (*expr_p);
15293 ret = MIN (r0, r1);
15294 break;
15297 default:
15298 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
15300 case tcc_comparison:
15301 /* Handle comparison of objects of non scalar mode aggregates
15302 with a call to memcmp. It would be nice to only have to do
15303 this for variable-sized objects, but then we'd have to allow
15304 the same nest of reference nodes we allow for MODIFY_EXPR and
15305 that's too complex.
15307 Compare scalar mode aggregates as scalar mode values. Using
15308 memcmp for them would be very inefficient at best, and is
15309 plain wrong if bitfields are involved. */
15311 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
15313 /* Vector comparisons need no boolification. */
15314 if (TREE_CODE (type) == VECTOR_TYPE)
15315 goto expr_2;
15316 else if (!AGGREGATE_TYPE_P (type))
15318 tree org_type = TREE_TYPE (*expr_p);
15319 *expr_p = gimple_boolify (*expr_p);
15320 if (!useless_type_conversion_p (org_type,
15321 TREE_TYPE (*expr_p)))
15323 *expr_p = fold_convert_loc (input_location,
15324 org_type, *expr_p);
15325 ret = GS_OK;
15327 else
15328 goto expr_2;
15330 else if (TYPE_MODE (type) != BLKmode)
15331 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
15332 else
15333 ret = gimplify_variable_sized_compare (expr_p);
15335 break;
15338 /* If *EXPR_P does not need to be special-cased, handle it
15339 according to its class. */
15340 case tcc_unary:
15341 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15342 post_p, is_gimple_val, fb_rvalue);
15343 break;
15345 case tcc_binary:
15346 expr_2:
15348 enum gimplify_status r0, r1;
15350 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15351 post_p, is_gimple_val, fb_rvalue);
15352 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
15353 post_p, is_gimple_val, fb_rvalue);
15355 ret = MIN (r0, r1);
15356 break;
15359 expr_3:
15361 enum gimplify_status r0, r1, r2;
15363 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15364 post_p, is_gimple_val, fb_rvalue);
15365 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
15366 post_p, is_gimple_val, fb_rvalue);
15367 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
15368 post_p, is_gimple_val, fb_rvalue);
15370 ret = MIN (MIN (r0, r1), r2);
15371 break;
15374 case tcc_declaration:
15375 case tcc_constant:
15376 ret = GS_ALL_DONE;
15377 goto dont_recalculate;
15379 default:
15380 gcc_unreachable ();
15383 recalculate_side_effects (*expr_p);
15385 dont_recalculate:
15386 break;
15389 gcc_assert (*expr_p || ret != GS_OK);
15391 while (ret == GS_OK);
15393 /* If we encountered an error_mark somewhere nested inside, either
15394 stub out the statement or propagate the error back out. */
15395 if (ret == GS_ERROR)
15397 if (is_statement)
15398 *expr_p = NULL;
15399 goto out;
15402 /* This was only valid as a return value from the langhook, which
15403 we handled. Make sure it doesn't escape from any other context. */
15404 gcc_assert (ret != GS_UNHANDLED);
15406 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
15408 /* We aren't looking for a value, and we don't have a valid
15409 statement. If it doesn't have side-effects, throw it away.
15410 We can also get here with code such as "*&&L;", where L is
15411 a LABEL_DECL that is marked as FORCED_LABEL. */
15412 if (TREE_CODE (*expr_p) == LABEL_DECL
15413 || !TREE_SIDE_EFFECTS (*expr_p))
15414 *expr_p = NULL;
15415 else if (!TREE_THIS_VOLATILE (*expr_p))
15417 /* This is probably a _REF that contains something nested that
15418 has side effects. Recurse through the operands to find it. */
15419 enum tree_code code = TREE_CODE (*expr_p);
15421 switch (code)
15423 case COMPONENT_REF:
15424 case REALPART_EXPR:
15425 case IMAGPART_EXPR:
15426 case VIEW_CONVERT_EXPR:
15427 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
15428 gimple_test_f, fallback);
15429 break;
15431 case ARRAY_REF:
15432 case ARRAY_RANGE_REF:
15433 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
15434 gimple_test_f, fallback);
15435 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
15436 gimple_test_f, fallback);
15437 break;
15439 default:
15440 /* Anything else with side-effects must be converted to
15441 a valid statement before we get here. */
15442 gcc_unreachable ();
15445 *expr_p = NULL;
15447 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
15448 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode
15449 && !is_empty_type (TREE_TYPE (*expr_p)))
15451 /* Historically, the compiler has treated a bare reference
15452 to a non-BLKmode volatile lvalue as forcing a load. */
15453 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
15455 /* Normally, we do not want to create a temporary for a
15456 TREE_ADDRESSABLE type because such a type should not be
15457 copied by bitwise-assignment. However, we make an
15458 exception here, as all we are doing here is ensuring that
15459 we read the bytes that make up the type. We use
15460 create_tmp_var_raw because create_tmp_var will abort when
15461 given a TREE_ADDRESSABLE type. */
15462 tree tmp = create_tmp_var_raw (type, "vol");
15463 gimple_add_tmp_var (tmp);
15464 gimplify_assign (tmp, *expr_p, pre_p);
15465 *expr_p = NULL;
15467 else
15468 /* We can't do anything useful with a volatile reference to
15469 an incomplete type, so just throw it away. Likewise for
15470 a BLKmode type, since any implicit inner load should
15471 already have been turned into an explicit one by the
15472 gimplification process. */
15473 *expr_p = NULL;
15476 /* If we are gimplifying at the statement level, we're done. Tack
15477 everything together and return. */
15478 if (fallback == fb_none || is_statement)
15480 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
15481 it out for GC to reclaim it. */
15482 *expr_p = NULL_TREE;
15484 if (!gimple_seq_empty_p (internal_pre)
15485 || !gimple_seq_empty_p (internal_post))
15487 gimplify_seq_add_seq (&internal_pre, internal_post);
15488 gimplify_seq_add_seq (pre_p, internal_pre);
15491 /* The result of gimplifying *EXPR_P is going to be the last few
15492 statements in *PRE_P and *POST_P. Add location information
15493 to all the statements that were added by the gimplification
15494 helpers. */
15495 if (!gimple_seq_empty_p (*pre_p))
15496 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
15498 if (!gimple_seq_empty_p (*post_p))
15499 annotate_all_with_location_after (*post_p, post_last_gsi,
15500 input_location);
15502 goto out;
15505 #ifdef ENABLE_GIMPLE_CHECKING
15506 if (*expr_p)
15508 enum tree_code code = TREE_CODE (*expr_p);
15509 /* These expressions should already be in gimple IR form. */
15510 gcc_assert (code != MODIFY_EXPR
15511 && code != ASM_EXPR
15512 && code != BIND_EXPR
15513 && code != CATCH_EXPR
15514 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
15515 && code != EH_FILTER_EXPR
15516 && code != GOTO_EXPR
15517 && code != LABEL_EXPR
15518 && code != LOOP_EXPR
15519 && code != SWITCH_EXPR
15520 && code != TRY_FINALLY_EXPR
15521 && code != EH_ELSE_EXPR
15522 && code != OACC_PARALLEL
15523 && code != OACC_KERNELS
15524 && code != OACC_SERIAL
15525 && code != OACC_DATA
15526 && code != OACC_HOST_DATA
15527 && code != OACC_DECLARE
15528 && code != OACC_UPDATE
15529 && code != OACC_ENTER_DATA
15530 && code != OACC_EXIT_DATA
15531 && code != OACC_CACHE
15532 && code != OMP_CRITICAL
15533 && code != OMP_FOR
15534 && code != OACC_LOOP
15535 && code != OMP_MASTER
15536 && code != OMP_MASKED
15537 && code != OMP_TASKGROUP
15538 && code != OMP_ORDERED
15539 && code != OMP_PARALLEL
15540 && code != OMP_SCAN
15541 && code != OMP_SECTIONS
15542 && code != OMP_SECTION
15543 && code != OMP_SINGLE
15544 && code != OMP_SCOPE);
15546 #endif
15548 /* Otherwise we're gimplifying a subexpression, so the resulting
15549 value is interesting. If it's a valid operand that matches
15550 GIMPLE_TEST_F, we're done. Unless we are handling some
15551 post-effects internally; if that's the case, we need to copy into
15552 a temporary before adding the post-effects to POST_P. */
15553 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
15554 goto out;
15556 /* Otherwise, we need to create a new temporary for the gimplified
15557 expression. */
15559 /* We can't return an lvalue if we have an internal postqueue. The
15560 object the lvalue refers to would (probably) be modified by the
15561 postqueue; we need to copy the value out first, which means an
15562 rvalue. */
15563 if ((fallback & fb_lvalue)
15564 && gimple_seq_empty_p (internal_post)
15565 && is_gimple_addressable (*expr_p))
15567 /* An lvalue will do. Take the address of the expression, store it
15568 in a temporary, and replace the expression with an INDIRECT_REF of
15569 that temporary. */
15570 tree ref_alias_type = reference_alias_ptr_type (*expr_p);
15571 unsigned int ref_align = get_object_alignment (*expr_p);
15572 tree ref_type = TREE_TYPE (*expr_p);
15573 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
15574 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
15575 if (TYPE_ALIGN (ref_type) != ref_align)
15576 ref_type = build_aligned_type (ref_type, ref_align);
15577 *expr_p = build2 (MEM_REF, ref_type,
15578 tmp, build_zero_cst (ref_alias_type));
15580 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
15582 /* An rvalue will do. Assign the gimplified expression into a
15583 new temporary TMP and replace the original expression with
15584 TMP. First, make sure that the expression has a type so that
15585 it can be assigned into a temporary. */
15586 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
15587 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
15589 else
15591 #ifdef ENABLE_GIMPLE_CHECKING
15592 if (!(fallback & fb_mayfail))
15594 fprintf (stderr, "gimplification failed:\n");
15595 print_generic_expr (stderr, *expr_p);
15596 debug_tree (*expr_p);
15597 internal_error ("gimplification failed");
15599 #endif
15600 gcc_assert (fallback & fb_mayfail);
15602 /* If this is an asm statement, and the user asked for the
15603 impossible, don't die. Fail and let gimplify_asm_expr
15604 issue an error. */
15605 ret = GS_ERROR;
15606 goto out;
15609 /* Make sure the temporary matches our predicate. */
15610 gcc_assert ((*gimple_test_f) (*expr_p));
15612 if (!gimple_seq_empty_p (internal_post))
15614 annotate_all_with_location (internal_post, input_location);
15615 gimplify_seq_add_seq (pre_p, internal_post);
15618 out:
15619 input_location = saved_location;
15620 return ret;
15623 /* Like gimplify_expr but make sure the gimplified result is not itself
15624 a SSA name (but a decl if it were). Temporaries required by
15625 evaluating *EXPR_P may be still SSA names. */
15627 static enum gimplify_status
15628 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
15629 bool (*gimple_test_f) (tree), fallback_t fallback,
15630 bool allow_ssa)
15632 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
15633 gimple_test_f, fallback);
15634 if (! allow_ssa
15635 && TREE_CODE (*expr_p) == SSA_NAME)
15636 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
15637 return ret;
15640 /* Look through TYPE for variable-sized objects and gimplify each such
15641 size that we find. Add to LIST_P any statements generated. */
15643 void
15644 gimplify_type_sizes (tree type, gimple_seq *list_p)
15646 if (type == NULL || type == error_mark_node)
15647 return;
15649 const bool ignored_p
15650 = TYPE_NAME (type)
15651 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
15652 && DECL_IGNORED_P (TYPE_NAME (type));
15653 tree t;
15655 /* We first do the main variant, then copy into any other variants. */
15656 type = TYPE_MAIN_VARIANT (type);
15658 /* Avoid infinite recursion. */
15659 if (TYPE_SIZES_GIMPLIFIED (type))
15660 return;
15662 TYPE_SIZES_GIMPLIFIED (type) = 1;
15664 switch (TREE_CODE (type))
15666 case INTEGER_TYPE:
15667 case ENUMERAL_TYPE:
15668 case BOOLEAN_TYPE:
15669 case REAL_TYPE:
15670 case FIXED_POINT_TYPE:
15671 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
15672 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
15674 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
15676 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
15677 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
15679 break;
15681 case ARRAY_TYPE:
15682 /* These types may not have declarations, so handle them here. */
15683 gimplify_type_sizes (TREE_TYPE (type), list_p);
15684 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
15685 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
15686 with assigned stack slots, for -O1+ -g they should be tracked
15687 by VTA. */
15688 if (!ignored_p
15689 && TYPE_DOMAIN (type)
15690 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
15692 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
15693 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
15694 DECL_IGNORED_P (t) = 0;
15695 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
15696 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
15697 DECL_IGNORED_P (t) = 0;
15699 break;
15701 case RECORD_TYPE:
15702 case UNION_TYPE:
15703 case QUAL_UNION_TYPE:
15704 for (tree field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
15705 if (TREE_CODE (field) == FIELD_DECL)
15707 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
15708 /* Likewise, ensure variable offsets aren't removed. */
15709 if (!ignored_p
15710 && (t = DECL_FIELD_OFFSET (field))
15711 && VAR_P (t)
15712 && DECL_ARTIFICIAL (t))
15713 DECL_IGNORED_P (t) = 0;
15714 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
15715 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
15716 gimplify_type_sizes (TREE_TYPE (field), list_p);
15718 break;
15720 case POINTER_TYPE:
15721 case REFERENCE_TYPE:
15722 /* We used to recurse on the pointed-to type here, which turned out to
15723 be incorrect because its definition might refer to variables not
15724 yet initialized at this point if a forward declaration is involved.
15726 It was actually useful for anonymous pointed-to types to ensure
15727 that the sizes evaluation dominates every possible later use of the
15728 values. Restricting to such types here would be safe since there
15729 is no possible forward declaration around, but would introduce an
15730 undesirable middle-end semantic to anonymity. We then defer to
15731 front-ends the responsibility of ensuring that the sizes are
15732 evaluated both early and late enough, e.g. by attaching artificial
15733 type declarations to the tree. */
15734 break;
15736 default:
15737 break;
15740 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
15741 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
15743 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
15745 TYPE_SIZE (t) = TYPE_SIZE (type);
15746 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
15747 TYPE_SIZES_GIMPLIFIED (t) = 1;
15751 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
15752 a size or position, has had all of its SAVE_EXPRs evaluated.
15753 We add any required statements to *STMT_P. */
15755 void
15756 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
15758 tree expr = *expr_p;
15760 /* We don't do anything if the value isn't there, is constant, or contains
15761 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
15762 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
15763 will want to replace it with a new variable, but that will cause problems
15764 if this type is from outside the function. It's OK to have that here. */
15765 if (expr == NULL_TREE
15766 || is_gimple_constant (expr)
15767 || TREE_CODE (expr) == VAR_DECL
15768 || CONTAINS_PLACEHOLDER_P (expr))
15769 return;
15771 *expr_p = unshare_expr (expr);
15773 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
15774 if the def vanishes. */
15775 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
15777 /* If expr wasn't already is_gimple_sizepos or is_gimple_constant from the
15778 FE, ensure that it is a VAR_DECL, otherwise we might handle some decls
15779 as gimplify_vla_decl even when they would have all sizes INTEGER_CSTs. */
15780 if (is_gimple_constant (*expr_p))
15781 *expr_p = get_initialized_tmp_var (*expr_p, stmt_p, NULL, false);
15784 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
15785 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
15786 is true, also gimplify the parameters. */
15788 gbind *
15789 gimplify_body (tree fndecl, bool do_parms)
15791 location_t saved_location = input_location;
15792 gimple_seq parm_stmts, parm_cleanup = NULL, seq;
15793 gimple *outer_stmt;
15794 gbind *outer_bind;
15796 timevar_push (TV_TREE_GIMPLIFY);
15798 init_tree_ssa (cfun);
15800 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
15801 gimplification. */
15802 default_rtl_profile ();
15804 gcc_assert (gimplify_ctxp == NULL);
15805 push_gimplify_context (true);
15807 if (flag_openacc || flag_openmp)
15809 gcc_assert (gimplify_omp_ctxp == NULL);
15810 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
15811 gimplify_omp_ctxp = new_omp_context (ORT_IMPLICIT_TARGET);
15814 /* Unshare most shared trees in the body and in that of any nested functions.
15815 It would seem we don't have to do this for nested functions because
15816 they are supposed to be output and then the outer function gimplified
15817 first, but the g++ front end doesn't always do it that way. */
15818 unshare_body (fndecl);
15819 unvisit_body (fndecl);
15821 /* Make sure input_location isn't set to something weird. */
15822 input_location = DECL_SOURCE_LOCATION (fndecl);
15824 /* Resolve callee-copies. This has to be done before processing
15825 the body so that DECL_VALUE_EXPR gets processed correctly. */
15826 parm_stmts = do_parms ? gimplify_parameters (&parm_cleanup) : NULL;
15828 /* Gimplify the function's body. */
15829 seq = NULL;
15830 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
15831 outer_stmt = gimple_seq_first_nondebug_stmt (seq);
15832 if (!outer_stmt)
15834 outer_stmt = gimple_build_nop ();
15835 gimplify_seq_add_stmt (&seq, outer_stmt);
15838 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
15839 not the case, wrap everything in a GIMPLE_BIND to make it so. */
15840 if (gimple_code (outer_stmt) == GIMPLE_BIND
15841 && (gimple_seq_first_nondebug_stmt (seq)
15842 == gimple_seq_last_nondebug_stmt (seq)))
15844 outer_bind = as_a <gbind *> (outer_stmt);
15845 if (gimple_seq_first_stmt (seq) != outer_stmt
15846 || gimple_seq_last_stmt (seq) != outer_stmt)
15848 /* If there are debug stmts before or after outer_stmt, move them
15849 inside of outer_bind body. */
15850 gimple_stmt_iterator gsi = gsi_for_stmt (outer_stmt, &seq);
15851 gimple_seq second_seq = NULL;
15852 if (gimple_seq_first_stmt (seq) != outer_stmt
15853 && gimple_seq_last_stmt (seq) != outer_stmt)
15855 second_seq = gsi_split_seq_after (gsi);
15856 gsi_remove (&gsi, false);
15858 else if (gimple_seq_first_stmt (seq) != outer_stmt)
15859 gsi_remove (&gsi, false);
15860 else
15862 gsi_remove (&gsi, false);
15863 second_seq = seq;
15864 seq = NULL;
15866 gimple_seq_add_seq_without_update (&seq,
15867 gimple_bind_body (outer_bind));
15868 gimple_seq_add_seq_without_update (&seq, second_seq);
15869 gimple_bind_set_body (outer_bind, seq);
15872 else
15873 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
15875 DECL_SAVED_TREE (fndecl) = NULL_TREE;
15877 /* If we had callee-copies statements, insert them at the beginning
15878 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
15879 if (!gimple_seq_empty_p (parm_stmts))
15881 tree parm;
15883 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
15884 if (parm_cleanup)
15886 gtry *g = gimple_build_try (parm_stmts, parm_cleanup,
15887 GIMPLE_TRY_FINALLY);
15888 parm_stmts = NULL;
15889 gimple_seq_add_stmt (&parm_stmts, g);
15891 gimple_bind_set_body (outer_bind, parm_stmts);
15893 for (parm = DECL_ARGUMENTS (current_function_decl);
15894 parm; parm = DECL_CHAIN (parm))
15895 if (DECL_HAS_VALUE_EXPR_P (parm))
15897 DECL_HAS_VALUE_EXPR_P (parm) = 0;
15898 DECL_IGNORED_P (parm) = 0;
15902 if ((flag_openacc || flag_openmp || flag_openmp_simd)
15903 && gimplify_omp_ctxp)
15905 delete_omp_context (gimplify_omp_ctxp);
15906 gimplify_omp_ctxp = NULL;
15909 pop_gimplify_context (outer_bind);
15910 gcc_assert (gimplify_ctxp == NULL);
15912 if (flag_checking && !seen_error ())
15913 verify_gimple_in_seq (gimple_bind_body (outer_bind));
15915 timevar_pop (TV_TREE_GIMPLIFY);
15916 input_location = saved_location;
15918 return outer_bind;
15921 typedef char *char_p; /* For DEF_VEC_P. */
15923 /* Return whether we should exclude FNDECL from instrumentation. */
15925 static bool
15926 flag_instrument_functions_exclude_p (tree fndecl)
15928 vec<char_p> *v;
15930 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
15931 if (v && v->length () > 0)
15933 const char *name;
15934 int i;
15935 char *s;
15937 name = lang_hooks.decl_printable_name (fndecl, 1);
15938 FOR_EACH_VEC_ELT (*v, i, s)
15939 if (strstr (name, s) != NULL)
15940 return true;
15943 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
15944 if (v && v->length () > 0)
15946 const char *name;
15947 int i;
15948 char *s;
15950 name = DECL_SOURCE_FILE (fndecl);
15951 FOR_EACH_VEC_ELT (*v, i, s)
15952 if (strstr (name, s) != NULL)
15953 return true;
15956 return false;
15959 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
15960 node for the function we want to gimplify.
15962 Return the sequence of GIMPLE statements corresponding to the body
15963 of FNDECL. */
15965 void
15966 gimplify_function_tree (tree fndecl)
15968 gimple_seq seq;
15969 gbind *bind;
15971 gcc_assert (!gimple_body (fndecl));
15973 if (DECL_STRUCT_FUNCTION (fndecl))
15974 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
15975 else
15976 push_struct_function (fndecl);
15978 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
15979 if necessary. */
15980 cfun->curr_properties |= PROP_gimple_lva;
15982 if (asan_sanitize_use_after_scope ())
15983 asan_poisoned_variables = new hash_set<tree> ();
15984 bind = gimplify_body (fndecl, true);
15985 if (asan_poisoned_variables)
15987 delete asan_poisoned_variables;
15988 asan_poisoned_variables = NULL;
15991 /* The tree body of the function is no longer needed, replace it
15992 with the new GIMPLE body. */
15993 seq = NULL;
15994 gimple_seq_add_stmt (&seq, bind);
15995 gimple_set_body (fndecl, seq);
15997 /* If we're instrumenting function entry/exit, then prepend the call to
15998 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
15999 catch the exit hook. */
16000 /* ??? Add some way to ignore exceptions for this TFE. */
16001 if (flag_instrument_function_entry_exit
16002 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
16003 /* Do not instrument extern inline functions. */
16004 && !(DECL_DECLARED_INLINE_P (fndecl)
16005 && DECL_EXTERNAL (fndecl)
16006 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
16007 && !flag_instrument_functions_exclude_p (fndecl))
16009 tree x;
16010 gbind *new_bind;
16011 gimple *tf;
16012 gimple_seq cleanup = NULL, body = NULL;
16013 tree tmp_var, this_fn_addr;
16014 gcall *call;
16016 /* The instrumentation hooks aren't going to call the instrumented
16017 function and the address they receive is expected to be matchable
16018 against symbol addresses. Make sure we don't create a trampoline,
16019 in case the current function is nested. */
16020 this_fn_addr = build_fold_addr_expr (current_function_decl);
16021 TREE_NO_TRAMPOLINE (this_fn_addr) = 1;
16023 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
16024 call = gimple_build_call (x, 1, integer_zero_node);
16025 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
16026 gimple_call_set_lhs (call, tmp_var);
16027 gimplify_seq_add_stmt (&cleanup, call);
16028 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
16029 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
16030 gimplify_seq_add_stmt (&cleanup, call);
16031 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
16033 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
16034 call = gimple_build_call (x, 1, integer_zero_node);
16035 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
16036 gimple_call_set_lhs (call, tmp_var);
16037 gimplify_seq_add_stmt (&body, call);
16038 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
16039 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
16040 gimplify_seq_add_stmt (&body, call);
16041 gimplify_seq_add_stmt (&body, tf);
16042 new_bind = gimple_build_bind (NULL, body, NULL);
16044 /* Replace the current function body with the body
16045 wrapped in the try/finally TF. */
16046 seq = NULL;
16047 gimple_seq_add_stmt (&seq, new_bind);
16048 gimple_set_body (fndecl, seq);
16049 bind = new_bind;
16052 if (sanitize_flags_p (SANITIZE_THREAD)
16053 && param_tsan_instrument_func_entry_exit)
16055 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
16056 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
16057 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
16058 /* Replace the current function body with the body
16059 wrapped in the try/finally TF. */
16060 seq = NULL;
16061 gimple_seq_add_stmt (&seq, new_bind);
16062 gimple_set_body (fndecl, seq);
16065 DECL_SAVED_TREE (fndecl) = NULL_TREE;
16066 cfun->curr_properties |= PROP_gimple_any;
16068 pop_cfun ();
16070 dump_function (TDI_gimple, fndecl);
16073 /* Return a dummy expression of type TYPE in order to keep going after an
16074 error. */
16076 static tree
16077 dummy_object (tree type)
16079 tree t = build_int_cst (build_pointer_type (type), 0);
16080 return build2 (MEM_REF, type, t, t);
16083 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
16084 builtin function, but a very special sort of operator. */
16086 enum gimplify_status
16087 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
16088 gimple_seq *post_p ATTRIBUTE_UNUSED)
16090 tree promoted_type, have_va_type;
16091 tree valist = TREE_OPERAND (*expr_p, 0);
16092 tree type = TREE_TYPE (*expr_p);
16093 tree t, tag, aptag;
16094 location_t loc = EXPR_LOCATION (*expr_p);
16096 /* Verify that valist is of the proper type. */
16097 have_va_type = TREE_TYPE (valist);
16098 if (have_va_type == error_mark_node)
16099 return GS_ERROR;
16100 have_va_type = targetm.canonical_va_list_type (have_va_type);
16101 if (have_va_type == NULL_TREE
16102 && POINTER_TYPE_P (TREE_TYPE (valist)))
16103 /* Handle 'Case 1: Not an array type' from c-common.c/build_va_arg. */
16104 have_va_type
16105 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
16106 gcc_assert (have_va_type != NULL_TREE);
16108 /* Generate a diagnostic for requesting data of a type that cannot
16109 be passed through `...' due to type promotion at the call site. */
16110 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
16111 != type)
16113 static bool gave_help;
16114 bool warned;
16115 /* Use the expansion point to handle cases such as passing bool (defined
16116 in a system header) through `...'. */
16117 location_t xloc
16118 = expansion_point_location_if_in_system_header (loc);
16120 /* Unfortunately, this is merely undefined, rather than a constraint
16121 violation, so we cannot make this an error. If this call is never
16122 executed, the program is still strictly conforming. */
16123 auto_diagnostic_group d;
16124 warned = warning_at (xloc, 0,
16125 "%qT is promoted to %qT when passed through %<...%>",
16126 type, promoted_type);
16127 if (!gave_help && warned)
16129 gave_help = true;
16130 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
16131 promoted_type, type);
16134 /* We can, however, treat "undefined" any way we please.
16135 Call abort to encourage the user to fix the program. */
16136 if (warned)
16137 inform (xloc, "if this code is reached, the program will abort");
16138 /* Before the abort, allow the evaluation of the va_list
16139 expression to exit or longjmp. */
16140 gimplify_and_add (valist, pre_p);
16141 t = build_call_expr_loc (loc,
16142 builtin_decl_implicit (BUILT_IN_TRAP), 0);
16143 gimplify_and_add (t, pre_p);
16145 /* This is dead code, but go ahead and finish so that the
16146 mode of the result comes out right. */
16147 *expr_p = dummy_object (type);
16148 return GS_ALL_DONE;
16151 tag = build_int_cst (build_pointer_type (type), 0);
16152 aptag = build_int_cst (TREE_TYPE (valist), 0);
16154 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
16155 valist, tag, aptag);
16157 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
16158 needs to be expanded. */
16159 cfun->curr_properties &= ~PROP_gimple_lva;
16161 return GS_OK;
16164 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
16166 DST/SRC are the destination and source respectively. You can pass
16167 ungimplified trees in DST or SRC, in which case they will be
16168 converted to a gimple operand if necessary.
16170 This function returns the newly created GIMPLE_ASSIGN tuple. */
16172 gimple *
16173 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
16175 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
16176 gimplify_and_add (t, seq_p);
16177 ggc_free (t);
16178 return gimple_seq_last_stmt (*seq_p);
16181 inline hashval_t
16182 gimplify_hasher::hash (const elt_t *p)
16184 tree t = p->val;
16185 return iterative_hash_expr (t, 0);
16188 inline bool
16189 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
16191 tree t1 = p1->val;
16192 tree t2 = p2->val;
16193 enum tree_code code = TREE_CODE (t1);
16195 if (TREE_CODE (t2) != code
16196 || TREE_TYPE (t1) != TREE_TYPE (t2))
16197 return false;
16199 if (!operand_equal_p (t1, t2, 0))
16200 return false;
16202 /* Only allow them to compare equal if they also hash equal; otherwise
16203 results are nondeterminate, and we fail bootstrap comparison. */
16204 gcc_checking_assert (hash (p1) == hash (p2));
16206 return true;