Default to dwarf version 4 on hppa64-hpux
[official-gcc.git] / gcc / gimplify.c
blobf4bc649632eca1b1cc55274db7909a4a8de2258d
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 && (flag_auto_var_init > AUTO_INIT_UNINITIALIZED)
1829 && (!lookup_attribute ("uninitialized", DECL_ATTRIBUTES (decl)))
1830 && !is_empty_type (TREE_TYPE (decl)))
1831 return true;
1832 return false;
1835 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1836 and initialization explicit. */
1838 static enum gimplify_status
1839 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1841 tree stmt = *stmt_p;
1842 tree decl = DECL_EXPR_DECL (stmt);
1844 *stmt_p = NULL_TREE;
1846 if (TREE_TYPE (decl) == error_mark_node)
1847 return GS_ERROR;
1849 if ((TREE_CODE (decl) == TYPE_DECL
1850 || VAR_P (decl))
1851 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1853 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1854 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
1855 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
1858 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1859 in case its size expressions contain problematic nodes like CALL_EXPR. */
1860 if (TREE_CODE (decl) == TYPE_DECL
1861 && DECL_ORIGINAL_TYPE (decl)
1862 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1864 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1865 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
1866 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
1869 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
1871 tree init = DECL_INITIAL (decl);
1872 bool is_vla = false;
1874 poly_uint64 size;
1875 if (!poly_int_tree_p (DECL_SIZE_UNIT (decl), &size)
1876 || (!TREE_STATIC (decl)
1877 && flag_stack_check == GENERIC_STACK_CHECK
1878 && maybe_gt (size,
1879 (unsigned HOST_WIDE_INT) STACK_CHECK_MAX_VAR_SIZE)))
1881 gimplify_vla_decl (decl, seq_p);
1882 is_vla = true;
1885 if (asan_poisoned_variables
1886 && !is_vla
1887 && TREE_ADDRESSABLE (decl)
1888 && !TREE_STATIC (decl)
1889 && !DECL_HAS_VALUE_EXPR_P (decl)
1890 && DECL_ALIGN (decl) <= MAX_SUPPORTED_STACK_ALIGNMENT
1891 && dbg_cnt (asan_use_after_scope)
1892 && !gimplify_omp_ctxp
1893 /* GNAT introduces temporaries to hold return values of calls in
1894 initializers of variables defined in other units, so the
1895 declaration of the variable is discarded completely. We do not
1896 want to issue poison calls for such dropped variables. */
1897 && (DECL_SEEN_IN_BIND_EXPR_P (decl)
1898 || (DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)))
1900 asan_poisoned_variables->add (decl);
1901 asan_poison_variable (decl, false, seq_p);
1902 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
1903 gimplify_ctxp->live_switch_vars->add (decl);
1906 /* Some front ends do not explicitly declare all anonymous
1907 artificial variables. We compensate here by declaring the
1908 variables, though it would be better if the front ends would
1909 explicitly declare them. */
1910 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1911 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1912 gimple_add_tmp_var (decl);
1914 if (init && init != error_mark_node)
1916 if (!TREE_STATIC (decl))
1918 DECL_INITIAL (decl) = NULL_TREE;
1919 init = build2 (INIT_EXPR, void_type_node, decl, init);
1920 gimplify_and_add (init, seq_p);
1921 ggc_free (init);
1922 /* Clear TREE_READONLY if we really have an initialization. */
1923 if (!DECL_INITIAL (decl)
1924 && !omp_privatize_by_reference (decl))
1925 TREE_READONLY (decl) = 0;
1927 else
1928 /* We must still examine initializers for static variables
1929 as they may contain a label address. */
1930 walk_tree (&init, force_labels_r, NULL, NULL);
1932 /* When there is no explicit initializer, if the user requested,
1933 We should insert an artifical initializer for this automatic
1934 variable. */
1935 else if (is_var_need_auto_init (decl))
1937 gimple_add_init_for_auto_var (decl,
1938 flag_auto_var_init,
1939 is_vla,
1940 seq_p);
1941 /* The expanding of a call to the above .DEFERRED_INIT will apply
1942 block initialization to the whole space covered by this variable.
1943 As a result, all the paddings will be initialized to zeroes
1944 for zero initialization and 0xFE byte-repeatable patterns for
1945 pattern initialization.
1946 In order to make the paddings as zeroes for pattern init, We
1947 should add a call to __builtin_clear_padding to clear the
1948 paddings to zero in compatiple with CLANG. */
1949 if (flag_auto_var_init == AUTO_INIT_PATTERN)
1950 gimple_add_padding_init_for_auto_var (decl, is_vla, seq_p);
1954 return GS_ALL_DONE;
1957 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1958 and replacing the LOOP_EXPR with goto, but if the loop contains an
1959 EXIT_EXPR, we need to append a label for it to jump to. */
1961 static enum gimplify_status
1962 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1964 tree saved_label = gimplify_ctxp->exit_label;
1965 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1967 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1969 gimplify_ctxp->exit_label = NULL_TREE;
1971 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1973 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
1975 if (gimplify_ctxp->exit_label)
1976 gimplify_seq_add_stmt (pre_p,
1977 gimple_build_label (gimplify_ctxp->exit_label));
1979 gimplify_ctxp->exit_label = saved_label;
1981 *expr_p = NULL;
1982 return GS_ALL_DONE;
1985 /* Gimplify a statement list onto a sequence. These may be created either
1986 by an enlightened front-end, or by shortcut_cond_expr. */
1988 static enum gimplify_status
1989 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
1991 tree temp = voidify_wrapper_expr (*expr_p, NULL);
1993 tree_stmt_iterator i = tsi_start (*expr_p);
1995 while (!tsi_end_p (i))
1997 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
1998 tsi_delink (&i);
2001 if (temp)
2003 *expr_p = temp;
2004 return GS_OK;
2007 return GS_ALL_DONE;
2010 /* Callback for walk_gimple_seq. */
2012 static tree
2013 warn_switch_unreachable_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2014 struct walk_stmt_info *wi)
2016 gimple *stmt = gsi_stmt (*gsi_p);
2018 *handled_ops_p = true;
2019 switch (gimple_code (stmt))
2021 case GIMPLE_TRY:
2022 /* A compiler-generated cleanup or a user-written try block.
2023 If it's empty, don't dive into it--that would result in
2024 worse location info. */
2025 if (gimple_try_eval (stmt) == NULL)
2027 wi->info = stmt;
2028 return integer_zero_node;
2030 /* Fall through. */
2031 case GIMPLE_BIND:
2032 case GIMPLE_CATCH:
2033 case GIMPLE_EH_FILTER:
2034 case GIMPLE_TRANSACTION:
2035 /* Walk the sub-statements. */
2036 *handled_ops_p = false;
2037 break;
2039 case GIMPLE_DEBUG:
2040 /* Ignore these. We may generate them before declarations that
2041 are never executed. If there's something to warn about,
2042 there will be non-debug stmts too, and we'll catch those. */
2043 break;
2045 case GIMPLE_CALL:
2046 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2048 *handled_ops_p = false;
2049 break;
2051 /* Fall through. */
2052 default:
2053 /* Save the first "real" statement (not a decl/lexical scope/...). */
2054 wi->info = stmt;
2055 return integer_zero_node;
2057 return NULL_TREE;
2060 /* Possibly warn about unreachable statements between switch's controlling
2061 expression and the first case. SEQ is the body of a switch expression. */
2063 static void
2064 maybe_warn_switch_unreachable (gimple_seq seq)
2066 if (!warn_switch_unreachable
2067 /* This warning doesn't play well with Fortran when optimizations
2068 are on. */
2069 || lang_GNU_Fortran ()
2070 || seq == NULL)
2071 return;
2073 struct walk_stmt_info wi;
2074 memset (&wi, 0, sizeof (wi));
2075 walk_gimple_seq (seq, warn_switch_unreachable_r, NULL, &wi);
2076 gimple *stmt = (gimple *) wi.info;
2078 if (stmt && gimple_code (stmt) != GIMPLE_LABEL)
2080 if (gimple_code (stmt) == GIMPLE_GOTO
2081 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
2082 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
2083 /* Don't warn for compiler-generated gotos. These occur
2084 in Duff's devices, for example. */;
2085 else
2086 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
2087 "statement will never be executed");
2092 /* A label entry that pairs label and a location. */
2093 struct label_entry
2095 tree label;
2096 location_t loc;
2099 /* Find LABEL in vector of label entries VEC. */
2101 static struct label_entry *
2102 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
2104 unsigned int i;
2105 struct label_entry *l;
2107 FOR_EACH_VEC_ELT (*vec, i, l)
2108 if (l->label == label)
2109 return l;
2110 return NULL;
2113 /* Return true if LABEL, a LABEL_DECL, represents a case label
2114 in a vector of labels CASES. */
2116 static bool
2117 case_label_p (const vec<tree> *cases, tree label)
2119 unsigned int i;
2120 tree l;
2122 FOR_EACH_VEC_ELT (*cases, i, l)
2123 if (CASE_LABEL (l) == label)
2124 return true;
2125 return false;
2128 /* Find the last nondebug statement in a scope STMT. */
2130 static gimple *
2131 last_stmt_in_scope (gimple *stmt)
2133 if (!stmt)
2134 return NULL;
2136 switch (gimple_code (stmt))
2138 case GIMPLE_BIND:
2140 gbind *bind = as_a <gbind *> (stmt);
2141 stmt = gimple_seq_last_nondebug_stmt (gimple_bind_body (bind));
2142 return last_stmt_in_scope (stmt);
2145 case GIMPLE_TRY:
2147 gtry *try_stmt = as_a <gtry *> (stmt);
2148 stmt = gimple_seq_last_nondebug_stmt (gimple_try_eval (try_stmt));
2149 gimple *last_eval = last_stmt_in_scope (stmt);
2150 if (gimple_stmt_may_fallthru (last_eval)
2151 && (last_eval == NULL
2152 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
2153 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
2155 stmt = gimple_seq_last_nondebug_stmt (gimple_try_cleanup (try_stmt));
2156 return last_stmt_in_scope (stmt);
2158 else
2159 return last_eval;
2162 case GIMPLE_DEBUG:
2163 gcc_unreachable ();
2165 default:
2166 return stmt;
2170 /* Collect interesting labels in LABELS and return the statement preceding
2171 another case label, or a user-defined label. Store a location useful
2172 to give warnings at *PREVLOC (usually the location of the returned
2173 statement or of its surrounding scope). */
2175 static gimple *
2176 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
2177 auto_vec <struct label_entry> *labels,
2178 location_t *prevloc)
2180 gimple *prev = NULL;
2182 *prevloc = UNKNOWN_LOCATION;
2185 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND)
2187 /* Recognize the special GIMPLE_BIND added by gimplify_switch_expr,
2188 which starts on a GIMPLE_SWITCH and ends with a break label.
2189 Handle that as a single statement that can fall through. */
2190 gbind *bind = as_a <gbind *> (gsi_stmt (*gsi_p));
2191 gimple *first = gimple_seq_first_stmt (gimple_bind_body (bind));
2192 gimple *last = gimple_seq_last_stmt (gimple_bind_body (bind));
2193 if (last
2194 && gimple_code (first) == GIMPLE_SWITCH
2195 && gimple_code (last) == GIMPLE_LABEL)
2197 tree label = gimple_label_label (as_a <glabel *> (last));
2198 if (SWITCH_BREAK_LABEL_P (label))
2200 prev = bind;
2201 gsi_next (gsi_p);
2202 continue;
2206 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
2207 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
2209 /* Nested scope. Only look at the last statement of
2210 the innermost scope. */
2211 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
2212 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
2213 if (last)
2215 prev = last;
2216 /* It might be a label without a location. Use the
2217 location of the scope then. */
2218 if (!gimple_has_location (prev))
2219 *prevloc = bind_loc;
2221 gsi_next (gsi_p);
2222 continue;
2225 /* Ifs are tricky. */
2226 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
2228 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
2229 tree false_lab = gimple_cond_false_label (cond_stmt);
2230 location_t if_loc = gimple_location (cond_stmt);
2232 /* If we have e.g.
2233 if (i > 1) goto <D.2259>; else goto D;
2234 we can't do much with the else-branch. */
2235 if (!DECL_ARTIFICIAL (false_lab))
2236 break;
2238 /* Go on until the false label, then one step back. */
2239 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
2241 gimple *stmt = gsi_stmt (*gsi_p);
2242 if (gimple_code (stmt) == GIMPLE_LABEL
2243 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
2244 break;
2247 /* Not found? Oops. */
2248 if (gsi_end_p (*gsi_p))
2249 break;
2251 struct label_entry l = { false_lab, if_loc };
2252 labels->safe_push (l);
2254 /* Go to the last statement of the then branch. */
2255 gsi_prev (gsi_p);
2257 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
2258 <D.1759>:
2259 <stmt>;
2260 goto <D.1761>;
2261 <D.1760>:
2263 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
2264 && !gimple_has_location (gsi_stmt (*gsi_p)))
2266 /* Look at the statement before, it might be
2267 attribute fallthrough, in which case don't warn. */
2268 gsi_prev (gsi_p);
2269 bool fallthru_before_dest
2270 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
2271 gsi_next (gsi_p);
2272 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
2273 if (!fallthru_before_dest)
2275 struct label_entry l = { goto_dest, if_loc };
2276 labels->safe_push (l);
2279 /* And move back. */
2280 gsi_next (gsi_p);
2283 /* Remember the last statement. Skip labels that are of no interest
2284 to us. */
2285 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2287 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
2288 if (find_label_entry (labels, label))
2289 prev = gsi_stmt (*gsi_p);
2291 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
2293 else if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_PREDICT)
2295 else if (!is_gimple_debug (gsi_stmt (*gsi_p)))
2296 prev = gsi_stmt (*gsi_p);
2297 gsi_next (gsi_p);
2299 while (!gsi_end_p (*gsi_p)
2300 /* Stop if we find a case or a user-defined label. */
2301 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
2302 || !gimple_has_location (gsi_stmt (*gsi_p))));
2304 if (prev && gimple_has_location (prev))
2305 *prevloc = gimple_location (prev);
2306 return prev;
2309 /* Return true if the switch fallthough warning should occur. LABEL is
2310 the label statement that we're falling through to. */
2312 static bool
2313 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
2315 gimple_stmt_iterator gsi = *gsi_p;
2317 /* Don't warn if the label is marked with a "falls through" comment. */
2318 if (FALLTHROUGH_LABEL_P (label))
2319 return false;
2321 /* Don't warn for non-case labels followed by a statement:
2322 case 0:
2323 foo ();
2324 label:
2325 bar ();
2326 as these are likely intentional. */
2327 if (!case_label_p (&gimplify_ctxp->case_labels, label))
2329 tree l;
2330 while (!gsi_end_p (gsi)
2331 && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2332 && (l = gimple_label_label (as_a <glabel *> (gsi_stmt (gsi))))
2333 && !case_label_p (&gimplify_ctxp->case_labels, l))
2334 gsi_next_nondebug (&gsi);
2335 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
2336 return false;
2339 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2340 immediately breaks. */
2341 gsi = *gsi_p;
2343 /* Skip all immediately following labels. */
2344 while (!gsi_end_p (gsi)
2345 && (gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2346 || gimple_code (gsi_stmt (gsi)) == GIMPLE_PREDICT))
2347 gsi_next_nondebug (&gsi);
2349 /* { ... something; default:; } */
2350 if (gsi_end_p (gsi)
2351 /* { ... something; default: break; } or
2352 { ... something; default: goto L; } */
2353 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2354 /* { ... something; default: return; } */
2355 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2356 return false;
2358 return true;
2361 /* Callback for walk_gimple_seq. */
2363 static tree
2364 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2365 struct walk_stmt_info *)
2367 gimple *stmt = gsi_stmt (*gsi_p);
2369 *handled_ops_p = true;
2370 switch (gimple_code (stmt))
2372 case GIMPLE_TRY:
2373 case GIMPLE_BIND:
2374 case GIMPLE_CATCH:
2375 case GIMPLE_EH_FILTER:
2376 case GIMPLE_TRANSACTION:
2377 /* Walk the sub-statements. */
2378 *handled_ops_p = false;
2379 break;
2381 /* Find a sequence of form:
2383 GIMPLE_LABEL
2384 [...]
2385 <may fallthru stmt>
2386 GIMPLE_LABEL
2388 and possibly warn. */
2389 case GIMPLE_LABEL:
2391 /* Found a label. Skip all immediately following labels. */
2392 while (!gsi_end_p (*gsi_p)
2393 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2394 gsi_next_nondebug (gsi_p);
2396 /* There might be no more statements. */
2397 if (gsi_end_p (*gsi_p))
2398 return integer_zero_node;
2400 /* Vector of labels that fall through. */
2401 auto_vec <struct label_entry> labels;
2402 location_t prevloc;
2403 gimple *prev = collect_fallthrough_labels (gsi_p, &labels, &prevloc);
2405 /* There might be no more statements. */
2406 if (gsi_end_p (*gsi_p))
2407 return integer_zero_node;
2409 gimple *next = gsi_stmt (*gsi_p);
2410 tree label;
2411 /* If what follows is a label, then we may have a fallthrough. */
2412 if (gimple_code (next) == GIMPLE_LABEL
2413 && gimple_has_location (next)
2414 && (label = gimple_label_label (as_a <glabel *> (next)))
2415 && prev != NULL)
2417 struct label_entry *l;
2418 bool warned_p = false;
2419 auto_diagnostic_group d;
2420 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2421 /* Quiet. */;
2422 else if (gimple_code (prev) == GIMPLE_LABEL
2423 && (label = gimple_label_label (as_a <glabel *> (prev)))
2424 && (l = find_label_entry (&labels, label)))
2425 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2426 "this statement may fall through");
2427 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2428 /* Try to be clever and don't warn when the statement
2429 can't actually fall through. */
2430 && gimple_stmt_may_fallthru (prev)
2431 && prevloc != UNKNOWN_LOCATION)
2432 warned_p = warning_at (prevloc,
2433 OPT_Wimplicit_fallthrough_,
2434 "this statement may fall through");
2435 if (warned_p)
2436 inform (gimple_location (next), "here");
2438 /* Mark this label as processed so as to prevent multiple
2439 warnings in nested switches. */
2440 FALLTHROUGH_LABEL_P (label) = true;
2442 /* So that next warn_implicit_fallthrough_r will start looking for
2443 a new sequence starting with this label. */
2444 gsi_prev (gsi_p);
2447 break;
2448 default:
2449 break;
2451 return NULL_TREE;
2454 /* Warn when a switch case falls through. */
2456 static void
2457 maybe_warn_implicit_fallthrough (gimple_seq seq)
2459 if (!warn_implicit_fallthrough)
2460 return;
2462 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2463 if (!(lang_GNU_C ()
2464 || lang_GNU_CXX ()
2465 || lang_GNU_OBJC ()))
2466 return;
2468 struct walk_stmt_info wi;
2469 memset (&wi, 0, sizeof (wi));
2470 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2473 /* Callback for walk_gimple_seq. */
2475 static tree
2476 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2477 struct walk_stmt_info *wi)
2479 gimple *stmt = gsi_stmt (*gsi_p);
2481 *handled_ops_p = true;
2482 switch (gimple_code (stmt))
2484 case GIMPLE_TRY:
2485 case GIMPLE_BIND:
2486 case GIMPLE_CATCH:
2487 case GIMPLE_EH_FILTER:
2488 case GIMPLE_TRANSACTION:
2489 /* Walk the sub-statements. */
2490 *handled_ops_p = false;
2491 break;
2492 case GIMPLE_CALL:
2493 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2495 gsi_remove (gsi_p, true);
2496 if (gsi_end_p (*gsi_p))
2498 *static_cast<location_t *>(wi->info) = gimple_location (stmt);
2499 return integer_zero_node;
2502 bool found = false;
2503 location_t loc = gimple_location (stmt);
2505 gimple_stmt_iterator gsi2 = *gsi_p;
2506 stmt = gsi_stmt (gsi2);
2507 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2509 /* Go on until the artificial label. */
2510 tree goto_dest = gimple_goto_dest (stmt);
2511 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2513 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2514 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2515 == goto_dest)
2516 break;
2519 /* Not found? Stop. */
2520 if (gsi_end_p (gsi2))
2521 break;
2523 /* Look one past it. */
2524 gsi_next (&gsi2);
2527 /* We're looking for a case label or default label here. */
2528 while (!gsi_end_p (gsi2))
2530 stmt = gsi_stmt (gsi2);
2531 if (gimple_code (stmt) == GIMPLE_LABEL)
2533 tree label = gimple_label_label (as_a <glabel *> (stmt));
2534 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2536 found = true;
2537 break;
2540 else if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2542 else if (!is_gimple_debug (stmt))
2543 /* Anything else is not expected. */
2544 break;
2545 gsi_next (&gsi2);
2547 if (!found)
2548 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2549 "a case label or default label");
2551 break;
2552 default:
2553 break;
2555 return NULL_TREE;
2558 /* Expand all FALLTHROUGH () calls in SEQ. */
2560 static void
2561 expand_FALLTHROUGH (gimple_seq *seq_p)
2563 struct walk_stmt_info wi;
2564 location_t loc;
2565 memset (&wi, 0, sizeof (wi));
2566 wi.info = (void *) &loc;
2567 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2568 if (wi.callback_result == integer_zero_node)
2569 /* We've found [[fallthrough]]; at the end of a switch, which the C++
2570 standard says is ill-formed; see [dcl.attr.fallthrough]. */
2571 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2572 "a case label or default label");
2576 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2577 branch to. */
2579 static enum gimplify_status
2580 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2582 tree switch_expr = *expr_p;
2583 gimple_seq switch_body_seq = NULL;
2584 enum gimplify_status ret;
2585 tree index_type = TREE_TYPE (switch_expr);
2586 if (index_type == NULL_TREE)
2587 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2589 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2590 fb_rvalue);
2591 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2592 return ret;
2594 if (SWITCH_BODY (switch_expr))
2596 vec<tree> labels;
2597 vec<tree> saved_labels;
2598 hash_set<tree> *saved_live_switch_vars = NULL;
2599 tree default_case = NULL_TREE;
2600 gswitch *switch_stmt;
2602 /* Save old labels, get new ones from body, then restore the old
2603 labels. Save all the things from the switch body to append after. */
2604 saved_labels = gimplify_ctxp->case_labels;
2605 gimplify_ctxp->case_labels.create (8);
2607 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2608 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2609 tree_code body_type = TREE_CODE (SWITCH_BODY (switch_expr));
2610 if (body_type == BIND_EXPR || body_type == STATEMENT_LIST)
2611 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2612 else
2613 gimplify_ctxp->live_switch_vars = NULL;
2615 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2616 gimplify_ctxp->in_switch_expr = true;
2618 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2620 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2621 maybe_warn_switch_unreachable (switch_body_seq);
2622 maybe_warn_implicit_fallthrough (switch_body_seq);
2623 /* Only do this for the outermost GIMPLE_SWITCH. */
2624 if (!gimplify_ctxp->in_switch_expr)
2625 expand_FALLTHROUGH (&switch_body_seq);
2627 labels = gimplify_ctxp->case_labels;
2628 gimplify_ctxp->case_labels = saved_labels;
2630 if (gimplify_ctxp->live_switch_vars)
2632 gcc_assert (gimplify_ctxp->live_switch_vars->is_empty ());
2633 delete gimplify_ctxp->live_switch_vars;
2635 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2637 preprocess_case_label_vec_for_gimple (labels, index_type,
2638 &default_case);
2640 bool add_bind = false;
2641 if (!default_case)
2643 glabel *new_default;
2645 default_case
2646 = build_case_label (NULL_TREE, NULL_TREE,
2647 create_artificial_label (UNKNOWN_LOCATION));
2648 if (old_in_switch_expr)
2650 SWITCH_BREAK_LABEL_P (CASE_LABEL (default_case)) = 1;
2651 add_bind = true;
2653 new_default = gimple_build_label (CASE_LABEL (default_case));
2654 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2656 else if (old_in_switch_expr)
2658 gimple *last = gimple_seq_last_stmt (switch_body_seq);
2659 if (last && gimple_code (last) == GIMPLE_LABEL)
2661 tree label = gimple_label_label (as_a <glabel *> (last));
2662 if (SWITCH_BREAK_LABEL_P (label))
2663 add_bind = true;
2667 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2668 default_case, labels);
2669 /* For the benefit of -Wimplicit-fallthrough, if switch_body_seq
2670 ends with a GIMPLE_LABEL holding SWITCH_BREAK_LABEL_P LABEL_DECL,
2671 wrap the GIMPLE_SWITCH up to that GIMPLE_LABEL into a GIMPLE_BIND,
2672 so that we can easily find the start and end of the switch
2673 statement. */
2674 if (add_bind)
2676 gimple_seq bind_body = NULL;
2677 gimplify_seq_add_stmt (&bind_body, switch_stmt);
2678 gimple_seq_add_seq (&bind_body, switch_body_seq);
2679 gbind *bind = gimple_build_bind (NULL_TREE, bind_body, NULL_TREE);
2680 gimple_set_location (bind, EXPR_LOCATION (switch_expr));
2681 gimplify_seq_add_stmt (pre_p, bind);
2683 else
2685 gimplify_seq_add_stmt (pre_p, switch_stmt);
2686 gimplify_seq_add_seq (pre_p, switch_body_seq);
2688 labels.release ();
2690 else
2691 gcc_unreachable ();
2693 return GS_ALL_DONE;
2696 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
2698 static enum gimplify_status
2699 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
2701 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
2702 == current_function_decl);
2704 tree label = LABEL_EXPR_LABEL (*expr_p);
2705 glabel *label_stmt = gimple_build_label (label);
2706 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2707 gimplify_seq_add_stmt (pre_p, label_stmt);
2709 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2710 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2711 NOT_TAKEN));
2712 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2713 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2714 TAKEN));
2716 return GS_ALL_DONE;
2719 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
2721 static enum gimplify_status
2722 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
2724 struct gimplify_ctx *ctxp;
2725 glabel *label_stmt;
2727 /* Invalid programs can play Duff's Device type games with, for example,
2728 #pragma omp parallel. At least in the C front end, we don't
2729 detect such invalid branches until after gimplification, in the
2730 diagnose_omp_blocks pass. */
2731 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
2732 if (ctxp->case_labels.exists ())
2733 break;
2735 tree label = CASE_LABEL (*expr_p);
2736 label_stmt = gimple_build_label (label);
2737 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2738 ctxp->case_labels.safe_push (*expr_p);
2739 gimplify_seq_add_stmt (pre_p, label_stmt);
2741 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2742 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2743 NOT_TAKEN));
2744 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2745 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2746 TAKEN));
2748 return GS_ALL_DONE;
2751 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
2752 if necessary. */
2754 tree
2755 build_and_jump (tree *label_p)
2757 if (label_p == NULL)
2758 /* If there's nowhere to jump, just fall through. */
2759 return NULL_TREE;
2761 if (*label_p == NULL_TREE)
2763 tree label = create_artificial_label (UNKNOWN_LOCATION);
2764 *label_p = label;
2767 return build1 (GOTO_EXPR, void_type_node, *label_p);
2770 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
2771 This also involves building a label to jump to and communicating it to
2772 gimplify_loop_expr through gimplify_ctxp->exit_label. */
2774 static enum gimplify_status
2775 gimplify_exit_expr (tree *expr_p)
2777 tree cond = TREE_OPERAND (*expr_p, 0);
2778 tree expr;
2780 expr = build_and_jump (&gimplify_ctxp->exit_label);
2781 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
2782 *expr_p = expr;
2784 return GS_OK;
2787 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
2788 different from its canonical type, wrap the whole thing inside a
2789 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
2790 type.
2792 The canonical type of a COMPONENT_REF is the type of the field being
2793 referenced--unless the field is a bit-field which can be read directly
2794 in a smaller mode, in which case the canonical type is the
2795 sign-appropriate type corresponding to that mode. */
2797 static void
2798 canonicalize_component_ref (tree *expr_p)
2800 tree expr = *expr_p;
2801 tree type;
2803 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
2805 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
2806 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
2807 else
2808 type = TREE_TYPE (TREE_OPERAND (expr, 1));
2810 /* One could argue that all the stuff below is not necessary for
2811 the non-bitfield case and declare it a FE error if type
2812 adjustment would be needed. */
2813 if (TREE_TYPE (expr) != type)
2815 #ifdef ENABLE_TYPES_CHECKING
2816 tree old_type = TREE_TYPE (expr);
2817 #endif
2818 int type_quals;
2820 /* We need to preserve qualifiers and propagate them from
2821 operand 0. */
2822 type_quals = TYPE_QUALS (type)
2823 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
2824 if (TYPE_QUALS (type) != type_quals)
2825 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
2827 /* Set the type of the COMPONENT_REF to the underlying type. */
2828 TREE_TYPE (expr) = type;
2830 #ifdef ENABLE_TYPES_CHECKING
2831 /* It is now a FE error, if the conversion from the canonical
2832 type to the original expression type is not useless. */
2833 gcc_assert (useless_type_conversion_p (old_type, type));
2834 #endif
2838 /* If a NOP conversion is changing a pointer to array of foo to a pointer
2839 to foo, embed that change in the ADDR_EXPR by converting
2840 T array[U];
2841 (T *)&array
2843 &array[L]
2844 where L is the lower bound. For simplicity, only do this for constant
2845 lower bound.
2846 The constraint is that the type of &array[L] is trivially convertible
2847 to T *. */
2849 static void
2850 canonicalize_addr_expr (tree *expr_p)
2852 tree expr = *expr_p;
2853 tree addr_expr = TREE_OPERAND (expr, 0);
2854 tree datype, ddatype, pddatype;
2856 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
2857 if (!POINTER_TYPE_P (TREE_TYPE (expr))
2858 || TREE_CODE (addr_expr) != ADDR_EXPR)
2859 return;
2861 /* The addr_expr type should be a pointer to an array. */
2862 datype = TREE_TYPE (TREE_TYPE (addr_expr));
2863 if (TREE_CODE (datype) != ARRAY_TYPE)
2864 return;
2866 /* The pointer to element type shall be trivially convertible to
2867 the expression pointer type. */
2868 ddatype = TREE_TYPE (datype);
2869 pddatype = build_pointer_type (ddatype);
2870 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
2871 pddatype))
2872 return;
2874 /* The lower bound and element sizes must be constant. */
2875 if (!TYPE_SIZE_UNIT (ddatype)
2876 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
2877 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
2878 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
2879 return;
2881 /* All checks succeeded. Build a new node to merge the cast. */
2882 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
2883 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
2884 NULL_TREE, NULL_TREE);
2885 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
2887 /* We can have stripped a required restrict qualifier above. */
2888 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
2889 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
2892 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
2893 underneath as appropriate. */
2895 static enum gimplify_status
2896 gimplify_conversion (tree *expr_p)
2898 location_t loc = EXPR_LOCATION (*expr_p);
2899 gcc_assert (CONVERT_EXPR_P (*expr_p));
2901 /* Then strip away all but the outermost conversion. */
2902 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
2904 /* And remove the outermost conversion if it's useless. */
2905 if (tree_ssa_useless_type_conversion (*expr_p))
2906 *expr_p = TREE_OPERAND (*expr_p, 0);
2908 /* If we still have a conversion at the toplevel,
2909 then canonicalize some constructs. */
2910 if (CONVERT_EXPR_P (*expr_p))
2912 tree sub = TREE_OPERAND (*expr_p, 0);
2914 /* If a NOP conversion is changing the type of a COMPONENT_REF
2915 expression, then canonicalize its type now in order to expose more
2916 redundant conversions. */
2917 if (TREE_CODE (sub) == COMPONENT_REF)
2918 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
2920 /* If a NOP conversion is changing a pointer to array of foo
2921 to a pointer to foo, embed that change in the ADDR_EXPR. */
2922 else if (TREE_CODE (sub) == ADDR_EXPR)
2923 canonicalize_addr_expr (expr_p);
2926 /* If we have a conversion to a non-register type force the
2927 use of a VIEW_CONVERT_EXPR instead. */
2928 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
2929 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
2930 TREE_OPERAND (*expr_p, 0));
2932 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
2933 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
2934 TREE_SET_CODE (*expr_p, NOP_EXPR);
2936 return GS_OK;
2939 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
2940 DECL_VALUE_EXPR, and it's worth re-examining things. */
2942 static enum gimplify_status
2943 gimplify_var_or_parm_decl (tree *expr_p)
2945 tree decl = *expr_p;
2947 /* ??? If this is a local variable, and it has not been seen in any
2948 outer BIND_EXPR, then it's probably the result of a duplicate
2949 declaration, for which we've already issued an error. It would
2950 be really nice if the front end wouldn't leak these at all.
2951 Currently the only known culprit is C++ destructors, as seen
2952 in g++.old-deja/g++.jason/binding.C. */
2953 if (VAR_P (decl)
2954 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
2955 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
2956 && decl_function_context (decl) == current_function_decl)
2958 gcc_assert (seen_error ());
2959 return GS_ERROR;
2962 /* When within an OMP context, notice uses of variables. */
2963 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
2964 return GS_ALL_DONE;
2966 /* If the decl is an alias for another expression, substitute it now. */
2967 if (DECL_HAS_VALUE_EXPR_P (decl))
2969 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
2970 return GS_OK;
2973 return GS_ALL_DONE;
2976 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
2978 static void
2979 recalculate_side_effects (tree t)
2981 enum tree_code code = TREE_CODE (t);
2982 int len = TREE_OPERAND_LENGTH (t);
2983 int i;
2985 switch (TREE_CODE_CLASS (code))
2987 case tcc_expression:
2988 switch (code)
2990 case INIT_EXPR:
2991 case MODIFY_EXPR:
2992 case VA_ARG_EXPR:
2993 case PREDECREMENT_EXPR:
2994 case PREINCREMENT_EXPR:
2995 case POSTDECREMENT_EXPR:
2996 case POSTINCREMENT_EXPR:
2997 /* All of these have side-effects, no matter what their
2998 operands are. */
2999 return;
3001 default:
3002 break;
3004 /* Fall through. */
3006 case tcc_comparison: /* a comparison expression */
3007 case tcc_unary: /* a unary arithmetic expression */
3008 case tcc_binary: /* a binary arithmetic expression */
3009 case tcc_reference: /* a reference */
3010 case tcc_vl_exp: /* a function call */
3011 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
3012 for (i = 0; i < len; ++i)
3014 tree op = TREE_OPERAND (t, i);
3015 if (op && TREE_SIDE_EFFECTS (op))
3016 TREE_SIDE_EFFECTS (t) = 1;
3018 break;
3020 case tcc_constant:
3021 /* No side-effects. */
3022 return;
3024 default:
3025 gcc_unreachable ();
3029 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
3030 node *EXPR_P.
3032 compound_lval
3033 : min_lval '[' val ']'
3034 | min_lval '.' ID
3035 | compound_lval '[' val ']'
3036 | compound_lval '.' ID
3038 This is not part of the original SIMPLE definition, which separates
3039 array and member references, but it seems reasonable to handle them
3040 together. Also, this way we don't run into problems with union
3041 aliasing; gcc requires that for accesses through a union to alias, the
3042 union reference must be explicit, which was not always the case when we
3043 were splitting up array and member refs.
3045 PRE_P points to the sequence where side effects that must happen before
3046 *EXPR_P should be stored.
3048 POST_P points to the sequence where side effects that must happen after
3049 *EXPR_P should be stored. */
3051 static enum gimplify_status
3052 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3053 fallback_t fallback)
3055 tree *p;
3056 enum gimplify_status ret = GS_ALL_DONE, tret;
3057 int i;
3058 location_t loc = EXPR_LOCATION (*expr_p);
3059 tree expr = *expr_p;
3061 /* Create a stack of the subexpressions so later we can walk them in
3062 order from inner to outer. */
3063 auto_vec<tree, 10> expr_stack;
3065 /* We can handle anything that get_inner_reference can deal with. */
3066 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
3068 restart:
3069 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
3070 if (TREE_CODE (*p) == INDIRECT_REF)
3071 *p = fold_indirect_ref_loc (loc, *p);
3073 if (handled_component_p (*p))
3075 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
3076 additional COMPONENT_REFs. */
3077 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
3078 && gimplify_var_or_parm_decl (p) == GS_OK)
3079 goto restart;
3080 else
3081 break;
3083 expr_stack.safe_push (*p);
3086 gcc_assert (expr_stack.length ());
3088 /* Now EXPR_STACK is a stack of pointers to all the refs we've
3089 walked through and P points to the innermost expression.
3091 Java requires that we elaborated nodes in source order. That
3092 means we must gimplify the inner expression followed by each of
3093 the indices, in order. But we can't gimplify the inner
3094 expression until we deal with any variable bounds, sizes, or
3095 positions in order to deal with PLACEHOLDER_EXPRs.
3097 So we do this in three steps. First we deal with the annotations
3098 for any variables in the components, then we gimplify the base,
3099 then we gimplify any indices, from left to right. */
3100 for (i = expr_stack.length () - 1; i >= 0; i--)
3102 tree t = expr_stack[i];
3104 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3106 /* Gimplify the low bound and element type size and put them into
3107 the ARRAY_REF. If these values are set, they have already been
3108 gimplified. */
3109 if (TREE_OPERAND (t, 2) == NULL_TREE)
3111 tree low = unshare_expr (array_ref_low_bound (t));
3112 if (!is_gimple_min_invariant (low))
3114 TREE_OPERAND (t, 2) = low;
3115 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
3116 post_p, is_gimple_reg,
3117 fb_rvalue);
3118 ret = MIN (ret, tret);
3121 else
3123 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3124 is_gimple_reg, fb_rvalue);
3125 ret = MIN (ret, tret);
3128 if (TREE_OPERAND (t, 3) == NULL_TREE)
3130 tree elmt_size = array_ref_element_size (t);
3131 if (!is_gimple_min_invariant (elmt_size))
3133 elmt_size = unshare_expr (elmt_size);
3134 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
3135 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
3137 /* Divide the element size by the alignment of the element
3138 type (above). */
3139 elmt_size = size_binop_loc (loc, EXACT_DIV_EXPR,
3140 elmt_size, factor);
3142 TREE_OPERAND (t, 3) = elmt_size;
3143 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
3144 post_p, is_gimple_reg,
3145 fb_rvalue);
3146 ret = MIN (ret, tret);
3149 else
3151 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
3152 is_gimple_reg, fb_rvalue);
3153 ret = MIN (ret, tret);
3156 else if (TREE_CODE (t) == COMPONENT_REF)
3158 /* Set the field offset into T and gimplify it. */
3159 if (TREE_OPERAND (t, 2) == NULL_TREE)
3161 tree offset = component_ref_field_offset (t);
3162 if (!is_gimple_min_invariant (offset))
3164 offset = unshare_expr (offset);
3165 tree field = TREE_OPERAND (t, 1);
3166 tree factor
3167 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
3169 /* Divide the offset by its alignment. */
3170 offset = size_binop_loc (loc, EXACT_DIV_EXPR,
3171 offset, factor);
3173 TREE_OPERAND (t, 2) = offset;
3174 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
3175 post_p, is_gimple_reg,
3176 fb_rvalue);
3177 ret = MIN (ret, tret);
3180 else
3182 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3183 is_gimple_reg, fb_rvalue);
3184 ret = MIN (ret, tret);
3189 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
3190 so as to match the min_lval predicate. Failure to do so may result
3191 in the creation of large aggregate temporaries. */
3192 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
3193 fallback | fb_lvalue);
3194 ret = MIN (ret, tret);
3196 /* And finally, the indices and operands of ARRAY_REF. During this
3197 loop we also remove any useless conversions. */
3198 for (; expr_stack.length () > 0; )
3200 tree t = expr_stack.pop ();
3202 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3204 /* Gimplify the dimension. */
3205 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
3207 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
3208 is_gimple_val, fb_rvalue);
3209 ret = MIN (ret, tret);
3213 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
3215 /* The innermost expression P may have originally had
3216 TREE_SIDE_EFFECTS set which would have caused all the outer
3217 expressions in *EXPR_P leading to P to also have had
3218 TREE_SIDE_EFFECTS set. */
3219 recalculate_side_effects (t);
3222 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
3223 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
3225 canonicalize_component_ref (expr_p);
3228 expr_stack.release ();
3230 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
3232 return ret;
3235 /* Gimplify the self modifying expression pointed to by EXPR_P
3236 (++, --, +=, -=).
3238 PRE_P points to the list where side effects that must happen before
3239 *EXPR_P should be stored.
3241 POST_P points to the list where side effects that must happen after
3242 *EXPR_P should be stored.
3244 WANT_VALUE is nonzero iff we want to use the value of this expression
3245 in another expression.
3247 ARITH_TYPE is the type the computation should be performed in. */
3249 enum gimplify_status
3250 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3251 bool want_value, tree arith_type)
3253 enum tree_code code;
3254 tree lhs, lvalue, rhs, t1;
3255 gimple_seq post = NULL, *orig_post_p = post_p;
3256 bool postfix;
3257 enum tree_code arith_code;
3258 enum gimplify_status ret;
3259 location_t loc = EXPR_LOCATION (*expr_p);
3261 code = TREE_CODE (*expr_p);
3263 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
3264 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
3266 /* Prefix or postfix? */
3267 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
3268 /* Faster to treat as prefix if result is not used. */
3269 postfix = want_value;
3270 else
3271 postfix = false;
3273 /* For postfix, make sure the inner expression's post side effects
3274 are executed after side effects from this expression. */
3275 if (postfix)
3276 post_p = &post;
3278 /* Add or subtract? */
3279 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
3280 arith_code = PLUS_EXPR;
3281 else
3282 arith_code = MINUS_EXPR;
3284 /* Gimplify the LHS into a GIMPLE lvalue. */
3285 lvalue = TREE_OPERAND (*expr_p, 0);
3286 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3287 if (ret == GS_ERROR)
3288 return ret;
3290 /* Extract the operands to the arithmetic operation. */
3291 lhs = lvalue;
3292 rhs = TREE_OPERAND (*expr_p, 1);
3294 /* For postfix operator, we evaluate the LHS to an rvalue and then use
3295 that as the result value and in the postqueue operation. */
3296 if (postfix)
3298 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
3299 if (ret == GS_ERROR)
3300 return ret;
3302 lhs = get_initialized_tmp_var (lhs, pre_p);
3305 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
3306 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
3308 rhs = convert_to_ptrofftype_loc (loc, rhs);
3309 if (arith_code == MINUS_EXPR)
3310 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
3311 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
3313 else
3314 t1 = fold_convert (TREE_TYPE (*expr_p),
3315 fold_build2 (arith_code, arith_type,
3316 fold_convert (arith_type, lhs),
3317 fold_convert (arith_type, rhs)));
3319 if (postfix)
3321 gimplify_assign (lvalue, t1, pre_p);
3322 gimplify_seq_add_seq (orig_post_p, post);
3323 *expr_p = lhs;
3324 return GS_ALL_DONE;
3326 else
3328 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
3329 return GS_OK;
3333 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
3335 static void
3336 maybe_with_size_expr (tree *expr_p)
3338 tree expr = *expr_p;
3339 tree type = TREE_TYPE (expr);
3340 tree size;
3342 /* If we've already wrapped this or the type is error_mark_node, we can't do
3343 anything. */
3344 if (TREE_CODE (expr) == WITH_SIZE_EXPR
3345 || type == error_mark_node)
3346 return;
3348 /* If the size isn't known or is a constant, we have nothing to do. */
3349 size = TYPE_SIZE_UNIT (type);
3350 if (!size || poly_int_tree_p (size))
3351 return;
3353 /* Otherwise, make a WITH_SIZE_EXPR. */
3354 size = unshare_expr (size);
3355 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
3356 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
3359 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
3360 Store any side-effects in PRE_P. CALL_LOCATION is the location of
3361 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
3362 gimplified to an SSA name. */
3364 enum gimplify_status
3365 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3366 bool allow_ssa)
3368 bool (*test) (tree);
3369 fallback_t fb;
3371 /* In general, we allow lvalues for function arguments to avoid
3372 extra overhead of copying large aggregates out of even larger
3373 aggregates into temporaries only to copy the temporaries to
3374 the argument list. Make optimizers happy by pulling out to
3375 temporaries those types that fit in registers. */
3376 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3377 test = is_gimple_val, fb = fb_rvalue;
3378 else
3380 test = is_gimple_lvalue, fb = fb_either;
3381 /* Also strip a TARGET_EXPR that would force an extra copy. */
3382 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3384 tree init = TARGET_EXPR_INITIAL (*arg_p);
3385 if (init
3386 && !VOID_TYPE_P (TREE_TYPE (init)))
3387 *arg_p = init;
3391 /* If this is a variable sized type, we must remember the size. */
3392 maybe_with_size_expr (arg_p);
3394 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3395 /* Make sure arguments have the same location as the function call
3396 itself. */
3397 protected_set_expr_location (*arg_p, call_location);
3399 /* There is a sequence point before a function call. Side effects in
3400 the argument list must occur before the actual call. So, when
3401 gimplifying arguments, force gimplify_expr to use an internal
3402 post queue which is then appended to the end of PRE_P. */
3403 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3406 /* Don't fold inside offloading or taskreg regions: it can break code by
3407 adding decl references that weren't in the source. We'll do it during
3408 omplower pass instead. */
3410 static bool
3411 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3413 struct gimplify_omp_ctx *ctx;
3414 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3415 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3416 return false;
3417 else if ((ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
3418 return false;
3419 /* Delay folding of builtins until the IL is in consistent state
3420 so the diagnostic machinery can do a better job. */
3421 if (gimple_call_builtin_p (gsi_stmt (*gsi)))
3422 return false;
3423 return fold_stmt (gsi);
3426 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3427 WANT_VALUE is true if the result of the call is desired. */
3429 static enum gimplify_status
3430 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3432 tree fndecl, parms, p, fnptrtype;
3433 enum gimplify_status ret;
3434 int i, nargs;
3435 gcall *call;
3436 bool builtin_va_start_p = false;
3437 location_t loc = EXPR_LOCATION (*expr_p);
3439 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3441 /* For reliable diagnostics during inlining, it is necessary that
3442 every call_expr be annotated with file and line. */
3443 if (! EXPR_HAS_LOCATION (*expr_p))
3444 SET_EXPR_LOCATION (*expr_p, input_location);
3446 /* Gimplify internal functions created in the FEs. */
3447 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3449 if (want_value)
3450 return GS_ALL_DONE;
3452 nargs = call_expr_nargs (*expr_p);
3453 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3454 auto_vec<tree> vargs (nargs);
3456 for (i = 0; i < nargs; i++)
3458 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3459 EXPR_LOCATION (*expr_p));
3460 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3463 gcall *call = gimple_build_call_internal_vec (ifn, vargs);
3464 gimple_call_set_nothrow (call, TREE_NOTHROW (*expr_p));
3465 gimplify_seq_add_stmt (pre_p, call);
3466 return GS_ALL_DONE;
3469 /* This may be a call to a builtin function.
3471 Builtin function calls may be transformed into different
3472 (and more efficient) builtin function calls under certain
3473 circumstances. Unfortunately, gimplification can muck things
3474 up enough that the builtin expanders are not aware that certain
3475 transformations are still valid.
3477 So we attempt transformation/gimplification of the call before
3478 we gimplify the CALL_EXPR. At this time we do not manage to
3479 transform all calls in the same manner as the expanders do, but
3480 we do transform most of them. */
3481 fndecl = get_callee_fndecl (*expr_p);
3482 if (fndecl && fndecl_built_in_p (fndecl, BUILT_IN_NORMAL))
3483 switch (DECL_FUNCTION_CODE (fndecl))
3485 CASE_BUILT_IN_ALLOCA:
3486 /* If the call has been built for a variable-sized object, then we
3487 want to restore the stack level when the enclosing BIND_EXPR is
3488 exited to reclaim the allocated space; otherwise, we precisely
3489 need to do the opposite and preserve the latest stack level. */
3490 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3491 gimplify_ctxp->save_stack = true;
3492 else
3493 gimplify_ctxp->keep_stack = true;
3494 break;
3496 case BUILT_IN_VA_START:
3498 builtin_va_start_p = TRUE;
3499 if (call_expr_nargs (*expr_p) < 2)
3501 error ("too few arguments to function %<va_start%>");
3502 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3503 return GS_OK;
3506 if (fold_builtin_next_arg (*expr_p, true))
3508 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3509 return GS_OK;
3511 break;
3514 case BUILT_IN_EH_RETURN:
3515 cfun->calls_eh_return = true;
3516 break;
3518 case BUILT_IN_CLEAR_PADDING:
3519 if (call_expr_nargs (*expr_p) == 1)
3521 /* Remember the original type of the argument in an internal
3522 dummy second argument, as in GIMPLE pointer conversions are
3523 useless. also mark this call as not for automatic initialization
3524 in the internal dummy third argument. */
3525 p = CALL_EXPR_ARG (*expr_p, 0);
3526 bool for_auto_init = false;
3527 *expr_p
3528 = build_call_expr_loc (EXPR_LOCATION (*expr_p), fndecl, 3, p,
3529 build_zero_cst (TREE_TYPE (p)),
3530 build_int_cst (integer_type_node,
3531 (int) for_auto_init));
3532 return GS_OK;
3534 break;
3536 default:
3539 if (fndecl && fndecl_built_in_p (fndecl))
3541 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3542 if (new_tree && new_tree != *expr_p)
3544 /* There was a transformation of this call which computes the
3545 same value, but in a more efficient way. Return and try
3546 again. */
3547 *expr_p = new_tree;
3548 return GS_OK;
3552 /* Remember the original function pointer type. */
3553 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3555 if (flag_openmp
3556 && fndecl
3557 && cfun
3558 && (cfun->curr_properties & PROP_gimple_any) == 0)
3560 tree variant = omp_resolve_declare_variant (fndecl);
3561 if (variant != fndecl)
3562 CALL_EXPR_FN (*expr_p) = build1 (ADDR_EXPR, fnptrtype, variant);
3565 /* There is a sequence point before the call, so any side effects in
3566 the calling expression must occur before the actual call. Force
3567 gimplify_expr to use an internal post queue. */
3568 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3569 is_gimple_call_addr, fb_rvalue);
3571 nargs = call_expr_nargs (*expr_p);
3573 /* Get argument types for verification. */
3574 fndecl = get_callee_fndecl (*expr_p);
3575 parms = NULL_TREE;
3576 if (fndecl)
3577 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3578 else
3579 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3581 if (fndecl && DECL_ARGUMENTS (fndecl))
3582 p = DECL_ARGUMENTS (fndecl);
3583 else if (parms)
3584 p = parms;
3585 else
3586 p = NULL_TREE;
3587 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3590 /* If the last argument is __builtin_va_arg_pack () and it is not
3591 passed as a named argument, decrease the number of CALL_EXPR
3592 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3593 if (!p
3594 && i < nargs
3595 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3597 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3598 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3600 if (last_arg_fndecl
3601 && fndecl_built_in_p (last_arg_fndecl, BUILT_IN_VA_ARG_PACK))
3603 tree call = *expr_p;
3605 --nargs;
3606 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
3607 CALL_EXPR_FN (call),
3608 nargs, CALL_EXPR_ARGP (call));
3610 /* Copy all CALL_EXPR flags, location and block, except
3611 CALL_EXPR_VA_ARG_PACK flag. */
3612 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
3613 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
3614 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
3615 = CALL_EXPR_RETURN_SLOT_OPT (call);
3616 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
3617 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
3619 /* Set CALL_EXPR_VA_ARG_PACK. */
3620 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
3624 /* If the call returns twice then after building the CFG the call
3625 argument computations will no longer dominate the call because
3626 we add an abnormal incoming edge to the call. So do not use SSA
3627 vars there. */
3628 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
3630 /* Gimplify the function arguments. */
3631 if (nargs > 0)
3633 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
3634 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
3635 PUSH_ARGS_REVERSED ? i-- : i++)
3637 enum gimplify_status t;
3639 /* Avoid gimplifying the second argument to va_start, which needs to
3640 be the plain PARM_DECL. */
3641 if ((i != 1) || !builtin_va_start_p)
3643 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3644 EXPR_LOCATION (*expr_p), ! returns_twice);
3646 if (t == GS_ERROR)
3647 ret = GS_ERROR;
3652 /* Gimplify the static chain. */
3653 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
3655 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
3656 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
3657 else
3659 enum gimplify_status t;
3660 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
3661 EXPR_LOCATION (*expr_p), ! returns_twice);
3662 if (t == GS_ERROR)
3663 ret = GS_ERROR;
3667 /* Verify the function result. */
3668 if (want_value && fndecl
3669 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
3671 error_at (loc, "using result of function returning %<void%>");
3672 ret = GS_ERROR;
3675 /* Try this again in case gimplification exposed something. */
3676 if (ret != GS_ERROR)
3678 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3680 if (new_tree && new_tree != *expr_p)
3682 /* There was a transformation of this call which computes the
3683 same value, but in a more efficient way. Return and try
3684 again. */
3685 *expr_p = new_tree;
3686 return GS_OK;
3689 else
3691 *expr_p = error_mark_node;
3692 return GS_ERROR;
3695 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
3696 decl. This allows us to eliminate redundant or useless
3697 calls to "const" functions. */
3698 if (TREE_CODE (*expr_p) == CALL_EXPR)
3700 int flags = call_expr_flags (*expr_p);
3701 if (flags & (ECF_CONST | ECF_PURE)
3702 /* An infinite loop is considered a side effect. */
3703 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
3704 TREE_SIDE_EFFECTS (*expr_p) = 0;
3707 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
3708 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
3709 form and delegate the creation of a GIMPLE_CALL to
3710 gimplify_modify_expr. This is always possible because when
3711 WANT_VALUE is true, the caller wants the result of this call into
3712 a temporary, which means that we will emit an INIT_EXPR in
3713 internal_get_tmp_var which will then be handled by
3714 gimplify_modify_expr. */
3715 if (!want_value)
3717 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
3718 have to do is replicate it as a GIMPLE_CALL tuple. */
3719 gimple_stmt_iterator gsi;
3720 call = gimple_build_call_from_tree (*expr_p, fnptrtype);
3721 notice_special_calls (call);
3722 gimplify_seq_add_stmt (pre_p, call);
3723 gsi = gsi_last (*pre_p);
3724 maybe_fold_stmt (&gsi);
3725 *expr_p = NULL_TREE;
3727 else
3728 /* Remember the original function type. */
3729 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
3730 CALL_EXPR_FN (*expr_p));
3732 return ret;
3735 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
3736 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
3738 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
3739 condition is true or false, respectively. If null, we should generate
3740 our own to skip over the evaluation of this specific expression.
3742 LOCUS is the source location of the COND_EXPR.
3744 This function is the tree equivalent of do_jump.
3746 shortcut_cond_r should only be called by shortcut_cond_expr. */
3748 static tree
3749 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
3750 location_t locus)
3752 tree local_label = NULL_TREE;
3753 tree t, expr = NULL;
3755 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
3756 retain the shortcut semantics. Just insert the gotos here;
3757 shortcut_cond_expr will append the real blocks later. */
3758 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3760 location_t new_locus;
3762 /* Turn if (a && b) into
3764 if (a); else goto no;
3765 if (b) goto yes; else goto no;
3766 (no:) */
3768 if (false_label_p == NULL)
3769 false_label_p = &local_label;
3771 /* Keep the original source location on the first 'if'. */
3772 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
3773 append_to_statement_list (t, &expr);
3775 /* Set the source location of the && on the second 'if'. */
3776 new_locus = rexpr_location (pred, locus);
3777 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3778 new_locus);
3779 append_to_statement_list (t, &expr);
3781 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3783 location_t new_locus;
3785 /* Turn if (a || b) into
3787 if (a) goto yes;
3788 if (b) goto yes; else goto no;
3789 (yes:) */
3791 if (true_label_p == NULL)
3792 true_label_p = &local_label;
3794 /* Keep the original source location on the first 'if'. */
3795 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
3796 append_to_statement_list (t, &expr);
3798 /* Set the source location of the || on the second 'if'. */
3799 new_locus = rexpr_location (pred, locus);
3800 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3801 new_locus);
3802 append_to_statement_list (t, &expr);
3804 else if (TREE_CODE (pred) == COND_EXPR
3805 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
3806 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
3808 location_t new_locus;
3810 /* As long as we're messing with gotos, turn if (a ? b : c) into
3811 if (a)
3812 if (b) goto yes; else goto no;
3813 else
3814 if (c) goto yes; else goto no;
3816 Don't do this if one of the arms has void type, which can happen
3817 in C++ when the arm is throw. */
3819 /* Keep the original source location on the first 'if'. Set the source
3820 location of the ? on the second 'if'. */
3821 new_locus = rexpr_location (pred, locus);
3822 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
3823 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
3824 false_label_p, locus),
3825 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
3826 false_label_p, new_locus));
3828 else
3830 expr = build3 (COND_EXPR, void_type_node, pred,
3831 build_and_jump (true_label_p),
3832 build_and_jump (false_label_p));
3833 SET_EXPR_LOCATION (expr, locus);
3836 if (local_label)
3838 t = build1 (LABEL_EXPR, void_type_node, local_label);
3839 append_to_statement_list (t, &expr);
3842 return expr;
3845 /* If EXPR is a GOTO_EXPR, return it. If it is a STATEMENT_LIST, skip
3846 any of its leading DEBUG_BEGIN_STMTS and recurse on the subsequent
3847 statement, if it is the last one. Otherwise, return NULL. */
3849 static tree
3850 find_goto (tree expr)
3852 if (!expr)
3853 return NULL_TREE;
3855 if (TREE_CODE (expr) == GOTO_EXPR)
3856 return expr;
3858 if (TREE_CODE (expr) != STATEMENT_LIST)
3859 return NULL_TREE;
3861 tree_stmt_iterator i = tsi_start (expr);
3863 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
3864 tsi_next (&i);
3866 if (!tsi_one_before_end_p (i))
3867 return NULL_TREE;
3869 return find_goto (tsi_stmt (i));
3872 /* Same as find_goto, except that it returns NULL if the destination
3873 is not a LABEL_DECL. */
3875 static inline tree
3876 find_goto_label (tree expr)
3878 tree dest = find_goto (expr);
3879 if (dest && TREE_CODE (GOTO_DESTINATION (dest)) == LABEL_DECL)
3880 return dest;
3881 return NULL_TREE;
3884 /* Given a conditional expression EXPR with short-circuit boolean
3885 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
3886 predicate apart into the equivalent sequence of conditionals. */
3888 static tree
3889 shortcut_cond_expr (tree expr)
3891 tree pred = TREE_OPERAND (expr, 0);
3892 tree then_ = TREE_OPERAND (expr, 1);
3893 tree else_ = TREE_OPERAND (expr, 2);
3894 tree true_label, false_label, end_label, t;
3895 tree *true_label_p;
3896 tree *false_label_p;
3897 bool emit_end, emit_false, jump_over_else;
3898 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
3899 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
3901 /* First do simple transformations. */
3902 if (!else_se)
3904 /* If there is no 'else', turn
3905 if (a && b) then c
3906 into
3907 if (a) if (b) then c. */
3908 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3910 /* Keep the original source location on the first 'if'. */
3911 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3912 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3913 /* Set the source location of the && on the second 'if'. */
3914 if (rexpr_has_location (pred))
3915 SET_EXPR_LOCATION (expr, rexpr_location (pred));
3916 then_ = shortcut_cond_expr (expr);
3917 then_se = then_ && TREE_SIDE_EFFECTS (then_);
3918 pred = TREE_OPERAND (pred, 0);
3919 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
3920 SET_EXPR_LOCATION (expr, locus);
3924 if (!then_se)
3926 /* If there is no 'then', turn
3927 if (a || b); else d
3928 into
3929 if (a); else if (b); else d. */
3930 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3932 /* Keep the original source location on the first 'if'. */
3933 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3934 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3935 /* Set the source location of the || on the second 'if'. */
3936 if (rexpr_has_location (pred))
3937 SET_EXPR_LOCATION (expr, rexpr_location (pred));
3938 else_ = shortcut_cond_expr (expr);
3939 else_se = else_ && TREE_SIDE_EFFECTS (else_);
3940 pred = TREE_OPERAND (pred, 0);
3941 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
3942 SET_EXPR_LOCATION (expr, locus);
3946 /* If we're done, great. */
3947 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
3948 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
3949 return expr;
3951 /* Otherwise we need to mess with gotos. Change
3952 if (a) c; else d;
3954 if (a); else goto no;
3955 c; goto end;
3956 no: d; end:
3957 and recursively gimplify the condition. */
3959 true_label = false_label = end_label = NULL_TREE;
3961 /* If our arms just jump somewhere, hijack those labels so we don't
3962 generate jumps to jumps. */
3964 if (tree then_goto = find_goto_label (then_))
3966 true_label = GOTO_DESTINATION (then_goto);
3967 then_ = NULL;
3968 then_se = false;
3971 if (tree else_goto = find_goto_label (else_))
3973 false_label = GOTO_DESTINATION (else_goto);
3974 else_ = NULL;
3975 else_se = false;
3978 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
3979 if (true_label)
3980 true_label_p = &true_label;
3981 else
3982 true_label_p = NULL;
3984 /* The 'else' branch also needs a label if it contains interesting code. */
3985 if (false_label || else_se)
3986 false_label_p = &false_label;
3987 else
3988 false_label_p = NULL;
3990 /* If there was nothing else in our arms, just forward the label(s). */
3991 if (!then_se && !else_se)
3992 return shortcut_cond_r (pred, true_label_p, false_label_p,
3993 EXPR_LOC_OR_LOC (expr, input_location));
3995 /* If our last subexpression already has a terminal label, reuse it. */
3996 if (else_se)
3997 t = expr_last (else_);
3998 else if (then_se)
3999 t = expr_last (then_);
4000 else
4001 t = NULL;
4002 if (t && TREE_CODE (t) == LABEL_EXPR)
4003 end_label = LABEL_EXPR_LABEL (t);
4005 /* If we don't care about jumping to the 'else' branch, jump to the end
4006 if the condition is false. */
4007 if (!false_label_p)
4008 false_label_p = &end_label;
4010 /* We only want to emit these labels if we aren't hijacking them. */
4011 emit_end = (end_label == NULL_TREE);
4012 emit_false = (false_label == NULL_TREE);
4014 /* We only emit the jump over the else clause if we have to--if the
4015 then clause may fall through. Otherwise we can wind up with a
4016 useless jump and a useless label at the end of gimplified code,
4017 which will cause us to think that this conditional as a whole
4018 falls through even if it doesn't. If we then inline a function
4019 which ends with such a condition, that can cause us to issue an
4020 inappropriate warning about control reaching the end of a
4021 non-void function. */
4022 jump_over_else = block_may_fallthru (then_);
4024 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
4025 EXPR_LOC_OR_LOC (expr, input_location));
4027 expr = NULL;
4028 append_to_statement_list (pred, &expr);
4030 append_to_statement_list (then_, &expr);
4031 if (else_se)
4033 if (jump_over_else)
4035 tree last = expr_last (expr);
4036 t = build_and_jump (&end_label);
4037 if (rexpr_has_location (last))
4038 SET_EXPR_LOCATION (t, rexpr_location (last));
4039 append_to_statement_list (t, &expr);
4041 if (emit_false)
4043 t = build1 (LABEL_EXPR, void_type_node, false_label);
4044 append_to_statement_list (t, &expr);
4046 append_to_statement_list (else_, &expr);
4048 if (emit_end && end_label)
4050 t = build1 (LABEL_EXPR, void_type_node, end_label);
4051 append_to_statement_list (t, &expr);
4054 return expr;
4057 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
4059 tree
4060 gimple_boolify (tree expr)
4062 tree type = TREE_TYPE (expr);
4063 location_t loc = EXPR_LOCATION (expr);
4065 if (TREE_CODE (expr) == NE_EXPR
4066 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
4067 && integer_zerop (TREE_OPERAND (expr, 1)))
4069 tree call = TREE_OPERAND (expr, 0);
4070 tree fn = get_callee_fndecl (call);
4072 /* For __builtin_expect ((long) (x), y) recurse into x as well
4073 if x is truth_value_p. */
4074 if (fn
4075 && fndecl_built_in_p (fn, BUILT_IN_EXPECT)
4076 && call_expr_nargs (call) == 2)
4078 tree arg = CALL_EXPR_ARG (call, 0);
4079 if (arg)
4081 if (TREE_CODE (arg) == NOP_EXPR
4082 && TREE_TYPE (arg) == TREE_TYPE (call))
4083 arg = TREE_OPERAND (arg, 0);
4084 if (truth_value_p (TREE_CODE (arg)))
4086 arg = gimple_boolify (arg);
4087 CALL_EXPR_ARG (call, 0)
4088 = fold_convert_loc (loc, TREE_TYPE (call), arg);
4094 switch (TREE_CODE (expr))
4096 case TRUTH_AND_EXPR:
4097 case TRUTH_OR_EXPR:
4098 case TRUTH_XOR_EXPR:
4099 case TRUTH_ANDIF_EXPR:
4100 case TRUTH_ORIF_EXPR:
4101 /* Also boolify the arguments of truth exprs. */
4102 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
4103 /* FALLTHRU */
4105 case TRUTH_NOT_EXPR:
4106 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4108 /* These expressions always produce boolean results. */
4109 if (TREE_CODE (type) != BOOLEAN_TYPE)
4110 TREE_TYPE (expr) = boolean_type_node;
4111 return expr;
4113 case ANNOTATE_EXPR:
4114 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
4116 case annot_expr_ivdep_kind:
4117 case annot_expr_unroll_kind:
4118 case annot_expr_no_vector_kind:
4119 case annot_expr_vector_kind:
4120 case annot_expr_parallel_kind:
4121 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4122 if (TREE_CODE (type) != BOOLEAN_TYPE)
4123 TREE_TYPE (expr) = boolean_type_node;
4124 return expr;
4125 default:
4126 gcc_unreachable ();
4129 default:
4130 if (COMPARISON_CLASS_P (expr))
4132 /* There expressions always prduce boolean results. */
4133 if (TREE_CODE (type) != BOOLEAN_TYPE)
4134 TREE_TYPE (expr) = boolean_type_node;
4135 return expr;
4137 /* Other expressions that get here must have boolean values, but
4138 might need to be converted to the appropriate mode. */
4139 if (TREE_CODE (type) == BOOLEAN_TYPE)
4140 return expr;
4141 return fold_convert_loc (loc, boolean_type_node, expr);
4145 /* Given a conditional expression *EXPR_P without side effects, gimplify
4146 its operands. New statements are inserted to PRE_P. */
4148 static enum gimplify_status
4149 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
4151 tree expr = *expr_p, cond;
4152 enum gimplify_status ret, tret;
4153 enum tree_code code;
4155 cond = gimple_boolify (COND_EXPR_COND (expr));
4157 /* We need to handle && and || specially, as their gimplification
4158 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
4159 code = TREE_CODE (cond);
4160 if (code == TRUTH_ANDIF_EXPR)
4161 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
4162 else if (code == TRUTH_ORIF_EXPR)
4163 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
4164 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_condexpr, fb_rvalue);
4165 COND_EXPR_COND (*expr_p) = cond;
4167 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
4168 is_gimple_val, fb_rvalue);
4169 ret = MIN (ret, tret);
4170 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
4171 is_gimple_val, fb_rvalue);
4173 return MIN (ret, tret);
4176 /* Return true if evaluating EXPR could trap.
4177 EXPR is GENERIC, while tree_could_trap_p can be called
4178 only on GIMPLE. */
4180 bool
4181 generic_expr_could_trap_p (tree expr)
4183 unsigned i, n;
4185 if (!expr || is_gimple_val (expr))
4186 return false;
4188 if (!EXPR_P (expr) || tree_could_trap_p (expr))
4189 return true;
4191 n = TREE_OPERAND_LENGTH (expr);
4192 for (i = 0; i < n; i++)
4193 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
4194 return true;
4196 return false;
4199 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
4200 into
4202 if (p) if (p)
4203 t1 = a; a;
4204 else or else
4205 t1 = b; b;
4208 The second form is used when *EXPR_P is of type void.
4210 PRE_P points to the list where side effects that must happen before
4211 *EXPR_P should be stored. */
4213 static enum gimplify_status
4214 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
4216 tree expr = *expr_p;
4217 tree type = TREE_TYPE (expr);
4218 location_t loc = EXPR_LOCATION (expr);
4219 tree tmp, arm1, arm2;
4220 enum gimplify_status ret;
4221 tree label_true, label_false, label_cont;
4222 bool have_then_clause_p, have_else_clause_p;
4223 gcond *cond_stmt;
4224 enum tree_code pred_code;
4225 gimple_seq seq = NULL;
4227 /* If this COND_EXPR has a value, copy the values into a temporary within
4228 the arms. */
4229 if (!VOID_TYPE_P (type))
4231 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
4232 tree result;
4234 /* If either an rvalue is ok or we do not require an lvalue, create the
4235 temporary. But we cannot do that if the type is addressable. */
4236 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
4237 && !TREE_ADDRESSABLE (type))
4239 if (gimplify_ctxp->allow_rhs_cond_expr
4240 /* If either branch has side effects or could trap, it can't be
4241 evaluated unconditionally. */
4242 && !TREE_SIDE_EFFECTS (then_)
4243 && !generic_expr_could_trap_p (then_)
4244 && !TREE_SIDE_EFFECTS (else_)
4245 && !generic_expr_could_trap_p (else_))
4246 return gimplify_pure_cond_expr (expr_p, pre_p);
4248 tmp = create_tmp_var (type, "iftmp");
4249 result = tmp;
4252 /* Otherwise, only create and copy references to the values. */
4253 else
4255 type = build_pointer_type (type);
4257 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4258 then_ = build_fold_addr_expr_loc (loc, then_);
4260 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4261 else_ = build_fold_addr_expr_loc (loc, else_);
4263 expr
4264 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
4266 tmp = create_tmp_var (type, "iftmp");
4267 result = build_simple_mem_ref_loc (loc, tmp);
4270 /* Build the new then clause, `tmp = then_;'. But don't build the
4271 assignment if the value is void; in C++ it can be if it's a throw. */
4272 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4273 TREE_OPERAND (expr, 1) = build2 (INIT_EXPR, type, tmp, then_);
4275 /* Similarly, build the new else clause, `tmp = else_;'. */
4276 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4277 TREE_OPERAND (expr, 2) = build2 (INIT_EXPR, type, tmp, else_);
4279 TREE_TYPE (expr) = void_type_node;
4280 recalculate_side_effects (expr);
4282 /* Move the COND_EXPR to the prequeue. */
4283 gimplify_stmt (&expr, pre_p);
4285 *expr_p = result;
4286 return GS_ALL_DONE;
4289 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
4290 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
4291 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
4292 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
4294 /* Make sure the condition has BOOLEAN_TYPE. */
4295 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4297 /* Break apart && and || conditions. */
4298 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
4299 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
4301 expr = shortcut_cond_expr (expr);
4303 if (expr != *expr_p)
4305 *expr_p = expr;
4307 /* We can't rely on gimplify_expr to re-gimplify the expanded
4308 form properly, as cleanups might cause the target labels to be
4309 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
4310 set up a conditional context. */
4311 gimple_push_condition ();
4312 gimplify_stmt (expr_p, &seq);
4313 gimple_pop_condition (pre_p);
4314 gimple_seq_add_seq (pre_p, seq);
4316 return GS_ALL_DONE;
4320 /* Now do the normal gimplification. */
4322 /* Gimplify condition. */
4323 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
4324 is_gimple_condexpr_for_cond, fb_rvalue);
4325 if (ret == GS_ERROR)
4326 return GS_ERROR;
4327 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
4329 gimple_push_condition ();
4331 have_then_clause_p = have_else_clause_p = false;
4332 label_true = find_goto_label (TREE_OPERAND (expr, 1));
4333 if (label_true
4334 && DECL_CONTEXT (GOTO_DESTINATION (label_true)) == current_function_decl
4335 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4336 have different locations, otherwise we end up with incorrect
4337 location information on the branches. */
4338 && (optimize
4339 || !EXPR_HAS_LOCATION (expr)
4340 || !rexpr_has_location (label_true)
4341 || EXPR_LOCATION (expr) == rexpr_location (label_true)))
4343 have_then_clause_p = true;
4344 label_true = GOTO_DESTINATION (label_true);
4346 else
4347 label_true = create_artificial_label (UNKNOWN_LOCATION);
4348 label_false = find_goto_label (TREE_OPERAND (expr, 2));
4349 if (label_false
4350 && DECL_CONTEXT (GOTO_DESTINATION (label_false)) == current_function_decl
4351 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4352 have different locations, otherwise we end up with incorrect
4353 location information on the branches. */
4354 && (optimize
4355 || !EXPR_HAS_LOCATION (expr)
4356 || !rexpr_has_location (label_false)
4357 || EXPR_LOCATION (expr) == rexpr_location (label_false)))
4359 have_else_clause_p = true;
4360 label_false = GOTO_DESTINATION (label_false);
4362 else
4363 label_false = create_artificial_label (UNKNOWN_LOCATION);
4365 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
4366 &arm2);
4367 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
4368 label_false);
4369 gimple_set_location (cond_stmt, EXPR_LOCATION (expr));
4370 copy_warning (cond_stmt, COND_EXPR_COND (expr));
4371 gimplify_seq_add_stmt (&seq, cond_stmt);
4372 gimple_stmt_iterator gsi = gsi_last (seq);
4373 maybe_fold_stmt (&gsi);
4375 label_cont = NULL_TREE;
4376 if (!have_then_clause_p)
4378 /* For if (...) {} else { code; } put label_true after
4379 the else block. */
4380 if (TREE_OPERAND (expr, 1) == NULL_TREE
4381 && !have_else_clause_p
4382 && TREE_OPERAND (expr, 2) != NULL_TREE)
4383 label_cont = label_true;
4384 else
4386 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
4387 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
4388 /* For if (...) { code; } else {} or
4389 if (...) { code; } else goto label; or
4390 if (...) { code; return; } else { ... }
4391 label_cont isn't needed. */
4392 if (!have_else_clause_p
4393 && TREE_OPERAND (expr, 2) != NULL_TREE
4394 && gimple_seq_may_fallthru (seq))
4396 gimple *g;
4397 label_cont = create_artificial_label (UNKNOWN_LOCATION);
4399 g = gimple_build_goto (label_cont);
4401 /* GIMPLE_COND's are very low level; they have embedded
4402 gotos. This particular embedded goto should not be marked
4403 with the location of the original COND_EXPR, as it would
4404 correspond to the COND_EXPR's condition, not the ELSE or the
4405 THEN arms. To avoid marking it with the wrong location, flag
4406 it as "no location". */
4407 gimple_set_do_not_emit_location (g);
4409 gimplify_seq_add_stmt (&seq, g);
4413 if (!have_else_clause_p)
4415 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
4416 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
4418 if (label_cont)
4419 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
4421 gimple_pop_condition (pre_p);
4422 gimple_seq_add_seq (pre_p, seq);
4424 if (ret == GS_ERROR)
4425 ; /* Do nothing. */
4426 else if (have_then_clause_p || have_else_clause_p)
4427 ret = GS_ALL_DONE;
4428 else
4430 /* Both arms are empty; replace the COND_EXPR with its predicate. */
4431 expr = TREE_OPERAND (expr, 0);
4432 gimplify_stmt (&expr, pre_p);
4435 *expr_p = NULL;
4436 return ret;
4439 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4440 to be marked addressable.
4442 We cannot rely on such an expression being directly markable if a temporary
4443 has been created by the gimplification. In this case, we create another
4444 temporary and initialize it with a copy, which will become a store after we
4445 mark it addressable. This can happen if the front-end passed us something
4446 that it could not mark addressable yet, like a Fortran pass-by-reference
4447 parameter (int) floatvar. */
4449 static void
4450 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4452 while (handled_component_p (*expr_p))
4453 expr_p = &TREE_OPERAND (*expr_p, 0);
4454 if (is_gimple_reg (*expr_p))
4456 /* Do not allow an SSA name as the temporary. */
4457 tree var = get_initialized_tmp_var (*expr_p, seq_p, NULL, false);
4458 DECL_NOT_GIMPLE_REG_P (var) = 1;
4459 *expr_p = var;
4463 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4464 a call to __builtin_memcpy. */
4466 static enum gimplify_status
4467 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4468 gimple_seq *seq_p)
4470 tree t, to, to_ptr, from, from_ptr;
4471 gcall *gs;
4472 location_t loc = EXPR_LOCATION (*expr_p);
4474 to = TREE_OPERAND (*expr_p, 0);
4475 from = TREE_OPERAND (*expr_p, 1);
4477 /* Mark the RHS addressable. Beware that it may not be possible to do so
4478 directly if a temporary has been created by the gimplification. */
4479 prepare_gimple_addressable (&from, seq_p);
4481 mark_addressable (from);
4482 from_ptr = build_fold_addr_expr_loc (loc, from);
4483 gimplify_arg (&from_ptr, seq_p, loc);
4485 mark_addressable (to);
4486 to_ptr = build_fold_addr_expr_loc (loc, to);
4487 gimplify_arg (&to_ptr, seq_p, loc);
4489 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4491 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4492 gimple_call_set_alloca_for_var (gs, true);
4494 if (want_value)
4496 /* tmp = memcpy() */
4497 t = create_tmp_var (TREE_TYPE (to_ptr));
4498 gimple_call_set_lhs (gs, t);
4499 gimplify_seq_add_stmt (seq_p, gs);
4501 *expr_p = build_simple_mem_ref (t);
4502 return GS_ALL_DONE;
4505 gimplify_seq_add_stmt (seq_p, gs);
4506 *expr_p = NULL;
4507 return GS_ALL_DONE;
4510 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4511 a call to __builtin_memset. In this case we know that the RHS is
4512 a CONSTRUCTOR with an empty element list. */
4514 static enum gimplify_status
4515 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4516 gimple_seq *seq_p)
4518 tree t, from, to, to_ptr;
4519 gcall *gs;
4520 location_t loc = EXPR_LOCATION (*expr_p);
4522 /* Assert our assumptions, to abort instead of producing wrong code
4523 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4524 not be immediately exposed. */
4525 from = TREE_OPERAND (*expr_p, 1);
4526 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4527 from = TREE_OPERAND (from, 0);
4529 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4530 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4532 /* Now proceed. */
4533 to = TREE_OPERAND (*expr_p, 0);
4535 to_ptr = build_fold_addr_expr_loc (loc, to);
4536 gimplify_arg (&to_ptr, seq_p, loc);
4537 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4539 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4541 if (want_value)
4543 /* tmp = memset() */
4544 t = create_tmp_var (TREE_TYPE (to_ptr));
4545 gimple_call_set_lhs (gs, t);
4546 gimplify_seq_add_stmt (seq_p, gs);
4548 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4549 return GS_ALL_DONE;
4552 gimplify_seq_add_stmt (seq_p, gs);
4553 *expr_p = NULL;
4554 return GS_ALL_DONE;
4557 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4558 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4559 assignment. Return non-null if we detect a potential overlap. */
4561 struct gimplify_init_ctor_preeval_data
4563 /* The base decl of the lhs object. May be NULL, in which case we
4564 have to assume the lhs is indirect. */
4565 tree lhs_base_decl;
4567 /* The alias set of the lhs object. */
4568 alias_set_type lhs_alias_set;
4571 static tree
4572 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4574 struct gimplify_init_ctor_preeval_data *data
4575 = (struct gimplify_init_ctor_preeval_data *) xdata;
4576 tree t = *tp;
4578 /* If we find the base object, obviously we have overlap. */
4579 if (data->lhs_base_decl == t)
4580 return t;
4582 /* If the constructor component is indirect, determine if we have a
4583 potential overlap with the lhs. The only bits of information we
4584 have to go on at this point are addressability and alias sets. */
4585 if ((INDIRECT_REF_P (t)
4586 || TREE_CODE (t) == MEM_REF)
4587 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4588 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
4589 return t;
4591 /* If the constructor component is a call, determine if it can hide a
4592 potential overlap with the lhs through an INDIRECT_REF like above.
4593 ??? Ugh - this is completely broken. In fact this whole analysis
4594 doesn't look conservative. */
4595 if (TREE_CODE (t) == CALL_EXPR)
4597 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
4599 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
4600 if (POINTER_TYPE_P (TREE_VALUE (type))
4601 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4602 && alias_sets_conflict_p (data->lhs_alias_set,
4603 get_alias_set
4604 (TREE_TYPE (TREE_VALUE (type)))))
4605 return t;
4608 if (IS_TYPE_OR_DECL_P (t))
4609 *walk_subtrees = 0;
4610 return NULL;
4613 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
4614 force values that overlap with the lhs (as described by *DATA)
4615 into temporaries. */
4617 static void
4618 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4619 struct gimplify_init_ctor_preeval_data *data)
4621 enum gimplify_status one;
4623 /* If the value is constant, then there's nothing to pre-evaluate. */
4624 if (TREE_CONSTANT (*expr_p))
4626 /* Ensure it does not have side effects, it might contain a reference to
4627 the object we're initializing. */
4628 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
4629 return;
4632 /* If the type has non-trivial constructors, we can't pre-evaluate. */
4633 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
4634 return;
4636 /* Recurse for nested constructors. */
4637 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
4639 unsigned HOST_WIDE_INT ix;
4640 constructor_elt *ce;
4641 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
4643 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
4644 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
4646 return;
4649 /* If this is a variable sized type, we must remember the size. */
4650 maybe_with_size_expr (expr_p);
4652 /* Gimplify the constructor element to something appropriate for the rhs
4653 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
4654 the gimplifier will consider this a store to memory. Doing this
4655 gimplification now means that we won't have to deal with complicated
4656 language-specific trees, nor trees like SAVE_EXPR that can induce
4657 exponential search behavior. */
4658 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
4659 if (one == GS_ERROR)
4661 *expr_p = NULL;
4662 return;
4665 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
4666 with the lhs, since "a = { .x=a }" doesn't make sense. This will
4667 always be true for all scalars, since is_gimple_mem_rhs insists on a
4668 temporary variable for them. */
4669 if (DECL_P (*expr_p))
4670 return;
4672 /* If this is of variable size, we have no choice but to assume it doesn't
4673 overlap since we can't make a temporary for it. */
4674 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
4675 return;
4677 /* Otherwise, we must search for overlap ... */
4678 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
4679 return;
4681 /* ... and if found, force the value into a temporary. */
4682 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
4685 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
4686 a RANGE_EXPR in a CONSTRUCTOR for an array.
4688 var = lower;
4689 loop_entry:
4690 object[var] = value;
4691 if (var == upper)
4692 goto loop_exit;
4693 var = var + 1;
4694 goto loop_entry;
4695 loop_exit:
4697 We increment var _after_ the loop exit check because we might otherwise
4698 fail if upper == TYPE_MAX_VALUE (type for upper).
4700 Note that we never have to deal with SAVE_EXPRs here, because this has
4701 already been taken care of for us, in gimplify_init_ctor_preeval(). */
4703 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
4704 gimple_seq *, bool);
4706 static void
4707 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
4708 tree value, tree array_elt_type,
4709 gimple_seq *pre_p, bool cleared)
4711 tree loop_entry_label, loop_exit_label, fall_thru_label;
4712 tree var, var_type, cref, tmp;
4714 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
4715 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
4716 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
4718 /* Create and initialize the index variable. */
4719 var_type = TREE_TYPE (upper);
4720 var = create_tmp_var (var_type);
4721 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
4723 /* Add the loop entry label. */
4724 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
4726 /* Build the reference. */
4727 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4728 var, NULL_TREE, NULL_TREE);
4730 /* If we are a constructor, just call gimplify_init_ctor_eval to do
4731 the store. Otherwise just assign value to the reference. */
4733 if (TREE_CODE (value) == CONSTRUCTOR)
4734 /* NB we might have to call ourself recursively through
4735 gimplify_init_ctor_eval if the value is a constructor. */
4736 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4737 pre_p, cleared);
4738 else
4740 if (gimplify_expr (&value, pre_p, NULL, is_gimple_val, fb_rvalue)
4741 != GS_ERROR)
4742 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
4745 /* We exit the loop when the index var is equal to the upper bound. */
4746 gimplify_seq_add_stmt (pre_p,
4747 gimple_build_cond (EQ_EXPR, var, upper,
4748 loop_exit_label, fall_thru_label));
4750 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
4752 /* Otherwise, increment the index var... */
4753 tmp = build2 (PLUS_EXPR, var_type, var,
4754 fold_convert (var_type, integer_one_node));
4755 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
4757 /* ...and jump back to the loop entry. */
4758 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
4760 /* Add the loop exit label. */
4761 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
4764 /* A subroutine of gimplify_init_constructor. Generate individual
4765 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
4766 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
4767 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
4768 zeroed first. */
4770 static void
4771 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
4772 gimple_seq *pre_p, bool cleared)
4774 tree array_elt_type = NULL;
4775 unsigned HOST_WIDE_INT ix;
4776 tree purpose, value;
4778 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
4779 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
4781 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
4783 tree cref;
4785 /* NULL values are created above for gimplification errors. */
4786 if (value == NULL)
4787 continue;
4789 if (cleared && initializer_zerop (value))
4790 continue;
4792 /* ??? Here's to hoping the front end fills in all of the indices,
4793 so we don't have to figure out what's missing ourselves. */
4794 gcc_assert (purpose);
4796 /* Skip zero-sized fields, unless value has side-effects. This can
4797 happen with calls to functions returning a empty type, which
4798 we shouldn't discard. As a number of downstream passes don't
4799 expect sets of empty type fields, we rely on the gimplification of
4800 the MODIFY_EXPR we make below to drop the assignment statement. */
4801 if (!TREE_SIDE_EFFECTS (value)
4802 && TREE_CODE (purpose) == FIELD_DECL
4803 && is_empty_type (TREE_TYPE (purpose)))
4804 continue;
4806 /* If we have a RANGE_EXPR, we have to build a loop to assign the
4807 whole range. */
4808 if (TREE_CODE (purpose) == RANGE_EXPR)
4810 tree lower = TREE_OPERAND (purpose, 0);
4811 tree upper = TREE_OPERAND (purpose, 1);
4813 /* If the lower bound is equal to upper, just treat it as if
4814 upper was the index. */
4815 if (simple_cst_equal (lower, upper))
4816 purpose = upper;
4817 else
4819 gimplify_init_ctor_eval_range (object, lower, upper, value,
4820 array_elt_type, pre_p, cleared);
4821 continue;
4825 if (array_elt_type)
4827 /* Do not use bitsizetype for ARRAY_REF indices. */
4828 if (TYPE_DOMAIN (TREE_TYPE (object)))
4829 purpose
4830 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
4831 purpose);
4832 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4833 purpose, NULL_TREE, NULL_TREE);
4835 else
4837 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
4838 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
4839 unshare_expr (object), purpose, NULL_TREE);
4842 if (TREE_CODE (value) == CONSTRUCTOR
4843 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
4844 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4845 pre_p, cleared);
4846 else
4848 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
4849 gimplify_and_add (init, pre_p);
4850 ggc_free (init);
4855 /* Return the appropriate RHS predicate for this LHS. */
4857 gimple_predicate
4858 rhs_predicate_for (tree lhs)
4860 if (is_gimple_reg (lhs))
4861 return is_gimple_reg_rhs_or_call;
4862 else
4863 return is_gimple_mem_rhs_or_call;
4866 /* Return the initial guess for an appropriate RHS predicate for this LHS,
4867 before the LHS has been gimplified. */
4869 static gimple_predicate
4870 initial_rhs_predicate_for (tree lhs)
4872 if (is_gimple_reg_type (TREE_TYPE (lhs)))
4873 return is_gimple_reg_rhs_or_call;
4874 else
4875 return is_gimple_mem_rhs_or_call;
4878 /* Gimplify a C99 compound literal expression. This just means adding
4879 the DECL_EXPR before the current statement and using its anonymous
4880 decl instead. */
4882 static enum gimplify_status
4883 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
4884 bool (*gimple_test_f) (tree),
4885 fallback_t fallback)
4887 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
4888 tree decl = DECL_EXPR_DECL (decl_s);
4889 tree init = DECL_INITIAL (decl);
4890 /* Mark the decl as addressable if the compound literal
4891 expression is addressable now, otherwise it is marked too late
4892 after we gimplify the initialization expression. */
4893 if (TREE_ADDRESSABLE (*expr_p))
4894 TREE_ADDRESSABLE (decl) = 1;
4895 /* Otherwise, if we don't need an lvalue and have a literal directly
4896 substitute it. Check if it matches the gimple predicate, as
4897 otherwise we'd generate a new temporary, and we can as well just
4898 use the decl we already have. */
4899 else if (!TREE_ADDRESSABLE (decl)
4900 && !TREE_THIS_VOLATILE (decl)
4901 && init
4902 && (fallback & fb_lvalue) == 0
4903 && gimple_test_f (init))
4905 *expr_p = init;
4906 return GS_OK;
4909 /* If the decl is not addressable, then it is being used in some
4910 expression or on the right hand side of a statement, and it can
4911 be put into a readonly data section. */
4912 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
4913 TREE_READONLY (decl) = 1;
4915 /* This decl isn't mentioned in the enclosing block, so add it to the
4916 list of temps. FIXME it seems a bit of a kludge to say that
4917 anonymous artificial vars aren't pushed, but everything else is. */
4918 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
4919 gimple_add_tmp_var (decl);
4921 gimplify_and_add (decl_s, pre_p);
4922 *expr_p = decl;
4923 return GS_OK;
4926 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
4927 return a new CONSTRUCTOR if something changed. */
4929 static tree
4930 optimize_compound_literals_in_ctor (tree orig_ctor)
4932 tree ctor = orig_ctor;
4933 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
4934 unsigned int idx, num = vec_safe_length (elts);
4936 for (idx = 0; idx < num; idx++)
4938 tree value = (*elts)[idx].value;
4939 tree newval = value;
4940 if (TREE_CODE (value) == CONSTRUCTOR)
4941 newval = optimize_compound_literals_in_ctor (value);
4942 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
4944 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
4945 tree decl = DECL_EXPR_DECL (decl_s);
4946 tree init = DECL_INITIAL (decl);
4948 if (!TREE_ADDRESSABLE (value)
4949 && !TREE_ADDRESSABLE (decl)
4950 && init
4951 && TREE_CODE (init) == CONSTRUCTOR)
4952 newval = optimize_compound_literals_in_ctor (init);
4954 if (newval == value)
4955 continue;
4957 if (ctor == orig_ctor)
4959 ctor = copy_node (orig_ctor);
4960 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
4961 elts = CONSTRUCTOR_ELTS (ctor);
4963 (*elts)[idx].value = newval;
4965 return ctor;
4968 /* A subroutine of gimplify_modify_expr. Break out elements of a
4969 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
4971 Note that we still need to clear any elements that don't have explicit
4972 initializers, so if not all elements are initialized we keep the
4973 original MODIFY_EXPR, we just remove all of the constructor elements.
4975 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
4976 GS_ERROR if we would have to create a temporary when gimplifying
4977 this constructor. Otherwise, return GS_OK.
4979 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
4981 static enum gimplify_status
4982 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4983 bool want_value, bool notify_temp_creation)
4985 tree object, ctor, type;
4986 enum gimplify_status ret;
4987 vec<constructor_elt, va_gc> *elts;
4988 bool cleared = false;
4989 bool is_empty_ctor = false;
4990 bool is_init_expr = (TREE_CODE (*expr_p) == INIT_EXPR);
4992 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
4994 if (!notify_temp_creation)
4996 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
4997 is_gimple_lvalue, fb_lvalue);
4998 if (ret == GS_ERROR)
4999 return ret;
5002 object = TREE_OPERAND (*expr_p, 0);
5003 ctor = TREE_OPERAND (*expr_p, 1)
5004 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
5005 type = TREE_TYPE (ctor);
5006 elts = CONSTRUCTOR_ELTS (ctor);
5007 ret = GS_ALL_DONE;
5009 switch (TREE_CODE (type))
5011 case RECORD_TYPE:
5012 case UNION_TYPE:
5013 case QUAL_UNION_TYPE:
5014 case ARRAY_TYPE:
5016 /* Use readonly data for initializers of this or smaller size
5017 regardless of the num_nonzero_elements / num_unique_nonzero_elements
5018 ratio. */
5019 const HOST_WIDE_INT min_unique_size = 64;
5020 /* If num_nonzero_elements / num_unique_nonzero_elements ratio
5021 is smaller than this, use readonly data. */
5022 const int unique_nonzero_ratio = 8;
5023 /* True if a single access of the object must be ensured. This is the
5024 case if the target is volatile, the type is non-addressable and more
5025 than one field need to be assigned. */
5026 const bool ensure_single_access
5027 = TREE_THIS_VOLATILE (object)
5028 && !TREE_ADDRESSABLE (type)
5029 && vec_safe_length (elts) > 1;
5030 struct gimplify_init_ctor_preeval_data preeval_data;
5031 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
5032 HOST_WIDE_INT num_unique_nonzero_elements;
5033 bool complete_p, valid_const_initializer;
5035 /* Aggregate types must lower constructors to initialization of
5036 individual elements. The exception is that a CONSTRUCTOR node
5037 with no elements indicates zero-initialization of the whole. */
5038 if (vec_safe_is_empty (elts))
5040 if (notify_temp_creation)
5041 return GS_OK;
5042 is_empty_ctor = true;
5043 break;
5046 /* Fetch information about the constructor to direct later processing.
5047 We might want to make static versions of it in various cases, and
5048 can only do so if it known to be a valid constant initializer. */
5049 valid_const_initializer
5050 = categorize_ctor_elements (ctor, &num_nonzero_elements,
5051 &num_unique_nonzero_elements,
5052 &num_ctor_elements, &complete_p);
5054 /* If a const aggregate variable is being initialized, then it
5055 should never be a lose to promote the variable to be static. */
5056 if (valid_const_initializer
5057 && num_nonzero_elements > 1
5058 && TREE_READONLY (object)
5059 && VAR_P (object)
5060 && !DECL_REGISTER (object)
5061 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object))
5062 /* For ctors that have many repeated nonzero elements
5063 represented through RANGE_EXPRs, prefer initializing
5064 those through runtime loops over copies of large amounts
5065 of data from readonly data section. */
5066 && (num_unique_nonzero_elements
5067 > num_nonzero_elements / unique_nonzero_ratio
5068 || ((unsigned HOST_WIDE_INT) int_size_in_bytes (type)
5069 <= (unsigned HOST_WIDE_INT) min_unique_size)))
5071 if (notify_temp_creation)
5072 return GS_ERROR;
5074 DECL_INITIAL (object) = ctor;
5075 TREE_STATIC (object) = 1;
5076 if (!DECL_NAME (object))
5077 DECL_NAME (object) = create_tmp_var_name ("C");
5078 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
5080 /* ??? C++ doesn't automatically append a .<number> to the
5081 assembler name, and even when it does, it looks at FE private
5082 data structures to figure out what that number should be,
5083 which are not set for this variable. I suppose this is
5084 important for local statics for inline functions, which aren't
5085 "local" in the object file sense. So in order to get a unique
5086 TU-local symbol, we must invoke the lhd version now. */
5087 lhd_set_decl_assembler_name (object);
5089 *expr_p = NULL_TREE;
5090 break;
5093 /* If there are "lots" of initialized elements, even discounting
5094 those that are not address constants (and thus *must* be
5095 computed at runtime), then partition the constructor into
5096 constant and non-constant parts. Block copy the constant
5097 parts in, then generate code for the non-constant parts. */
5098 /* TODO. There's code in cp/typeck.c to do this. */
5100 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
5101 /* store_constructor will ignore the clearing of variable-sized
5102 objects. Initializers for such objects must explicitly set
5103 every field that needs to be set. */
5104 cleared = false;
5105 else if (!complete_p)
5106 /* If the constructor isn't complete, clear the whole object
5107 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
5109 ??? This ought not to be needed. For any element not present
5110 in the initializer, we should simply set them to zero. Except
5111 we'd need to *find* the elements that are not present, and that
5112 requires trickery to avoid quadratic compile-time behavior in
5113 large cases or excessive memory use in small cases. */
5114 cleared = !CONSTRUCTOR_NO_CLEARING (ctor);
5115 else if (num_ctor_elements - num_nonzero_elements
5116 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
5117 && num_nonzero_elements < num_ctor_elements / 4)
5118 /* If there are "lots" of zeros, it's more efficient to clear
5119 the memory and then set the nonzero elements. */
5120 cleared = true;
5121 else if (ensure_single_access && num_nonzero_elements == 0)
5122 /* If a single access to the target must be ensured and all elements
5123 are zero, then it's optimal to clear whatever their number. */
5124 cleared = true;
5125 else
5126 cleared = false;
5128 /* If there are "lots" of initialized elements, and all of them
5129 are valid address constants, then the entire initializer can
5130 be dropped to memory, and then memcpy'd out. Don't do this
5131 for sparse arrays, though, as it's more efficient to follow
5132 the standard CONSTRUCTOR behavior of memset followed by
5133 individual element initialization. Also don't do this for small
5134 all-zero initializers (which aren't big enough to merit
5135 clearing), and don't try to make bitwise copies of
5136 TREE_ADDRESSABLE types. */
5137 if (valid_const_initializer
5138 && complete_p
5139 && !(cleared || num_nonzero_elements == 0)
5140 && !TREE_ADDRESSABLE (type))
5142 HOST_WIDE_INT size = int_size_in_bytes (type);
5143 unsigned int align;
5145 /* ??? We can still get unbounded array types, at least
5146 from the C++ front end. This seems wrong, but attempt
5147 to work around it for now. */
5148 if (size < 0)
5150 size = int_size_in_bytes (TREE_TYPE (object));
5151 if (size >= 0)
5152 TREE_TYPE (ctor) = type = TREE_TYPE (object);
5155 /* Find the maximum alignment we can assume for the object. */
5156 /* ??? Make use of DECL_OFFSET_ALIGN. */
5157 if (DECL_P (object))
5158 align = DECL_ALIGN (object);
5159 else
5160 align = TYPE_ALIGN (type);
5162 /* Do a block move either if the size is so small as to make
5163 each individual move a sub-unit move on average, or if it
5164 is so large as to make individual moves inefficient. */
5165 if (size > 0
5166 && num_nonzero_elements > 1
5167 /* For ctors that have many repeated nonzero elements
5168 represented through RANGE_EXPRs, prefer initializing
5169 those through runtime loops over copies of large amounts
5170 of data from readonly data section. */
5171 && (num_unique_nonzero_elements
5172 > num_nonzero_elements / unique_nonzero_ratio
5173 || size <= min_unique_size)
5174 && (size < num_nonzero_elements
5175 || !can_move_by_pieces (size, align)))
5177 if (notify_temp_creation)
5178 return GS_ERROR;
5180 walk_tree (&ctor, force_labels_r, NULL, NULL);
5181 ctor = tree_output_constant_def (ctor);
5182 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
5183 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
5184 TREE_OPERAND (*expr_p, 1) = ctor;
5186 /* This is no longer an assignment of a CONSTRUCTOR, but
5187 we still may have processing to do on the LHS. So
5188 pretend we didn't do anything here to let that happen. */
5189 return GS_UNHANDLED;
5193 /* If a single access to the target must be ensured and there are
5194 nonzero elements or the zero elements are not assigned en masse,
5195 initialize the target from a temporary. */
5196 if (ensure_single_access && (num_nonzero_elements > 0 || !cleared))
5198 if (notify_temp_creation)
5199 return GS_ERROR;
5201 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
5202 TREE_OPERAND (*expr_p, 0) = temp;
5203 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
5204 *expr_p,
5205 build2 (MODIFY_EXPR, void_type_node,
5206 object, temp));
5207 return GS_OK;
5210 if (notify_temp_creation)
5211 return GS_OK;
5213 /* If there are nonzero elements and if needed, pre-evaluate to capture
5214 elements overlapping with the lhs into temporaries. We must do this
5215 before clearing to fetch the values before they are zeroed-out. */
5216 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
5218 preeval_data.lhs_base_decl = get_base_address (object);
5219 if (!DECL_P (preeval_data.lhs_base_decl))
5220 preeval_data.lhs_base_decl = NULL;
5221 preeval_data.lhs_alias_set = get_alias_set (object);
5223 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
5224 pre_p, post_p, &preeval_data);
5227 bool ctor_has_side_effects_p
5228 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
5230 if (cleared)
5232 /* Zap the CONSTRUCTOR element list, which simplifies this case.
5233 Note that we still have to gimplify, in order to handle the
5234 case of variable sized types. Avoid shared tree structures. */
5235 CONSTRUCTOR_ELTS (ctor) = NULL;
5236 TREE_SIDE_EFFECTS (ctor) = 0;
5237 object = unshare_expr (object);
5238 gimplify_stmt (expr_p, pre_p);
5241 /* If we have not block cleared the object, or if there are nonzero
5242 elements in the constructor, or if the constructor has side effects,
5243 add assignments to the individual scalar fields of the object. */
5244 if (!cleared
5245 || num_nonzero_elements > 0
5246 || ctor_has_side_effects_p)
5247 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
5249 *expr_p = NULL_TREE;
5251 break;
5253 case COMPLEX_TYPE:
5255 tree r, i;
5257 if (notify_temp_creation)
5258 return GS_OK;
5260 /* Extract the real and imaginary parts out of the ctor. */
5261 gcc_assert (elts->length () == 2);
5262 r = (*elts)[0].value;
5263 i = (*elts)[1].value;
5264 if (r == NULL || i == NULL)
5266 tree zero = build_zero_cst (TREE_TYPE (type));
5267 if (r == NULL)
5268 r = zero;
5269 if (i == NULL)
5270 i = zero;
5273 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
5274 represent creation of a complex value. */
5275 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
5277 ctor = build_complex (type, r, i);
5278 TREE_OPERAND (*expr_p, 1) = ctor;
5280 else
5282 ctor = build2 (COMPLEX_EXPR, type, r, i);
5283 TREE_OPERAND (*expr_p, 1) = ctor;
5284 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
5285 pre_p,
5286 post_p,
5287 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
5288 fb_rvalue);
5291 break;
5293 case VECTOR_TYPE:
5295 unsigned HOST_WIDE_INT ix;
5296 constructor_elt *ce;
5298 if (notify_temp_creation)
5299 return GS_OK;
5301 /* Go ahead and simplify constant constructors to VECTOR_CST. */
5302 if (TREE_CONSTANT (ctor))
5304 bool constant_p = true;
5305 tree value;
5307 /* Even when ctor is constant, it might contain non-*_CST
5308 elements, such as addresses or trapping values like
5309 1.0/0.0 - 1.0/0.0. Such expressions don't belong
5310 in VECTOR_CST nodes. */
5311 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
5312 if (!CONSTANT_CLASS_P (value))
5314 constant_p = false;
5315 break;
5318 if (constant_p)
5320 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
5321 break;
5324 TREE_CONSTANT (ctor) = 0;
5327 /* Vector types use CONSTRUCTOR all the way through gimple
5328 compilation as a general initializer. */
5329 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
5331 enum gimplify_status tret;
5332 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
5333 fb_rvalue);
5334 if (tret == GS_ERROR)
5335 ret = GS_ERROR;
5336 else if (TREE_STATIC (ctor)
5337 && !initializer_constant_valid_p (ce->value,
5338 TREE_TYPE (ce->value)))
5339 TREE_STATIC (ctor) = 0;
5341 recompute_constructor_flags (ctor);
5342 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
5343 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
5345 break;
5347 default:
5348 /* So how did we get a CONSTRUCTOR for a scalar type? */
5349 gcc_unreachable ();
5352 if (ret == GS_ERROR)
5353 return GS_ERROR;
5354 /* If we have gimplified both sides of the initializer but have
5355 not emitted an assignment, do so now. */
5356 if (*expr_p)
5358 tree lhs = TREE_OPERAND (*expr_p, 0);
5359 tree rhs = TREE_OPERAND (*expr_p, 1);
5360 if (want_value && object == lhs)
5361 lhs = unshare_expr (lhs);
5362 gassign *init = gimple_build_assign (lhs, rhs);
5363 gimplify_seq_add_stmt (pre_p, init);
5365 if (want_value)
5367 *expr_p = object;
5368 ret = GS_OK;
5370 else
5372 *expr_p = NULL;
5373 ret = GS_ALL_DONE;
5376 /* If the user requests to initialize automatic variables, we
5377 should initialize paddings inside the variable. Add a call to
5378 __BUILTIN_CLEAR_PADDING (&object, 0, for_auto_init = true) to
5379 initialize paddings of object always to zero regardless of
5380 INIT_TYPE. Note, we will not insert this call if the aggregate
5381 variable has be completely cleared already or it's initialized
5382 with an empty constructor. */
5383 if (is_init_expr
5384 && ((AGGREGATE_TYPE_P (type) && !cleared && !is_empty_ctor)
5385 || !AGGREGATE_TYPE_P (type))
5386 && is_var_need_auto_init (object))
5387 gimple_add_padding_init_for_auto_var (object, false, pre_p);
5389 return ret;
5392 /* Given a pointer value OP0, return a simplified version of an
5393 indirection through OP0, or NULL_TREE if no simplification is
5394 possible. This may only be applied to a rhs of an expression.
5395 Note that the resulting type may be different from the type pointed
5396 to in the sense that it is still compatible from the langhooks
5397 point of view. */
5399 static tree
5400 gimple_fold_indirect_ref_rhs (tree t)
5402 return gimple_fold_indirect_ref (t);
5405 /* Subroutine of gimplify_modify_expr to do simplifications of
5406 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
5407 something changes. */
5409 static enum gimplify_status
5410 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
5411 gimple_seq *pre_p, gimple_seq *post_p,
5412 bool want_value)
5414 enum gimplify_status ret = GS_UNHANDLED;
5415 bool changed;
5419 changed = false;
5420 switch (TREE_CODE (*from_p))
5422 case VAR_DECL:
5423 /* If we're assigning from a read-only variable initialized with
5424 a constructor and not volatile, do the direct assignment from
5425 the constructor, but only if the target is not volatile either
5426 since this latter assignment might end up being done on a per
5427 field basis. However, if the target is volatile and the type
5428 is aggregate and non-addressable, gimplify_init_constructor
5429 knows that it needs to ensure a single access to the target
5430 and it will return GS_OK only in this case. */
5431 if (TREE_READONLY (*from_p)
5432 && DECL_INITIAL (*from_p)
5433 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR
5434 && !TREE_THIS_VOLATILE (*from_p)
5435 && (!TREE_THIS_VOLATILE (*to_p)
5436 || (AGGREGATE_TYPE_P (TREE_TYPE (*to_p))
5437 && !TREE_ADDRESSABLE (TREE_TYPE (*to_p)))))
5439 tree old_from = *from_p;
5440 enum gimplify_status subret;
5442 /* Move the constructor into the RHS. */
5443 *from_p = unshare_expr (DECL_INITIAL (*from_p));
5445 /* Let's see if gimplify_init_constructor will need to put
5446 it in memory. */
5447 subret = gimplify_init_constructor (expr_p, NULL, NULL,
5448 false, true);
5449 if (subret == GS_ERROR)
5451 /* If so, revert the change. */
5452 *from_p = old_from;
5454 else
5456 ret = GS_OK;
5457 changed = true;
5460 break;
5461 case INDIRECT_REF:
5463 /* If we have code like
5465 *(const A*)(A*)&x
5467 where the type of "x" is a (possibly cv-qualified variant
5468 of "A"), treat the entire expression as identical to "x".
5469 This kind of code arises in C++ when an object is bound
5470 to a const reference, and if "x" is a TARGET_EXPR we want
5471 to take advantage of the optimization below. */
5472 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5473 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
5474 if (t)
5476 if (TREE_THIS_VOLATILE (t) != volatile_p)
5478 if (DECL_P (t))
5479 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5480 build_fold_addr_expr (t));
5481 if (REFERENCE_CLASS_P (t))
5482 TREE_THIS_VOLATILE (t) = volatile_p;
5484 *from_p = t;
5485 ret = GS_OK;
5486 changed = true;
5488 break;
5491 case TARGET_EXPR:
5493 /* If we are initializing something from a TARGET_EXPR, strip the
5494 TARGET_EXPR and initialize it directly, if possible. This can't
5495 be done if the initializer is void, since that implies that the
5496 temporary is set in some non-trivial way.
5498 ??? What about code that pulls out the temp and uses it
5499 elsewhere? I think that such code never uses the TARGET_EXPR as
5500 an initializer. If I'm wrong, we'll die because the temp won't
5501 have any RTL. In that case, I guess we'll need to replace
5502 references somehow. */
5503 tree init = TARGET_EXPR_INITIAL (*from_p);
5505 if (init
5506 && (TREE_CODE (*expr_p) != MODIFY_EXPR
5507 || !TARGET_EXPR_NO_ELIDE (*from_p))
5508 && !VOID_TYPE_P (TREE_TYPE (init)))
5510 *from_p = init;
5511 ret = GS_OK;
5512 changed = true;
5515 break;
5517 case COMPOUND_EXPR:
5518 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5519 caught. */
5520 gimplify_compound_expr (from_p, pre_p, true);
5521 ret = GS_OK;
5522 changed = true;
5523 break;
5525 case CONSTRUCTOR:
5526 /* If we already made some changes, let the front end have a
5527 crack at this before we break it down. */
5528 if (ret != GS_UNHANDLED)
5529 break;
5531 /* If we're initializing from a CONSTRUCTOR, break this into
5532 individual MODIFY_EXPRs. */
5533 ret = gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5534 false);
5535 return ret;
5537 case COND_EXPR:
5538 /* If we're assigning to a non-register type, push the assignment
5539 down into the branches. This is mandatory for ADDRESSABLE types,
5540 since we cannot generate temporaries for such, but it saves a
5541 copy in other cases as well. */
5542 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5544 /* This code should mirror the code in gimplify_cond_expr. */
5545 enum tree_code code = TREE_CODE (*expr_p);
5546 tree cond = *from_p;
5547 tree result = *to_p;
5549 ret = gimplify_expr (&result, pre_p, post_p,
5550 is_gimple_lvalue, fb_lvalue);
5551 if (ret != GS_ERROR)
5552 ret = GS_OK;
5554 /* If we are going to write RESULT more than once, clear
5555 TREE_READONLY flag, otherwise we might incorrectly promote
5556 the variable to static const and initialize it at compile
5557 time in one of the branches. */
5558 if (VAR_P (result)
5559 && TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node
5560 && TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5561 TREE_READONLY (result) = 0;
5562 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
5563 TREE_OPERAND (cond, 1)
5564 = build2 (code, void_type_node, result,
5565 TREE_OPERAND (cond, 1));
5566 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5567 TREE_OPERAND (cond, 2)
5568 = build2 (code, void_type_node, unshare_expr (result),
5569 TREE_OPERAND (cond, 2));
5571 TREE_TYPE (cond) = void_type_node;
5572 recalculate_side_effects (cond);
5574 if (want_value)
5576 gimplify_and_add (cond, pre_p);
5577 *expr_p = unshare_expr (result);
5579 else
5580 *expr_p = cond;
5581 return ret;
5583 break;
5585 case CALL_EXPR:
5586 /* For calls that return in memory, give *to_p as the CALL_EXPR's
5587 return slot so that we don't generate a temporary. */
5588 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
5589 && aggregate_value_p (*from_p, *from_p))
5591 bool use_target;
5593 if (!(rhs_predicate_for (*to_p))(*from_p))
5594 /* If we need a temporary, *to_p isn't accurate. */
5595 use_target = false;
5596 /* It's OK to use the return slot directly unless it's an NRV. */
5597 else if (TREE_CODE (*to_p) == RESULT_DECL
5598 && DECL_NAME (*to_p) == NULL_TREE
5599 && needs_to_live_in_memory (*to_p))
5600 use_target = true;
5601 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
5602 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
5603 /* Don't force regs into memory. */
5604 use_target = false;
5605 else if (TREE_CODE (*expr_p) == INIT_EXPR)
5606 /* It's OK to use the target directly if it's being
5607 initialized. */
5608 use_target = true;
5609 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
5610 != INTEGER_CST)
5611 /* Always use the target and thus RSO for variable-sized types.
5612 GIMPLE cannot deal with a variable-sized assignment
5613 embedded in a call statement. */
5614 use_target = true;
5615 else if (TREE_CODE (*to_p) != SSA_NAME
5616 && (!is_gimple_variable (*to_p)
5617 || needs_to_live_in_memory (*to_p)))
5618 /* Don't use the original target if it's already addressable;
5619 if its address escapes, and the called function uses the
5620 NRV optimization, a conforming program could see *to_p
5621 change before the called function returns; see c++/19317.
5622 When optimizing, the return_slot pass marks more functions
5623 as safe after we have escape info. */
5624 use_target = false;
5625 else
5626 use_target = true;
5628 if (use_target)
5630 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
5631 mark_addressable (*to_p);
5634 break;
5636 case WITH_SIZE_EXPR:
5637 /* Likewise for calls that return an aggregate of non-constant size,
5638 since we would not be able to generate a temporary at all. */
5639 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
5641 *from_p = TREE_OPERAND (*from_p, 0);
5642 /* We don't change ret in this case because the
5643 WITH_SIZE_EXPR might have been added in
5644 gimplify_modify_expr, so returning GS_OK would lead to an
5645 infinite loop. */
5646 changed = true;
5648 break;
5650 /* If we're initializing from a container, push the initialization
5651 inside it. */
5652 case CLEANUP_POINT_EXPR:
5653 case BIND_EXPR:
5654 case STATEMENT_LIST:
5656 tree wrap = *from_p;
5657 tree t;
5659 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
5660 fb_lvalue);
5661 if (ret != GS_ERROR)
5662 ret = GS_OK;
5664 t = voidify_wrapper_expr (wrap, *expr_p);
5665 gcc_assert (t == *expr_p);
5667 if (want_value)
5669 gimplify_and_add (wrap, pre_p);
5670 *expr_p = unshare_expr (*to_p);
5672 else
5673 *expr_p = wrap;
5674 return GS_OK;
5677 case NOP_EXPR:
5678 /* Pull out compound literal expressions from a NOP_EXPR.
5679 Those are created in the C FE to drop qualifiers during
5680 lvalue conversion. */
5681 if ((TREE_CODE (TREE_OPERAND (*from_p, 0)) == COMPOUND_LITERAL_EXPR)
5682 && tree_ssa_useless_type_conversion (*from_p))
5684 *from_p = TREE_OPERAND (*from_p, 0);
5685 ret = GS_OK;
5686 changed = true;
5688 break;
5690 case COMPOUND_LITERAL_EXPR:
5692 tree complit = TREE_OPERAND (*expr_p, 1);
5693 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
5694 tree decl = DECL_EXPR_DECL (decl_s);
5695 tree init = DECL_INITIAL (decl);
5697 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
5698 into struct T x = { 0, 1, 2 } if the address of the
5699 compound literal has never been taken. */
5700 if (!TREE_ADDRESSABLE (complit)
5701 && !TREE_ADDRESSABLE (decl)
5702 && init)
5704 *expr_p = copy_node (*expr_p);
5705 TREE_OPERAND (*expr_p, 1) = init;
5706 return GS_OK;
5710 default:
5711 break;
5714 while (changed);
5716 return ret;
5720 /* Return true if T looks like a valid GIMPLE statement. */
5722 static bool
5723 is_gimple_stmt (tree t)
5725 const enum tree_code code = TREE_CODE (t);
5727 switch (code)
5729 case NOP_EXPR:
5730 /* The only valid NOP_EXPR is the empty statement. */
5731 return IS_EMPTY_STMT (t);
5733 case BIND_EXPR:
5734 case COND_EXPR:
5735 /* These are only valid if they're void. */
5736 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
5738 case SWITCH_EXPR:
5739 case GOTO_EXPR:
5740 case RETURN_EXPR:
5741 case LABEL_EXPR:
5742 case CASE_LABEL_EXPR:
5743 case TRY_CATCH_EXPR:
5744 case TRY_FINALLY_EXPR:
5745 case EH_FILTER_EXPR:
5746 case CATCH_EXPR:
5747 case ASM_EXPR:
5748 case STATEMENT_LIST:
5749 case OACC_PARALLEL:
5750 case OACC_KERNELS:
5751 case OACC_SERIAL:
5752 case OACC_DATA:
5753 case OACC_HOST_DATA:
5754 case OACC_DECLARE:
5755 case OACC_UPDATE:
5756 case OACC_ENTER_DATA:
5757 case OACC_EXIT_DATA:
5758 case OACC_CACHE:
5759 case OMP_PARALLEL:
5760 case OMP_FOR:
5761 case OMP_SIMD:
5762 case OMP_DISTRIBUTE:
5763 case OMP_LOOP:
5764 case OACC_LOOP:
5765 case OMP_SCAN:
5766 case OMP_SCOPE:
5767 case OMP_SECTIONS:
5768 case OMP_SECTION:
5769 case OMP_SINGLE:
5770 case OMP_MASTER:
5771 case OMP_MASKED:
5772 case OMP_TASKGROUP:
5773 case OMP_ORDERED:
5774 case OMP_CRITICAL:
5775 case OMP_TASK:
5776 case OMP_TARGET:
5777 case OMP_TARGET_DATA:
5778 case OMP_TARGET_UPDATE:
5779 case OMP_TARGET_ENTER_DATA:
5780 case OMP_TARGET_EXIT_DATA:
5781 case OMP_TASKLOOP:
5782 case OMP_TEAMS:
5783 /* These are always void. */
5784 return true;
5786 case CALL_EXPR:
5787 case MODIFY_EXPR:
5788 case PREDICT_EXPR:
5789 /* These are valid regardless of their type. */
5790 return true;
5792 default:
5793 return false;
5798 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
5799 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a gimple register.
5801 IMPORTANT NOTE: This promotion is performed by introducing a load of the
5802 other, unmodified part of the complex object just before the total store.
5803 As a consequence, if the object is still uninitialized, an undefined value
5804 will be loaded into a register, which may result in a spurious exception
5805 if the register is floating-point and the value happens to be a signaling
5806 NaN for example. Then the fully-fledged complex operations lowering pass
5807 followed by a DCE pass are necessary in order to fix things up. */
5809 static enum gimplify_status
5810 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
5811 bool want_value)
5813 enum tree_code code, ocode;
5814 tree lhs, rhs, new_rhs, other, realpart, imagpart;
5816 lhs = TREE_OPERAND (*expr_p, 0);
5817 rhs = TREE_OPERAND (*expr_p, 1);
5818 code = TREE_CODE (lhs);
5819 lhs = TREE_OPERAND (lhs, 0);
5821 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
5822 other = build1 (ocode, TREE_TYPE (rhs), lhs);
5823 suppress_warning (other);
5824 other = get_formal_tmp_var (other, pre_p);
5826 realpart = code == REALPART_EXPR ? rhs : other;
5827 imagpart = code == REALPART_EXPR ? other : rhs;
5829 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
5830 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
5831 else
5832 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
5834 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
5835 *expr_p = (want_value) ? rhs : NULL_TREE;
5837 return GS_ALL_DONE;
5840 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
5842 modify_expr
5843 : varname '=' rhs
5844 | '*' ID '=' rhs
5846 PRE_P points to the list where side effects that must happen before
5847 *EXPR_P should be stored.
5849 POST_P points to the list where side effects that must happen after
5850 *EXPR_P should be stored.
5852 WANT_VALUE is nonzero iff we want to use the value of this expression
5853 in another expression. */
5855 static enum gimplify_status
5856 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5857 bool want_value)
5859 tree *from_p = &TREE_OPERAND (*expr_p, 1);
5860 tree *to_p = &TREE_OPERAND (*expr_p, 0);
5861 enum gimplify_status ret = GS_UNHANDLED;
5862 gimple *assign;
5863 location_t loc = EXPR_LOCATION (*expr_p);
5864 gimple_stmt_iterator gsi;
5866 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
5867 || TREE_CODE (*expr_p) == INIT_EXPR);
5869 /* Trying to simplify a clobber using normal logic doesn't work,
5870 so handle it here. */
5871 if (TREE_CLOBBER_P (*from_p))
5873 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5874 if (ret == GS_ERROR)
5875 return ret;
5876 gcc_assert (!want_value);
5877 if (!VAR_P (*to_p) && TREE_CODE (*to_p) != MEM_REF)
5879 tree addr = get_initialized_tmp_var (build_fold_addr_expr (*to_p),
5880 pre_p, post_p);
5881 *to_p = build_simple_mem_ref_loc (EXPR_LOCATION (*to_p), addr);
5883 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
5884 *expr_p = NULL;
5885 return GS_ALL_DONE;
5888 /* Insert pointer conversions required by the middle-end that are not
5889 required by the frontend. This fixes middle-end type checking for
5890 for example gcc.dg/redecl-6.c. */
5891 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
5893 STRIP_USELESS_TYPE_CONVERSION (*from_p);
5894 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
5895 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
5898 /* See if any simplifications can be done based on what the RHS is. */
5899 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5900 want_value);
5901 if (ret != GS_UNHANDLED)
5902 return ret;
5904 /* For empty types only gimplify the left hand side and right hand
5905 side as statements and throw away the assignment. Do this after
5906 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
5907 types properly. */
5908 if (is_empty_type (TREE_TYPE (*from_p))
5909 && !want_value
5910 /* Don't do this for calls that return addressable types, expand_call
5911 relies on those having a lhs. */
5912 && !(TREE_ADDRESSABLE (TREE_TYPE (*from_p))
5913 && TREE_CODE (*from_p) == CALL_EXPR))
5915 gimplify_stmt (from_p, pre_p);
5916 gimplify_stmt (to_p, pre_p);
5917 *expr_p = NULL_TREE;
5918 return GS_ALL_DONE;
5921 /* If the value being copied is of variable width, compute the length
5922 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
5923 before gimplifying any of the operands so that we can resolve any
5924 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
5925 the size of the expression to be copied, not of the destination, so
5926 that is what we must do here. */
5927 maybe_with_size_expr (from_p);
5929 /* As a special case, we have to temporarily allow for assignments
5930 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
5931 a toplevel statement, when gimplifying the GENERIC expression
5932 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
5933 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
5935 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
5936 prevent gimplify_expr from trying to create a new temporary for
5937 foo's LHS, we tell it that it should only gimplify until it
5938 reaches the CALL_EXPR. On return from gimplify_expr, the newly
5939 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
5940 and all we need to do here is set 'a' to be its LHS. */
5942 /* Gimplify the RHS first for C++17 and bug 71104. */
5943 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
5944 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
5945 if (ret == GS_ERROR)
5946 return ret;
5948 /* Then gimplify the LHS. */
5949 /* If we gimplified the RHS to a CALL_EXPR and that call may return
5950 twice we have to make sure to gimplify into non-SSA as otherwise
5951 the abnormal edge added later will make those defs not dominate
5952 their uses.
5953 ??? Technically this applies only to the registers used in the
5954 resulting non-register *TO_P. */
5955 bool saved_into_ssa = gimplify_ctxp->into_ssa;
5956 if (saved_into_ssa
5957 && TREE_CODE (*from_p) == CALL_EXPR
5958 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
5959 gimplify_ctxp->into_ssa = false;
5960 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5961 gimplify_ctxp->into_ssa = saved_into_ssa;
5962 if (ret == GS_ERROR)
5963 return ret;
5965 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
5966 guess for the predicate was wrong. */
5967 gimple_predicate final_pred = rhs_predicate_for (*to_p);
5968 if (final_pred != initial_pred)
5970 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
5971 if (ret == GS_ERROR)
5972 return ret;
5975 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
5976 size as argument to the call. */
5977 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5979 tree call = TREE_OPERAND (*from_p, 0);
5980 tree vlasize = TREE_OPERAND (*from_p, 1);
5982 if (TREE_CODE (call) == CALL_EXPR
5983 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
5985 int nargs = call_expr_nargs (call);
5986 tree type = TREE_TYPE (call);
5987 tree ap = CALL_EXPR_ARG (call, 0);
5988 tree tag = CALL_EXPR_ARG (call, 1);
5989 tree aptag = CALL_EXPR_ARG (call, 2);
5990 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
5991 IFN_VA_ARG, type,
5992 nargs + 1, ap, tag,
5993 aptag, vlasize);
5994 TREE_OPERAND (*from_p, 0) = newcall;
5998 /* Now see if the above changed *from_p to something we handle specially. */
5999 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
6000 want_value);
6001 if (ret != GS_UNHANDLED)
6002 return ret;
6004 /* If we've got a variable sized assignment between two lvalues (i.e. does
6005 not involve a call), then we can make things a bit more straightforward
6006 by converting the assignment to memcpy or memset. */
6007 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
6009 tree from = TREE_OPERAND (*from_p, 0);
6010 tree size = TREE_OPERAND (*from_p, 1);
6012 if (TREE_CODE (from) == CONSTRUCTOR)
6013 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
6015 if (is_gimple_addressable (from))
6017 *from_p = from;
6018 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
6019 pre_p);
6023 /* Transform partial stores to non-addressable complex variables into
6024 total stores. This allows us to use real instead of virtual operands
6025 for these variables, which improves optimization. */
6026 if ((TREE_CODE (*to_p) == REALPART_EXPR
6027 || TREE_CODE (*to_p) == IMAGPART_EXPR)
6028 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
6029 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
6031 /* Try to alleviate the effects of the gimplification creating artificial
6032 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
6033 make sure not to create DECL_DEBUG_EXPR links across functions. */
6034 if (!gimplify_ctxp->into_ssa
6035 && VAR_P (*from_p)
6036 && DECL_IGNORED_P (*from_p)
6037 && DECL_P (*to_p)
6038 && !DECL_IGNORED_P (*to_p)
6039 && decl_function_context (*to_p) == current_function_decl
6040 && decl_function_context (*from_p) == current_function_decl)
6042 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
6043 DECL_NAME (*from_p)
6044 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
6045 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
6046 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
6049 if (want_value && TREE_THIS_VOLATILE (*to_p))
6050 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
6052 if (TREE_CODE (*from_p) == CALL_EXPR)
6054 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
6055 instead of a GIMPLE_ASSIGN. */
6056 gcall *call_stmt;
6057 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
6059 /* Gimplify internal functions created in the FEs. */
6060 int nargs = call_expr_nargs (*from_p), i;
6061 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
6062 auto_vec<tree> vargs (nargs);
6064 for (i = 0; i < nargs; i++)
6066 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
6067 EXPR_LOCATION (*from_p));
6068 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
6070 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
6071 gimple_call_set_nothrow (call_stmt, TREE_NOTHROW (*from_p));
6072 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
6074 else
6076 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
6077 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
6078 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
6079 tree fndecl = get_callee_fndecl (*from_p);
6080 if (fndecl
6081 && fndecl_built_in_p (fndecl, BUILT_IN_EXPECT)
6082 && call_expr_nargs (*from_p) == 3)
6083 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
6084 CALL_EXPR_ARG (*from_p, 0),
6085 CALL_EXPR_ARG (*from_p, 1),
6086 CALL_EXPR_ARG (*from_p, 2));
6087 else
6089 call_stmt = gimple_build_call_from_tree (*from_p, fnptrtype);
6092 notice_special_calls (call_stmt);
6093 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
6094 gimple_call_set_lhs (call_stmt, *to_p);
6095 else if (TREE_CODE (*to_p) == SSA_NAME)
6096 /* The above is somewhat premature, avoid ICEing later for a
6097 SSA name w/o a definition. We may have uses in the GIMPLE IL.
6098 ??? This doesn't make it a default-def. */
6099 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
6101 assign = call_stmt;
6103 else
6105 assign = gimple_build_assign (*to_p, *from_p);
6106 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
6107 if (COMPARISON_CLASS_P (*from_p))
6108 copy_warning (assign, *from_p);
6111 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
6113 /* We should have got an SSA name from the start. */
6114 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
6115 || ! gimple_in_ssa_p (cfun));
6118 gimplify_seq_add_stmt (pre_p, assign);
6119 gsi = gsi_last (*pre_p);
6120 maybe_fold_stmt (&gsi);
6122 if (want_value)
6124 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
6125 return GS_OK;
6127 else
6128 *expr_p = NULL;
6130 return GS_ALL_DONE;
6133 /* Gimplify a comparison between two variable-sized objects. Do this
6134 with a call to BUILT_IN_MEMCMP. */
6136 static enum gimplify_status
6137 gimplify_variable_sized_compare (tree *expr_p)
6139 location_t loc = EXPR_LOCATION (*expr_p);
6140 tree op0 = TREE_OPERAND (*expr_p, 0);
6141 tree op1 = TREE_OPERAND (*expr_p, 1);
6142 tree t, arg, dest, src, expr;
6144 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
6145 arg = unshare_expr (arg);
6146 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
6147 src = build_fold_addr_expr_loc (loc, op1);
6148 dest = build_fold_addr_expr_loc (loc, op0);
6149 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
6150 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
6152 expr
6153 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
6154 SET_EXPR_LOCATION (expr, loc);
6155 *expr_p = expr;
6157 return GS_OK;
6160 /* Gimplify a comparison between two aggregate objects of integral scalar
6161 mode as a comparison between the bitwise equivalent scalar values. */
6163 static enum gimplify_status
6164 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
6166 location_t loc = EXPR_LOCATION (*expr_p);
6167 tree op0 = TREE_OPERAND (*expr_p, 0);
6168 tree op1 = TREE_OPERAND (*expr_p, 1);
6170 tree type = TREE_TYPE (op0);
6171 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
6173 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
6174 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
6176 *expr_p
6177 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
6179 return GS_OK;
6182 /* Gimplify an expression sequence. This function gimplifies each
6183 expression and rewrites the original expression with the last
6184 expression of the sequence in GIMPLE form.
6186 PRE_P points to the list where the side effects for all the
6187 expressions in the sequence will be emitted.
6189 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
6191 static enum gimplify_status
6192 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
6194 tree t = *expr_p;
6198 tree *sub_p = &TREE_OPERAND (t, 0);
6200 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
6201 gimplify_compound_expr (sub_p, pre_p, false);
6202 else
6203 gimplify_stmt (sub_p, pre_p);
6205 t = TREE_OPERAND (t, 1);
6207 while (TREE_CODE (t) == COMPOUND_EXPR);
6209 *expr_p = t;
6210 if (want_value)
6211 return GS_OK;
6212 else
6214 gimplify_stmt (expr_p, pre_p);
6215 return GS_ALL_DONE;
6219 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
6220 gimplify. After gimplification, EXPR_P will point to a new temporary
6221 that holds the original value of the SAVE_EXPR node.
6223 PRE_P points to the list where side effects that must happen before
6224 *EXPR_P should be stored. */
6226 static enum gimplify_status
6227 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6229 enum gimplify_status ret = GS_ALL_DONE;
6230 tree val;
6232 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
6233 val = TREE_OPERAND (*expr_p, 0);
6235 if (TREE_TYPE (val) == error_mark_node)
6236 return GS_ERROR;
6238 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
6239 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
6241 /* The operand may be a void-valued expression. It is
6242 being executed only for its side-effects. */
6243 if (TREE_TYPE (val) == void_type_node)
6245 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
6246 is_gimple_stmt, fb_none);
6247 val = NULL;
6249 else
6250 /* The temporary may not be an SSA name as later abnormal and EH
6251 control flow may invalidate use/def domination. When in SSA
6252 form then assume there are no such issues and SAVE_EXPRs only
6253 appear via GENERIC foldings. */
6254 val = get_initialized_tmp_var (val, pre_p, post_p,
6255 gimple_in_ssa_p (cfun));
6257 TREE_OPERAND (*expr_p, 0) = val;
6258 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
6261 *expr_p = val;
6263 return ret;
6266 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
6268 unary_expr
6269 : ...
6270 | '&' varname
6273 PRE_P points to the list where side effects that must happen before
6274 *EXPR_P should be stored.
6276 POST_P points to the list where side effects that must happen after
6277 *EXPR_P should be stored. */
6279 static enum gimplify_status
6280 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6282 tree expr = *expr_p;
6283 tree op0 = TREE_OPERAND (expr, 0);
6284 enum gimplify_status ret;
6285 location_t loc = EXPR_LOCATION (*expr_p);
6287 switch (TREE_CODE (op0))
6289 case INDIRECT_REF:
6290 do_indirect_ref:
6291 /* Check if we are dealing with an expression of the form '&*ptr'.
6292 While the front end folds away '&*ptr' into 'ptr', these
6293 expressions may be generated internally by the compiler (e.g.,
6294 builtins like __builtin_va_end). */
6295 /* Caution: the silent array decomposition semantics we allow for
6296 ADDR_EXPR means we can't always discard the pair. */
6297 /* Gimplification of the ADDR_EXPR operand may drop
6298 cv-qualification conversions, so make sure we add them if
6299 needed. */
6301 tree op00 = TREE_OPERAND (op0, 0);
6302 tree t_expr = TREE_TYPE (expr);
6303 tree t_op00 = TREE_TYPE (op00);
6305 if (!useless_type_conversion_p (t_expr, t_op00))
6306 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
6307 *expr_p = op00;
6308 ret = GS_OK;
6310 break;
6312 case VIEW_CONVERT_EXPR:
6313 /* Take the address of our operand and then convert it to the type of
6314 this ADDR_EXPR.
6316 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
6317 all clear. The impact of this transformation is even less clear. */
6319 /* If the operand is a useless conversion, look through it. Doing so
6320 guarantees that the ADDR_EXPR and its operand will remain of the
6321 same type. */
6322 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
6323 op0 = TREE_OPERAND (op0, 0);
6325 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
6326 build_fold_addr_expr_loc (loc,
6327 TREE_OPERAND (op0, 0)));
6328 ret = GS_OK;
6329 break;
6331 case MEM_REF:
6332 if (integer_zerop (TREE_OPERAND (op0, 1)))
6333 goto do_indirect_ref;
6335 /* fall through */
6337 default:
6338 /* If we see a call to a declared builtin or see its address
6339 being taken (we can unify those cases here) then we can mark
6340 the builtin for implicit generation by GCC. */
6341 if (TREE_CODE (op0) == FUNCTION_DECL
6342 && fndecl_built_in_p (op0, BUILT_IN_NORMAL)
6343 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
6344 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
6346 /* We use fb_either here because the C frontend sometimes takes
6347 the address of a call that returns a struct; see
6348 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
6349 the implied temporary explicit. */
6351 /* Make the operand addressable. */
6352 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
6353 is_gimple_addressable, fb_either);
6354 if (ret == GS_ERROR)
6355 break;
6357 /* Then mark it. Beware that it may not be possible to do so directly
6358 if a temporary has been created by the gimplification. */
6359 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
6361 op0 = TREE_OPERAND (expr, 0);
6363 /* For various reasons, the gimplification of the expression
6364 may have made a new INDIRECT_REF. */
6365 if (TREE_CODE (op0) == INDIRECT_REF
6366 || (TREE_CODE (op0) == MEM_REF
6367 && integer_zerop (TREE_OPERAND (op0, 1))))
6368 goto do_indirect_ref;
6370 mark_addressable (TREE_OPERAND (expr, 0));
6372 /* The FEs may end up building ADDR_EXPRs early on a decl with
6373 an incomplete type. Re-build ADDR_EXPRs in canonical form
6374 here. */
6375 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
6376 *expr_p = build_fold_addr_expr (op0);
6378 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
6379 recompute_tree_invariant_for_addr_expr (*expr_p);
6381 /* If we re-built the ADDR_EXPR add a conversion to the original type
6382 if required. */
6383 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
6384 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
6386 break;
6389 return ret;
6392 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
6393 value; output operands should be a gimple lvalue. */
6395 static enum gimplify_status
6396 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6398 tree expr;
6399 int noutputs;
6400 const char **oconstraints;
6401 int i;
6402 tree link;
6403 const char *constraint;
6404 bool allows_mem, allows_reg, is_inout;
6405 enum gimplify_status ret, tret;
6406 gasm *stmt;
6407 vec<tree, va_gc> *inputs;
6408 vec<tree, va_gc> *outputs;
6409 vec<tree, va_gc> *clobbers;
6410 vec<tree, va_gc> *labels;
6411 tree link_next;
6413 expr = *expr_p;
6414 noutputs = list_length (ASM_OUTPUTS (expr));
6415 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
6417 inputs = NULL;
6418 outputs = NULL;
6419 clobbers = NULL;
6420 labels = NULL;
6422 ret = GS_ALL_DONE;
6423 link_next = NULL_TREE;
6424 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
6426 bool ok;
6427 size_t constraint_len;
6429 link_next = TREE_CHAIN (link);
6431 oconstraints[i]
6432 = constraint
6433 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6434 constraint_len = strlen (constraint);
6435 if (constraint_len == 0)
6436 continue;
6438 ok = parse_output_constraint (&constraint, i, 0, 0,
6439 &allows_mem, &allows_reg, &is_inout);
6440 if (!ok)
6442 ret = GS_ERROR;
6443 is_inout = false;
6446 /* If we can't make copies, we can only accept memory.
6447 Similarly for VLAs. */
6448 tree outtype = TREE_TYPE (TREE_VALUE (link));
6449 if (outtype != error_mark_node
6450 && (TREE_ADDRESSABLE (outtype)
6451 || !COMPLETE_TYPE_P (outtype)
6452 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (outtype))))
6454 if (allows_mem)
6455 allows_reg = 0;
6456 else
6458 error ("impossible constraint in %<asm%>");
6459 error ("non-memory output %d must stay in memory", i);
6460 return GS_ERROR;
6464 if (!allows_reg && allows_mem)
6465 mark_addressable (TREE_VALUE (link));
6467 tree orig = TREE_VALUE (link);
6468 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6469 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
6470 fb_lvalue | fb_mayfail);
6471 if (tret == GS_ERROR)
6473 if (orig != error_mark_node)
6474 error ("invalid lvalue in %<asm%> output %d", i);
6475 ret = tret;
6478 /* If the constraint does not allow memory make sure we gimplify
6479 it to a register if it is not already but its base is. This
6480 happens for complex and vector components. */
6481 if (!allows_mem)
6483 tree op = TREE_VALUE (link);
6484 if (! is_gimple_val (op)
6485 && is_gimple_reg_type (TREE_TYPE (op))
6486 && is_gimple_reg (get_base_address (op)))
6488 tree tem = create_tmp_reg (TREE_TYPE (op));
6489 tree ass;
6490 if (is_inout)
6492 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
6493 tem, unshare_expr (op));
6494 gimplify_and_add (ass, pre_p);
6496 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
6497 gimplify_and_add (ass, post_p);
6499 TREE_VALUE (link) = tem;
6500 tret = GS_OK;
6504 vec_safe_push (outputs, link);
6505 TREE_CHAIN (link) = NULL_TREE;
6507 if (is_inout)
6509 /* An input/output operand. To give the optimizers more
6510 flexibility, split it into separate input and output
6511 operands. */
6512 tree input;
6513 /* Buffer big enough to format a 32-bit UINT_MAX into. */
6514 char buf[11];
6516 /* Turn the in/out constraint into an output constraint. */
6517 char *p = xstrdup (constraint);
6518 p[0] = '=';
6519 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
6521 /* And add a matching input constraint. */
6522 if (allows_reg)
6524 sprintf (buf, "%u", i);
6526 /* If there are multiple alternatives in the constraint,
6527 handle each of them individually. Those that allow register
6528 will be replaced with operand number, the others will stay
6529 unchanged. */
6530 if (strchr (p, ',') != NULL)
6532 size_t len = 0, buflen = strlen (buf);
6533 char *beg, *end, *str, *dst;
6535 for (beg = p + 1;;)
6537 end = strchr (beg, ',');
6538 if (end == NULL)
6539 end = strchr (beg, '\0');
6540 if ((size_t) (end - beg) < buflen)
6541 len += buflen + 1;
6542 else
6543 len += end - beg + 1;
6544 if (*end)
6545 beg = end + 1;
6546 else
6547 break;
6550 str = (char *) alloca (len);
6551 for (beg = p + 1, dst = str;;)
6553 const char *tem;
6554 bool mem_p, reg_p, inout_p;
6556 end = strchr (beg, ',');
6557 if (end)
6558 *end = '\0';
6559 beg[-1] = '=';
6560 tem = beg - 1;
6561 parse_output_constraint (&tem, i, 0, 0,
6562 &mem_p, &reg_p, &inout_p);
6563 if (dst != str)
6564 *dst++ = ',';
6565 if (reg_p)
6567 memcpy (dst, buf, buflen);
6568 dst += buflen;
6570 else
6572 if (end)
6573 len = end - beg;
6574 else
6575 len = strlen (beg);
6576 memcpy (dst, beg, len);
6577 dst += len;
6579 if (end)
6580 beg = end + 1;
6581 else
6582 break;
6584 *dst = '\0';
6585 input = build_string (dst - str, str);
6587 else
6588 input = build_string (strlen (buf), buf);
6590 else
6591 input = build_string (constraint_len - 1, constraint + 1);
6593 free (p);
6595 input = build_tree_list (build_tree_list (NULL_TREE, input),
6596 unshare_expr (TREE_VALUE (link)));
6597 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
6601 link_next = NULL_TREE;
6602 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
6604 link_next = TREE_CHAIN (link);
6605 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6606 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
6607 oconstraints, &allows_mem, &allows_reg);
6609 /* If we can't make copies, we can only accept memory. */
6610 tree intype = TREE_TYPE (TREE_VALUE (link));
6611 if (intype != error_mark_node
6612 && (TREE_ADDRESSABLE (intype)
6613 || !COMPLETE_TYPE_P (intype)
6614 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (intype))))
6616 if (allows_mem)
6617 allows_reg = 0;
6618 else
6620 error ("impossible constraint in %<asm%>");
6621 error ("non-memory input %d must stay in memory", i);
6622 return GS_ERROR;
6626 /* If the operand is a memory input, it should be an lvalue. */
6627 if (!allows_reg && allows_mem)
6629 tree inputv = TREE_VALUE (link);
6630 STRIP_NOPS (inputv);
6631 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
6632 || TREE_CODE (inputv) == PREINCREMENT_EXPR
6633 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
6634 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
6635 || TREE_CODE (inputv) == MODIFY_EXPR)
6636 TREE_VALUE (link) = error_mark_node;
6637 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6638 is_gimple_lvalue, fb_lvalue | fb_mayfail);
6639 if (tret != GS_ERROR)
6641 /* Unlike output operands, memory inputs are not guaranteed
6642 to be lvalues by the FE, and while the expressions are
6643 marked addressable there, if it is e.g. a statement
6644 expression, temporaries in it might not end up being
6645 addressable. They might be already used in the IL and thus
6646 it is too late to make them addressable now though. */
6647 tree x = TREE_VALUE (link);
6648 while (handled_component_p (x))
6649 x = TREE_OPERAND (x, 0);
6650 if (TREE_CODE (x) == MEM_REF
6651 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
6652 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
6653 if ((VAR_P (x)
6654 || TREE_CODE (x) == PARM_DECL
6655 || TREE_CODE (x) == RESULT_DECL)
6656 && !TREE_ADDRESSABLE (x)
6657 && is_gimple_reg (x))
6659 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
6660 input_location), 0,
6661 "memory input %d is not directly addressable",
6663 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
6666 mark_addressable (TREE_VALUE (link));
6667 if (tret == GS_ERROR)
6669 if (inputv != error_mark_node)
6670 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
6671 "memory input %d is not directly addressable", i);
6672 ret = tret;
6675 else
6677 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6678 is_gimple_asm_val, fb_rvalue);
6679 if (tret == GS_ERROR)
6680 ret = tret;
6683 TREE_CHAIN (link) = NULL_TREE;
6684 vec_safe_push (inputs, link);
6687 link_next = NULL_TREE;
6688 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
6690 link_next = TREE_CHAIN (link);
6691 TREE_CHAIN (link) = NULL_TREE;
6692 vec_safe_push (clobbers, link);
6695 link_next = NULL_TREE;
6696 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
6698 link_next = TREE_CHAIN (link);
6699 TREE_CHAIN (link) = NULL_TREE;
6700 vec_safe_push (labels, link);
6703 /* Do not add ASMs with errors to the gimple IL stream. */
6704 if (ret != GS_ERROR)
6706 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
6707 inputs, outputs, clobbers, labels);
6709 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
6710 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
6711 gimple_asm_set_inline (stmt, ASM_INLINE_P (expr));
6713 gimplify_seq_add_stmt (pre_p, stmt);
6716 return ret;
6719 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
6720 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
6721 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
6722 return to this function.
6724 FIXME should we complexify the prequeue handling instead? Or use flags
6725 for all the cleanups and let the optimizer tighten them up? The current
6726 code seems pretty fragile; it will break on a cleanup within any
6727 non-conditional nesting. But any such nesting would be broken, anyway;
6728 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
6729 and continues out of it. We can do that at the RTL level, though, so
6730 having an optimizer to tighten up try/finally regions would be a Good
6731 Thing. */
6733 static enum gimplify_status
6734 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
6736 gimple_stmt_iterator iter;
6737 gimple_seq body_sequence = NULL;
6739 tree temp = voidify_wrapper_expr (*expr_p, NULL);
6741 /* We only care about the number of conditions between the innermost
6742 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
6743 any cleanups collected outside the CLEANUP_POINT_EXPR. */
6744 int old_conds = gimplify_ctxp->conditions;
6745 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
6746 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
6747 gimplify_ctxp->conditions = 0;
6748 gimplify_ctxp->conditional_cleanups = NULL;
6749 gimplify_ctxp->in_cleanup_point_expr = true;
6751 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
6753 gimplify_ctxp->conditions = old_conds;
6754 gimplify_ctxp->conditional_cleanups = old_cleanups;
6755 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
6757 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
6759 gimple *wce = gsi_stmt (iter);
6761 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
6763 if (gsi_one_before_end_p (iter))
6765 /* Note that gsi_insert_seq_before and gsi_remove do not
6766 scan operands, unlike some other sequence mutators. */
6767 if (!gimple_wce_cleanup_eh_only (wce))
6768 gsi_insert_seq_before_without_update (&iter,
6769 gimple_wce_cleanup (wce),
6770 GSI_SAME_STMT);
6771 gsi_remove (&iter, true);
6772 break;
6774 else
6776 gtry *gtry;
6777 gimple_seq seq;
6778 enum gimple_try_flags kind;
6780 if (gimple_wce_cleanup_eh_only (wce))
6781 kind = GIMPLE_TRY_CATCH;
6782 else
6783 kind = GIMPLE_TRY_FINALLY;
6784 seq = gsi_split_seq_after (iter);
6786 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
6787 /* Do not use gsi_replace here, as it may scan operands.
6788 We want to do a simple structural modification only. */
6789 gsi_set_stmt (&iter, gtry);
6790 iter = gsi_start (gtry->eval);
6793 else
6794 gsi_next (&iter);
6797 gimplify_seq_add_seq (pre_p, body_sequence);
6798 if (temp)
6800 *expr_p = temp;
6801 return GS_OK;
6803 else
6805 *expr_p = NULL;
6806 return GS_ALL_DONE;
6810 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
6811 is the cleanup action required. EH_ONLY is true if the cleanup should
6812 only be executed if an exception is thrown, not on normal exit.
6813 If FORCE_UNCOND is true perform the cleanup unconditionally; this is
6814 only valid for clobbers. */
6816 static void
6817 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p,
6818 bool force_uncond = false)
6820 gimple *wce;
6821 gimple_seq cleanup_stmts = NULL;
6823 /* Errors can result in improperly nested cleanups. Which results in
6824 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
6825 if (seen_error ())
6826 return;
6828 if (gimple_conditional_context ())
6830 /* If we're in a conditional context, this is more complex. We only
6831 want to run the cleanup if we actually ran the initialization that
6832 necessitates it, but we want to run it after the end of the
6833 conditional context. So we wrap the try/finally around the
6834 condition and use a flag to determine whether or not to actually
6835 run the destructor. Thus
6837 test ? f(A()) : 0
6839 becomes (approximately)
6841 flag = 0;
6842 try {
6843 if (test) { A::A(temp); flag = 1; val = f(temp); }
6844 else { val = 0; }
6845 } finally {
6846 if (flag) A::~A(temp);
6850 if (force_uncond)
6852 gimplify_stmt (&cleanup, &cleanup_stmts);
6853 wce = gimple_build_wce (cleanup_stmts);
6854 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6856 else
6858 tree flag = create_tmp_var (boolean_type_node, "cleanup");
6859 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
6860 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
6862 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
6863 gimplify_stmt (&cleanup, &cleanup_stmts);
6864 wce = gimple_build_wce (cleanup_stmts);
6866 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
6867 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6868 gimplify_seq_add_stmt (pre_p, ftrue);
6870 /* Because of this manipulation, and the EH edges that jump
6871 threading cannot redirect, the temporary (VAR) will appear
6872 to be used uninitialized. Don't warn. */
6873 suppress_warning (var, OPT_Wuninitialized);
6876 else
6878 gimplify_stmt (&cleanup, &cleanup_stmts);
6879 wce = gimple_build_wce (cleanup_stmts);
6880 gimple_wce_set_cleanup_eh_only (wce, eh_only);
6881 gimplify_seq_add_stmt (pre_p, wce);
6885 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
6887 static enum gimplify_status
6888 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6890 tree targ = *expr_p;
6891 tree temp = TARGET_EXPR_SLOT (targ);
6892 tree init = TARGET_EXPR_INITIAL (targ);
6893 enum gimplify_status ret;
6895 bool unpoison_empty_seq = false;
6896 gimple_stmt_iterator unpoison_it;
6898 if (init)
6900 tree cleanup = NULL_TREE;
6902 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
6903 to the temps list. Handle also variable length TARGET_EXPRs. */
6904 if (!poly_int_tree_p (DECL_SIZE (temp)))
6906 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
6907 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
6908 gimplify_vla_decl (temp, pre_p);
6910 else
6912 /* Save location where we need to place unpoisoning. It's possible
6913 that a variable will be converted to needs_to_live_in_memory. */
6914 unpoison_it = gsi_last (*pre_p);
6915 unpoison_empty_seq = gsi_end_p (unpoison_it);
6917 gimple_add_tmp_var (temp);
6920 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
6921 expression is supposed to initialize the slot. */
6922 if (VOID_TYPE_P (TREE_TYPE (init)))
6923 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6924 else
6926 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
6927 init = init_expr;
6928 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6929 init = NULL;
6930 ggc_free (init_expr);
6932 if (ret == GS_ERROR)
6934 /* PR c++/28266 Make sure this is expanded only once. */
6935 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6936 return GS_ERROR;
6938 if (init)
6939 gimplify_and_add (init, pre_p);
6941 /* If needed, push the cleanup for the temp. */
6942 if (TARGET_EXPR_CLEANUP (targ))
6944 if (CLEANUP_EH_ONLY (targ))
6945 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
6946 CLEANUP_EH_ONLY (targ), pre_p);
6947 else
6948 cleanup = TARGET_EXPR_CLEANUP (targ);
6951 /* Add a clobber for the temporary going out of scope, like
6952 gimplify_bind_expr. */
6953 if (gimplify_ctxp->in_cleanup_point_expr
6954 && needs_to_live_in_memory (temp))
6956 if (flag_stack_reuse == SR_ALL)
6958 tree clobber = build_clobber (TREE_TYPE (temp));
6959 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
6960 gimple_push_cleanup (temp, clobber, false, pre_p, true);
6962 if (asan_poisoned_variables
6963 && DECL_ALIGN (temp) <= MAX_SUPPORTED_STACK_ALIGNMENT
6964 && !TREE_STATIC (temp)
6965 && dbg_cnt (asan_use_after_scope)
6966 && !gimplify_omp_ctxp)
6968 tree asan_cleanup = build_asan_poison_call_expr (temp);
6969 if (asan_cleanup)
6971 if (unpoison_empty_seq)
6972 unpoison_it = gsi_start (*pre_p);
6974 asan_poison_variable (temp, false, &unpoison_it,
6975 unpoison_empty_seq);
6976 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
6980 if (cleanup)
6981 gimple_push_cleanup (temp, cleanup, false, pre_p);
6983 /* Only expand this once. */
6984 TREE_OPERAND (targ, 3) = init;
6985 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6987 else
6988 /* We should have expanded this before. */
6989 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
6991 *expr_p = temp;
6992 return GS_OK;
6995 /* Gimplification of expression trees. */
6997 /* Gimplify an expression which appears at statement context. The
6998 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
6999 NULL, a new sequence is allocated.
7001 Return true if we actually added a statement to the queue. */
7003 bool
7004 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
7006 gimple_seq_node last;
7008 last = gimple_seq_last (*seq_p);
7009 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
7010 return last != gimple_seq_last (*seq_p);
7013 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
7014 to CTX. If entries already exist, force them to be some flavor of private.
7015 If there is no enclosing parallel, do nothing. */
7017 void
7018 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
7020 splay_tree_node n;
7022 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
7023 return;
7027 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7028 if (n != NULL)
7030 if (n->value & GOVD_SHARED)
7031 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
7032 else if (n->value & GOVD_MAP)
7033 n->value |= GOVD_MAP_TO_ONLY;
7034 else
7035 return;
7037 else if ((ctx->region_type & ORT_TARGET) != 0)
7039 if (ctx->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
7040 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7041 else
7042 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
7044 else if (ctx->region_type != ORT_WORKSHARE
7045 && ctx->region_type != ORT_TASKGROUP
7046 && ctx->region_type != ORT_SIMD
7047 && ctx->region_type != ORT_ACC
7048 && !(ctx->region_type & ORT_TARGET_DATA))
7049 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7051 ctx = ctx->outer_context;
7053 while (ctx);
7056 /* Similarly for each of the type sizes of TYPE. */
7058 static void
7059 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
7061 if (type == NULL || type == error_mark_node)
7062 return;
7063 type = TYPE_MAIN_VARIANT (type);
7065 if (ctx->privatized_types->add (type))
7066 return;
7068 switch (TREE_CODE (type))
7070 case INTEGER_TYPE:
7071 case ENUMERAL_TYPE:
7072 case BOOLEAN_TYPE:
7073 case REAL_TYPE:
7074 case FIXED_POINT_TYPE:
7075 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
7076 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
7077 break;
7079 case ARRAY_TYPE:
7080 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7081 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
7082 break;
7084 case RECORD_TYPE:
7085 case UNION_TYPE:
7086 case QUAL_UNION_TYPE:
7088 tree field;
7089 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
7090 if (TREE_CODE (field) == FIELD_DECL)
7092 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
7093 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
7096 break;
7098 case POINTER_TYPE:
7099 case REFERENCE_TYPE:
7100 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7101 break;
7103 default:
7104 break;
7107 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
7108 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
7109 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
7112 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
7114 static void
7115 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
7117 splay_tree_node n;
7118 unsigned int nflags;
7119 tree t;
7121 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
7122 return;
7124 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
7125 there are constructors involved somewhere. Exception is a shared clause,
7126 there is nothing privatized in that case. */
7127 if ((flags & GOVD_SHARED) == 0
7128 && (TREE_ADDRESSABLE (TREE_TYPE (decl))
7129 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl))))
7130 flags |= GOVD_SEEN;
7132 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7133 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7135 /* We shouldn't be re-adding the decl with the same data
7136 sharing class. */
7137 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
7138 nflags = n->value | flags;
7139 /* The only combination of data sharing classes we should see is
7140 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
7141 reduction variables to be used in data sharing clauses. */
7142 gcc_assert ((ctx->region_type & ORT_ACC) != 0
7143 || ((nflags & GOVD_DATA_SHARE_CLASS)
7144 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
7145 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
7146 n->value = nflags;
7147 return;
7150 /* When adding a variable-sized variable, we have to handle all sorts
7151 of additional bits of data: the pointer replacement variable, and
7152 the parameters of the type. */
7153 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7155 /* Add the pointer replacement variable as PRIVATE if the variable
7156 replacement is private, else FIRSTPRIVATE since we'll need the
7157 address of the original variable either for SHARED, or for the
7158 copy into or out of the context. */
7159 if (!(flags & GOVD_LOCAL) && ctx->region_type != ORT_TASKGROUP)
7161 if (flags & GOVD_MAP)
7162 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
7163 else if (flags & GOVD_PRIVATE)
7164 nflags = GOVD_PRIVATE;
7165 else if (((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7166 && (flags & GOVD_FIRSTPRIVATE))
7167 || (ctx->region_type == ORT_TARGET_DATA
7168 && (flags & GOVD_DATA_SHARE_CLASS) == 0))
7169 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
7170 else
7171 nflags = GOVD_FIRSTPRIVATE;
7172 nflags |= flags & GOVD_SEEN;
7173 t = DECL_VALUE_EXPR (decl);
7174 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7175 t = TREE_OPERAND (t, 0);
7176 gcc_assert (DECL_P (t));
7177 omp_add_variable (ctx, t, nflags);
7180 /* Add all of the variable and type parameters (which should have
7181 been gimplified to a formal temporary) as FIRSTPRIVATE. */
7182 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
7183 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
7184 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7186 /* The variable-sized variable itself is never SHARED, only some form
7187 of PRIVATE. The sharing would take place via the pointer variable
7188 which we remapped above. */
7189 if (flags & GOVD_SHARED)
7190 flags = GOVD_SHARED | GOVD_DEBUG_PRIVATE
7191 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
7193 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
7194 alloca statement we generate for the variable, so make sure it
7195 is available. This isn't automatically needed for the SHARED
7196 case, since we won't be allocating local storage then.
7197 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
7198 in this case omp_notice_variable will be called later
7199 on when it is gimplified. */
7200 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
7201 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
7202 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
7204 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
7205 && omp_privatize_by_reference (decl))
7207 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7209 /* Similar to the direct variable sized case above, we'll need the
7210 size of references being privatized. */
7211 if ((flags & GOVD_SHARED) == 0)
7213 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7214 if (t && DECL_P (t))
7215 omp_notice_variable (ctx, t, true);
7219 if (n != NULL)
7220 n->value |= flags;
7221 else
7222 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
7224 /* For reductions clauses in OpenACC loop directives, by default create a
7225 copy clause on the enclosing parallel construct for carrying back the
7226 results. */
7227 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
7229 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
7230 while (outer_ctx)
7232 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
7233 if (n != NULL)
7235 /* Ignore local variables and explicitly declared clauses. */
7236 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
7237 break;
7238 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
7240 /* According to the OpenACC spec, such a reduction variable
7241 should already have a copy map on a kernels construct,
7242 verify that here. */
7243 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
7244 && (n->value & GOVD_MAP));
7246 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7248 /* Remove firstprivate and make it a copy map. */
7249 n->value &= ~GOVD_FIRSTPRIVATE;
7250 n->value |= GOVD_MAP;
7253 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7255 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
7256 GOVD_MAP | GOVD_SEEN);
7257 break;
7259 outer_ctx = outer_ctx->outer_context;
7264 /* Notice a threadprivate variable DECL used in OMP context CTX.
7265 This just prints out diagnostics about threadprivate variable uses
7266 in untied tasks. If DECL2 is non-NULL, prevent this warning
7267 on that variable. */
7269 static bool
7270 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
7271 tree decl2)
7273 splay_tree_node n;
7274 struct gimplify_omp_ctx *octx;
7276 for (octx = ctx; octx; octx = octx->outer_context)
7277 if ((octx->region_type & ORT_TARGET) != 0
7278 || octx->order_concurrent)
7280 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
7281 if (n == NULL)
7283 if (octx->order_concurrent)
7285 error ("threadprivate variable %qE used in a region with"
7286 " %<order(concurrent)%> clause", DECL_NAME (decl));
7287 inform (octx->location, "enclosing region");
7289 else
7291 error ("threadprivate variable %qE used in target region",
7292 DECL_NAME (decl));
7293 inform (octx->location, "enclosing target region");
7295 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
7297 if (decl2)
7298 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
7301 if (ctx->region_type != ORT_UNTIED_TASK)
7302 return false;
7303 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7304 if (n == NULL)
7306 error ("threadprivate variable %qE used in untied task",
7307 DECL_NAME (decl));
7308 inform (ctx->location, "enclosing task");
7309 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
7311 if (decl2)
7312 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
7313 return false;
7316 /* Return true if global var DECL is device resident. */
7318 static bool
7319 device_resident_p (tree decl)
7321 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
7323 if (!attr)
7324 return false;
7326 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
7328 tree c = TREE_VALUE (t);
7329 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
7330 return true;
7333 return false;
7336 /* Return true if DECL has an ACC DECLARE attribute. */
7338 static bool
7339 is_oacc_declared (tree decl)
7341 tree t = TREE_CODE (decl) == MEM_REF ? TREE_OPERAND (decl, 0) : decl;
7342 tree declared = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (t));
7343 return declared != NULL_TREE;
7346 /* Determine outer default flags for DECL mentioned in an OMP region
7347 but not declared in an enclosing clause.
7349 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
7350 remapped firstprivate instead of shared. To some extent this is
7351 addressed in omp_firstprivatize_type_sizes, but not
7352 effectively. */
7354 static unsigned
7355 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
7356 bool in_code, unsigned flags)
7358 enum omp_clause_default_kind default_kind = ctx->default_kind;
7359 enum omp_clause_default_kind kind;
7361 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
7362 if (ctx->region_type & ORT_TASK)
7364 tree detach_clause = omp_find_clause (ctx->clauses, OMP_CLAUSE_DETACH);
7366 /* The event-handle specified by a detach clause should always be firstprivate,
7367 regardless of the current default. */
7368 if (detach_clause && OMP_CLAUSE_DECL (detach_clause) == decl)
7369 kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
7371 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
7372 default_kind = kind;
7373 else if (VAR_P (decl) && TREE_STATIC (decl) && DECL_IN_CONSTANT_POOL (decl))
7374 default_kind = OMP_CLAUSE_DEFAULT_SHARED;
7375 /* For C/C++ default({,first}private), variables with static storage duration
7376 declared in a namespace or global scope and referenced in construct
7377 must be explicitly specified, i.e. acts as default(none). */
7378 else if ((default_kind == OMP_CLAUSE_DEFAULT_PRIVATE
7379 || default_kind == OMP_CLAUSE_DEFAULT_FIRSTPRIVATE)
7380 && VAR_P (decl)
7381 && is_global_var (decl)
7382 && (DECL_FILE_SCOPE_P (decl)
7383 || (DECL_CONTEXT (decl)
7384 && TREE_CODE (DECL_CONTEXT (decl)) == NAMESPACE_DECL))
7385 && !lang_GNU_Fortran ())
7386 default_kind = OMP_CLAUSE_DEFAULT_NONE;
7388 switch (default_kind)
7390 case OMP_CLAUSE_DEFAULT_NONE:
7392 const char *rtype;
7394 if (ctx->region_type & ORT_PARALLEL)
7395 rtype = "parallel";
7396 else if ((ctx->region_type & ORT_TASKLOOP) == ORT_TASKLOOP)
7397 rtype = "taskloop";
7398 else if (ctx->region_type & ORT_TASK)
7399 rtype = "task";
7400 else if (ctx->region_type & ORT_TEAMS)
7401 rtype = "teams";
7402 else
7403 gcc_unreachable ();
7405 error ("%qE not specified in enclosing %qs",
7406 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
7407 inform (ctx->location, "enclosing %qs", rtype);
7409 /* FALLTHRU */
7410 case OMP_CLAUSE_DEFAULT_SHARED:
7411 flags |= GOVD_SHARED;
7412 break;
7413 case OMP_CLAUSE_DEFAULT_PRIVATE:
7414 flags |= GOVD_PRIVATE;
7415 break;
7416 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
7417 flags |= GOVD_FIRSTPRIVATE;
7418 break;
7419 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
7420 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
7421 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
7422 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
7424 omp_notice_variable (octx, decl, in_code);
7425 for (; octx; octx = octx->outer_context)
7427 splay_tree_node n2;
7429 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
7430 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
7431 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
7432 continue;
7433 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
7435 flags |= GOVD_FIRSTPRIVATE;
7436 goto found_outer;
7438 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
7440 flags |= GOVD_SHARED;
7441 goto found_outer;
7446 if (TREE_CODE (decl) == PARM_DECL
7447 || (!is_global_var (decl)
7448 && DECL_CONTEXT (decl) == current_function_decl))
7449 flags |= GOVD_FIRSTPRIVATE;
7450 else
7451 flags |= GOVD_SHARED;
7452 found_outer:
7453 break;
7455 default:
7456 gcc_unreachable ();
7459 return flags;
7463 /* Determine outer default flags for DECL mentioned in an OACC region
7464 but not declared in an enclosing clause. */
7466 static unsigned
7467 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
7469 const char *rkind;
7470 bool on_device = false;
7471 bool is_private = false;
7472 bool declared = is_oacc_declared (decl);
7473 tree type = TREE_TYPE (decl);
7475 if (omp_privatize_by_reference (decl))
7476 type = TREE_TYPE (type);
7478 /* For Fortran COMMON blocks, only used variables in those blocks are
7479 transfered and remapped. The block itself will have a private clause to
7480 avoid transfering the data twice.
7481 The hook evaluates to false by default. For a variable in Fortran's COMMON
7482 or EQUIVALENCE block, returns 'true' (as we have shared=false) - as only
7483 the variables in such a COMMON/EQUIVALENCE block shall be privatized not
7484 the whole block. For C++ and Fortran, it can also be true under certain
7485 other conditions, if DECL_HAS_VALUE_EXPR. */
7486 if (RECORD_OR_UNION_TYPE_P (type))
7487 is_private = lang_hooks.decls.omp_disregard_value_expr (decl, false);
7489 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
7490 && is_global_var (decl)
7491 && device_resident_p (decl)
7492 && !is_private)
7494 on_device = true;
7495 flags |= GOVD_MAP_TO_ONLY;
7498 switch (ctx->region_type)
7500 case ORT_ACC_KERNELS:
7501 rkind = "kernels";
7503 if (is_private)
7504 flags |= GOVD_FIRSTPRIVATE;
7505 else if (AGGREGATE_TYPE_P (type))
7507 /* Aggregates default to 'present_or_copy', or 'present'. */
7508 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7509 flags |= GOVD_MAP;
7510 else
7511 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7513 else
7514 /* Scalars default to 'copy'. */
7515 flags |= GOVD_MAP | GOVD_MAP_FORCE;
7517 break;
7519 case ORT_ACC_PARALLEL:
7520 case ORT_ACC_SERIAL:
7521 rkind = ctx->region_type == ORT_ACC_PARALLEL ? "parallel" : "serial";
7523 if (is_private)
7524 flags |= GOVD_FIRSTPRIVATE;
7525 else if (on_device || declared)
7526 flags |= GOVD_MAP;
7527 else if (AGGREGATE_TYPE_P (type))
7529 /* Aggregates default to 'present_or_copy', or 'present'. */
7530 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7531 flags |= GOVD_MAP;
7532 else
7533 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7535 else
7536 /* Scalars default to 'firstprivate'. */
7537 flags |= GOVD_FIRSTPRIVATE;
7539 break;
7541 default:
7542 gcc_unreachable ();
7545 if (DECL_ARTIFICIAL (decl))
7546 ; /* We can get compiler-generated decls, and should not complain
7547 about them. */
7548 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_NONE)
7550 error ("%qE not specified in enclosing OpenACC %qs construct",
7551 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rkind);
7552 inform (ctx->location, "enclosing OpenACC %qs construct", rkind);
7554 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_PRESENT)
7555 ; /* Handled above. */
7556 else
7557 gcc_checking_assert (ctx->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
7559 return flags;
7562 /* Record the fact that DECL was used within the OMP context CTX.
7563 IN_CODE is true when real code uses DECL, and false when we should
7564 merely emit default(none) errors. Return true if DECL is going to
7565 be remapped and thus DECL shouldn't be gimplified into its
7566 DECL_VALUE_EXPR (if any). */
7568 static bool
7569 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
7571 splay_tree_node n;
7572 unsigned flags = in_code ? GOVD_SEEN : 0;
7573 bool ret = false, shared;
7575 if (error_operand_p (decl))
7576 return false;
7578 if (ctx->region_type == ORT_NONE)
7579 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
7581 if (is_global_var (decl))
7583 /* Threadprivate variables are predetermined. */
7584 if (DECL_THREAD_LOCAL_P (decl))
7585 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
7587 if (DECL_HAS_VALUE_EXPR_P (decl))
7589 if (ctx->region_type & ORT_ACC)
7590 /* For OpenACC, defer expansion of value to avoid transfering
7591 privatized common block data instead of im-/explicitly transfered
7592 variables which are in common blocks. */
7594 else
7596 tree value = get_base_address (DECL_VALUE_EXPR (decl));
7598 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
7599 return omp_notice_threadprivate_variable (ctx, decl, value);
7603 if (gimplify_omp_ctxp->outer_context == NULL
7604 && VAR_P (decl)
7605 && oacc_get_fn_attrib (current_function_decl))
7607 location_t loc = DECL_SOURCE_LOCATION (decl);
7609 if (lookup_attribute ("omp declare target link",
7610 DECL_ATTRIBUTES (decl)))
7612 error_at (loc,
7613 "%qE with %<link%> clause used in %<routine%> function",
7614 DECL_NAME (decl));
7615 return false;
7617 else if (!lookup_attribute ("omp declare target",
7618 DECL_ATTRIBUTES (decl)))
7620 error_at (loc,
7621 "%qE requires a %<declare%> directive for use "
7622 "in a %<routine%> function", DECL_NAME (decl));
7623 return false;
7628 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7629 if ((ctx->region_type & ORT_TARGET) != 0)
7631 if (ctx->region_type & ORT_ACC)
7632 /* For OpenACC, as remarked above, defer expansion. */
7633 shared = false;
7634 else
7635 shared = true;
7637 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7638 if (n == NULL)
7640 unsigned nflags = flags;
7641 if ((ctx->region_type & ORT_ACC) == 0)
7643 bool is_declare_target = false;
7644 if (is_global_var (decl)
7645 && varpool_node::get_create (decl)->offloadable)
7647 struct gimplify_omp_ctx *octx;
7648 for (octx = ctx->outer_context;
7649 octx; octx = octx->outer_context)
7651 n = splay_tree_lookup (octx->variables,
7652 (splay_tree_key)decl);
7653 if (n
7654 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
7655 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7656 break;
7658 is_declare_target = octx == NULL;
7660 if (!is_declare_target)
7662 int gdmk;
7663 enum omp_clause_defaultmap_kind kind;
7664 if (lang_hooks.decls.omp_allocatable_p (decl))
7665 gdmk = GDMK_ALLOCATABLE;
7666 else if (lang_hooks.decls.omp_scalar_target_p (decl))
7667 gdmk = GDMK_SCALAR_TARGET;
7668 else if (lang_hooks.decls.omp_scalar_p (decl, false))
7669 gdmk = GDMK_SCALAR;
7670 else if (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
7671 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
7672 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
7673 == POINTER_TYPE)))
7674 gdmk = GDMK_POINTER;
7675 else
7676 gdmk = GDMK_AGGREGATE;
7677 kind = lang_hooks.decls.omp_predetermined_mapping (decl);
7678 if (kind != OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED)
7680 if (kind == OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE)
7681 nflags |= GOVD_FIRSTPRIVATE;
7682 else if (kind == OMP_CLAUSE_DEFAULTMAP_TO)
7683 nflags |= GOVD_MAP | GOVD_MAP_TO_ONLY;
7684 else
7685 gcc_unreachable ();
7687 else if (ctx->defaultmap[gdmk] == 0)
7689 tree d = lang_hooks.decls.omp_report_decl (decl);
7690 error ("%qE not specified in enclosing %<target%>",
7691 DECL_NAME (d));
7692 inform (ctx->location, "enclosing %<target%>");
7694 else if (ctx->defaultmap[gdmk]
7695 & (GOVD_MAP_0LEN_ARRAY | GOVD_FIRSTPRIVATE))
7696 nflags |= ctx->defaultmap[gdmk];
7697 else
7699 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
7700 nflags |= ctx->defaultmap[gdmk] & ~GOVD_MAP;
7705 struct gimplify_omp_ctx *octx = ctx->outer_context;
7706 if ((ctx->region_type & ORT_ACC) && octx)
7708 /* Look in outer OpenACC contexts, to see if there's a
7709 data attribute for this variable. */
7710 omp_notice_variable (octx, decl, in_code);
7712 for (; octx; octx = octx->outer_context)
7714 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
7715 break;
7716 splay_tree_node n2
7717 = splay_tree_lookup (octx->variables,
7718 (splay_tree_key) decl);
7719 if (n2)
7721 if (octx->region_type == ORT_ACC_HOST_DATA)
7722 error ("variable %qE declared in enclosing "
7723 "%<host_data%> region", DECL_NAME (decl));
7724 nflags |= GOVD_MAP;
7725 if (octx->region_type == ORT_ACC_DATA
7726 && (n2->value & GOVD_MAP_0LEN_ARRAY))
7727 nflags |= GOVD_MAP_0LEN_ARRAY;
7728 goto found_outer;
7733 if ((nflags & ~(GOVD_MAP_TO_ONLY | GOVD_MAP_FROM_ONLY
7734 | GOVD_MAP_ALLOC_ONLY)) == flags)
7736 tree type = TREE_TYPE (decl);
7738 if (gimplify_omp_ctxp->target_firstprivatize_array_bases
7739 && omp_privatize_by_reference (decl))
7740 type = TREE_TYPE (type);
7741 if (!lang_hooks.types.omp_mappable_type (type))
7743 error ("%qD referenced in target region does not have "
7744 "a mappable type", decl);
7745 nflags |= GOVD_MAP | GOVD_EXPLICIT;
7747 else
7749 if ((ctx->region_type & ORT_ACC) != 0)
7750 nflags = oacc_default_clause (ctx, decl, flags);
7751 else
7752 nflags |= GOVD_MAP;
7755 found_outer:
7756 omp_add_variable (ctx, decl, nflags);
7758 else
7760 /* If nothing changed, there's nothing left to do. */
7761 if ((n->value & flags) == flags)
7762 return ret;
7763 flags |= n->value;
7764 n->value = flags;
7766 goto do_outer;
7769 if (n == NULL)
7771 if (ctx->region_type == ORT_WORKSHARE
7772 || ctx->region_type == ORT_TASKGROUP
7773 || ctx->region_type == ORT_SIMD
7774 || ctx->region_type == ORT_ACC
7775 || (ctx->region_type & ORT_TARGET_DATA) != 0)
7776 goto do_outer;
7778 flags = omp_default_clause (ctx, decl, in_code, flags);
7780 if ((flags & GOVD_PRIVATE)
7781 && lang_hooks.decls.omp_private_outer_ref (decl))
7782 flags |= GOVD_PRIVATE_OUTER_REF;
7784 omp_add_variable (ctx, decl, flags);
7786 shared = (flags & GOVD_SHARED) != 0;
7787 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7788 goto do_outer;
7791 /* Don't mark as GOVD_SEEN addressable temporaries seen only in simd
7792 lb, b or incr expressions, those shouldn't be turned into simd arrays. */
7793 if (ctx->region_type == ORT_SIMD
7794 && ctx->in_for_exprs
7795 && ((n->value & (GOVD_PRIVATE | GOVD_SEEN | GOVD_EXPLICIT))
7796 == GOVD_PRIVATE))
7797 flags &= ~GOVD_SEEN;
7799 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
7800 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
7801 && DECL_SIZE (decl))
7803 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7805 splay_tree_node n2;
7806 tree t = DECL_VALUE_EXPR (decl);
7807 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7808 t = TREE_OPERAND (t, 0);
7809 gcc_assert (DECL_P (t));
7810 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7811 n2->value |= GOVD_SEEN;
7813 else if (omp_privatize_by_reference (decl)
7814 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
7815 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
7816 != INTEGER_CST))
7818 splay_tree_node n2;
7819 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7820 gcc_assert (DECL_P (t));
7821 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7822 if (n2)
7823 omp_notice_variable (ctx, t, true);
7827 if (ctx->region_type & ORT_ACC)
7828 /* For OpenACC, as remarked above, defer expansion. */
7829 shared = false;
7830 else
7831 shared = ((flags | n->value) & GOVD_SHARED) != 0;
7832 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7834 /* If nothing changed, there's nothing left to do. */
7835 if ((n->value & flags) == flags)
7836 return ret;
7837 flags |= n->value;
7838 n->value = flags;
7840 do_outer:
7841 /* If the variable is private in the current context, then we don't
7842 need to propagate anything to an outer context. */
7843 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
7844 return ret;
7845 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7846 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7847 return ret;
7848 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
7849 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7850 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7851 return ret;
7852 if (ctx->outer_context
7853 && omp_notice_variable (ctx->outer_context, decl, in_code))
7854 return true;
7855 return ret;
7858 /* Verify that DECL is private within CTX. If there's specific information
7859 to the contrary in the innermost scope, generate an error. */
7861 static bool
7862 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
7864 splay_tree_node n;
7866 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7867 if (n != NULL)
7869 if (n->value & GOVD_SHARED)
7871 if (ctx == gimplify_omp_ctxp)
7873 if (simd)
7874 error ("iteration variable %qE is predetermined linear",
7875 DECL_NAME (decl));
7876 else
7877 error ("iteration variable %qE should be private",
7878 DECL_NAME (decl));
7879 n->value = GOVD_PRIVATE;
7880 return true;
7882 else
7883 return false;
7885 else if ((n->value & GOVD_EXPLICIT) != 0
7886 && (ctx == gimplify_omp_ctxp
7887 || (ctx->region_type == ORT_COMBINED_PARALLEL
7888 && gimplify_omp_ctxp->outer_context == ctx)))
7890 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
7891 error ("iteration variable %qE should not be firstprivate",
7892 DECL_NAME (decl));
7893 else if ((n->value & GOVD_REDUCTION) != 0)
7894 error ("iteration variable %qE should not be reduction",
7895 DECL_NAME (decl));
7896 else if (simd != 1 && (n->value & GOVD_LINEAR) != 0)
7897 error ("iteration variable %qE should not be linear",
7898 DECL_NAME (decl));
7900 return (ctx == gimplify_omp_ctxp
7901 || (ctx->region_type == ORT_COMBINED_PARALLEL
7902 && gimplify_omp_ctxp->outer_context == ctx));
7905 if (ctx->region_type != ORT_WORKSHARE
7906 && ctx->region_type != ORT_TASKGROUP
7907 && ctx->region_type != ORT_SIMD
7908 && ctx->region_type != ORT_ACC)
7909 return false;
7910 else if (ctx->outer_context)
7911 return omp_is_private (ctx->outer_context, decl, simd);
7912 return false;
7915 /* Return true if DECL is private within a parallel region
7916 that binds to the current construct's context or in parallel
7917 region's REDUCTION clause. */
7919 static bool
7920 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
7922 splay_tree_node n;
7926 ctx = ctx->outer_context;
7927 if (ctx == NULL)
7929 if (is_global_var (decl))
7930 return false;
7932 /* References might be private, but might be shared too,
7933 when checking for copyprivate, assume they might be
7934 private, otherwise assume they might be shared. */
7935 if (copyprivate)
7936 return true;
7938 if (omp_privatize_by_reference (decl))
7939 return false;
7941 /* Treat C++ privatized non-static data members outside
7942 of the privatization the same. */
7943 if (omp_member_access_dummy_var (decl))
7944 return false;
7946 return true;
7949 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
7951 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7952 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
7954 if ((ctx->region_type & ORT_TARGET_DATA) != 0
7955 || n == NULL
7956 || (n->value & GOVD_MAP) == 0)
7957 continue;
7958 return false;
7961 if (n != NULL)
7963 if ((n->value & GOVD_LOCAL) != 0
7964 && omp_member_access_dummy_var (decl))
7965 return false;
7966 return (n->value & GOVD_SHARED) == 0;
7969 if (ctx->region_type == ORT_WORKSHARE
7970 || ctx->region_type == ORT_TASKGROUP
7971 || ctx->region_type == ORT_SIMD
7972 || ctx->region_type == ORT_ACC)
7973 continue;
7975 break;
7977 while (1);
7978 return false;
7981 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
7983 static tree
7984 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
7986 tree t = *tp;
7988 /* If this node has been visited, unmark it and keep looking. */
7989 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
7990 return t;
7992 if (IS_TYPE_OR_DECL_P (t))
7993 *walk_subtrees = 0;
7994 return NULL_TREE;
7998 /* Gimplify the affinity clause but effectively ignore it.
7999 Generate:
8000 var = begin;
8001 if ((step > 1) ? var <= end : var > end)
8002 locatator_var_expr; */
8004 static void
8005 gimplify_omp_affinity (tree *list_p, gimple_seq *pre_p)
8007 tree last_iter = NULL_TREE;
8008 tree last_bind = NULL_TREE;
8009 tree label = NULL_TREE;
8010 tree *last_body = NULL;
8011 for (tree c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8012 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_AFFINITY)
8014 tree t = OMP_CLAUSE_DECL (c);
8015 if (TREE_CODE (t) == TREE_LIST
8016 && TREE_PURPOSE (t)
8017 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8019 if (TREE_VALUE (t) == null_pointer_node)
8020 continue;
8021 if (TREE_PURPOSE (t) != last_iter)
8023 if (last_bind)
8025 append_to_statement_list (label, last_body);
8026 gimplify_and_add (last_bind, pre_p);
8027 last_bind = NULL_TREE;
8029 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8031 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8032 is_gimple_val, fb_rvalue) == GS_ERROR
8033 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8034 is_gimple_val, fb_rvalue) == GS_ERROR
8035 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8036 is_gimple_val, fb_rvalue) == GS_ERROR
8037 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8038 is_gimple_val, fb_rvalue)
8039 == GS_ERROR))
8040 return;
8042 last_iter = TREE_PURPOSE (t);
8043 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8044 last_bind = build3 (BIND_EXPR, void_type_node, BLOCK_VARS (block),
8045 NULL, block);
8046 last_body = &BIND_EXPR_BODY (last_bind);
8047 tree cond = NULL_TREE;
8048 location_t loc = OMP_CLAUSE_LOCATION (c);
8049 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8051 tree var = TREE_VEC_ELT (it, 0);
8052 tree begin = TREE_VEC_ELT (it, 1);
8053 tree end = TREE_VEC_ELT (it, 2);
8054 tree step = TREE_VEC_ELT (it, 3);
8055 loc = DECL_SOURCE_LOCATION (var);
8056 tree tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8057 var, begin);
8058 append_to_statement_list_force (tem, last_body);
8060 tree cond1 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8061 step, build_zero_cst (TREE_TYPE (step)));
8062 tree cond2 = fold_build2_loc (loc, LE_EXPR, boolean_type_node,
8063 var, end);
8064 tree cond3 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8065 var, end);
8066 cond1 = fold_build3_loc (loc, COND_EXPR, boolean_type_node,
8067 cond1, cond2, cond3);
8068 if (cond)
8069 cond = fold_build2_loc (loc, TRUTH_AND_EXPR,
8070 boolean_type_node, cond, cond1);
8071 else
8072 cond = cond1;
8074 tree cont_label = create_artificial_label (loc);
8075 label = build1 (LABEL_EXPR, void_type_node, cont_label);
8076 tree tem = fold_build3_loc (loc, COND_EXPR, void_type_node, cond,
8077 void_node,
8078 build_and_jump (&cont_label));
8079 append_to_statement_list_force (tem, last_body);
8081 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8083 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t), 0),
8084 last_body);
8085 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8087 if (error_operand_p (TREE_VALUE (t)))
8088 return;
8089 append_to_statement_list_force (TREE_VALUE (t), last_body);
8090 TREE_VALUE (t) = null_pointer_node;
8092 else
8094 if (last_bind)
8096 append_to_statement_list (label, last_body);
8097 gimplify_and_add (last_bind, pre_p);
8098 last_bind = NULL_TREE;
8100 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8102 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8103 NULL, is_gimple_val, fb_rvalue);
8104 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8106 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8107 return;
8108 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8109 is_gimple_val, fb_rvalue) == GS_ERROR)
8110 return;
8111 gimplify_and_add (OMP_CLAUSE_DECL (c), pre_p);
8114 if (last_bind)
8116 append_to_statement_list (label, last_body);
8117 gimplify_and_add (last_bind, pre_p);
8119 return;
8122 /* If *LIST_P contains any OpenMP depend clauses with iterators,
8123 lower all the depend clauses by populating corresponding depend
8124 array. Returns 0 if there are no such depend clauses, or
8125 2 if all depend clauses should be removed, 1 otherwise. */
8127 static int
8128 gimplify_omp_depend (tree *list_p, gimple_seq *pre_p)
8130 tree c;
8131 gimple *g;
8132 size_t n[4] = { 0, 0, 0, 0 };
8133 bool unused[4];
8134 tree counts[4] = { NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE };
8135 tree last_iter = NULL_TREE, last_count = NULL_TREE;
8136 size_t i, j;
8137 location_t first_loc = UNKNOWN_LOCATION;
8139 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8140 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8142 switch (OMP_CLAUSE_DEPEND_KIND (c))
8144 case OMP_CLAUSE_DEPEND_IN:
8145 i = 2;
8146 break;
8147 case OMP_CLAUSE_DEPEND_OUT:
8148 case OMP_CLAUSE_DEPEND_INOUT:
8149 i = 0;
8150 break;
8151 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8152 i = 1;
8153 break;
8154 case OMP_CLAUSE_DEPEND_DEPOBJ:
8155 i = 3;
8156 break;
8157 case OMP_CLAUSE_DEPEND_SOURCE:
8158 case OMP_CLAUSE_DEPEND_SINK:
8159 continue;
8160 default:
8161 gcc_unreachable ();
8163 tree t = OMP_CLAUSE_DECL (c);
8164 if (first_loc == UNKNOWN_LOCATION)
8165 first_loc = OMP_CLAUSE_LOCATION (c);
8166 if (TREE_CODE (t) == TREE_LIST
8167 && TREE_PURPOSE (t)
8168 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8170 if (TREE_PURPOSE (t) != last_iter)
8172 tree tcnt = size_one_node;
8173 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8175 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8176 is_gimple_val, fb_rvalue) == GS_ERROR
8177 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8178 is_gimple_val, fb_rvalue) == GS_ERROR
8179 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8180 is_gimple_val, fb_rvalue) == GS_ERROR
8181 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8182 is_gimple_val, fb_rvalue)
8183 == GS_ERROR))
8184 return 2;
8185 tree var = TREE_VEC_ELT (it, 0);
8186 tree begin = TREE_VEC_ELT (it, 1);
8187 tree end = TREE_VEC_ELT (it, 2);
8188 tree step = TREE_VEC_ELT (it, 3);
8189 tree orig_step = TREE_VEC_ELT (it, 4);
8190 tree type = TREE_TYPE (var);
8191 tree stype = TREE_TYPE (step);
8192 location_t loc = DECL_SOURCE_LOCATION (var);
8193 tree endmbegin;
8194 /* Compute count for this iterator as
8195 orig_step > 0
8196 ? (begin < end ? (end - begin + (step - 1)) / step : 0)
8197 : (begin > end ? (end - begin + (step + 1)) / step : 0)
8198 and compute product of those for the entire depend
8199 clause. */
8200 if (POINTER_TYPE_P (type))
8201 endmbegin = fold_build2_loc (loc, POINTER_DIFF_EXPR,
8202 stype, end, begin);
8203 else
8204 endmbegin = fold_build2_loc (loc, MINUS_EXPR, type,
8205 end, begin);
8206 tree stepm1 = fold_build2_loc (loc, MINUS_EXPR, stype,
8207 step,
8208 build_int_cst (stype, 1));
8209 tree stepp1 = fold_build2_loc (loc, PLUS_EXPR, stype, step,
8210 build_int_cst (stype, 1));
8211 tree pos = fold_build2_loc (loc, PLUS_EXPR, stype,
8212 unshare_expr (endmbegin),
8213 stepm1);
8214 pos = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8215 pos, step);
8216 tree neg = fold_build2_loc (loc, PLUS_EXPR, stype,
8217 endmbegin, stepp1);
8218 if (TYPE_UNSIGNED (stype))
8220 neg = fold_build1_loc (loc, NEGATE_EXPR, stype, neg);
8221 step = fold_build1_loc (loc, NEGATE_EXPR, stype, step);
8223 neg = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8224 neg, step);
8225 step = NULL_TREE;
8226 tree cond = fold_build2_loc (loc, LT_EXPR,
8227 boolean_type_node,
8228 begin, end);
8229 pos = fold_build3_loc (loc, COND_EXPR, stype, cond, pos,
8230 build_int_cst (stype, 0));
8231 cond = fold_build2_loc (loc, LT_EXPR, boolean_type_node,
8232 end, begin);
8233 neg = fold_build3_loc (loc, COND_EXPR, stype, cond, neg,
8234 build_int_cst (stype, 0));
8235 tree osteptype = TREE_TYPE (orig_step);
8236 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8237 orig_step,
8238 build_int_cst (osteptype, 0));
8239 tree cnt = fold_build3_loc (loc, COND_EXPR, stype,
8240 cond, pos, neg);
8241 cnt = fold_convert_loc (loc, sizetype, cnt);
8242 if (gimplify_expr (&cnt, pre_p, NULL, is_gimple_val,
8243 fb_rvalue) == GS_ERROR)
8244 return 2;
8245 tcnt = size_binop_loc (loc, MULT_EXPR, tcnt, cnt);
8247 if (gimplify_expr (&tcnt, pre_p, NULL, is_gimple_val,
8248 fb_rvalue) == GS_ERROR)
8249 return 2;
8250 last_iter = TREE_PURPOSE (t);
8251 last_count = tcnt;
8253 if (counts[i] == NULL_TREE)
8254 counts[i] = last_count;
8255 else
8256 counts[i] = size_binop_loc (OMP_CLAUSE_LOCATION (c),
8257 PLUS_EXPR, counts[i], last_count);
8259 else
8260 n[i]++;
8262 for (i = 0; i < 4; i++)
8263 if (counts[i])
8264 break;
8265 if (i == 4)
8266 return 0;
8268 tree total = size_zero_node;
8269 for (i = 0; i < 4; i++)
8271 unused[i] = counts[i] == NULL_TREE && n[i] == 0;
8272 if (counts[i] == NULL_TREE)
8273 counts[i] = size_zero_node;
8274 if (n[i])
8275 counts[i] = size_binop (PLUS_EXPR, counts[i], size_int (n[i]));
8276 if (gimplify_expr (&counts[i], pre_p, NULL, is_gimple_val,
8277 fb_rvalue) == GS_ERROR)
8278 return 2;
8279 total = size_binop (PLUS_EXPR, total, counts[i]);
8282 if (gimplify_expr (&total, pre_p, NULL, is_gimple_val, fb_rvalue)
8283 == GS_ERROR)
8284 return 2;
8285 bool is_old = unused[1] && unused[3];
8286 tree totalpx = size_binop (PLUS_EXPR, unshare_expr (total),
8287 size_int (is_old ? 1 : 4));
8288 tree type = build_array_type (ptr_type_node, build_index_type (totalpx));
8289 tree array = create_tmp_var_raw (type);
8290 TREE_ADDRESSABLE (array) = 1;
8291 if (!poly_int_tree_p (totalpx))
8293 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (array)))
8294 gimplify_type_sizes (TREE_TYPE (array), pre_p);
8295 if (gimplify_omp_ctxp)
8297 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8298 while (ctx
8299 && (ctx->region_type == ORT_WORKSHARE
8300 || ctx->region_type == ORT_TASKGROUP
8301 || ctx->region_type == ORT_SIMD
8302 || ctx->region_type == ORT_ACC))
8303 ctx = ctx->outer_context;
8304 if (ctx)
8305 omp_add_variable (ctx, array, GOVD_LOCAL | GOVD_SEEN);
8307 gimplify_vla_decl (array, pre_p);
8309 else
8310 gimple_add_tmp_var (array);
8311 tree r = build4 (ARRAY_REF, ptr_type_node, array, size_int (0), NULL_TREE,
8312 NULL_TREE);
8313 tree tem;
8314 if (!is_old)
8316 tem = build2 (MODIFY_EXPR, void_type_node, r,
8317 build_int_cst (ptr_type_node, 0));
8318 gimplify_and_add (tem, pre_p);
8319 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (1), NULL_TREE,
8320 NULL_TREE);
8322 tem = build2 (MODIFY_EXPR, void_type_node, r,
8323 fold_convert (ptr_type_node, total));
8324 gimplify_and_add (tem, pre_p);
8325 for (i = 1; i < (is_old ? 2 : 4); i++)
8327 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (i + !is_old),
8328 NULL_TREE, NULL_TREE);
8329 tem = build2 (MODIFY_EXPR, void_type_node, r, counts[i - 1]);
8330 gimplify_and_add (tem, pre_p);
8333 tree cnts[4];
8334 for (j = 4; j; j--)
8335 if (!unused[j - 1])
8336 break;
8337 for (i = 0; i < 4; i++)
8339 if (i && (i >= j || unused[i - 1]))
8341 cnts[i] = cnts[i - 1];
8342 continue;
8344 cnts[i] = create_tmp_var (sizetype);
8345 if (i == 0)
8346 g = gimple_build_assign (cnts[i], size_int (is_old ? 2 : 5));
8347 else
8349 tree t;
8350 if (is_old)
8351 t = size_binop (PLUS_EXPR, counts[0], size_int (2));
8352 else
8353 t = size_binop (PLUS_EXPR, cnts[i - 1], counts[i - 1]);
8354 if (gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue)
8355 == GS_ERROR)
8356 return 2;
8357 g = gimple_build_assign (cnts[i], t);
8359 gimple_seq_add_stmt (pre_p, g);
8362 last_iter = NULL_TREE;
8363 tree last_bind = NULL_TREE;
8364 tree *last_body = NULL;
8365 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8366 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8368 switch (OMP_CLAUSE_DEPEND_KIND (c))
8370 case OMP_CLAUSE_DEPEND_IN:
8371 i = 2;
8372 break;
8373 case OMP_CLAUSE_DEPEND_OUT:
8374 case OMP_CLAUSE_DEPEND_INOUT:
8375 i = 0;
8376 break;
8377 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8378 i = 1;
8379 break;
8380 case OMP_CLAUSE_DEPEND_DEPOBJ:
8381 i = 3;
8382 break;
8383 case OMP_CLAUSE_DEPEND_SOURCE:
8384 case OMP_CLAUSE_DEPEND_SINK:
8385 continue;
8386 default:
8387 gcc_unreachable ();
8389 tree t = OMP_CLAUSE_DECL (c);
8390 if (TREE_CODE (t) == TREE_LIST
8391 && TREE_PURPOSE (t)
8392 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8394 if (TREE_PURPOSE (t) != last_iter)
8396 if (last_bind)
8397 gimplify_and_add (last_bind, pre_p);
8398 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8399 last_bind = build3 (BIND_EXPR, void_type_node,
8400 BLOCK_VARS (block), NULL, block);
8401 TREE_SIDE_EFFECTS (last_bind) = 1;
8402 SET_EXPR_LOCATION (last_bind, OMP_CLAUSE_LOCATION (c));
8403 tree *p = &BIND_EXPR_BODY (last_bind);
8404 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8406 tree var = TREE_VEC_ELT (it, 0);
8407 tree begin = TREE_VEC_ELT (it, 1);
8408 tree end = TREE_VEC_ELT (it, 2);
8409 tree step = TREE_VEC_ELT (it, 3);
8410 tree orig_step = TREE_VEC_ELT (it, 4);
8411 tree type = TREE_TYPE (var);
8412 location_t loc = DECL_SOURCE_LOCATION (var);
8413 /* Emit:
8414 var = begin;
8415 goto cond_label;
8416 beg_label:
8418 var = var + step;
8419 cond_label:
8420 if (orig_step > 0) {
8421 if (var < end) goto beg_label;
8422 } else {
8423 if (var > end) goto beg_label;
8425 for each iterator, with inner iterators added to
8426 the ... above. */
8427 tree beg_label = create_artificial_label (loc);
8428 tree cond_label = NULL_TREE;
8429 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8430 var, begin);
8431 append_to_statement_list_force (tem, p);
8432 tem = build_and_jump (&cond_label);
8433 append_to_statement_list_force (tem, p);
8434 tem = build1 (LABEL_EXPR, void_type_node, beg_label);
8435 append_to_statement_list (tem, p);
8436 tree bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
8437 NULL_TREE, NULL_TREE);
8438 TREE_SIDE_EFFECTS (bind) = 1;
8439 SET_EXPR_LOCATION (bind, loc);
8440 append_to_statement_list_force (bind, p);
8441 if (POINTER_TYPE_P (type))
8442 tem = build2_loc (loc, POINTER_PLUS_EXPR, type,
8443 var, fold_convert_loc (loc, sizetype,
8444 step));
8445 else
8446 tem = build2_loc (loc, PLUS_EXPR, type, var, step);
8447 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8448 var, tem);
8449 append_to_statement_list_force (tem, p);
8450 tem = build1 (LABEL_EXPR, void_type_node, cond_label);
8451 append_to_statement_list (tem, p);
8452 tree cond = fold_build2_loc (loc, LT_EXPR,
8453 boolean_type_node,
8454 var, end);
8455 tree pos
8456 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8457 cond, build_and_jump (&beg_label),
8458 void_node);
8459 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8460 var, end);
8461 tree neg
8462 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8463 cond, build_and_jump (&beg_label),
8464 void_node);
8465 tree osteptype = TREE_TYPE (orig_step);
8466 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8467 orig_step,
8468 build_int_cst (osteptype, 0));
8469 tem = fold_build3_loc (loc, COND_EXPR, void_type_node,
8470 cond, pos, neg);
8471 append_to_statement_list_force (tem, p);
8472 p = &BIND_EXPR_BODY (bind);
8474 last_body = p;
8476 last_iter = TREE_PURPOSE (t);
8477 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8479 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t),
8480 0), last_body);
8481 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8483 if (error_operand_p (TREE_VALUE (t)))
8484 return 2;
8485 TREE_VALUE (t) = build_fold_addr_expr (TREE_VALUE (t));
8486 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8487 NULL_TREE, NULL_TREE);
8488 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8489 void_type_node, r, TREE_VALUE (t));
8490 append_to_statement_list_force (tem, last_body);
8491 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8492 void_type_node, cnts[i],
8493 size_binop (PLUS_EXPR, cnts[i], size_int (1)));
8494 append_to_statement_list_force (tem, last_body);
8495 TREE_VALUE (t) = null_pointer_node;
8497 else
8499 if (last_bind)
8501 gimplify_and_add (last_bind, pre_p);
8502 last_bind = NULL_TREE;
8504 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8506 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8507 NULL, is_gimple_val, fb_rvalue);
8508 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8510 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8511 return 2;
8512 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
8513 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8514 is_gimple_val, fb_rvalue) == GS_ERROR)
8515 return 2;
8516 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8517 NULL_TREE, NULL_TREE);
8518 tem = build2 (MODIFY_EXPR, void_type_node, r, OMP_CLAUSE_DECL (c));
8519 gimplify_and_add (tem, pre_p);
8520 g = gimple_build_assign (cnts[i], size_binop (PLUS_EXPR, cnts[i],
8521 size_int (1)));
8522 gimple_seq_add_stmt (pre_p, g);
8525 if (last_bind)
8526 gimplify_and_add (last_bind, pre_p);
8527 tree cond = boolean_false_node;
8528 if (is_old)
8530 if (!unused[0])
8531 cond = build2_loc (first_loc, NE_EXPR, boolean_type_node, cnts[0],
8532 size_binop_loc (first_loc, PLUS_EXPR, counts[0],
8533 size_int (2)));
8534 if (!unused[2])
8535 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8536 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8537 cnts[2],
8538 size_binop_loc (first_loc, PLUS_EXPR,
8539 totalpx,
8540 size_int (1))));
8542 else
8544 tree prev = size_int (5);
8545 for (i = 0; i < 4; i++)
8547 if (unused[i])
8548 continue;
8549 prev = size_binop_loc (first_loc, PLUS_EXPR, counts[i], prev);
8550 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8551 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8552 cnts[i], unshare_expr (prev)));
8555 tem = build3_loc (first_loc, COND_EXPR, void_type_node, cond,
8556 build_call_expr_loc (first_loc,
8557 builtin_decl_explicit (BUILT_IN_TRAP),
8558 0), void_node);
8559 gimplify_and_add (tem, pre_p);
8560 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_DEPEND);
8561 OMP_CLAUSE_DEPEND_KIND (c) = OMP_CLAUSE_DEPEND_LAST;
8562 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (array);
8563 OMP_CLAUSE_CHAIN (c) = *list_p;
8564 *list_p = c;
8565 return 1;
8568 /* Insert a GOMP_MAP_ALLOC or GOMP_MAP_RELEASE node following a
8569 GOMP_MAP_STRUCT mapping. C is an always_pointer mapping. STRUCT_NODE is
8570 the struct node to insert the new mapping after (when the struct node is
8571 initially created). PREV_NODE is the first of two or three mappings for a
8572 pointer, and is either:
8573 - the node before C, when a pair of mappings is used, e.g. for a C/C++
8574 array section.
8575 - not the node before C. This is true when we have a reference-to-pointer
8576 type (with a mapping for the reference and for the pointer), or for
8577 Fortran derived-type mappings with a GOMP_MAP_TO_PSET.
8578 If SCP is non-null, the new node is inserted before *SCP.
8579 if SCP is null, the new node is inserted before PREV_NODE.
8580 The return type is:
8581 - PREV_NODE, if SCP is non-null.
8582 - The newly-created ALLOC or RELEASE node, if SCP is null.
8583 - The second newly-created ALLOC or RELEASE node, if we are mapping a
8584 reference to a pointer. */
8586 static tree
8587 insert_struct_comp_map (enum tree_code code, tree c, tree struct_node,
8588 tree prev_node, tree *scp)
8590 enum gomp_map_kind mkind
8591 = (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA)
8592 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
8594 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8595 tree cl = scp ? prev_node : c2;
8596 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
8597 OMP_CLAUSE_DECL (c2) = unshare_expr (OMP_CLAUSE_DECL (c));
8598 OMP_CLAUSE_CHAIN (c2) = scp ? *scp : prev_node;
8599 if (OMP_CLAUSE_CHAIN (prev_node) != c
8600 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8601 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8602 == GOMP_MAP_TO_PSET))
8603 OMP_CLAUSE_SIZE (c2) = OMP_CLAUSE_SIZE (OMP_CLAUSE_CHAIN (prev_node));
8604 else
8605 OMP_CLAUSE_SIZE (c2) = TYPE_SIZE_UNIT (ptr_type_node);
8606 if (struct_node)
8607 OMP_CLAUSE_CHAIN (struct_node) = c2;
8609 /* We might need to create an additional mapping if we have a reference to a
8610 pointer (in C++). Don't do this if we have something other than a
8611 GOMP_MAP_ALWAYS_POINTER though, i.e. a GOMP_MAP_TO_PSET. */
8612 if (OMP_CLAUSE_CHAIN (prev_node) != c
8613 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8614 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8615 == GOMP_MAP_ALWAYS_POINTER)
8616 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8617 == GOMP_MAP_ATTACH_DETACH)))
8619 tree c4 = OMP_CLAUSE_CHAIN (prev_node);
8620 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8621 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
8622 OMP_CLAUSE_DECL (c3) = unshare_expr (OMP_CLAUSE_DECL (c4));
8623 OMP_CLAUSE_SIZE (c3) = TYPE_SIZE_UNIT (ptr_type_node);
8624 OMP_CLAUSE_CHAIN (c3) = prev_node;
8625 if (!scp)
8626 OMP_CLAUSE_CHAIN (c2) = c3;
8627 else
8628 cl = c3;
8631 if (scp)
8632 *scp = c2;
8634 return cl;
8637 /* Strip ARRAY_REFS or an indirect ref off BASE, find the containing object,
8638 and set *BITPOSP and *POFFSETP to the bit offset of the access.
8639 If BASE_REF is non-NULL and the containing object is a reference, set
8640 *BASE_REF to that reference before dereferencing the object.
8641 If BASE_REF is NULL, check that the containing object is a COMPONENT_REF or
8642 has array type, else return NULL. */
8644 static tree
8645 extract_base_bit_offset (tree base, tree *base_ref, poly_int64 *bitposp,
8646 poly_offset_int *poffsetp)
8648 tree offset;
8649 poly_int64 bitsize, bitpos;
8650 machine_mode mode;
8651 int unsignedp, reversep, volatilep = 0;
8652 poly_offset_int poffset;
8654 if (base_ref)
8656 *base_ref = NULL_TREE;
8658 while (TREE_CODE (base) == ARRAY_REF)
8659 base = TREE_OPERAND (base, 0);
8661 if (TREE_CODE (base) == INDIRECT_REF)
8662 base = TREE_OPERAND (base, 0);
8664 else
8666 if (TREE_CODE (base) == ARRAY_REF)
8668 while (TREE_CODE (base) == ARRAY_REF)
8669 base = TREE_OPERAND (base, 0);
8670 if (TREE_CODE (base) != COMPONENT_REF
8671 || TREE_CODE (TREE_TYPE (base)) != ARRAY_TYPE)
8672 return NULL_TREE;
8674 else if (TREE_CODE (base) == INDIRECT_REF
8675 && TREE_CODE (TREE_OPERAND (base, 0)) == COMPONENT_REF
8676 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0)))
8677 == REFERENCE_TYPE))
8678 base = TREE_OPERAND (base, 0);
8681 base = get_inner_reference (base, &bitsize, &bitpos, &offset, &mode,
8682 &unsignedp, &reversep, &volatilep);
8684 tree orig_base = base;
8686 if ((TREE_CODE (base) == INDIRECT_REF
8687 || (TREE_CODE (base) == MEM_REF
8688 && integer_zerop (TREE_OPERAND (base, 1))))
8689 && DECL_P (TREE_OPERAND (base, 0))
8690 && TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0))) == REFERENCE_TYPE)
8691 base = TREE_OPERAND (base, 0);
8693 gcc_assert (offset == NULL_TREE || poly_int_tree_p (offset));
8695 if (offset)
8696 poffset = wi::to_poly_offset (offset);
8697 else
8698 poffset = 0;
8700 if (maybe_ne (bitpos, 0))
8701 poffset += bits_to_bytes_round_down (bitpos);
8703 *bitposp = bitpos;
8704 *poffsetp = poffset;
8706 /* Set *BASE_REF if BASE was a dereferenced reference variable. */
8707 if (base_ref && orig_base != base)
8708 *base_ref = orig_base;
8710 return base;
8713 /* Returns true if EXPR is or contains (as a sub-component) BASE_PTR. */
8715 static bool
8716 is_or_contains_p (tree expr, tree base_ptr)
8718 while (expr != base_ptr)
8719 if (TREE_CODE (base_ptr) == COMPONENT_REF)
8720 base_ptr = TREE_OPERAND (base_ptr, 0);
8721 else
8722 break;
8723 return expr == base_ptr;
8726 /* Implement OpenMP 5.x map ordering rules for target directives. There are
8727 several rules, and with some level of ambiguity, hopefully we can at least
8728 collect the complexity here in one place. */
8730 static void
8731 omp_target_reorder_clauses (tree *list_p)
8733 /* Collect refs to alloc/release/delete maps. */
8734 auto_vec<tree, 32> ard;
8735 tree *cp = list_p;
8736 while (*cp != NULL_TREE)
8737 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8738 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALLOC
8739 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_RELEASE
8740 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_DELETE))
8742 /* Unlink cp and push to ard. */
8743 tree c = *cp;
8744 tree nc = OMP_CLAUSE_CHAIN (c);
8745 *cp = nc;
8746 ard.safe_push (c);
8748 /* Any associated pointer type maps should also move along. */
8749 while (*cp != NULL_TREE
8750 && OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8751 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
8752 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_POINTER
8753 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ATTACH_DETACH
8754 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_POINTER
8755 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALWAYS_POINTER
8756 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_TO_PSET))
8758 c = *cp;
8759 nc = OMP_CLAUSE_CHAIN (c);
8760 *cp = nc;
8761 ard.safe_push (c);
8764 else
8765 cp = &OMP_CLAUSE_CHAIN (*cp);
8767 /* Link alloc/release/delete maps to the end of list. */
8768 for (unsigned int i = 0; i < ard.length (); i++)
8770 *cp = ard[i];
8771 cp = &OMP_CLAUSE_CHAIN (ard[i]);
8773 *cp = NULL_TREE;
8775 /* OpenMP 5.0 requires that pointer variables are mapped before
8776 its use as a base-pointer. */
8777 auto_vec<tree *, 32> atf;
8778 for (tree *cp = list_p; *cp; cp = &OMP_CLAUSE_CHAIN (*cp))
8779 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP)
8781 /* Collect alloc, to, from, to/from clause tree pointers. */
8782 gomp_map_kind k = OMP_CLAUSE_MAP_KIND (*cp);
8783 if (k == GOMP_MAP_ALLOC
8784 || k == GOMP_MAP_TO
8785 || k == GOMP_MAP_FROM
8786 || k == GOMP_MAP_TOFROM
8787 || k == GOMP_MAP_ALWAYS_TO
8788 || k == GOMP_MAP_ALWAYS_FROM
8789 || k == GOMP_MAP_ALWAYS_TOFROM)
8790 atf.safe_push (cp);
8793 for (unsigned int i = 0; i < atf.length (); i++)
8794 if (atf[i])
8796 tree *cp = atf[i];
8797 tree decl = OMP_CLAUSE_DECL (*cp);
8798 if (TREE_CODE (decl) == INDIRECT_REF || TREE_CODE (decl) == MEM_REF)
8800 tree base_ptr = TREE_OPERAND (decl, 0);
8801 STRIP_TYPE_NOPS (base_ptr);
8802 for (unsigned int j = i + 1; j < atf.length (); j++)
8804 tree *cp2 = atf[j];
8805 tree decl2 = OMP_CLAUSE_DECL (*cp2);
8806 if (is_or_contains_p (decl2, base_ptr))
8808 /* Move *cp2 to before *cp. */
8809 tree c = *cp2;
8810 *cp2 = OMP_CLAUSE_CHAIN (c);
8811 OMP_CLAUSE_CHAIN (c) = *cp;
8812 *cp = c;
8813 atf[j] = NULL;
8820 /* DECL is supposed to have lastprivate semantics in the outer contexts
8821 of combined/composite constructs, starting with OCTX.
8822 Add needed lastprivate, shared or map clause if no data sharing or
8823 mapping clause are present. IMPLICIT_P is true if it is an implicit
8824 clause (IV on simd), in which case the lastprivate will not be
8825 copied to some constructs. */
8827 static void
8828 omp_lastprivate_for_combined_outer_constructs (struct gimplify_omp_ctx *octx,
8829 tree decl, bool implicit_p)
8831 struct gimplify_omp_ctx *orig_octx = octx;
8832 for (; octx; octx = octx->outer_context)
8834 if ((octx->region_type == ORT_COMBINED_PARALLEL
8835 || (octx->region_type & ORT_COMBINED_TEAMS) == ORT_COMBINED_TEAMS)
8836 && splay_tree_lookup (octx->variables,
8837 (splay_tree_key) decl) == NULL)
8839 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
8840 continue;
8842 if ((octx->region_type & ORT_TASK) != 0
8843 && octx->combined_loop
8844 && splay_tree_lookup (octx->variables,
8845 (splay_tree_key) decl) == NULL)
8847 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8848 continue;
8850 if (implicit_p
8851 && octx->region_type == ORT_WORKSHARE
8852 && octx->combined_loop
8853 && splay_tree_lookup (octx->variables,
8854 (splay_tree_key) decl) == NULL
8855 && octx->outer_context
8856 && octx->outer_context->region_type == ORT_COMBINED_PARALLEL
8857 && splay_tree_lookup (octx->outer_context->variables,
8858 (splay_tree_key) decl) == NULL)
8860 octx = octx->outer_context;
8861 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8862 continue;
8864 if ((octx->region_type == ORT_WORKSHARE || octx->region_type == ORT_ACC)
8865 && octx->combined_loop
8866 && splay_tree_lookup (octx->variables,
8867 (splay_tree_key) decl) == NULL
8868 && !omp_check_private (octx, decl, false))
8870 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8871 continue;
8873 if (octx->region_type == ORT_COMBINED_TARGET)
8875 splay_tree_node n = splay_tree_lookup (octx->variables,
8876 (splay_tree_key) decl);
8877 if (n == NULL)
8879 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
8880 octx = octx->outer_context;
8882 else if (!implicit_p
8883 && (n->value & GOVD_FIRSTPRIVATE_IMPLICIT))
8885 n->value &= ~(GOVD_FIRSTPRIVATE
8886 | GOVD_FIRSTPRIVATE_IMPLICIT
8887 | GOVD_EXPLICIT);
8888 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
8889 octx = octx->outer_context;
8892 break;
8894 if (octx && (implicit_p || octx != orig_octx))
8895 omp_notice_variable (octx, decl, true);
8898 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
8899 and previous omp contexts. */
8901 static void
8902 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
8903 enum omp_region_type region_type,
8904 enum tree_code code)
8906 struct gimplify_omp_ctx *ctx, *outer_ctx;
8907 tree c;
8908 hash_map<tree, tree> *struct_map_to_clause = NULL;
8909 hash_set<tree> *struct_deref_set = NULL;
8910 tree *prev_list_p = NULL, *orig_list_p = list_p;
8911 int handled_depend_iterators = -1;
8912 int nowait = -1;
8914 ctx = new_omp_context (region_type);
8915 ctx->code = code;
8916 outer_ctx = ctx->outer_context;
8917 if (code == OMP_TARGET)
8919 if (!lang_GNU_Fortran ())
8920 ctx->defaultmap[GDMK_POINTER] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
8921 ctx->defaultmap[GDMK_SCALAR] = GOVD_FIRSTPRIVATE;
8922 ctx->defaultmap[GDMK_SCALAR_TARGET] = (lang_GNU_Fortran ()
8923 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
8925 if (!lang_GNU_Fortran ())
8926 switch (code)
8928 case OMP_TARGET:
8929 case OMP_TARGET_DATA:
8930 case OMP_TARGET_ENTER_DATA:
8931 case OMP_TARGET_EXIT_DATA:
8932 case OACC_DECLARE:
8933 case OACC_HOST_DATA:
8934 case OACC_PARALLEL:
8935 case OACC_KERNELS:
8936 ctx->target_firstprivatize_array_bases = true;
8937 default:
8938 break;
8941 if (code == OMP_TARGET
8942 || code == OMP_TARGET_DATA
8943 || code == OMP_TARGET_ENTER_DATA
8944 || code == OMP_TARGET_EXIT_DATA)
8945 omp_target_reorder_clauses (list_p);
8947 while ((c = *list_p) != NULL)
8949 bool remove = false;
8950 bool notice_outer = true;
8951 const char *check_non_private = NULL;
8952 unsigned int flags;
8953 tree decl;
8955 switch (OMP_CLAUSE_CODE (c))
8957 case OMP_CLAUSE_PRIVATE:
8958 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
8959 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
8961 flags |= GOVD_PRIVATE_OUTER_REF;
8962 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
8964 else
8965 notice_outer = false;
8966 goto do_add;
8967 case OMP_CLAUSE_SHARED:
8968 flags = GOVD_SHARED | GOVD_EXPLICIT;
8969 goto do_add;
8970 case OMP_CLAUSE_FIRSTPRIVATE:
8971 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
8972 check_non_private = "firstprivate";
8973 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
8975 gcc_assert (code == OMP_TARGET);
8976 flags |= GOVD_FIRSTPRIVATE_IMPLICIT;
8978 goto do_add;
8979 case OMP_CLAUSE_LASTPRIVATE:
8980 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
8981 switch (code)
8983 case OMP_DISTRIBUTE:
8984 error_at (OMP_CLAUSE_LOCATION (c),
8985 "conditional %<lastprivate%> clause on "
8986 "%qs construct", "distribute");
8987 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8988 break;
8989 case OMP_TASKLOOP:
8990 error_at (OMP_CLAUSE_LOCATION (c),
8991 "conditional %<lastprivate%> clause on "
8992 "%qs construct", "taskloop");
8993 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8994 break;
8995 default:
8996 break;
8998 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
8999 if (code != OMP_LOOP)
9000 check_non_private = "lastprivate";
9001 decl = OMP_CLAUSE_DECL (c);
9002 if (error_operand_p (decl))
9003 goto do_add;
9004 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c)
9005 && !lang_hooks.decls.omp_scalar_p (decl, true))
9007 error_at (OMP_CLAUSE_LOCATION (c),
9008 "non-scalar variable %qD in conditional "
9009 "%<lastprivate%> clause", decl);
9010 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
9012 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
9013 flags |= GOVD_LASTPRIVATE_CONDITIONAL;
9014 omp_lastprivate_for_combined_outer_constructs (outer_ctx, decl,
9015 false);
9016 goto do_add;
9017 case OMP_CLAUSE_REDUCTION:
9018 if (OMP_CLAUSE_REDUCTION_TASK (c))
9020 if (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
9022 if (nowait == -1)
9023 nowait = omp_find_clause (*list_p,
9024 OMP_CLAUSE_NOWAIT) != NULL_TREE;
9025 if (nowait
9026 && (outer_ctx == NULL
9027 || outer_ctx->region_type != ORT_COMBINED_PARALLEL))
9029 error_at (OMP_CLAUSE_LOCATION (c),
9030 "%<task%> reduction modifier on a construct "
9031 "with a %<nowait%> clause");
9032 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
9035 else if ((region_type & ORT_PARALLEL) != ORT_PARALLEL)
9037 error_at (OMP_CLAUSE_LOCATION (c),
9038 "invalid %<task%> reduction modifier on construct "
9039 "other than %<parallel%>, %qs, %<sections%> or "
9040 "%<scope%>", lang_GNU_Fortran () ? "do" : "for");
9041 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
9044 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
9045 switch (code)
9047 case OMP_SECTIONS:
9048 error_at (OMP_CLAUSE_LOCATION (c),
9049 "%<inscan%> %<reduction%> clause on "
9050 "%qs construct", "sections");
9051 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9052 break;
9053 case OMP_PARALLEL:
9054 error_at (OMP_CLAUSE_LOCATION (c),
9055 "%<inscan%> %<reduction%> clause on "
9056 "%qs construct", "parallel");
9057 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9058 break;
9059 case OMP_TEAMS:
9060 error_at (OMP_CLAUSE_LOCATION (c),
9061 "%<inscan%> %<reduction%> clause on "
9062 "%qs construct", "teams");
9063 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9064 break;
9065 case OMP_TASKLOOP:
9066 error_at (OMP_CLAUSE_LOCATION (c),
9067 "%<inscan%> %<reduction%> clause on "
9068 "%qs construct", "taskloop");
9069 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9070 break;
9071 case OMP_SCOPE:
9072 error_at (OMP_CLAUSE_LOCATION (c),
9073 "%<inscan%> %<reduction%> clause on "
9074 "%qs construct", "scope");
9075 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9076 break;
9077 default:
9078 break;
9080 /* FALLTHRU */
9081 case OMP_CLAUSE_IN_REDUCTION:
9082 case OMP_CLAUSE_TASK_REDUCTION:
9083 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
9084 /* OpenACC permits reductions on private variables. */
9085 if (!(region_type & ORT_ACC)
9086 /* taskgroup is actually not a worksharing region. */
9087 && code != OMP_TASKGROUP)
9088 check_non_private = omp_clause_code_name[OMP_CLAUSE_CODE (c)];
9089 decl = OMP_CLAUSE_DECL (c);
9090 if (TREE_CODE (decl) == MEM_REF)
9092 tree type = TREE_TYPE (decl);
9093 bool saved_into_ssa = gimplify_ctxp->into_ssa;
9094 gimplify_ctxp->into_ssa = false;
9095 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
9096 NULL, is_gimple_val, fb_rvalue, false)
9097 == GS_ERROR)
9099 gimplify_ctxp->into_ssa = saved_into_ssa;
9100 remove = true;
9101 break;
9103 gimplify_ctxp->into_ssa = saved_into_ssa;
9104 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
9105 if (DECL_P (v))
9107 omp_firstprivatize_variable (ctx, v);
9108 omp_notice_variable (ctx, v, true);
9110 decl = TREE_OPERAND (decl, 0);
9111 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
9113 gimplify_ctxp->into_ssa = false;
9114 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
9115 NULL, is_gimple_val, fb_rvalue, false)
9116 == GS_ERROR)
9118 gimplify_ctxp->into_ssa = saved_into_ssa;
9119 remove = true;
9120 break;
9122 gimplify_ctxp->into_ssa = saved_into_ssa;
9123 v = TREE_OPERAND (decl, 1);
9124 if (DECL_P (v))
9126 omp_firstprivatize_variable (ctx, v);
9127 omp_notice_variable (ctx, v, true);
9129 decl = TREE_OPERAND (decl, 0);
9131 if (TREE_CODE (decl) == ADDR_EXPR
9132 || TREE_CODE (decl) == INDIRECT_REF)
9133 decl = TREE_OPERAND (decl, 0);
9135 goto do_add_decl;
9136 case OMP_CLAUSE_LINEAR:
9137 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
9138 is_gimple_val, fb_rvalue) == GS_ERROR)
9140 remove = true;
9141 break;
9143 else
9145 if (code == OMP_SIMD
9146 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
9148 struct gimplify_omp_ctx *octx = outer_ctx;
9149 if (octx
9150 && octx->region_type == ORT_WORKSHARE
9151 && octx->combined_loop
9152 && !octx->distribute)
9154 if (octx->outer_context
9155 && (octx->outer_context->region_type
9156 == ORT_COMBINED_PARALLEL))
9157 octx = octx->outer_context->outer_context;
9158 else
9159 octx = octx->outer_context;
9161 if (octx
9162 && octx->region_type == ORT_WORKSHARE
9163 && octx->combined_loop
9164 && octx->distribute)
9166 error_at (OMP_CLAUSE_LOCATION (c),
9167 "%<linear%> clause for variable other than "
9168 "loop iterator specified on construct "
9169 "combined with %<distribute%>");
9170 remove = true;
9171 break;
9174 /* For combined #pragma omp parallel for simd, need to put
9175 lastprivate and perhaps firstprivate too on the
9176 parallel. Similarly for #pragma omp for simd. */
9177 struct gimplify_omp_ctx *octx = outer_ctx;
9178 bool taskloop_seen = false;
9179 decl = NULL_TREE;
9182 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9183 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9184 break;
9185 decl = OMP_CLAUSE_DECL (c);
9186 if (error_operand_p (decl))
9188 decl = NULL_TREE;
9189 break;
9191 flags = GOVD_SEEN;
9192 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
9193 flags |= GOVD_FIRSTPRIVATE;
9194 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9195 flags |= GOVD_LASTPRIVATE;
9196 if (octx
9197 && octx->region_type == ORT_WORKSHARE
9198 && octx->combined_loop)
9200 if (octx->outer_context
9201 && (octx->outer_context->region_type
9202 == ORT_COMBINED_PARALLEL))
9203 octx = octx->outer_context;
9204 else if (omp_check_private (octx, decl, false))
9205 break;
9207 else if (octx
9208 && (octx->region_type & ORT_TASK) != 0
9209 && octx->combined_loop)
9210 taskloop_seen = true;
9211 else if (octx
9212 && octx->region_type == ORT_COMBINED_PARALLEL
9213 && ((ctx->region_type == ORT_WORKSHARE
9214 && octx == outer_ctx)
9215 || taskloop_seen))
9216 flags = GOVD_SEEN | GOVD_SHARED;
9217 else if (octx
9218 && ((octx->region_type & ORT_COMBINED_TEAMS)
9219 == ORT_COMBINED_TEAMS))
9220 flags = GOVD_SEEN | GOVD_SHARED;
9221 else if (octx
9222 && octx->region_type == ORT_COMBINED_TARGET)
9224 if (flags & GOVD_LASTPRIVATE)
9225 flags = GOVD_SEEN | GOVD_MAP;
9227 else
9228 break;
9229 splay_tree_node on
9230 = splay_tree_lookup (octx->variables,
9231 (splay_tree_key) decl);
9232 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
9234 octx = NULL;
9235 break;
9237 omp_add_variable (octx, decl, flags);
9238 if (octx->outer_context == NULL)
9239 break;
9240 octx = octx->outer_context;
9242 while (1);
9243 if (octx
9244 && decl
9245 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9246 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
9247 omp_notice_variable (octx, decl, true);
9249 flags = GOVD_LINEAR | GOVD_EXPLICIT;
9250 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9251 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9253 notice_outer = false;
9254 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9256 goto do_add;
9258 case OMP_CLAUSE_MAP:
9259 decl = OMP_CLAUSE_DECL (c);
9260 if (error_operand_p (decl))
9261 remove = true;
9262 switch (code)
9264 case OMP_TARGET:
9265 break;
9266 case OACC_DATA:
9267 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
9268 break;
9269 /* FALLTHRU */
9270 case OMP_TARGET_DATA:
9271 case OMP_TARGET_ENTER_DATA:
9272 case OMP_TARGET_EXIT_DATA:
9273 case OACC_ENTER_DATA:
9274 case OACC_EXIT_DATA:
9275 case OACC_HOST_DATA:
9276 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9277 || (OMP_CLAUSE_MAP_KIND (c)
9278 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
9279 /* For target {,enter ,exit }data only the array slice is
9280 mapped, but not the pointer to it. */
9281 remove = true;
9282 break;
9283 default:
9284 break;
9286 /* For Fortran, not only the pointer to the data is mapped but also
9287 the address of the pointer, the array descriptor etc.; for
9288 'exit data' - and in particular for 'delete:' - having an 'alloc:'
9289 does not make sense. Likewise, for 'update' only transferring the
9290 data itself is needed as the rest has been handled in previous
9291 directives. However, for 'exit data', the array descriptor needs
9292 to be delete; hence, we turn the MAP_TO_PSET into a MAP_DELETE.
9294 NOTE: Generally, it is not safe to perform "enter data" operations
9295 on arrays where the data *or the descriptor* may go out of scope
9296 before a corresponding "exit data" operation -- and such a
9297 descriptor may be synthesized temporarily, e.g. to pass an
9298 explicit-shape array to a function expecting an assumed-shape
9299 argument. Performing "enter data" inside the called function
9300 would thus be problematic. */
9301 if (code == OMP_TARGET_EXIT_DATA
9302 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
9303 OMP_CLAUSE_SET_MAP_KIND (c, OMP_CLAUSE_MAP_KIND (*prev_list_p)
9304 == GOMP_MAP_DELETE
9305 ? GOMP_MAP_DELETE : GOMP_MAP_RELEASE);
9306 else if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
9307 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
9308 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
9309 remove = true;
9311 if (remove)
9312 break;
9313 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
9315 struct gimplify_omp_ctx *octx;
9316 for (octx = outer_ctx; octx; octx = octx->outer_context)
9318 if (octx->region_type != ORT_ACC_HOST_DATA)
9319 break;
9320 splay_tree_node n2
9321 = splay_tree_lookup (octx->variables,
9322 (splay_tree_key) decl);
9323 if (n2)
9324 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
9325 "declared in enclosing %<host_data%> region",
9326 DECL_NAME (decl));
9329 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9330 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9331 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9332 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9333 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
9335 remove = true;
9336 break;
9338 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9339 || (OMP_CLAUSE_MAP_KIND (c)
9340 == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9341 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9342 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
9344 OMP_CLAUSE_SIZE (c)
9345 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
9346 false);
9347 if ((region_type & ORT_TARGET) != 0)
9348 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
9349 GOVD_FIRSTPRIVATE | GOVD_SEEN);
9352 if (!DECL_P (decl))
9354 tree d = decl, *pd;
9355 if (TREE_CODE (d) == ARRAY_REF)
9357 while (TREE_CODE (d) == ARRAY_REF)
9358 d = TREE_OPERAND (d, 0);
9359 if (TREE_CODE (d) == COMPONENT_REF
9360 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
9361 decl = d;
9363 pd = &OMP_CLAUSE_DECL (c);
9364 if (d == decl
9365 && TREE_CODE (decl) == INDIRECT_REF
9366 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
9367 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9368 == REFERENCE_TYPE))
9370 pd = &TREE_OPERAND (decl, 0);
9371 decl = TREE_OPERAND (decl, 0);
9373 bool indir_p = false;
9374 tree orig_decl = decl;
9375 tree decl_ref = NULL_TREE;
9376 if ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA)) != 0
9377 && TREE_CODE (*pd) == COMPONENT_REF
9378 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH
9379 && code != OACC_UPDATE)
9381 while (TREE_CODE (decl) == COMPONENT_REF)
9383 decl = TREE_OPERAND (decl, 0);
9384 if (((TREE_CODE (decl) == MEM_REF
9385 && integer_zerop (TREE_OPERAND (decl, 1)))
9386 || INDIRECT_REF_P (decl))
9387 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9388 == POINTER_TYPE))
9390 indir_p = true;
9391 decl = TREE_OPERAND (decl, 0);
9393 if (TREE_CODE (decl) == INDIRECT_REF
9394 && DECL_P (TREE_OPERAND (decl, 0))
9395 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9396 == REFERENCE_TYPE))
9398 decl_ref = decl;
9399 decl = TREE_OPERAND (decl, 0);
9403 else if (TREE_CODE (decl) == COMPONENT_REF)
9405 while (TREE_CODE (decl) == COMPONENT_REF)
9406 decl = TREE_OPERAND (decl, 0);
9407 if (TREE_CODE (decl) == INDIRECT_REF
9408 && DECL_P (TREE_OPERAND (decl, 0))
9409 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9410 == REFERENCE_TYPE))
9411 decl = TREE_OPERAND (decl, 0);
9413 if (decl != orig_decl && DECL_P (decl) && indir_p)
9415 gomp_map_kind k
9416 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9417 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9418 /* We have a dereference of a struct member. Make this an
9419 attach/detach operation, and ensure the base pointer is
9420 mapped as a FIRSTPRIVATE_POINTER. */
9421 OMP_CLAUSE_SET_MAP_KIND (c, k);
9422 flags = GOVD_MAP | GOVD_SEEN | GOVD_EXPLICIT;
9423 tree next_clause = OMP_CLAUSE_CHAIN (c);
9424 if (k == GOMP_MAP_ATTACH
9425 && code != OACC_ENTER_DATA
9426 && code != OMP_TARGET_ENTER_DATA
9427 && (!next_clause
9428 || (OMP_CLAUSE_CODE (next_clause) != OMP_CLAUSE_MAP)
9429 || (OMP_CLAUSE_MAP_KIND (next_clause)
9430 != GOMP_MAP_POINTER)
9431 || OMP_CLAUSE_DECL (next_clause) != decl)
9432 && (!struct_deref_set
9433 || !struct_deref_set->contains (decl)))
9435 if (!struct_deref_set)
9436 struct_deref_set = new hash_set<tree> ();
9437 /* As well as the attach, we also need a
9438 FIRSTPRIVATE_POINTER clause to properly map the
9439 pointer to the struct base. */
9440 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9441 OMP_CLAUSE_MAP);
9442 OMP_CLAUSE_SET_MAP_KIND (c2, GOMP_MAP_ALLOC);
9443 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (c2)
9444 = 1;
9445 tree charptr_zero
9446 = build_int_cst (build_pointer_type (char_type_node),
9448 OMP_CLAUSE_DECL (c2)
9449 = build2 (MEM_REF, char_type_node,
9450 decl_ref ? decl_ref : decl, charptr_zero);
9451 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9452 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9453 OMP_CLAUSE_MAP);
9454 OMP_CLAUSE_SET_MAP_KIND (c3,
9455 GOMP_MAP_FIRSTPRIVATE_POINTER);
9456 OMP_CLAUSE_DECL (c3) = decl;
9457 OMP_CLAUSE_SIZE (c3) = size_zero_node;
9458 tree mapgrp = *prev_list_p;
9459 *prev_list_p = c2;
9460 OMP_CLAUSE_CHAIN (c3) = mapgrp;
9461 OMP_CLAUSE_CHAIN (c2) = c3;
9463 struct_deref_set->add (decl);
9465 goto do_add_decl;
9467 /* An "attach/detach" operation on an update directive should
9468 behave as a GOMP_MAP_ALWAYS_POINTER. Beware that
9469 unlike attach or detach map kinds, GOMP_MAP_ALWAYS_POINTER
9470 depends on the previous mapping. */
9471 if (code == OACC_UPDATE
9472 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9473 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_ALWAYS_POINTER);
9474 if (DECL_P (decl)
9475 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9476 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH
9477 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_DETACH
9478 && code != OACC_UPDATE
9479 && code != OMP_TARGET_UPDATE)
9481 if (error_operand_p (decl))
9483 remove = true;
9484 break;
9487 tree stype = TREE_TYPE (decl);
9488 if (TREE_CODE (stype) == REFERENCE_TYPE)
9489 stype = TREE_TYPE (stype);
9490 if (TYPE_SIZE_UNIT (stype) == NULL
9491 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
9493 error_at (OMP_CLAUSE_LOCATION (c),
9494 "mapping field %qE of variable length "
9495 "structure", OMP_CLAUSE_DECL (c));
9496 remove = true;
9497 break;
9500 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER
9501 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9503 /* Error recovery. */
9504 if (prev_list_p == NULL)
9506 remove = true;
9507 break;
9509 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
9511 tree ch = OMP_CLAUSE_CHAIN (*prev_list_p);
9512 if (ch == NULL_TREE || OMP_CLAUSE_CHAIN (ch) != c)
9514 remove = true;
9515 break;
9520 poly_offset_int offset1;
9521 poly_int64 bitpos1;
9522 tree base_ref;
9524 tree base
9525 = extract_base_bit_offset (OMP_CLAUSE_DECL (c), &base_ref,
9526 &bitpos1, &offset1);
9528 gcc_assert (base == decl);
9530 splay_tree_node n
9531 = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
9532 bool ptr = (OMP_CLAUSE_MAP_KIND (c)
9533 == GOMP_MAP_ALWAYS_POINTER);
9534 bool attach_detach = (OMP_CLAUSE_MAP_KIND (c)
9535 == GOMP_MAP_ATTACH_DETACH);
9536 bool attach = OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
9537 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DETACH;
9538 bool has_attachments = false;
9539 /* For OpenACC, pointers in structs should trigger an
9540 attach action. */
9541 if (attach_detach
9542 && ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA))
9543 || code == OMP_TARGET_ENTER_DATA
9544 || code == OMP_TARGET_EXIT_DATA))
9547 /* Turn a GOMP_MAP_ATTACH_DETACH clause into a
9548 GOMP_MAP_ATTACH or GOMP_MAP_DETACH clause after we
9549 have detected a case that needs a GOMP_MAP_STRUCT
9550 mapping added. */
9551 gomp_map_kind k
9552 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9553 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9554 OMP_CLAUSE_SET_MAP_KIND (c, k);
9555 has_attachments = true;
9557 if (n == NULL || (n->value & GOVD_MAP) == 0)
9559 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9560 OMP_CLAUSE_MAP);
9561 gomp_map_kind k = attach ? GOMP_MAP_FORCE_PRESENT
9562 : GOMP_MAP_STRUCT;
9564 OMP_CLAUSE_SET_MAP_KIND (l, k);
9565 if (base_ref)
9566 OMP_CLAUSE_DECL (l) = unshare_expr (base_ref);
9567 else
9568 OMP_CLAUSE_DECL (l) = decl;
9569 OMP_CLAUSE_SIZE (l)
9570 = (!attach
9571 ? size_int (1)
9572 : DECL_P (OMP_CLAUSE_DECL (l))
9573 ? DECL_SIZE_UNIT (OMP_CLAUSE_DECL (l))
9574 : TYPE_SIZE_UNIT (TREE_TYPE (OMP_CLAUSE_DECL (l))));
9575 if (struct_map_to_clause == NULL)
9576 struct_map_to_clause = new hash_map<tree, tree>;
9577 struct_map_to_clause->put (decl, l);
9578 if (ptr || attach_detach)
9580 insert_struct_comp_map (code, c, l, *prev_list_p,
9581 NULL);
9582 *prev_list_p = l;
9583 prev_list_p = NULL;
9585 else
9587 OMP_CLAUSE_CHAIN (l) = c;
9588 *list_p = l;
9589 list_p = &OMP_CLAUSE_CHAIN (l);
9591 if (base_ref && code == OMP_TARGET)
9593 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9594 OMP_CLAUSE_MAP);
9595 enum gomp_map_kind mkind
9596 = GOMP_MAP_FIRSTPRIVATE_REFERENCE;
9597 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
9598 OMP_CLAUSE_DECL (c2) = decl;
9599 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9600 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
9601 OMP_CLAUSE_CHAIN (l) = c2;
9603 flags = GOVD_MAP | GOVD_EXPLICIT;
9604 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
9605 || ptr
9606 || attach_detach)
9607 flags |= GOVD_SEEN;
9608 if (has_attachments)
9609 flags |= GOVD_MAP_HAS_ATTACHMENTS;
9610 goto do_add_decl;
9612 else if (struct_map_to_clause)
9614 tree *osc = struct_map_to_clause->get (decl);
9615 tree *sc = NULL, *scp = NULL;
9616 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
9617 || ptr
9618 || attach_detach)
9619 n->value |= GOVD_SEEN;
9620 sc = &OMP_CLAUSE_CHAIN (*osc);
9621 if (*sc != c
9622 && (OMP_CLAUSE_MAP_KIND (*sc)
9623 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
9624 sc = &OMP_CLAUSE_CHAIN (*sc);
9625 /* Here "prev_list_p" is the end of the inserted
9626 alloc/release nodes after the struct node, OSC. */
9627 for (; *sc != c; sc = &OMP_CLAUSE_CHAIN (*sc))
9628 if ((ptr || attach_detach) && sc == prev_list_p)
9629 break;
9630 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9631 != COMPONENT_REF
9632 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9633 != INDIRECT_REF)
9634 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9635 != ARRAY_REF))
9636 break;
9637 else
9639 tree sc_decl = OMP_CLAUSE_DECL (*sc);
9640 poly_offset_int offsetn;
9641 poly_int64 bitposn;
9642 tree base
9643 = extract_base_bit_offset (sc_decl, NULL,
9644 &bitposn, &offsetn);
9645 if (base != decl)
9646 break;
9647 if (scp)
9648 continue;
9649 if ((region_type & ORT_ACC) != 0)
9651 /* This duplicate checking code is currently only
9652 enabled for OpenACC. */
9653 tree d1 = OMP_CLAUSE_DECL (*sc);
9654 tree d2 = OMP_CLAUSE_DECL (c);
9655 while (TREE_CODE (d1) == ARRAY_REF)
9656 d1 = TREE_OPERAND (d1, 0);
9657 while (TREE_CODE (d2) == ARRAY_REF)
9658 d2 = TREE_OPERAND (d2, 0);
9659 if (TREE_CODE (d1) == INDIRECT_REF)
9660 d1 = TREE_OPERAND (d1, 0);
9661 if (TREE_CODE (d2) == INDIRECT_REF)
9662 d2 = TREE_OPERAND (d2, 0);
9663 while (TREE_CODE (d1) == COMPONENT_REF)
9664 if (TREE_CODE (d2) == COMPONENT_REF
9665 && TREE_OPERAND (d1, 1)
9666 == TREE_OPERAND (d2, 1))
9668 d1 = TREE_OPERAND (d1, 0);
9669 d2 = TREE_OPERAND (d2, 0);
9671 else
9672 break;
9673 if (d1 == d2)
9675 error_at (OMP_CLAUSE_LOCATION (c),
9676 "%qE appears more than once in map "
9677 "clauses", OMP_CLAUSE_DECL (c));
9678 remove = true;
9679 break;
9682 if (maybe_lt (offset1, offsetn)
9683 || (known_eq (offset1, offsetn)
9684 && maybe_lt (bitpos1, bitposn)))
9686 if (ptr || attach_detach)
9687 scp = sc;
9688 else
9689 break;
9692 if (remove)
9693 break;
9694 if (!attach)
9695 OMP_CLAUSE_SIZE (*osc)
9696 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc),
9697 size_one_node);
9698 if (ptr || attach_detach)
9700 tree cl = insert_struct_comp_map (code, c, NULL,
9701 *prev_list_p, scp);
9702 if (sc == prev_list_p)
9704 *sc = cl;
9705 prev_list_p = NULL;
9707 else
9709 *prev_list_p = OMP_CLAUSE_CHAIN (c);
9710 list_p = prev_list_p;
9711 prev_list_p = NULL;
9712 OMP_CLAUSE_CHAIN (c) = *sc;
9713 *sc = cl;
9714 continue;
9717 else if (*sc != c)
9719 *list_p = OMP_CLAUSE_CHAIN (c);
9720 OMP_CLAUSE_CHAIN (c) = *sc;
9721 *sc = c;
9722 continue;
9726 else if ((code == OACC_ENTER_DATA
9727 || code == OACC_EXIT_DATA
9728 || code == OACC_DATA
9729 || code == OACC_PARALLEL
9730 || code == OACC_KERNELS
9731 || code == OACC_SERIAL)
9732 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9734 gomp_map_kind k = (code == OACC_EXIT_DATA
9735 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9736 OMP_CLAUSE_SET_MAP_KIND (c, k);
9739 if (code == OMP_TARGET && OMP_CLAUSE_MAP_IN_REDUCTION (c))
9741 /* Don't gimplify *pd fully at this point, as the base
9742 will need to be adjusted during omp lowering. */
9743 auto_vec<tree, 10> expr_stack;
9744 tree *p = pd;
9745 while (handled_component_p (*p)
9746 || TREE_CODE (*p) == INDIRECT_REF
9747 || TREE_CODE (*p) == ADDR_EXPR
9748 || TREE_CODE (*p) == MEM_REF
9749 || TREE_CODE (*p) == NON_LVALUE_EXPR)
9751 expr_stack.safe_push (*p);
9752 p = &TREE_OPERAND (*p, 0);
9754 for (int i = expr_stack.length () - 1; i >= 0; i--)
9756 tree t = expr_stack[i];
9757 if (TREE_CODE (t) == ARRAY_REF
9758 || TREE_CODE (t) == ARRAY_RANGE_REF)
9760 if (TREE_OPERAND (t, 2) == NULL_TREE)
9762 tree low = unshare_expr (array_ref_low_bound (t));
9763 if (!is_gimple_min_invariant (low))
9765 TREE_OPERAND (t, 2) = low;
9766 if (gimplify_expr (&TREE_OPERAND (t, 2),
9767 pre_p, NULL,
9768 is_gimple_reg,
9769 fb_rvalue) == GS_ERROR)
9770 remove = true;
9773 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
9774 NULL, is_gimple_reg,
9775 fb_rvalue) == GS_ERROR)
9776 remove = true;
9777 if (TREE_OPERAND (t, 3) == NULL_TREE)
9779 tree elmt_size = array_ref_element_size (t);
9780 if (!is_gimple_min_invariant (elmt_size))
9782 elmt_size = unshare_expr (elmt_size);
9783 tree elmt_type
9784 = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t,
9785 0)));
9786 tree factor
9787 = size_int (TYPE_ALIGN_UNIT (elmt_type));
9788 elmt_size
9789 = size_binop (EXACT_DIV_EXPR, elmt_size,
9790 factor);
9791 TREE_OPERAND (t, 3) = elmt_size;
9792 if (gimplify_expr (&TREE_OPERAND (t, 3),
9793 pre_p, NULL,
9794 is_gimple_reg,
9795 fb_rvalue) == GS_ERROR)
9796 remove = true;
9799 else if (gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
9800 NULL, is_gimple_reg,
9801 fb_rvalue) == GS_ERROR)
9802 remove = true;
9804 else if (TREE_CODE (t) == COMPONENT_REF)
9806 if (TREE_OPERAND (t, 2) == NULL_TREE)
9808 tree offset = component_ref_field_offset (t);
9809 if (!is_gimple_min_invariant (offset))
9811 offset = unshare_expr (offset);
9812 tree field = TREE_OPERAND (t, 1);
9813 tree factor
9814 = size_int (DECL_OFFSET_ALIGN (field)
9815 / BITS_PER_UNIT);
9816 offset = size_binop (EXACT_DIV_EXPR, offset,
9817 factor);
9818 TREE_OPERAND (t, 2) = offset;
9819 if (gimplify_expr (&TREE_OPERAND (t, 2),
9820 pre_p, NULL,
9821 is_gimple_reg,
9822 fb_rvalue) == GS_ERROR)
9823 remove = true;
9826 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
9827 NULL, is_gimple_reg,
9828 fb_rvalue) == GS_ERROR)
9829 remove = true;
9832 for (; expr_stack.length () > 0; )
9834 tree t = expr_stack.pop ();
9836 if (TREE_CODE (t) == ARRAY_REF
9837 || TREE_CODE (t) == ARRAY_RANGE_REF)
9839 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1))
9840 && gimplify_expr (&TREE_OPERAND (t, 1), pre_p,
9841 NULL, is_gimple_val,
9842 fb_rvalue) == GS_ERROR)
9843 remove = true;
9847 else if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue,
9848 fb_lvalue) == GS_ERROR)
9850 remove = true;
9851 break;
9854 if (!remove
9855 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ALWAYS_POINTER
9856 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH_DETACH
9857 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9858 && OMP_CLAUSE_CHAIN (c)
9859 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c)) == OMP_CLAUSE_MAP
9860 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9861 == GOMP_MAP_ALWAYS_POINTER)
9862 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9863 == GOMP_MAP_ATTACH_DETACH)
9864 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9865 == GOMP_MAP_TO_PSET)))
9866 prev_list_p = list_p;
9868 break;
9870 else
9872 /* DECL_P (decl) == true */
9873 tree *sc;
9874 if (struct_map_to_clause
9875 && (sc = struct_map_to_clause->get (decl)) != NULL
9876 && OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_STRUCT
9877 && decl == OMP_CLAUSE_DECL (*sc))
9879 /* We have found a map of the whole structure after a
9880 leading GOMP_MAP_STRUCT has been created, so refill the
9881 leading clause into a map of the whole structure
9882 variable, and remove the current one.
9883 TODO: we should be able to remove some maps of the
9884 following structure element maps if they are of
9885 compatible TO/FROM/ALLOC type. */
9886 OMP_CLAUSE_SET_MAP_KIND (*sc, OMP_CLAUSE_MAP_KIND (c));
9887 OMP_CLAUSE_SIZE (*sc) = unshare_expr (OMP_CLAUSE_SIZE (c));
9888 remove = true;
9889 break;
9892 flags = GOVD_MAP | GOVD_EXPLICIT;
9893 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
9894 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM)
9895 flags |= GOVD_MAP_ALWAYS_TO;
9897 if ((code == OMP_TARGET
9898 || code == OMP_TARGET_DATA
9899 || code == OMP_TARGET_ENTER_DATA
9900 || code == OMP_TARGET_EXIT_DATA)
9901 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9903 for (struct gimplify_omp_ctx *octx = outer_ctx; octx;
9904 octx = octx->outer_context)
9906 splay_tree_node n
9907 = splay_tree_lookup (octx->variables,
9908 (splay_tree_key) OMP_CLAUSE_DECL (c));
9909 /* If this is contained in an outer OpenMP region as a
9910 firstprivate value, remove the attach/detach. */
9911 if (n && (n->value & GOVD_FIRSTPRIVATE))
9913 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FIRSTPRIVATE_POINTER);
9914 goto do_add;
9918 enum gomp_map_kind map_kind = (code == OMP_TARGET_EXIT_DATA
9919 ? GOMP_MAP_DETACH
9920 : GOMP_MAP_ATTACH);
9921 OMP_CLAUSE_SET_MAP_KIND (c, map_kind);
9924 goto do_add;
9926 case OMP_CLAUSE_AFFINITY:
9927 gimplify_omp_affinity (list_p, pre_p);
9928 remove = true;
9929 break;
9930 case OMP_CLAUSE_DEPEND:
9931 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
9933 tree deps = OMP_CLAUSE_DECL (c);
9934 while (deps && TREE_CODE (deps) == TREE_LIST)
9936 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
9937 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
9938 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
9939 pre_p, NULL, is_gimple_val, fb_rvalue);
9940 deps = TREE_CHAIN (deps);
9942 break;
9944 else if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
9945 break;
9946 if (handled_depend_iterators == -1)
9947 handled_depend_iterators = gimplify_omp_depend (list_p, pre_p);
9948 if (handled_depend_iterators)
9950 if (handled_depend_iterators == 2)
9951 remove = true;
9952 break;
9954 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
9956 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
9957 NULL, is_gimple_val, fb_rvalue);
9958 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
9960 if (error_operand_p (OMP_CLAUSE_DECL (c)))
9962 remove = true;
9963 break;
9965 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
9966 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
9967 is_gimple_val, fb_rvalue) == GS_ERROR)
9969 remove = true;
9970 break;
9972 if (code == OMP_TASK)
9973 ctx->has_depend = true;
9974 break;
9976 case OMP_CLAUSE_TO:
9977 case OMP_CLAUSE_FROM:
9978 case OMP_CLAUSE__CACHE_:
9979 decl = OMP_CLAUSE_DECL (c);
9980 if (error_operand_p (decl))
9982 remove = true;
9983 break;
9985 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9986 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9987 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9988 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9989 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
9991 remove = true;
9992 break;
9994 if (!DECL_P (decl))
9996 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
9997 NULL, is_gimple_lvalue, fb_lvalue)
9998 == GS_ERROR)
10000 remove = true;
10001 break;
10003 break;
10005 goto do_notice;
10007 case OMP_CLAUSE_USE_DEVICE_PTR:
10008 case OMP_CLAUSE_USE_DEVICE_ADDR:
10009 flags = GOVD_EXPLICIT;
10010 goto do_add;
10012 case OMP_CLAUSE_IS_DEVICE_PTR:
10013 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
10014 goto do_add;
10016 do_add:
10017 decl = OMP_CLAUSE_DECL (c);
10018 do_add_decl:
10019 if (error_operand_p (decl))
10021 remove = true;
10022 break;
10024 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
10026 tree t = omp_member_access_dummy_var (decl);
10027 if (t)
10029 tree v = DECL_VALUE_EXPR (decl);
10030 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
10031 if (outer_ctx)
10032 omp_notice_variable (outer_ctx, t, true);
10035 if (code == OACC_DATA
10036 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
10037 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
10038 flags |= GOVD_MAP_0LEN_ARRAY;
10039 omp_add_variable (ctx, decl, flags);
10040 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10041 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_IN_REDUCTION
10042 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_TASK_REDUCTION)
10043 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
10045 struct gimplify_omp_ctx *pctx
10046 = code == OMP_TARGET ? outer_ctx : ctx;
10047 if (pctx)
10048 omp_add_variable (pctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
10049 GOVD_LOCAL | GOVD_SEEN);
10050 if (pctx
10051 && OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
10052 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
10053 find_decl_expr,
10054 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
10055 NULL) == NULL_TREE)
10056 omp_add_variable (pctx,
10057 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
10058 GOVD_LOCAL | GOVD_SEEN);
10059 gimplify_omp_ctxp = pctx;
10060 push_gimplify_context ();
10062 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
10063 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
10065 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
10066 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
10067 pop_gimplify_context
10068 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
10069 push_gimplify_context ();
10070 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
10071 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
10072 pop_gimplify_context
10073 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
10074 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
10075 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
10077 gimplify_omp_ctxp = outer_ctx;
10079 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10080 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
10082 gimplify_omp_ctxp = ctx;
10083 push_gimplify_context ();
10084 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
10086 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
10087 NULL, NULL);
10088 TREE_SIDE_EFFECTS (bind) = 1;
10089 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
10090 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
10092 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
10093 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
10094 pop_gimplify_context
10095 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
10096 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
10098 gimplify_omp_ctxp = outer_ctx;
10100 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
10101 && OMP_CLAUSE_LINEAR_STMT (c))
10103 gimplify_omp_ctxp = ctx;
10104 push_gimplify_context ();
10105 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
10107 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
10108 NULL, NULL);
10109 TREE_SIDE_EFFECTS (bind) = 1;
10110 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
10111 OMP_CLAUSE_LINEAR_STMT (c) = bind;
10113 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
10114 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
10115 pop_gimplify_context
10116 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
10117 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
10119 gimplify_omp_ctxp = outer_ctx;
10121 if (notice_outer)
10122 goto do_notice;
10123 break;
10125 case OMP_CLAUSE_COPYIN:
10126 case OMP_CLAUSE_COPYPRIVATE:
10127 decl = OMP_CLAUSE_DECL (c);
10128 if (error_operand_p (decl))
10130 remove = true;
10131 break;
10133 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
10134 && !remove
10135 && !omp_check_private (ctx, decl, true))
10137 remove = true;
10138 if (is_global_var (decl))
10140 if (DECL_THREAD_LOCAL_P (decl))
10141 remove = false;
10142 else if (DECL_HAS_VALUE_EXPR_P (decl))
10144 tree value = get_base_address (DECL_VALUE_EXPR (decl));
10146 if (value
10147 && DECL_P (value)
10148 && DECL_THREAD_LOCAL_P (value))
10149 remove = false;
10152 if (remove)
10153 error_at (OMP_CLAUSE_LOCATION (c),
10154 "copyprivate variable %qE is not threadprivate"
10155 " or private in outer context", DECL_NAME (decl));
10157 do_notice:
10158 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10159 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE
10160 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
10161 && outer_ctx
10162 && ((region_type & ORT_TASKLOOP) == ORT_TASKLOOP
10163 || (region_type == ORT_WORKSHARE
10164 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10165 && (OMP_CLAUSE_REDUCTION_INSCAN (c)
10166 || code == OMP_LOOP)))
10167 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
10168 || (code == OMP_LOOP
10169 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10170 && ((outer_ctx->region_type & ORT_COMBINED_TEAMS)
10171 == ORT_COMBINED_TEAMS))))
10173 splay_tree_node on
10174 = splay_tree_lookup (outer_ctx->variables,
10175 (splay_tree_key)decl);
10176 if (on == NULL || (on->value & GOVD_DATA_SHARE_CLASS) == 0)
10178 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10179 && TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
10180 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
10181 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
10182 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
10183 == POINTER_TYPE))))
10184 omp_firstprivatize_variable (outer_ctx, decl);
10185 else
10187 omp_add_variable (outer_ctx, decl,
10188 GOVD_SEEN | GOVD_SHARED);
10189 if (outer_ctx->outer_context)
10190 omp_notice_variable (outer_ctx->outer_context, decl,
10191 true);
10195 if (outer_ctx)
10196 omp_notice_variable (outer_ctx, decl, true);
10197 if (check_non_private
10198 && (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
10199 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
10200 || decl == OMP_CLAUSE_DECL (c)
10201 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
10202 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
10203 == ADDR_EXPR
10204 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
10205 == POINTER_PLUS_EXPR
10206 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
10207 (OMP_CLAUSE_DECL (c), 0), 0))
10208 == ADDR_EXPR)))))
10209 && omp_check_private (ctx, decl, false))
10211 error ("%s variable %qE is private in outer context",
10212 check_non_private, DECL_NAME (decl));
10213 remove = true;
10215 break;
10217 case OMP_CLAUSE_DETACH:
10218 flags = GOVD_FIRSTPRIVATE | GOVD_SEEN;
10219 goto do_add;
10221 case OMP_CLAUSE_IF:
10222 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
10223 && OMP_CLAUSE_IF_MODIFIER (c) != code)
10225 const char *p[2];
10226 for (int i = 0; i < 2; i++)
10227 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
10229 case VOID_CST: p[i] = "cancel"; break;
10230 case OMP_PARALLEL: p[i] = "parallel"; break;
10231 case OMP_SIMD: p[i] = "simd"; break;
10232 case OMP_TASK: p[i] = "task"; break;
10233 case OMP_TASKLOOP: p[i] = "taskloop"; break;
10234 case OMP_TARGET_DATA: p[i] = "target data"; break;
10235 case OMP_TARGET: p[i] = "target"; break;
10236 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
10237 case OMP_TARGET_ENTER_DATA:
10238 p[i] = "target enter data"; break;
10239 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
10240 default: gcc_unreachable ();
10242 error_at (OMP_CLAUSE_LOCATION (c),
10243 "expected %qs %<if%> clause modifier rather than %qs",
10244 p[0], p[1]);
10245 remove = true;
10247 /* Fall through. */
10249 case OMP_CLAUSE_FINAL:
10250 OMP_CLAUSE_OPERAND (c, 0)
10251 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
10252 /* Fall through. */
10254 case OMP_CLAUSE_SCHEDULE:
10255 case OMP_CLAUSE_NUM_THREADS:
10256 case OMP_CLAUSE_NUM_TEAMS:
10257 case OMP_CLAUSE_THREAD_LIMIT:
10258 case OMP_CLAUSE_DIST_SCHEDULE:
10259 case OMP_CLAUSE_DEVICE:
10260 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEVICE
10261 && OMP_CLAUSE_DEVICE_ANCESTOR (c))
10263 if (code != OMP_TARGET)
10265 error_at (OMP_CLAUSE_LOCATION (c),
10266 "%<device%> clause with %<ancestor%> is only "
10267 "allowed on %<target%> construct");
10268 remove = true;
10269 break;
10272 tree clauses = *orig_list_p;
10273 for (; clauses ; clauses = OMP_CLAUSE_CHAIN (clauses))
10274 if (OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEVICE
10275 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_FIRSTPRIVATE
10276 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_PRIVATE
10277 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEFAULTMAP
10278 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_MAP
10281 error_at (OMP_CLAUSE_LOCATION (c),
10282 "with %<ancestor%>, only the %<device%>, "
10283 "%<firstprivate%>, %<private%>, %<defaultmap%>, "
10284 "and %<map%> clauses may appear on the "
10285 "construct");
10286 remove = true;
10287 break;
10290 /* Fall through. */
10292 case OMP_CLAUSE_PRIORITY:
10293 case OMP_CLAUSE_GRAINSIZE:
10294 case OMP_CLAUSE_NUM_TASKS:
10295 case OMP_CLAUSE_FILTER:
10296 case OMP_CLAUSE_HINT:
10297 case OMP_CLAUSE_ASYNC:
10298 case OMP_CLAUSE_WAIT:
10299 case OMP_CLAUSE_NUM_GANGS:
10300 case OMP_CLAUSE_NUM_WORKERS:
10301 case OMP_CLAUSE_VECTOR_LENGTH:
10302 case OMP_CLAUSE_WORKER:
10303 case OMP_CLAUSE_VECTOR:
10304 if (OMP_CLAUSE_OPERAND (c, 0)
10305 && !is_gimple_min_invariant (OMP_CLAUSE_OPERAND (c, 0)))
10307 if (error_operand_p (OMP_CLAUSE_OPERAND (c, 0)))
10309 remove = true;
10310 break;
10312 /* All these clauses care about value, not a particular decl,
10313 so try to force it into a SSA_NAME or fresh temporary. */
10314 OMP_CLAUSE_OPERAND (c, 0)
10315 = get_initialized_tmp_var (OMP_CLAUSE_OPERAND (c, 0),
10316 pre_p, NULL, true);
10318 break;
10320 case OMP_CLAUSE_GANG:
10321 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
10322 is_gimple_val, fb_rvalue) == GS_ERROR)
10323 remove = true;
10324 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
10325 is_gimple_val, fb_rvalue) == GS_ERROR)
10326 remove = true;
10327 break;
10329 case OMP_CLAUSE_NOWAIT:
10330 nowait = 1;
10331 break;
10333 case OMP_CLAUSE_ORDERED:
10334 case OMP_CLAUSE_UNTIED:
10335 case OMP_CLAUSE_COLLAPSE:
10336 case OMP_CLAUSE_TILE:
10337 case OMP_CLAUSE_AUTO:
10338 case OMP_CLAUSE_SEQ:
10339 case OMP_CLAUSE_INDEPENDENT:
10340 case OMP_CLAUSE_MERGEABLE:
10341 case OMP_CLAUSE_PROC_BIND:
10342 case OMP_CLAUSE_SAFELEN:
10343 case OMP_CLAUSE_SIMDLEN:
10344 case OMP_CLAUSE_NOGROUP:
10345 case OMP_CLAUSE_THREADS:
10346 case OMP_CLAUSE_SIMD:
10347 case OMP_CLAUSE_BIND:
10348 case OMP_CLAUSE_IF_PRESENT:
10349 case OMP_CLAUSE_FINALIZE:
10350 break;
10352 case OMP_CLAUSE_ORDER:
10353 ctx->order_concurrent = true;
10354 break;
10356 case OMP_CLAUSE_DEFAULTMAP:
10357 enum gimplify_defaultmap_kind gdmkmin, gdmkmax;
10358 switch (OMP_CLAUSE_DEFAULTMAP_CATEGORY (c))
10360 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED:
10361 gdmkmin = GDMK_SCALAR;
10362 gdmkmax = GDMK_POINTER;
10363 break;
10364 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_SCALAR:
10365 gdmkmin = GDMK_SCALAR;
10366 gdmkmax = GDMK_SCALAR_TARGET;
10367 break;
10368 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_AGGREGATE:
10369 gdmkmin = gdmkmax = GDMK_AGGREGATE;
10370 break;
10371 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALLOCATABLE:
10372 gdmkmin = gdmkmax = GDMK_ALLOCATABLE;
10373 break;
10374 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_POINTER:
10375 gdmkmin = gdmkmax = GDMK_POINTER;
10376 break;
10377 default:
10378 gcc_unreachable ();
10380 for (int gdmk = gdmkmin; gdmk <= gdmkmax; gdmk++)
10381 switch (OMP_CLAUSE_DEFAULTMAP_BEHAVIOR (c))
10383 case OMP_CLAUSE_DEFAULTMAP_ALLOC:
10384 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_ALLOC_ONLY;
10385 break;
10386 case OMP_CLAUSE_DEFAULTMAP_TO:
10387 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_TO_ONLY;
10388 break;
10389 case OMP_CLAUSE_DEFAULTMAP_FROM:
10390 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FROM_ONLY;
10391 break;
10392 case OMP_CLAUSE_DEFAULTMAP_TOFROM:
10393 ctx->defaultmap[gdmk] = GOVD_MAP;
10394 break;
10395 case OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE:
10396 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
10397 break;
10398 case OMP_CLAUSE_DEFAULTMAP_NONE:
10399 ctx->defaultmap[gdmk] = 0;
10400 break;
10401 case OMP_CLAUSE_DEFAULTMAP_DEFAULT:
10402 switch (gdmk)
10404 case GDMK_SCALAR:
10405 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
10406 break;
10407 case GDMK_SCALAR_TARGET:
10408 ctx->defaultmap[gdmk] = (lang_GNU_Fortran ()
10409 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
10410 break;
10411 case GDMK_AGGREGATE:
10412 case GDMK_ALLOCATABLE:
10413 ctx->defaultmap[gdmk] = GOVD_MAP;
10414 break;
10415 case GDMK_POINTER:
10416 ctx->defaultmap[gdmk] = GOVD_MAP;
10417 if (!lang_GNU_Fortran ())
10418 ctx->defaultmap[gdmk] |= GOVD_MAP_0LEN_ARRAY;
10419 break;
10420 default:
10421 gcc_unreachable ();
10423 break;
10424 default:
10425 gcc_unreachable ();
10427 break;
10429 case OMP_CLAUSE_ALIGNED:
10430 decl = OMP_CLAUSE_DECL (c);
10431 if (error_operand_p (decl))
10433 remove = true;
10434 break;
10436 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
10437 is_gimple_val, fb_rvalue) == GS_ERROR)
10439 remove = true;
10440 break;
10442 if (!is_global_var (decl)
10443 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
10444 omp_add_variable (ctx, decl, GOVD_ALIGNED);
10445 break;
10447 case OMP_CLAUSE_NONTEMPORAL:
10448 decl = OMP_CLAUSE_DECL (c);
10449 if (error_operand_p (decl))
10451 remove = true;
10452 break;
10454 omp_add_variable (ctx, decl, GOVD_NONTEMPORAL);
10455 break;
10457 case OMP_CLAUSE_ALLOCATE:
10458 decl = OMP_CLAUSE_DECL (c);
10459 if (error_operand_p (decl))
10461 remove = true;
10462 break;
10464 if (gimplify_expr (&OMP_CLAUSE_ALLOCATE_ALLOCATOR (c), pre_p, NULL,
10465 is_gimple_val, fb_rvalue) == GS_ERROR)
10467 remove = true;
10468 break;
10470 else if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c) == NULL_TREE
10471 || (TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c))
10472 == INTEGER_CST))
10474 else if (code == OMP_TASKLOOP
10475 || !DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
10476 OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
10477 = get_initialized_tmp_var (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
10478 pre_p, NULL, false);
10479 break;
10481 case OMP_CLAUSE_DEFAULT:
10482 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
10483 break;
10485 case OMP_CLAUSE_INCLUSIVE:
10486 case OMP_CLAUSE_EXCLUSIVE:
10487 decl = OMP_CLAUSE_DECL (c);
10489 splay_tree_node n = splay_tree_lookup (outer_ctx->variables,
10490 (splay_tree_key) decl);
10491 if (n == NULL || (n->value & GOVD_REDUCTION) == 0)
10493 error_at (OMP_CLAUSE_LOCATION (c),
10494 "%qD specified in %qs clause but not in %<inscan%> "
10495 "%<reduction%> clause on the containing construct",
10496 decl, omp_clause_code_name[OMP_CLAUSE_CODE (c)]);
10497 remove = true;
10499 else
10501 n->value |= GOVD_REDUCTION_INSCAN;
10502 if (outer_ctx->region_type == ORT_SIMD
10503 && outer_ctx->outer_context
10504 && outer_ctx->outer_context->region_type == ORT_WORKSHARE)
10506 n = splay_tree_lookup (outer_ctx->outer_context->variables,
10507 (splay_tree_key) decl);
10508 if (n && (n->value & GOVD_REDUCTION) != 0)
10509 n->value |= GOVD_REDUCTION_INSCAN;
10513 break;
10515 case OMP_CLAUSE_NOHOST:
10516 default:
10517 gcc_unreachable ();
10520 if (code == OACC_DATA
10521 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
10522 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
10523 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10524 remove = true;
10525 if (remove)
10526 *list_p = OMP_CLAUSE_CHAIN (c);
10527 else
10528 list_p = &OMP_CLAUSE_CHAIN (c);
10531 ctx->clauses = *orig_list_p;
10532 gimplify_omp_ctxp = ctx;
10533 if (struct_map_to_clause)
10534 delete struct_map_to_clause;
10535 if (struct_deref_set)
10536 delete struct_deref_set;
10539 /* Return true if DECL is a candidate for shared to firstprivate
10540 optimization. We only consider non-addressable scalars, not
10541 too big, and not references. */
10543 static bool
10544 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
10546 if (TREE_ADDRESSABLE (decl))
10547 return false;
10548 tree type = TREE_TYPE (decl);
10549 if (!is_gimple_reg_type (type)
10550 || TREE_CODE (type) == REFERENCE_TYPE
10551 || TREE_ADDRESSABLE (type))
10552 return false;
10553 /* Don't optimize too large decls, as each thread/task will have
10554 its own. */
10555 HOST_WIDE_INT len = int_size_in_bytes (type);
10556 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
10557 return false;
10558 if (omp_privatize_by_reference (decl))
10559 return false;
10560 return true;
10563 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
10564 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
10565 GOVD_WRITTEN in outer contexts. */
10567 static void
10568 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
10570 for (; ctx; ctx = ctx->outer_context)
10572 splay_tree_node n = splay_tree_lookup (ctx->variables,
10573 (splay_tree_key) decl);
10574 if (n == NULL)
10575 continue;
10576 else if (n->value & GOVD_SHARED)
10578 n->value |= GOVD_WRITTEN;
10579 return;
10581 else if (n->value & GOVD_DATA_SHARE_CLASS)
10582 return;
10586 /* Helper callback for walk_gimple_seq to discover possible stores
10587 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
10588 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
10589 for those. */
10591 static tree
10592 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
10594 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
10596 *walk_subtrees = 0;
10597 if (!wi->is_lhs)
10598 return NULL_TREE;
10600 tree op = *tp;
10603 if (handled_component_p (op))
10604 op = TREE_OPERAND (op, 0);
10605 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
10606 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
10607 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
10608 else
10609 break;
10611 while (1);
10612 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
10613 return NULL_TREE;
10615 omp_mark_stores (gimplify_omp_ctxp, op);
10616 return NULL_TREE;
10619 /* Helper callback for walk_gimple_seq to discover possible stores
10620 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
10621 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
10622 for those. */
10624 static tree
10625 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
10626 bool *handled_ops_p,
10627 struct walk_stmt_info *wi)
10629 gimple *stmt = gsi_stmt (*gsi_p);
10630 switch (gimple_code (stmt))
10632 /* Don't recurse on OpenMP constructs for which
10633 gimplify_adjust_omp_clauses already handled the bodies,
10634 except handle gimple_omp_for_pre_body. */
10635 case GIMPLE_OMP_FOR:
10636 *handled_ops_p = true;
10637 if (gimple_omp_for_pre_body (stmt))
10638 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
10639 omp_find_stores_stmt, omp_find_stores_op, wi);
10640 break;
10641 case GIMPLE_OMP_PARALLEL:
10642 case GIMPLE_OMP_TASK:
10643 case GIMPLE_OMP_SECTIONS:
10644 case GIMPLE_OMP_SINGLE:
10645 case GIMPLE_OMP_SCOPE:
10646 case GIMPLE_OMP_TARGET:
10647 case GIMPLE_OMP_TEAMS:
10648 case GIMPLE_OMP_CRITICAL:
10649 *handled_ops_p = true;
10650 break;
10651 default:
10652 break;
10654 return NULL_TREE;
10657 struct gimplify_adjust_omp_clauses_data
10659 tree *list_p;
10660 gimple_seq *pre_p;
10663 /* For all variables that were not actually used within the context,
10664 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
10666 static int
10667 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
10669 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
10670 gimple_seq *pre_p
10671 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
10672 tree decl = (tree) n->key;
10673 unsigned flags = n->value;
10674 enum omp_clause_code code;
10675 tree clause;
10676 bool private_debug;
10678 if (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
10679 && (flags & GOVD_LASTPRIVATE_CONDITIONAL) != 0)
10680 flags = GOVD_SHARED | GOVD_SEEN | GOVD_WRITTEN;
10681 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
10682 return 0;
10683 if ((flags & GOVD_SEEN) == 0)
10684 return 0;
10685 if ((flags & GOVD_MAP_HAS_ATTACHMENTS) != 0)
10686 return 0;
10687 if (flags & GOVD_DEBUG_PRIVATE)
10689 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_SHARED);
10690 private_debug = true;
10692 else if (flags & GOVD_MAP)
10693 private_debug = false;
10694 else
10695 private_debug
10696 = lang_hooks.decls.omp_private_debug_clause (decl,
10697 !!(flags & GOVD_SHARED));
10698 if (private_debug)
10699 code = OMP_CLAUSE_PRIVATE;
10700 else if (flags & GOVD_MAP)
10702 code = OMP_CLAUSE_MAP;
10703 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
10704 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
10706 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
10707 return 0;
10709 if (VAR_P (decl)
10710 && DECL_IN_CONSTANT_POOL (decl)
10711 && !lookup_attribute ("omp declare target",
10712 DECL_ATTRIBUTES (decl)))
10714 tree id = get_identifier ("omp declare target");
10715 DECL_ATTRIBUTES (decl)
10716 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (decl));
10717 varpool_node *node = varpool_node::get (decl);
10718 if (node)
10720 node->offloadable = 1;
10721 if (ENABLE_OFFLOADING)
10722 g->have_offload = true;
10726 else if (flags & GOVD_SHARED)
10728 if (is_global_var (decl))
10730 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
10731 while (ctx != NULL)
10733 splay_tree_node on
10734 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10735 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
10736 | GOVD_PRIVATE | GOVD_REDUCTION
10737 | GOVD_LINEAR | GOVD_MAP)) != 0)
10738 break;
10739 ctx = ctx->outer_context;
10741 if (ctx == NULL)
10742 return 0;
10744 code = OMP_CLAUSE_SHARED;
10745 /* Don't optimize shared into firstprivate for read-only vars
10746 on tasks with depend clause, we shouldn't try to copy them
10747 until the dependencies are satisfied. */
10748 if (gimplify_omp_ctxp->has_depend)
10749 flags |= GOVD_WRITTEN;
10751 else if (flags & GOVD_PRIVATE)
10752 code = OMP_CLAUSE_PRIVATE;
10753 else if (flags & GOVD_FIRSTPRIVATE)
10755 code = OMP_CLAUSE_FIRSTPRIVATE;
10756 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
10757 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
10758 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
10760 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
10761 "%<target%> construct", decl);
10762 return 0;
10765 else if (flags & GOVD_LASTPRIVATE)
10766 code = OMP_CLAUSE_LASTPRIVATE;
10767 else if (flags & (GOVD_ALIGNED | GOVD_NONTEMPORAL))
10768 return 0;
10769 else if (flags & GOVD_CONDTEMP)
10771 code = OMP_CLAUSE__CONDTEMP_;
10772 gimple_add_tmp_var (decl);
10774 else
10775 gcc_unreachable ();
10777 if (((flags & GOVD_LASTPRIVATE)
10778 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
10779 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10780 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10782 tree chain = *list_p;
10783 clause = build_omp_clause (input_location, code);
10784 OMP_CLAUSE_DECL (clause) = decl;
10785 OMP_CLAUSE_CHAIN (clause) = chain;
10786 if (private_debug)
10787 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
10788 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
10789 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
10790 else if (code == OMP_CLAUSE_SHARED
10791 && (flags & GOVD_WRITTEN) == 0
10792 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10793 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
10794 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
10795 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
10796 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
10798 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
10799 OMP_CLAUSE_DECL (nc) = decl;
10800 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
10801 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
10802 OMP_CLAUSE_DECL (clause)
10803 = build_simple_mem_ref_loc (input_location, decl);
10804 OMP_CLAUSE_DECL (clause)
10805 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
10806 build_int_cst (build_pointer_type (char_type_node), 0));
10807 OMP_CLAUSE_SIZE (clause) = size_zero_node;
10808 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10809 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
10810 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
10811 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
10812 OMP_CLAUSE_CHAIN (nc) = chain;
10813 OMP_CLAUSE_CHAIN (clause) = nc;
10814 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10815 gimplify_omp_ctxp = ctx->outer_context;
10816 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
10817 pre_p, NULL, is_gimple_val, fb_rvalue);
10818 gimplify_omp_ctxp = ctx;
10820 else if (code == OMP_CLAUSE_MAP)
10822 int kind;
10823 /* Not all combinations of these GOVD_MAP flags are actually valid. */
10824 switch (flags & (GOVD_MAP_TO_ONLY
10825 | GOVD_MAP_FORCE
10826 | GOVD_MAP_FORCE_PRESENT
10827 | GOVD_MAP_ALLOC_ONLY
10828 | GOVD_MAP_FROM_ONLY))
10830 case 0:
10831 kind = GOMP_MAP_TOFROM;
10832 break;
10833 case GOVD_MAP_FORCE:
10834 kind = GOMP_MAP_TOFROM | GOMP_MAP_FLAG_FORCE;
10835 break;
10836 case GOVD_MAP_TO_ONLY:
10837 kind = GOMP_MAP_TO;
10838 break;
10839 case GOVD_MAP_FROM_ONLY:
10840 kind = GOMP_MAP_FROM;
10841 break;
10842 case GOVD_MAP_ALLOC_ONLY:
10843 kind = GOMP_MAP_ALLOC;
10844 break;
10845 case GOVD_MAP_TO_ONLY | GOVD_MAP_FORCE:
10846 kind = GOMP_MAP_TO | GOMP_MAP_FLAG_FORCE;
10847 break;
10848 case GOVD_MAP_FORCE_PRESENT:
10849 kind = GOMP_MAP_FORCE_PRESENT;
10850 break;
10851 default:
10852 gcc_unreachable ();
10854 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
10855 if (DECL_SIZE (decl)
10856 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
10858 tree decl2 = DECL_VALUE_EXPR (decl);
10859 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
10860 decl2 = TREE_OPERAND (decl2, 0);
10861 gcc_assert (DECL_P (decl2));
10862 tree mem = build_simple_mem_ref (decl2);
10863 OMP_CLAUSE_DECL (clause) = mem;
10864 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
10865 if (gimplify_omp_ctxp->outer_context)
10867 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
10868 omp_notice_variable (ctx, decl2, true);
10869 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
10871 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
10872 OMP_CLAUSE_MAP);
10873 OMP_CLAUSE_DECL (nc) = decl;
10874 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10875 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
10876 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
10877 else
10878 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
10879 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
10880 OMP_CLAUSE_CHAIN (clause) = nc;
10882 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
10883 && omp_privatize_by_reference (decl))
10885 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
10886 OMP_CLAUSE_SIZE (clause)
10887 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
10888 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10889 gimplify_omp_ctxp = ctx->outer_context;
10890 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
10891 pre_p, NULL, is_gimple_val, fb_rvalue);
10892 gimplify_omp_ctxp = ctx;
10893 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
10894 OMP_CLAUSE_MAP);
10895 OMP_CLAUSE_DECL (nc) = decl;
10896 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10897 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
10898 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
10899 OMP_CLAUSE_CHAIN (clause) = nc;
10901 else
10902 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
10904 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
10906 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
10907 OMP_CLAUSE_DECL (nc) = decl;
10908 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
10909 OMP_CLAUSE_CHAIN (nc) = chain;
10910 OMP_CLAUSE_CHAIN (clause) = nc;
10911 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10912 gimplify_omp_ctxp = ctx->outer_context;
10913 lang_hooks.decls.omp_finish_clause (nc, pre_p,
10914 (ctx->region_type & ORT_ACC) != 0);
10915 gimplify_omp_ctxp = ctx;
10917 *list_p = clause;
10918 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10919 gimplify_omp_ctxp = ctx->outer_context;
10920 /* Don't call omp_finish_clause on implicitly added OMP_CLAUSE_PRIVATE
10921 in simd. Those are only added for the local vars inside of simd body
10922 and they don't need to be e.g. default constructible. */
10923 if (code != OMP_CLAUSE_PRIVATE || ctx->region_type != ORT_SIMD)
10924 lang_hooks.decls.omp_finish_clause (clause, pre_p,
10925 (ctx->region_type & ORT_ACC) != 0);
10926 if (gimplify_omp_ctxp)
10927 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
10928 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
10929 && DECL_P (OMP_CLAUSE_SIZE (clause)))
10930 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
10931 true);
10932 gimplify_omp_ctxp = ctx;
10933 return 0;
10936 static void
10937 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
10938 enum tree_code code)
10940 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10941 tree *orig_list_p = list_p;
10942 tree c, decl;
10943 bool has_inscan_reductions = false;
10945 if (body)
10947 struct gimplify_omp_ctx *octx;
10948 for (octx = ctx; octx; octx = octx->outer_context)
10949 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
10950 break;
10951 if (octx)
10953 struct walk_stmt_info wi;
10954 memset (&wi, 0, sizeof (wi));
10955 walk_gimple_seq (body, omp_find_stores_stmt,
10956 omp_find_stores_op, &wi);
10960 if (ctx->add_safelen1)
10962 /* If there are VLAs in the body of simd loop, prevent
10963 vectorization. */
10964 gcc_assert (ctx->region_type == ORT_SIMD);
10965 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_SAFELEN);
10966 OMP_CLAUSE_SAFELEN_EXPR (c) = integer_one_node;
10967 OMP_CLAUSE_CHAIN (c) = *list_p;
10968 *list_p = c;
10969 list_p = &OMP_CLAUSE_CHAIN (c);
10972 if (ctx->region_type == ORT_WORKSHARE
10973 && ctx->outer_context
10974 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL)
10976 for (c = ctx->outer_context->clauses; c; c = OMP_CLAUSE_CHAIN (c))
10977 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10978 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
10980 decl = OMP_CLAUSE_DECL (c);
10981 splay_tree_node n
10982 = splay_tree_lookup (ctx->outer_context->variables,
10983 (splay_tree_key) decl);
10984 gcc_checking_assert (!splay_tree_lookup (ctx->variables,
10985 (splay_tree_key) decl));
10986 omp_add_variable (ctx, decl, n->value);
10987 tree c2 = copy_node (c);
10988 OMP_CLAUSE_CHAIN (c2) = *list_p;
10989 *list_p = c2;
10990 if ((n->value & GOVD_FIRSTPRIVATE) == 0)
10991 continue;
10992 c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10993 OMP_CLAUSE_FIRSTPRIVATE);
10994 OMP_CLAUSE_DECL (c2) = decl;
10995 OMP_CLAUSE_CHAIN (c2) = *list_p;
10996 *list_p = c2;
10999 while ((c = *list_p) != NULL)
11001 splay_tree_node n;
11002 bool remove = false;
11004 switch (OMP_CLAUSE_CODE (c))
11006 case OMP_CLAUSE_FIRSTPRIVATE:
11007 if ((ctx->region_type & ORT_TARGET)
11008 && (ctx->region_type & ORT_ACC) == 0
11009 && TYPE_ATOMIC (strip_array_types
11010 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
11012 error_at (OMP_CLAUSE_LOCATION (c),
11013 "%<_Atomic%> %qD in %<firstprivate%> clause on "
11014 "%<target%> construct", OMP_CLAUSE_DECL (c));
11015 remove = true;
11016 break;
11018 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
11020 decl = OMP_CLAUSE_DECL (c);
11021 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11022 if ((n->value & GOVD_MAP) != 0)
11024 remove = true;
11025 break;
11027 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT_TARGET (c) = 0;
11028 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c) = 0;
11030 /* FALLTHRU */
11031 case OMP_CLAUSE_PRIVATE:
11032 case OMP_CLAUSE_SHARED:
11033 case OMP_CLAUSE_LINEAR:
11034 decl = OMP_CLAUSE_DECL (c);
11035 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11036 remove = !(n->value & GOVD_SEEN);
11037 if ((n->value & GOVD_LASTPRIVATE_CONDITIONAL) != 0
11038 && code == OMP_PARALLEL
11039 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE)
11040 remove = true;
11041 if (! remove)
11043 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
11044 if ((n->value & GOVD_DEBUG_PRIVATE)
11045 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
11047 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
11048 || ((n->value & GOVD_DATA_SHARE_CLASS)
11049 == GOVD_SHARED));
11050 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
11051 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
11053 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11054 && ctx->has_depend
11055 && DECL_P (decl))
11056 n->value |= GOVD_WRITTEN;
11057 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11058 && (n->value & GOVD_WRITTEN) == 0
11059 && DECL_P (decl)
11060 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11061 OMP_CLAUSE_SHARED_READONLY (c) = 1;
11062 else if (DECL_P (decl)
11063 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11064 && (n->value & GOVD_WRITTEN) != 0)
11065 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11066 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
11067 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11068 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11070 else
11071 n->value &= ~GOVD_EXPLICIT;
11072 break;
11074 case OMP_CLAUSE_LASTPRIVATE:
11075 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
11076 accurately reflect the presence of a FIRSTPRIVATE clause. */
11077 decl = OMP_CLAUSE_DECL (c);
11078 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11079 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
11080 = (n->value & GOVD_FIRSTPRIVATE) != 0;
11081 if (code == OMP_DISTRIBUTE
11082 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
11084 remove = true;
11085 error_at (OMP_CLAUSE_LOCATION (c),
11086 "same variable used in %<firstprivate%> and "
11087 "%<lastprivate%> clauses on %<distribute%> "
11088 "construct");
11090 if (!remove
11091 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
11092 && DECL_P (decl)
11093 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11094 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11095 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) && code == OMP_PARALLEL)
11096 remove = true;
11097 break;
11099 case OMP_CLAUSE_ALIGNED:
11100 decl = OMP_CLAUSE_DECL (c);
11101 if (!is_global_var (decl))
11103 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11104 remove = n == NULL || !(n->value & GOVD_SEEN);
11105 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
11107 struct gimplify_omp_ctx *octx;
11108 if (n != NULL
11109 && (n->value & (GOVD_DATA_SHARE_CLASS
11110 & ~GOVD_FIRSTPRIVATE)))
11111 remove = true;
11112 else
11113 for (octx = ctx->outer_context; octx;
11114 octx = octx->outer_context)
11116 n = splay_tree_lookup (octx->variables,
11117 (splay_tree_key) decl);
11118 if (n == NULL)
11119 continue;
11120 if (n->value & GOVD_LOCAL)
11121 break;
11122 /* We have to avoid assigning a shared variable
11123 to itself when trying to add
11124 __builtin_assume_aligned. */
11125 if (n->value & GOVD_SHARED)
11127 remove = true;
11128 break;
11133 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
11135 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11136 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
11137 remove = true;
11139 break;
11141 case OMP_CLAUSE_NONTEMPORAL:
11142 decl = OMP_CLAUSE_DECL (c);
11143 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11144 remove = n == NULL || !(n->value & GOVD_SEEN);
11145 break;
11147 case OMP_CLAUSE_MAP:
11148 if (code == OMP_TARGET_EXIT_DATA
11149 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
11151 remove = true;
11152 break;
11154 decl = OMP_CLAUSE_DECL (c);
11155 /* Data clauses associated with reductions must be
11156 compatible with present_or_copy. Warn and adjust the clause
11157 if that is not the case. */
11158 if (ctx->region_type == ORT_ACC_PARALLEL
11159 || ctx->region_type == ORT_ACC_SERIAL)
11161 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
11162 n = NULL;
11164 if (DECL_P (t))
11165 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
11167 if (n && (n->value & GOVD_REDUCTION))
11169 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
11171 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
11172 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
11173 && kind != GOMP_MAP_FORCE_PRESENT
11174 && kind != GOMP_MAP_POINTER)
11176 warning_at (OMP_CLAUSE_LOCATION (c), 0,
11177 "incompatible data clause with reduction "
11178 "on %qE; promoting to %<present_or_copy%>",
11179 DECL_NAME (t));
11180 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
11184 if (!DECL_P (decl))
11186 if ((ctx->region_type & ORT_TARGET) != 0
11187 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
11189 if (TREE_CODE (decl) == INDIRECT_REF
11190 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
11191 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
11192 == REFERENCE_TYPE))
11193 decl = TREE_OPERAND (decl, 0);
11194 if (TREE_CODE (decl) == COMPONENT_REF)
11196 while (TREE_CODE (decl) == COMPONENT_REF)
11197 decl = TREE_OPERAND (decl, 0);
11198 if (DECL_P (decl))
11200 n = splay_tree_lookup (ctx->variables,
11201 (splay_tree_key) decl);
11202 if (!(n->value & GOVD_SEEN))
11203 remove = true;
11207 break;
11209 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11210 if ((ctx->region_type & ORT_TARGET) != 0
11211 && !(n->value & GOVD_SEEN)
11212 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
11213 && (!is_global_var (decl)
11214 || !lookup_attribute ("omp declare target link",
11215 DECL_ATTRIBUTES (decl))))
11217 remove = true;
11218 /* For struct element mapping, if struct is never referenced
11219 in target block and none of the mapping has always modifier,
11220 remove all the struct element mappings, which immediately
11221 follow the GOMP_MAP_STRUCT map clause. */
11222 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
11224 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
11225 while (cnt--)
11226 OMP_CLAUSE_CHAIN (c)
11227 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
11230 else if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
11231 && (code == OMP_TARGET_EXIT_DATA
11232 || code == OACC_EXIT_DATA))
11233 remove = true;
11234 else if (DECL_SIZE (decl)
11235 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
11236 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
11237 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
11238 && (OMP_CLAUSE_MAP_KIND (c)
11239 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
11241 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
11242 for these, TREE_CODE (DECL_SIZE (decl)) will always be
11243 INTEGER_CST. */
11244 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
11246 tree decl2 = DECL_VALUE_EXPR (decl);
11247 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
11248 decl2 = TREE_OPERAND (decl2, 0);
11249 gcc_assert (DECL_P (decl2));
11250 tree mem = build_simple_mem_ref (decl2);
11251 OMP_CLAUSE_DECL (c) = mem;
11252 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
11253 if (ctx->outer_context)
11255 omp_notice_variable (ctx->outer_context, decl2, true);
11256 omp_notice_variable (ctx->outer_context,
11257 OMP_CLAUSE_SIZE (c), true);
11259 if (((ctx->region_type & ORT_TARGET) != 0
11260 || !ctx->target_firstprivatize_array_bases)
11261 && ((n->value & GOVD_SEEN) == 0
11262 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
11264 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
11265 OMP_CLAUSE_MAP);
11266 OMP_CLAUSE_DECL (nc) = decl;
11267 OMP_CLAUSE_SIZE (nc) = size_zero_node;
11268 if (ctx->target_firstprivatize_array_bases)
11269 OMP_CLAUSE_SET_MAP_KIND (nc,
11270 GOMP_MAP_FIRSTPRIVATE_POINTER);
11271 else
11272 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
11273 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
11274 OMP_CLAUSE_CHAIN (c) = nc;
11275 c = nc;
11278 else
11280 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
11281 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
11282 gcc_assert ((n->value & GOVD_SEEN) == 0
11283 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
11284 == 0));
11286 break;
11288 case OMP_CLAUSE_TO:
11289 case OMP_CLAUSE_FROM:
11290 case OMP_CLAUSE__CACHE_:
11291 decl = OMP_CLAUSE_DECL (c);
11292 if (!DECL_P (decl))
11293 break;
11294 if (DECL_SIZE (decl)
11295 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
11297 tree decl2 = DECL_VALUE_EXPR (decl);
11298 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
11299 decl2 = TREE_OPERAND (decl2, 0);
11300 gcc_assert (DECL_P (decl2));
11301 tree mem = build_simple_mem_ref (decl2);
11302 OMP_CLAUSE_DECL (c) = mem;
11303 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
11304 if (ctx->outer_context)
11306 omp_notice_variable (ctx->outer_context, decl2, true);
11307 omp_notice_variable (ctx->outer_context,
11308 OMP_CLAUSE_SIZE (c), true);
11311 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
11312 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
11313 break;
11315 case OMP_CLAUSE_REDUCTION:
11316 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
11318 decl = OMP_CLAUSE_DECL (c);
11319 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11320 if ((n->value & GOVD_REDUCTION_INSCAN) == 0)
11322 remove = true;
11323 error_at (OMP_CLAUSE_LOCATION (c),
11324 "%qD specified in %<inscan%> %<reduction%> clause "
11325 "but not in %<scan%> directive clause", decl);
11326 break;
11328 has_inscan_reductions = true;
11330 /* FALLTHRU */
11331 case OMP_CLAUSE_IN_REDUCTION:
11332 case OMP_CLAUSE_TASK_REDUCTION:
11333 decl = OMP_CLAUSE_DECL (c);
11334 /* OpenACC reductions need a present_or_copy data clause.
11335 Add one if necessary. Emit error when the reduction is private. */
11336 if (ctx->region_type == ORT_ACC_PARALLEL
11337 || ctx->region_type == ORT_ACC_SERIAL)
11339 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11340 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
11342 remove = true;
11343 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
11344 "reduction on %qE", DECL_NAME (decl));
11346 else if ((n->value & GOVD_MAP) == 0)
11348 tree next = OMP_CLAUSE_CHAIN (c);
11349 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
11350 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
11351 OMP_CLAUSE_DECL (nc) = decl;
11352 OMP_CLAUSE_CHAIN (c) = nc;
11353 lang_hooks.decls.omp_finish_clause (nc, pre_p,
11354 (ctx->region_type
11355 & ORT_ACC) != 0);
11356 while (1)
11358 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
11359 if (OMP_CLAUSE_CHAIN (nc) == NULL)
11360 break;
11361 nc = OMP_CLAUSE_CHAIN (nc);
11363 OMP_CLAUSE_CHAIN (nc) = next;
11364 n->value |= GOVD_MAP;
11367 if (DECL_P (decl)
11368 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11369 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11370 break;
11372 case OMP_CLAUSE_ALLOCATE:
11373 decl = OMP_CLAUSE_DECL (c);
11374 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11375 if (n != NULL && !(n->value & GOVD_SEEN))
11377 if ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE | GOVD_LINEAR))
11378 != 0
11379 && (n->value & (GOVD_REDUCTION | GOVD_LASTPRIVATE)) == 0)
11380 remove = true;
11382 if (!remove
11383 && OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
11384 && TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)) != INTEGER_CST
11385 && ((ctx->region_type & (ORT_PARALLEL | ORT_TARGET)) != 0
11386 || (ctx->region_type & ORT_TASKLOOP) == ORT_TASK
11387 || (ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS))
11389 tree allocator = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
11390 n = splay_tree_lookup (ctx->variables, (splay_tree_key) allocator);
11391 if (n == NULL)
11393 enum omp_clause_default_kind default_kind
11394 = ctx->default_kind;
11395 ctx->default_kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
11396 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
11397 true);
11398 ctx->default_kind = default_kind;
11400 else
11401 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
11402 true);
11404 break;
11406 case OMP_CLAUSE_COPYIN:
11407 case OMP_CLAUSE_COPYPRIVATE:
11408 case OMP_CLAUSE_IF:
11409 case OMP_CLAUSE_NUM_THREADS:
11410 case OMP_CLAUSE_NUM_TEAMS:
11411 case OMP_CLAUSE_THREAD_LIMIT:
11412 case OMP_CLAUSE_DIST_SCHEDULE:
11413 case OMP_CLAUSE_DEVICE:
11414 case OMP_CLAUSE_SCHEDULE:
11415 case OMP_CLAUSE_NOWAIT:
11416 case OMP_CLAUSE_ORDERED:
11417 case OMP_CLAUSE_DEFAULT:
11418 case OMP_CLAUSE_UNTIED:
11419 case OMP_CLAUSE_COLLAPSE:
11420 case OMP_CLAUSE_FINAL:
11421 case OMP_CLAUSE_MERGEABLE:
11422 case OMP_CLAUSE_PROC_BIND:
11423 case OMP_CLAUSE_SAFELEN:
11424 case OMP_CLAUSE_SIMDLEN:
11425 case OMP_CLAUSE_DEPEND:
11426 case OMP_CLAUSE_PRIORITY:
11427 case OMP_CLAUSE_GRAINSIZE:
11428 case OMP_CLAUSE_NUM_TASKS:
11429 case OMP_CLAUSE_NOGROUP:
11430 case OMP_CLAUSE_THREADS:
11431 case OMP_CLAUSE_SIMD:
11432 case OMP_CLAUSE_FILTER:
11433 case OMP_CLAUSE_HINT:
11434 case OMP_CLAUSE_DEFAULTMAP:
11435 case OMP_CLAUSE_ORDER:
11436 case OMP_CLAUSE_BIND:
11437 case OMP_CLAUSE_DETACH:
11438 case OMP_CLAUSE_USE_DEVICE_PTR:
11439 case OMP_CLAUSE_USE_DEVICE_ADDR:
11440 case OMP_CLAUSE_IS_DEVICE_PTR:
11441 case OMP_CLAUSE_ASYNC:
11442 case OMP_CLAUSE_WAIT:
11443 case OMP_CLAUSE_INDEPENDENT:
11444 case OMP_CLAUSE_NUM_GANGS:
11445 case OMP_CLAUSE_NUM_WORKERS:
11446 case OMP_CLAUSE_VECTOR_LENGTH:
11447 case OMP_CLAUSE_GANG:
11448 case OMP_CLAUSE_WORKER:
11449 case OMP_CLAUSE_VECTOR:
11450 case OMP_CLAUSE_AUTO:
11451 case OMP_CLAUSE_SEQ:
11452 case OMP_CLAUSE_TILE:
11453 case OMP_CLAUSE_IF_PRESENT:
11454 case OMP_CLAUSE_FINALIZE:
11455 case OMP_CLAUSE_INCLUSIVE:
11456 case OMP_CLAUSE_EXCLUSIVE:
11457 break;
11459 case OMP_CLAUSE_NOHOST:
11460 default:
11461 gcc_unreachable ();
11464 if (remove)
11465 *list_p = OMP_CLAUSE_CHAIN (c);
11466 else
11467 list_p = &OMP_CLAUSE_CHAIN (c);
11470 /* Add in any implicit data sharing. */
11471 struct gimplify_adjust_omp_clauses_data data;
11472 data.list_p = list_p;
11473 data.pre_p = pre_p;
11474 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
11476 if (has_inscan_reductions)
11477 for (c = *orig_list_p; c; c = OMP_CLAUSE_CHAIN (c))
11478 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11479 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
11481 error_at (OMP_CLAUSE_LOCATION (c),
11482 "%<inscan%> %<reduction%> clause used together with "
11483 "%<linear%> clause for a variable other than loop "
11484 "iterator");
11485 break;
11488 gimplify_omp_ctxp = ctx->outer_context;
11489 delete_omp_context (ctx);
11492 /* Return 0 if CONSTRUCTS selectors don't match the OpenMP context,
11493 -1 if unknown yet (simd is involved, won't be known until vectorization)
11494 and 1 if they do. If SCORES is non-NULL, it should point to an array
11495 of at least 2*NCONSTRUCTS+2 ints, and will be filled with the positions
11496 of the CONSTRUCTS (position -1 if it will never match) followed by
11497 number of constructs in the OpenMP context construct trait. If the
11498 score depends on whether it will be in a declare simd clone or not,
11499 the function returns 2 and there will be two sets of the scores, the first
11500 one for the case that it is not in a declare simd clone, the other
11501 that it is in a declare simd clone. */
11504 omp_construct_selector_matches (enum tree_code *constructs, int nconstructs,
11505 int *scores)
11507 int matched = 0, cnt = 0;
11508 bool simd_seen = false;
11509 bool target_seen = false;
11510 int declare_simd_cnt = -1;
11511 auto_vec<enum tree_code, 16> codes;
11512 for (struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp; ctx;)
11514 if (((ctx->region_type & ORT_PARALLEL) && ctx->code == OMP_PARALLEL)
11515 || ((ctx->region_type & (ORT_TARGET | ORT_IMPLICIT_TARGET | ORT_ACC))
11516 == ORT_TARGET && ctx->code == OMP_TARGET)
11517 || ((ctx->region_type & ORT_TEAMS) && ctx->code == OMP_TEAMS)
11518 || (ctx->region_type == ORT_WORKSHARE && ctx->code == OMP_FOR)
11519 || (ctx->region_type == ORT_SIMD
11520 && ctx->code == OMP_SIMD
11521 && !omp_find_clause (ctx->clauses, OMP_CLAUSE_BIND)))
11523 ++cnt;
11524 if (scores)
11525 codes.safe_push (ctx->code);
11526 else if (matched < nconstructs && ctx->code == constructs[matched])
11528 if (ctx->code == OMP_SIMD)
11530 if (matched)
11531 return 0;
11532 simd_seen = true;
11534 ++matched;
11536 if (ctx->code == OMP_TARGET)
11538 if (scores == NULL)
11539 return matched < nconstructs ? 0 : simd_seen ? -1 : 1;
11540 target_seen = true;
11541 break;
11544 else if (ctx->region_type == ORT_WORKSHARE
11545 && ctx->code == OMP_LOOP
11546 && ctx->outer_context
11547 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL
11548 && ctx->outer_context->outer_context
11549 && ctx->outer_context->outer_context->code == OMP_LOOP
11550 && ctx->outer_context->outer_context->distribute)
11551 ctx = ctx->outer_context->outer_context;
11552 ctx = ctx->outer_context;
11554 if (!target_seen
11555 && lookup_attribute ("omp declare simd",
11556 DECL_ATTRIBUTES (current_function_decl)))
11558 /* Declare simd is a maybe case, it is supposed to be added only to the
11559 omp-simd-clone.c added clones and not to the base function. */
11560 declare_simd_cnt = cnt++;
11561 if (scores)
11562 codes.safe_push (OMP_SIMD);
11563 else if (cnt == 0
11564 && constructs[0] == OMP_SIMD)
11566 gcc_assert (matched == 0);
11567 simd_seen = true;
11568 if (++matched == nconstructs)
11569 return -1;
11572 if (tree attr = lookup_attribute ("omp declare variant variant",
11573 DECL_ATTRIBUTES (current_function_decl)))
11575 enum tree_code variant_constructs[5];
11576 int variant_nconstructs = 0;
11577 if (!target_seen)
11578 variant_nconstructs
11579 = omp_constructor_traits_to_codes (TREE_VALUE (attr),
11580 variant_constructs);
11581 for (int i = 0; i < variant_nconstructs; i++)
11583 ++cnt;
11584 if (scores)
11585 codes.safe_push (variant_constructs[i]);
11586 else if (matched < nconstructs
11587 && variant_constructs[i] == constructs[matched])
11589 if (variant_constructs[i] == OMP_SIMD)
11591 if (matched)
11592 return 0;
11593 simd_seen = true;
11595 ++matched;
11599 if (!target_seen
11600 && lookup_attribute ("omp declare target block",
11601 DECL_ATTRIBUTES (current_function_decl)))
11603 if (scores)
11604 codes.safe_push (OMP_TARGET);
11605 else if (matched < nconstructs && constructs[matched] == OMP_TARGET)
11606 ++matched;
11608 if (scores)
11610 for (int pass = 0; pass < (declare_simd_cnt == -1 ? 1 : 2); pass++)
11612 int j = codes.length () - 1;
11613 for (int i = nconstructs - 1; i >= 0; i--)
11615 while (j >= 0
11616 && (pass != 0 || declare_simd_cnt != j)
11617 && constructs[i] != codes[j])
11618 --j;
11619 if (pass == 0 && declare_simd_cnt != -1 && j > declare_simd_cnt)
11620 *scores++ = j - 1;
11621 else
11622 *scores++ = j;
11624 *scores++ = ((pass == 0 && declare_simd_cnt != -1)
11625 ? codes.length () - 1 : codes.length ());
11627 return declare_simd_cnt == -1 ? 1 : 2;
11629 if (matched == nconstructs)
11630 return simd_seen ? -1 : 1;
11631 return 0;
11634 /* Gimplify OACC_CACHE. */
11636 static void
11637 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
11639 tree expr = *expr_p;
11641 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
11642 OACC_CACHE);
11643 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
11644 OACC_CACHE);
11646 /* TODO: Do something sensible with this information. */
11648 *expr_p = NULL_TREE;
11651 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
11652 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
11653 kind. The entry kind will replace the one in CLAUSE, while the exit
11654 kind will be used in a new omp_clause and returned to the caller. */
11656 static tree
11657 gimplify_oacc_declare_1 (tree clause)
11659 HOST_WIDE_INT kind, new_op;
11660 bool ret = false;
11661 tree c = NULL;
11663 kind = OMP_CLAUSE_MAP_KIND (clause);
11665 switch (kind)
11667 case GOMP_MAP_ALLOC:
11668 new_op = GOMP_MAP_RELEASE;
11669 ret = true;
11670 break;
11672 case GOMP_MAP_FROM:
11673 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
11674 new_op = GOMP_MAP_FROM;
11675 ret = true;
11676 break;
11678 case GOMP_MAP_TOFROM:
11679 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
11680 new_op = GOMP_MAP_FROM;
11681 ret = true;
11682 break;
11684 case GOMP_MAP_DEVICE_RESIDENT:
11685 case GOMP_MAP_FORCE_DEVICEPTR:
11686 case GOMP_MAP_FORCE_PRESENT:
11687 case GOMP_MAP_LINK:
11688 case GOMP_MAP_POINTER:
11689 case GOMP_MAP_TO:
11690 break;
11692 default:
11693 gcc_unreachable ();
11694 break;
11697 if (ret)
11699 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
11700 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
11701 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
11704 return c;
11707 /* Gimplify OACC_DECLARE. */
11709 static void
11710 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
11712 tree expr = *expr_p;
11713 gomp_target *stmt;
11714 tree clauses, t, decl;
11716 clauses = OACC_DECLARE_CLAUSES (expr);
11718 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
11719 gimplify_adjust_omp_clauses (pre_p, NULL, &clauses, OACC_DECLARE);
11721 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
11723 decl = OMP_CLAUSE_DECL (t);
11725 if (TREE_CODE (decl) == MEM_REF)
11726 decl = TREE_OPERAND (decl, 0);
11728 if (VAR_P (decl) && !is_oacc_declared (decl))
11730 tree attr = get_identifier ("oacc declare target");
11731 DECL_ATTRIBUTES (decl) = tree_cons (attr, NULL_TREE,
11732 DECL_ATTRIBUTES (decl));
11735 if (VAR_P (decl)
11736 && !is_global_var (decl)
11737 && DECL_CONTEXT (decl) == current_function_decl)
11739 tree c = gimplify_oacc_declare_1 (t);
11740 if (c)
11742 if (oacc_declare_returns == NULL)
11743 oacc_declare_returns = new hash_map<tree, tree>;
11745 oacc_declare_returns->put (decl, c);
11749 if (gimplify_omp_ctxp)
11750 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
11753 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
11754 clauses);
11756 gimplify_seq_add_stmt (pre_p, stmt);
11758 *expr_p = NULL_TREE;
11761 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
11762 gimplification of the body, as well as scanning the body for used
11763 variables. We need to do this scan now, because variable-sized
11764 decls will be decomposed during gimplification. */
11766 static void
11767 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
11769 tree expr = *expr_p;
11770 gimple *g;
11771 gimple_seq body = NULL;
11773 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
11774 OMP_PARALLEL_COMBINED (expr)
11775 ? ORT_COMBINED_PARALLEL
11776 : ORT_PARALLEL, OMP_PARALLEL);
11778 push_gimplify_context ();
11780 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
11781 if (gimple_code (g) == GIMPLE_BIND)
11782 pop_gimplify_context (g);
11783 else
11784 pop_gimplify_context (NULL);
11786 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
11787 OMP_PARALLEL);
11789 g = gimple_build_omp_parallel (body,
11790 OMP_PARALLEL_CLAUSES (expr),
11791 NULL_TREE, NULL_TREE);
11792 if (OMP_PARALLEL_COMBINED (expr))
11793 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
11794 gimplify_seq_add_stmt (pre_p, g);
11795 *expr_p = NULL_TREE;
11798 /* Gimplify the contents of an OMP_TASK statement. This involves
11799 gimplification of the body, as well as scanning the body for used
11800 variables. We need to do this scan now, because variable-sized
11801 decls will be decomposed during gimplification. */
11803 static void
11804 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
11806 tree expr = *expr_p;
11807 gimple *g;
11808 gimple_seq body = NULL;
11810 if (OMP_TASK_BODY (expr) == NULL_TREE)
11811 for (tree c = OMP_TASK_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
11812 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
11813 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_MUTEXINOUTSET)
11815 error_at (OMP_CLAUSE_LOCATION (c),
11816 "%<mutexinoutset%> kind in %<depend%> clause on a "
11817 "%<taskwait%> construct");
11818 break;
11821 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
11822 omp_find_clause (OMP_TASK_CLAUSES (expr),
11823 OMP_CLAUSE_UNTIED)
11824 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
11826 if (OMP_TASK_BODY (expr))
11828 push_gimplify_context ();
11830 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
11831 if (gimple_code (g) == GIMPLE_BIND)
11832 pop_gimplify_context (g);
11833 else
11834 pop_gimplify_context (NULL);
11837 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
11838 OMP_TASK);
11840 g = gimple_build_omp_task (body,
11841 OMP_TASK_CLAUSES (expr),
11842 NULL_TREE, NULL_TREE,
11843 NULL_TREE, NULL_TREE, NULL_TREE);
11844 if (OMP_TASK_BODY (expr) == NULL_TREE)
11845 gimple_omp_task_set_taskwait_p (g, true);
11846 gimplify_seq_add_stmt (pre_p, g);
11847 *expr_p = NULL_TREE;
11850 /* Helper function for gimplify_omp_for. If *TP is not a gimple constant,
11851 force it into a temporary initialized in PRE_P and add firstprivate clause
11852 to ORIG_FOR_STMT. */
11854 static void
11855 gimplify_omp_taskloop_expr (tree type, tree *tp, gimple_seq *pre_p,
11856 tree orig_for_stmt)
11858 if (*tp == NULL || is_gimple_constant (*tp))
11859 return;
11861 *tp = get_initialized_tmp_var (*tp, pre_p, NULL, false);
11862 /* Reference to pointer conversion is considered useless,
11863 but is significant for firstprivate clause. Force it
11864 here. */
11865 if (type
11866 && TREE_CODE (type) == POINTER_TYPE
11867 && TREE_CODE (TREE_TYPE (*tp)) == REFERENCE_TYPE)
11869 tree v = create_tmp_var (TYPE_MAIN_VARIANT (type));
11870 tree m = build2 (INIT_EXPR, TREE_TYPE (v), v, *tp);
11871 gimplify_and_add (m, pre_p);
11872 *tp = v;
11875 tree c = build_omp_clause (input_location, OMP_CLAUSE_FIRSTPRIVATE);
11876 OMP_CLAUSE_DECL (c) = *tp;
11877 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
11878 OMP_FOR_CLAUSES (orig_for_stmt) = c;
11881 /* Gimplify the gross structure of an OMP_FOR statement. */
11883 static enum gimplify_status
11884 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
11886 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
11887 enum gimplify_status ret = GS_ALL_DONE;
11888 enum gimplify_status tret;
11889 gomp_for *gfor;
11890 gimple_seq for_body, for_pre_body;
11891 int i;
11892 bitmap has_decl_expr = NULL;
11893 enum omp_region_type ort = ORT_WORKSHARE;
11894 bool openacc = TREE_CODE (*expr_p) == OACC_LOOP;
11896 orig_for_stmt = for_stmt = *expr_p;
11898 bool loop_p = (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_BIND)
11899 != NULL_TREE);
11900 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
11902 tree *data[4] = { NULL, NULL, NULL, NULL };
11903 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
11904 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
11905 find_combined_omp_for, data, NULL);
11906 if (inner_for_stmt == NULL_TREE)
11908 gcc_assert (seen_error ());
11909 *expr_p = NULL_TREE;
11910 return GS_ERROR;
11912 if (data[2] && OMP_FOR_PRE_BODY (*data[2]))
11914 append_to_statement_list_force (OMP_FOR_PRE_BODY (*data[2]),
11915 &OMP_FOR_PRE_BODY (for_stmt));
11916 OMP_FOR_PRE_BODY (*data[2]) = NULL_TREE;
11918 if (OMP_FOR_PRE_BODY (inner_for_stmt))
11920 append_to_statement_list_force (OMP_FOR_PRE_BODY (inner_for_stmt),
11921 &OMP_FOR_PRE_BODY (for_stmt));
11922 OMP_FOR_PRE_BODY (inner_for_stmt) = NULL_TREE;
11925 if (data[0])
11927 /* We have some statements or variable declarations in between
11928 the composite construct directives. Move them around the
11929 inner_for_stmt. */
11930 data[0] = expr_p;
11931 for (i = 0; i < 3; i++)
11932 if (data[i])
11934 tree t = *data[i];
11935 if (i < 2 && data[i + 1] == &OMP_BODY (t))
11936 data[i + 1] = data[i];
11937 *data[i] = OMP_BODY (t);
11938 tree body = build3 (BIND_EXPR, void_type_node, NULL_TREE,
11939 NULL_TREE, make_node (BLOCK));
11940 OMP_BODY (t) = body;
11941 append_to_statement_list_force (inner_for_stmt,
11942 &BIND_EXPR_BODY (body));
11943 *data[3] = t;
11944 data[3] = tsi_stmt_ptr (tsi_start (BIND_EXPR_BODY (body)));
11945 gcc_assert (*data[3] == inner_for_stmt);
11947 return GS_OK;
11950 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
11951 if (!loop_p
11952 && OMP_FOR_ORIG_DECLS (inner_for_stmt)
11953 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11954 i)) == TREE_LIST
11955 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11956 i)))
11958 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
11959 /* Class iterators aren't allowed on OMP_SIMD, so the only
11960 case we need to solve is distribute parallel for. They are
11961 allowed on the loop construct, but that is already handled
11962 in gimplify_omp_loop. */
11963 gcc_assert (TREE_CODE (inner_for_stmt) == OMP_FOR
11964 && TREE_CODE (for_stmt) == OMP_DISTRIBUTE
11965 && data[1]);
11966 tree orig_decl = TREE_PURPOSE (orig);
11967 tree last = TREE_VALUE (orig);
11968 tree *pc;
11969 for (pc = &OMP_FOR_CLAUSES (inner_for_stmt);
11970 *pc; pc = &OMP_CLAUSE_CHAIN (*pc))
11971 if ((OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE
11972 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LASTPRIVATE)
11973 && OMP_CLAUSE_DECL (*pc) == orig_decl)
11974 break;
11975 if (*pc == NULL_TREE)
11977 tree *spc;
11978 for (spc = &OMP_PARALLEL_CLAUSES (*data[1]);
11979 *spc; spc = &OMP_CLAUSE_CHAIN (*spc))
11980 if (OMP_CLAUSE_CODE (*spc) == OMP_CLAUSE_PRIVATE
11981 && OMP_CLAUSE_DECL (*spc) == orig_decl)
11982 break;
11983 if (*spc)
11985 tree c = *spc;
11986 *spc = OMP_CLAUSE_CHAIN (c);
11987 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
11988 *pc = c;
11991 if (*pc == NULL_TREE)
11993 else if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE)
11995 /* private clause will appear only on inner_for_stmt.
11996 Change it into firstprivate, and add private clause
11997 on for_stmt. */
11998 tree c = copy_node (*pc);
11999 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12000 OMP_FOR_CLAUSES (for_stmt) = c;
12001 OMP_CLAUSE_CODE (*pc) = OMP_CLAUSE_FIRSTPRIVATE;
12002 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
12004 else
12006 /* lastprivate clause will appear on both inner_for_stmt
12007 and for_stmt. Add firstprivate clause to
12008 inner_for_stmt. */
12009 tree c = build_omp_clause (OMP_CLAUSE_LOCATION (*pc),
12010 OMP_CLAUSE_FIRSTPRIVATE);
12011 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (*pc);
12012 OMP_CLAUSE_CHAIN (c) = *pc;
12013 *pc = c;
12014 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
12016 tree c = build_omp_clause (UNKNOWN_LOCATION,
12017 OMP_CLAUSE_FIRSTPRIVATE);
12018 OMP_CLAUSE_DECL (c) = last;
12019 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12020 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12021 c = build_omp_clause (UNKNOWN_LOCATION,
12022 *pc ? OMP_CLAUSE_SHARED
12023 : OMP_CLAUSE_FIRSTPRIVATE);
12024 OMP_CLAUSE_DECL (c) = orig_decl;
12025 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12026 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12028 /* Similarly, take care of C++ range for temporaries, those should
12029 be firstprivate on OMP_PARALLEL if any. */
12030 if (data[1])
12031 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
12032 if (OMP_FOR_ORIG_DECLS (inner_for_stmt)
12033 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
12034 i)) == TREE_LIST
12035 && TREE_CHAIN (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
12036 i)))
12038 tree orig
12039 = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
12040 tree v = TREE_CHAIN (orig);
12041 tree c = build_omp_clause (UNKNOWN_LOCATION,
12042 OMP_CLAUSE_FIRSTPRIVATE);
12043 /* First add firstprivate clause for the __for_end artificial
12044 decl. */
12045 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 1);
12046 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
12047 == REFERENCE_TYPE)
12048 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
12049 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12050 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12051 if (TREE_VEC_ELT (v, 0))
12053 /* And now the same for __for_range artificial decl if it
12054 exists. */
12055 c = build_omp_clause (UNKNOWN_LOCATION,
12056 OMP_CLAUSE_FIRSTPRIVATE);
12057 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 0);
12058 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
12059 == REFERENCE_TYPE)
12060 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
12061 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12062 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12067 switch (TREE_CODE (for_stmt))
12069 case OMP_FOR:
12070 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
12072 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12073 OMP_CLAUSE_SCHEDULE))
12074 error_at (EXPR_LOCATION (for_stmt),
12075 "%qs clause may not appear on non-rectangular %qs",
12076 "schedule", "for");
12077 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED))
12078 error_at (EXPR_LOCATION (for_stmt),
12079 "%qs clause may not appear on non-rectangular %qs",
12080 "ordered", "for");
12082 break;
12083 case OMP_DISTRIBUTE:
12084 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt)
12085 && omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12086 OMP_CLAUSE_DIST_SCHEDULE))
12087 error_at (EXPR_LOCATION (for_stmt),
12088 "%qs clause may not appear on non-rectangular %qs",
12089 "dist_schedule", "distribute");
12090 break;
12091 case OACC_LOOP:
12092 ort = ORT_ACC;
12093 break;
12094 case OMP_TASKLOOP:
12095 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
12096 ort = ORT_UNTIED_TASKLOOP;
12097 else
12098 ort = ORT_TASKLOOP;
12099 break;
12100 case OMP_SIMD:
12101 ort = ORT_SIMD;
12102 break;
12103 default:
12104 gcc_unreachable ();
12107 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
12108 clause for the IV. */
12109 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
12111 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
12112 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12113 decl = TREE_OPERAND (t, 0);
12114 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
12115 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12116 && OMP_CLAUSE_DECL (c) == decl)
12118 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
12119 break;
12123 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
12124 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
12125 loop_p && TREE_CODE (for_stmt) != OMP_SIMD
12126 ? OMP_LOOP : TREE_CODE (for_stmt));
12128 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
12129 gimplify_omp_ctxp->distribute = true;
12131 /* Handle OMP_FOR_INIT. */
12132 for_pre_body = NULL;
12133 if ((ort == ORT_SIMD
12134 || (inner_for_stmt && TREE_CODE (inner_for_stmt) == OMP_SIMD))
12135 && OMP_FOR_PRE_BODY (for_stmt))
12137 has_decl_expr = BITMAP_ALLOC (NULL);
12138 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
12139 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
12140 == VAR_DECL)
12142 t = OMP_FOR_PRE_BODY (for_stmt);
12143 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
12145 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
12147 tree_stmt_iterator si;
12148 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
12149 tsi_next (&si))
12151 t = tsi_stmt (si);
12152 if (TREE_CODE (t) == DECL_EXPR
12153 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
12154 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
12158 if (OMP_FOR_PRE_BODY (for_stmt))
12160 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
12161 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
12162 else
12164 struct gimplify_omp_ctx ctx;
12165 memset (&ctx, 0, sizeof (ctx));
12166 ctx.region_type = ORT_NONE;
12167 gimplify_omp_ctxp = &ctx;
12168 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
12169 gimplify_omp_ctxp = NULL;
12172 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
12174 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
12175 for_stmt = inner_for_stmt;
12177 /* For taskloop, need to gimplify the start, end and step before the
12178 taskloop, outside of the taskloop omp context. */
12179 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12181 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12183 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12184 gimple_seq *for_pre_p = (gimple_seq_empty_p (for_pre_body)
12185 ? pre_p : &for_pre_body);
12186 tree type = TREE_TYPE (TREE_OPERAND (t, 0));
12187 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12189 tree v = TREE_OPERAND (t, 1);
12190 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
12191 for_pre_p, orig_for_stmt);
12192 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
12193 for_pre_p, orig_for_stmt);
12195 else
12196 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
12197 orig_for_stmt);
12199 /* Handle OMP_FOR_COND. */
12200 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12201 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12203 tree v = TREE_OPERAND (t, 1);
12204 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
12205 for_pre_p, orig_for_stmt);
12206 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
12207 for_pre_p, orig_for_stmt);
12209 else
12210 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
12211 orig_for_stmt);
12213 /* Handle OMP_FOR_INCR. */
12214 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12215 if (TREE_CODE (t) == MODIFY_EXPR)
12217 decl = TREE_OPERAND (t, 0);
12218 t = TREE_OPERAND (t, 1);
12219 tree *tp = &TREE_OPERAND (t, 1);
12220 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
12221 tp = &TREE_OPERAND (t, 0);
12223 gimplify_omp_taskloop_expr (NULL_TREE, tp, for_pre_p,
12224 orig_for_stmt);
12228 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
12229 OMP_TASKLOOP);
12232 if (orig_for_stmt != for_stmt)
12233 gimplify_omp_ctxp->combined_loop = true;
12235 for_body = NULL;
12236 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12237 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
12238 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12239 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
12241 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
12242 bool is_doacross = false;
12243 if (c && OMP_CLAUSE_ORDERED_EXPR (c))
12245 is_doacross = true;
12246 gimplify_omp_ctxp->loop_iter_var.create (TREE_VEC_LENGTH
12247 (OMP_FOR_INIT (for_stmt))
12248 * 2);
12250 int collapse = 1, tile = 0;
12251 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
12252 if (c)
12253 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
12254 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_TILE);
12255 if (c)
12256 tile = list_length (OMP_CLAUSE_TILE_LIST (c));
12257 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ALLOCATE);
12258 hash_set<tree> *allocate_uids = NULL;
12259 if (c)
12261 allocate_uids = new hash_set<tree>;
12262 for (; c; c = OMP_CLAUSE_CHAIN (c))
12263 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_ALLOCATE)
12264 allocate_uids->add (OMP_CLAUSE_DECL (c));
12266 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12268 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12269 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12270 decl = TREE_OPERAND (t, 0);
12271 gcc_assert (DECL_P (decl));
12272 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
12273 || POINTER_TYPE_P (TREE_TYPE (decl)));
12274 if (is_doacross)
12276 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
12278 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12279 if (TREE_CODE (orig_decl) == TREE_LIST)
12281 orig_decl = TREE_PURPOSE (orig_decl);
12282 if (!orig_decl)
12283 orig_decl = decl;
12285 gimplify_omp_ctxp->loop_iter_var.quick_push (orig_decl);
12287 else
12288 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
12289 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
12292 /* Make sure the iteration variable is private. */
12293 tree c = NULL_TREE;
12294 tree c2 = NULL_TREE;
12295 if (orig_for_stmt != for_stmt)
12297 /* Preserve this information until we gimplify the inner simd. */
12298 if (has_decl_expr
12299 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
12300 TREE_PRIVATE (t) = 1;
12302 else if (ort == ORT_SIMD)
12304 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
12305 (splay_tree_key) decl);
12306 omp_is_private (gimplify_omp_ctxp, decl,
12307 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12308 != 1));
12309 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
12311 omp_notice_variable (gimplify_omp_ctxp, decl, true);
12312 if (n->value & GOVD_LASTPRIVATE_CONDITIONAL)
12313 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12314 OMP_CLAUSE_LASTPRIVATE);
12315 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
12316 OMP_CLAUSE_LASTPRIVATE))
12317 if (OMP_CLAUSE_DECL (c3) == decl)
12319 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
12320 "conditional %<lastprivate%> on loop "
12321 "iterator %qD ignored", decl);
12322 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
12323 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
12326 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1 && !loop_p)
12328 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
12329 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
12330 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
12331 if ((has_decl_expr
12332 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
12333 || TREE_PRIVATE (t))
12335 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12336 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12338 struct gimplify_omp_ctx *outer
12339 = gimplify_omp_ctxp->outer_context;
12340 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12342 if (outer->region_type == ORT_WORKSHARE
12343 && outer->combined_loop)
12345 n = splay_tree_lookup (outer->variables,
12346 (splay_tree_key)decl);
12347 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
12349 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12350 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12352 else
12354 struct gimplify_omp_ctx *octx = outer->outer_context;
12355 if (octx
12356 && octx->region_type == ORT_COMBINED_PARALLEL
12357 && octx->outer_context
12358 && (octx->outer_context->region_type
12359 == ORT_WORKSHARE)
12360 && octx->outer_context->combined_loop)
12362 octx = octx->outer_context;
12363 n = splay_tree_lookup (octx->variables,
12364 (splay_tree_key)decl);
12365 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
12367 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12368 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12375 OMP_CLAUSE_DECL (c) = decl;
12376 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12377 OMP_FOR_CLAUSES (for_stmt) = c;
12378 omp_add_variable (gimplify_omp_ctxp, decl, flags);
12379 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12380 omp_lastprivate_for_combined_outer_constructs (outer, decl,
12381 true);
12383 else
12385 bool lastprivate
12386 = (!has_decl_expr
12387 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
12388 if (TREE_PRIVATE (t))
12389 lastprivate = false;
12390 if (loop_p && OMP_FOR_ORIG_DECLS (for_stmt))
12392 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12393 if (TREE_CODE (elt) == TREE_LIST && TREE_PURPOSE (elt))
12394 lastprivate = false;
12397 struct gimplify_omp_ctx *outer
12398 = gimplify_omp_ctxp->outer_context;
12399 if (outer && lastprivate)
12400 omp_lastprivate_for_combined_outer_constructs (outer, decl,
12401 true);
12403 c = build_omp_clause (input_location,
12404 lastprivate ? OMP_CLAUSE_LASTPRIVATE
12405 : OMP_CLAUSE_PRIVATE);
12406 OMP_CLAUSE_DECL (c) = decl;
12407 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12408 OMP_FOR_CLAUSES (for_stmt) = c;
12409 omp_add_variable (gimplify_omp_ctxp, decl,
12410 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
12411 | GOVD_EXPLICIT | GOVD_SEEN);
12412 c = NULL_TREE;
12415 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
12417 omp_notice_variable (gimplify_omp_ctxp, decl, true);
12418 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
12419 (splay_tree_key) decl);
12420 if (n && (n->value & GOVD_LASTPRIVATE_CONDITIONAL))
12421 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12422 OMP_CLAUSE_LASTPRIVATE);
12423 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
12424 OMP_CLAUSE_LASTPRIVATE))
12425 if (OMP_CLAUSE_DECL (c3) == decl)
12427 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
12428 "conditional %<lastprivate%> on loop "
12429 "iterator %qD ignored", decl);
12430 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
12431 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
12434 else
12435 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
12437 /* If DECL is not a gimple register, create a temporary variable to act
12438 as an iteration counter. This is valid, since DECL cannot be
12439 modified in the body of the loop. Similarly for any iteration vars
12440 in simd with collapse > 1 where the iterator vars must be
12441 lastprivate. And similarly for vars mentioned in allocate clauses. */
12442 if (orig_for_stmt != for_stmt)
12443 var = decl;
12444 else if (!is_gimple_reg (decl)
12445 || (ort == ORT_SIMD
12446 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
12447 || (allocate_uids && allocate_uids->contains (decl)))
12449 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12450 /* Make sure omp_add_variable is not called on it prematurely.
12451 We call it ourselves a few lines later. */
12452 gimplify_omp_ctxp = NULL;
12453 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
12454 gimplify_omp_ctxp = ctx;
12455 TREE_OPERAND (t, 0) = var;
12457 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
12459 if (ort == ORT_SIMD
12460 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
12462 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
12463 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
12464 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
12465 OMP_CLAUSE_DECL (c2) = var;
12466 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
12467 OMP_FOR_CLAUSES (for_stmt) = c2;
12468 omp_add_variable (gimplify_omp_ctxp, var,
12469 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
12470 if (c == NULL_TREE)
12472 c = c2;
12473 c2 = NULL_TREE;
12476 else
12477 omp_add_variable (gimplify_omp_ctxp, var,
12478 GOVD_PRIVATE | GOVD_SEEN);
12480 else
12481 var = decl;
12483 gimplify_omp_ctxp->in_for_exprs = true;
12484 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12486 tree lb = TREE_OPERAND (t, 1);
12487 tret = gimplify_expr (&TREE_VEC_ELT (lb, 1), &for_pre_body, NULL,
12488 is_gimple_val, fb_rvalue, false);
12489 ret = MIN (ret, tret);
12490 tret = gimplify_expr (&TREE_VEC_ELT (lb, 2), &for_pre_body, NULL,
12491 is_gimple_val, fb_rvalue, false);
12493 else
12494 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12495 is_gimple_val, fb_rvalue, false);
12496 gimplify_omp_ctxp->in_for_exprs = false;
12497 ret = MIN (ret, tret);
12498 if (ret == GS_ERROR)
12499 return ret;
12501 /* Handle OMP_FOR_COND. */
12502 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12503 gcc_assert (COMPARISON_CLASS_P (t));
12504 gcc_assert (TREE_OPERAND (t, 0) == decl);
12506 gimplify_omp_ctxp->in_for_exprs = true;
12507 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12509 tree ub = TREE_OPERAND (t, 1);
12510 tret = gimplify_expr (&TREE_VEC_ELT (ub, 1), &for_pre_body, NULL,
12511 is_gimple_val, fb_rvalue, false);
12512 ret = MIN (ret, tret);
12513 tret = gimplify_expr (&TREE_VEC_ELT (ub, 2), &for_pre_body, NULL,
12514 is_gimple_val, fb_rvalue, false);
12516 else
12517 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12518 is_gimple_val, fb_rvalue, false);
12519 gimplify_omp_ctxp->in_for_exprs = false;
12520 ret = MIN (ret, tret);
12522 /* Handle OMP_FOR_INCR. */
12523 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12524 switch (TREE_CODE (t))
12526 case PREINCREMENT_EXPR:
12527 case POSTINCREMENT_EXPR:
12529 tree decl = TREE_OPERAND (t, 0);
12530 /* c_omp_for_incr_canonicalize_ptr() should have been
12531 called to massage things appropriately. */
12532 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
12534 if (orig_for_stmt != for_stmt)
12535 break;
12536 t = build_int_cst (TREE_TYPE (decl), 1);
12537 if (c)
12538 OMP_CLAUSE_LINEAR_STEP (c) = t;
12539 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
12540 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
12541 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
12542 break;
12545 case PREDECREMENT_EXPR:
12546 case POSTDECREMENT_EXPR:
12547 /* c_omp_for_incr_canonicalize_ptr() should have been
12548 called to massage things appropriately. */
12549 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
12550 if (orig_for_stmt != for_stmt)
12551 break;
12552 t = build_int_cst (TREE_TYPE (decl), -1);
12553 if (c)
12554 OMP_CLAUSE_LINEAR_STEP (c) = t;
12555 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
12556 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
12557 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
12558 break;
12560 case MODIFY_EXPR:
12561 gcc_assert (TREE_OPERAND (t, 0) == decl);
12562 TREE_OPERAND (t, 0) = var;
12564 t = TREE_OPERAND (t, 1);
12565 switch (TREE_CODE (t))
12567 case PLUS_EXPR:
12568 if (TREE_OPERAND (t, 1) == decl)
12570 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
12571 TREE_OPERAND (t, 0) = var;
12572 break;
12575 /* Fallthru. */
12576 case MINUS_EXPR:
12577 case POINTER_PLUS_EXPR:
12578 gcc_assert (TREE_OPERAND (t, 0) == decl);
12579 TREE_OPERAND (t, 0) = var;
12580 break;
12581 default:
12582 gcc_unreachable ();
12585 gimplify_omp_ctxp->in_for_exprs = true;
12586 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12587 is_gimple_val, fb_rvalue, false);
12588 ret = MIN (ret, tret);
12589 if (c)
12591 tree step = TREE_OPERAND (t, 1);
12592 tree stept = TREE_TYPE (decl);
12593 if (POINTER_TYPE_P (stept))
12594 stept = sizetype;
12595 step = fold_convert (stept, step);
12596 if (TREE_CODE (t) == MINUS_EXPR)
12597 step = fold_build1 (NEGATE_EXPR, stept, step);
12598 OMP_CLAUSE_LINEAR_STEP (c) = step;
12599 if (step != TREE_OPERAND (t, 1))
12601 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
12602 &for_pre_body, NULL,
12603 is_gimple_val, fb_rvalue, false);
12604 ret = MIN (ret, tret);
12607 gimplify_omp_ctxp->in_for_exprs = false;
12608 break;
12610 default:
12611 gcc_unreachable ();
12614 if (c2)
12616 gcc_assert (c);
12617 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
12620 if ((var != decl || collapse > 1 || tile) && orig_for_stmt == for_stmt)
12622 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
12623 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12624 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
12625 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12626 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
12627 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
12628 && OMP_CLAUSE_DECL (c) == decl)
12630 if (is_doacross && (collapse == 1 || i >= collapse))
12631 t = var;
12632 else
12634 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12635 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12636 gcc_assert (TREE_OPERAND (t, 0) == var);
12637 t = TREE_OPERAND (t, 1);
12638 gcc_assert (TREE_CODE (t) == PLUS_EXPR
12639 || TREE_CODE (t) == MINUS_EXPR
12640 || TREE_CODE (t) == POINTER_PLUS_EXPR);
12641 gcc_assert (TREE_OPERAND (t, 0) == var);
12642 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
12643 is_doacross ? var : decl,
12644 TREE_OPERAND (t, 1));
12646 gimple_seq *seq;
12647 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
12648 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
12649 else
12650 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
12651 push_gimplify_context ();
12652 gimplify_assign (decl, t, seq);
12653 gimple *bind = NULL;
12654 if (gimplify_ctxp->temps)
12656 bind = gimple_build_bind (NULL_TREE, *seq, NULL_TREE);
12657 *seq = NULL;
12658 gimplify_seq_add_stmt (seq, bind);
12660 pop_gimplify_context (bind);
12663 if (OMP_FOR_NON_RECTANGULAR (for_stmt) && var != decl)
12664 for (int j = i + 1; j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
12666 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
12667 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12668 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12669 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12670 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12671 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
12672 gcc_assert (COMPARISON_CLASS_P (t));
12673 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12674 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12675 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12679 BITMAP_FREE (has_decl_expr);
12680 delete allocate_uids;
12682 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
12683 || (loop_p && orig_for_stmt == for_stmt))
12685 push_gimplify_context ();
12686 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
12688 OMP_FOR_BODY (orig_for_stmt)
12689 = build3 (BIND_EXPR, void_type_node, NULL,
12690 OMP_FOR_BODY (orig_for_stmt), NULL);
12691 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
12695 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
12696 &for_body);
12698 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
12699 || (loop_p && orig_for_stmt == for_stmt))
12701 if (gimple_code (g) == GIMPLE_BIND)
12702 pop_gimplify_context (g);
12703 else
12704 pop_gimplify_context (NULL);
12707 if (orig_for_stmt != for_stmt)
12708 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12710 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12711 decl = TREE_OPERAND (t, 0);
12712 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12713 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12714 gimplify_omp_ctxp = ctx->outer_context;
12715 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
12716 gimplify_omp_ctxp = ctx;
12717 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
12718 TREE_OPERAND (t, 0) = var;
12719 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12720 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12721 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
12722 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
12723 for (int j = i + 1;
12724 j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
12726 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
12727 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12728 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12729 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12731 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12732 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12734 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
12735 gcc_assert (COMPARISON_CLASS_P (t));
12736 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12737 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12739 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12740 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12745 gimplify_adjust_omp_clauses (pre_p, for_body,
12746 &OMP_FOR_CLAUSES (orig_for_stmt),
12747 TREE_CODE (orig_for_stmt));
12749 int kind;
12750 switch (TREE_CODE (orig_for_stmt))
12752 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
12753 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
12754 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
12755 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
12756 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
12757 default:
12758 gcc_unreachable ();
12760 if (loop_p && kind == GF_OMP_FOR_KIND_SIMD)
12762 gimplify_seq_add_seq (pre_p, for_pre_body);
12763 for_pre_body = NULL;
12765 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
12766 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
12767 for_pre_body);
12768 if (orig_for_stmt != for_stmt)
12769 gimple_omp_for_set_combined_p (gfor, true);
12770 if (gimplify_omp_ctxp
12771 && (gimplify_omp_ctxp->combined_loop
12772 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
12773 && gimplify_omp_ctxp->outer_context
12774 && gimplify_omp_ctxp->outer_context->combined_loop)))
12776 gimple_omp_for_set_combined_into_p (gfor, true);
12777 if (gimplify_omp_ctxp->combined_loop)
12778 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
12779 else
12780 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
12783 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12785 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12786 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
12787 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
12788 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12789 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
12790 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
12791 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12792 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
12795 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
12796 constructs with GIMPLE_OMP_TASK sandwiched in between them.
12797 The outer taskloop stands for computing the number of iterations,
12798 counts for collapsed loops and holding taskloop specific clauses.
12799 The task construct stands for the effect of data sharing on the
12800 explicit task it creates and the inner taskloop stands for expansion
12801 of the static loop inside of the explicit task construct. */
12802 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12804 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
12805 tree task_clauses = NULL_TREE;
12806 tree c = *gfor_clauses_ptr;
12807 tree *gtask_clauses_ptr = &task_clauses;
12808 tree outer_for_clauses = NULL_TREE;
12809 tree *gforo_clauses_ptr = &outer_for_clauses;
12810 bitmap lastprivate_uids = NULL;
12811 if (omp_find_clause (c, OMP_CLAUSE_ALLOCATE))
12813 c = omp_find_clause (c, OMP_CLAUSE_LASTPRIVATE);
12814 if (c)
12816 lastprivate_uids = BITMAP_ALLOC (NULL);
12817 for (; c; c = omp_find_clause (OMP_CLAUSE_CHAIN (c),
12818 OMP_CLAUSE_LASTPRIVATE))
12819 bitmap_set_bit (lastprivate_uids,
12820 DECL_UID (OMP_CLAUSE_DECL (c)));
12822 c = *gfor_clauses_ptr;
12824 for (; c; c = OMP_CLAUSE_CHAIN (c))
12825 switch (OMP_CLAUSE_CODE (c))
12827 /* These clauses are allowed on task, move them there. */
12828 case OMP_CLAUSE_SHARED:
12829 case OMP_CLAUSE_FIRSTPRIVATE:
12830 case OMP_CLAUSE_DEFAULT:
12831 case OMP_CLAUSE_IF:
12832 case OMP_CLAUSE_UNTIED:
12833 case OMP_CLAUSE_FINAL:
12834 case OMP_CLAUSE_MERGEABLE:
12835 case OMP_CLAUSE_PRIORITY:
12836 case OMP_CLAUSE_REDUCTION:
12837 case OMP_CLAUSE_IN_REDUCTION:
12838 *gtask_clauses_ptr = c;
12839 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12840 break;
12841 case OMP_CLAUSE_PRIVATE:
12842 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
12844 /* We want private on outer for and firstprivate
12845 on task. */
12846 *gtask_clauses_ptr
12847 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12848 OMP_CLAUSE_FIRSTPRIVATE);
12849 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12850 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
12851 openacc);
12852 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12853 *gforo_clauses_ptr = c;
12854 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12856 else
12858 *gtask_clauses_ptr = c;
12859 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12861 break;
12862 /* These clauses go into outer taskloop clauses. */
12863 case OMP_CLAUSE_GRAINSIZE:
12864 case OMP_CLAUSE_NUM_TASKS:
12865 case OMP_CLAUSE_NOGROUP:
12866 *gforo_clauses_ptr = c;
12867 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12868 break;
12869 /* Collapse clause we duplicate on both taskloops. */
12870 case OMP_CLAUSE_COLLAPSE:
12871 *gfor_clauses_ptr = c;
12872 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12873 *gforo_clauses_ptr = copy_node (c);
12874 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
12875 break;
12876 /* For lastprivate, keep the clause on inner taskloop, and add
12877 a shared clause on task. If the same decl is also firstprivate,
12878 add also firstprivate clause on the inner taskloop. */
12879 case OMP_CLAUSE_LASTPRIVATE:
12880 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
12882 /* For taskloop C++ lastprivate IVs, we want:
12883 1) private on outer taskloop
12884 2) firstprivate and shared on task
12885 3) lastprivate on inner taskloop */
12886 *gtask_clauses_ptr
12887 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12888 OMP_CLAUSE_FIRSTPRIVATE);
12889 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12890 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
12891 openacc);
12892 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12893 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
12894 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12895 OMP_CLAUSE_PRIVATE);
12896 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
12897 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
12898 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
12899 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
12901 *gfor_clauses_ptr = c;
12902 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12903 *gtask_clauses_ptr
12904 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
12905 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12906 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
12907 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
12908 gtask_clauses_ptr
12909 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12910 break;
12911 /* Allocate clause we duplicate on task and inner taskloop
12912 if the decl is lastprivate, otherwise just put on task. */
12913 case OMP_CLAUSE_ALLOCATE:
12914 if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
12915 && DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
12917 /* Additionally, put firstprivate clause on task
12918 for the allocator if it is not constant. */
12919 *gtask_clauses_ptr
12920 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12921 OMP_CLAUSE_FIRSTPRIVATE);
12922 OMP_CLAUSE_DECL (*gtask_clauses_ptr)
12923 = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
12924 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12926 if (lastprivate_uids
12927 && bitmap_bit_p (lastprivate_uids,
12928 DECL_UID (OMP_CLAUSE_DECL (c))))
12930 *gfor_clauses_ptr = c;
12931 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12932 *gtask_clauses_ptr = copy_node (c);
12933 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12935 else
12937 *gtask_clauses_ptr = c;
12938 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12940 break;
12941 default:
12942 gcc_unreachable ();
12944 *gfor_clauses_ptr = NULL_TREE;
12945 *gtask_clauses_ptr = NULL_TREE;
12946 *gforo_clauses_ptr = NULL_TREE;
12947 BITMAP_FREE (lastprivate_uids);
12948 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
12949 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
12950 NULL_TREE, NULL_TREE, NULL_TREE);
12951 gimple_omp_task_set_taskloop_p (g, true);
12952 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
12953 gomp_for *gforo
12954 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
12955 gimple_omp_for_collapse (gfor),
12956 gimple_omp_for_pre_body (gfor));
12957 gimple_omp_for_set_pre_body (gfor, NULL);
12958 gimple_omp_for_set_combined_p (gforo, true);
12959 gimple_omp_for_set_combined_into_p (gfor, true);
12960 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
12962 tree type = TREE_TYPE (gimple_omp_for_index (gfor, i));
12963 tree v = create_tmp_var (type);
12964 gimple_omp_for_set_index (gforo, i, v);
12965 t = unshare_expr (gimple_omp_for_initial (gfor, i));
12966 gimple_omp_for_set_initial (gforo, i, t);
12967 gimple_omp_for_set_cond (gforo, i,
12968 gimple_omp_for_cond (gfor, i));
12969 t = unshare_expr (gimple_omp_for_final (gfor, i));
12970 gimple_omp_for_set_final (gforo, i, t);
12971 t = unshare_expr (gimple_omp_for_incr (gfor, i));
12972 gcc_assert (TREE_OPERAND (t, 0) == gimple_omp_for_index (gfor, i));
12973 TREE_OPERAND (t, 0) = v;
12974 gimple_omp_for_set_incr (gforo, i, t);
12975 t = build_omp_clause (input_location, OMP_CLAUSE_PRIVATE);
12976 OMP_CLAUSE_DECL (t) = v;
12977 OMP_CLAUSE_CHAIN (t) = gimple_omp_for_clauses (gforo);
12978 gimple_omp_for_set_clauses (gforo, t);
12979 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
12981 tree *p1 = NULL, *p2 = NULL;
12982 t = gimple_omp_for_initial (gforo, i);
12983 if (TREE_CODE (t) == TREE_VEC)
12984 p1 = &TREE_VEC_ELT (t, 0);
12985 t = gimple_omp_for_final (gforo, i);
12986 if (TREE_CODE (t) == TREE_VEC)
12988 if (p1)
12989 p2 = &TREE_VEC_ELT (t, 0);
12990 else
12991 p1 = &TREE_VEC_ELT (t, 0);
12993 if (p1)
12995 int j;
12996 for (j = 0; j < i; j++)
12997 if (*p1 == gimple_omp_for_index (gfor, j))
12999 *p1 = gimple_omp_for_index (gforo, j);
13000 if (p2)
13001 *p2 = *p1;
13002 break;
13004 gcc_assert (j < i);
13008 gimplify_seq_add_stmt (pre_p, gforo);
13010 else
13011 gimplify_seq_add_stmt (pre_p, gfor);
13013 if (TREE_CODE (orig_for_stmt) == OMP_FOR)
13015 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13016 unsigned lastprivate_conditional = 0;
13017 while (ctx
13018 && (ctx->region_type == ORT_TARGET_DATA
13019 || ctx->region_type == ORT_TASKGROUP))
13020 ctx = ctx->outer_context;
13021 if (ctx && (ctx->region_type & ORT_PARALLEL) != 0)
13022 for (tree c = gimple_omp_for_clauses (gfor);
13023 c; c = OMP_CLAUSE_CHAIN (c))
13024 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13025 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
13026 ++lastprivate_conditional;
13027 if (lastprivate_conditional)
13029 struct omp_for_data fd;
13030 omp_extract_for_data (gfor, &fd, NULL);
13031 tree type = build_array_type_nelts (unsigned_type_for (fd.iter_type),
13032 lastprivate_conditional);
13033 tree var = create_tmp_var_raw (type);
13034 tree c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE__CONDTEMP_);
13035 OMP_CLAUSE_DECL (c) = var;
13036 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
13037 gimple_omp_for_set_clauses (gfor, c);
13038 omp_add_variable (ctx, var, GOVD_CONDTEMP | GOVD_SEEN);
13041 else if (TREE_CODE (orig_for_stmt) == OMP_SIMD)
13043 unsigned lastprivate_conditional = 0;
13044 for (tree c = gimple_omp_for_clauses (gfor); c; c = OMP_CLAUSE_CHAIN (c))
13045 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13046 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
13047 ++lastprivate_conditional;
13048 if (lastprivate_conditional)
13050 struct omp_for_data fd;
13051 omp_extract_for_data (gfor, &fd, NULL);
13052 tree type = unsigned_type_for (fd.iter_type);
13053 while (lastprivate_conditional--)
13055 tree c = build_omp_clause (UNKNOWN_LOCATION,
13056 OMP_CLAUSE__CONDTEMP_);
13057 OMP_CLAUSE_DECL (c) = create_tmp_var (type);
13058 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
13059 gimple_omp_for_set_clauses (gfor, c);
13064 if (ret != GS_ALL_DONE)
13065 return GS_ERROR;
13066 *expr_p = NULL_TREE;
13067 return GS_ALL_DONE;
13070 /* Helper for gimplify_omp_loop, called through walk_tree. */
13072 static tree
13073 replace_reduction_placeholders (tree *tp, int *walk_subtrees, void *data)
13075 if (DECL_P (*tp))
13077 tree *d = (tree *) data;
13078 if (*tp == OMP_CLAUSE_REDUCTION_PLACEHOLDER (d[0]))
13080 *tp = OMP_CLAUSE_REDUCTION_PLACEHOLDER (d[1]);
13081 *walk_subtrees = 0;
13083 else if (*tp == OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (d[0]))
13085 *tp = OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (d[1]);
13086 *walk_subtrees = 0;
13089 return NULL_TREE;
13092 /* Gimplify the gross structure of an OMP_LOOP statement. */
13094 static enum gimplify_status
13095 gimplify_omp_loop (tree *expr_p, gimple_seq *pre_p)
13097 tree for_stmt = *expr_p;
13098 tree clauses = OMP_FOR_CLAUSES (for_stmt);
13099 struct gimplify_omp_ctx *octx = gimplify_omp_ctxp;
13100 enum omp_clause_bind_kind kind = OMP_CLAUSE_BIND_THREAD;
13101 int i;
13103 /* If order is not present, the behavior is as if order(concurrent)
13104 appeared. */
13105 tree order = omp_find_clause (clauses, OMP_CLAUSE_ORDER);
13106 if (order == NULL_TREE)
13108 order = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_ORDER);
13109 OMP_CLAUSE_CHAIN (order) = clauses;
13110 OMP_FOR_CLAUSES (for_stmt) = clauses = order;
13113 tree bind = omp_find_clause (clauses, OMP_CLAUSE_BIND);
13114 if (bind == NULL_TREE)
13116 if (!flag_openmp) /* flag_openmp_simd */
13118 else if (octx && (octx->region_type & ORT_TEAMS) != 0)
13119 kind = OMP_CLAUSE_BIND_TEAMS;
13120 else if (octx && (octx->region_type & ORT_PARALLEL) != 0)
13121 kind = OMP_CLAUSE_BIND_PARALLEL;
13122 else
13124 for (; octx; octx = octx->outer_context)
13126 if ((octx->region_type & ORT_ACC) != 0
13127 || octx->region_type == ORT_NONE
13128 || octx->region_type == ORT_IMPLICIT_TARGET)
13129 continue;
13130 break;
13132 if (octx == NULL && !in_omp_construct)
13133 error_at (EXPR_LOCATION (for_stmt),
13134 "%<bind%> clause not specified on a %<loop%> "
13135 "construct not nested inside another OpenMP construct");
13137 bind = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_BIND);
13138 OMP_CLAUSE_CHAIN (bind) = clauses;
13139 OMP_CLAUSE_BIND_KIND (bind) = kind;
13140 OMP_FOR_CLAUSES (for_stmt) = bind;
13142 else
13143 switch (OMP_CLAUSE_BIND_KIND (bind))
13145 case OMP_CLAUSE_BIND_THREAD:
13146 break;
13147 case OMP_CLAUSE_BIND_PARALLEL:
13148 if (!flag_openmp) /* flag_openmp_simd */
13150 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13151 break;
13153 for (; octx; octx = octx->outer_context)
13154 if (octx->region_type == ORT_SIMD
13155 && omp_find_clause (octx->clauses, OMP_CLAUSE_BIND) == NULL_TREE)
13157 error_at (EXPR_LOCATION (for_stmt),
13158 "%<bind(parallel)%> on a %<loop%> construct nested "
13159 "inside %<simd%> construct");
13160 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13161 break;
13163 kind = OMP_CLAUSE_BIND_PARALLEL;
13164 break;
13165 case OMP_CLAUSE_BIND_TEAMS:
13166 if (!flag_openmp) /* flag_openmp_simd */
13168 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13169 break;
13171 if ((octx
13172 && octx->region_type != ORT_IMPLICIT_TARGET
13173 && octx->region_type != ORT_NONE
13174 && (octx->region_type & ORT_TEAMS) == 0)
13175 || in_omp_construct)
13177 error_at (EXPR_LOCATION (for_stmt),
13178 "%<bind(teams)%> on a %<loop%> region not strictly "
13179 "nested inside of a %<teams%> region");
13180 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13181 break;
13183 kind = OMP_CLAUSE_BIND_TEAMS;
13184 break;
13185 default:
13186 gcc_unreachable ();
13189 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
13190 switch (OMP_CLAUSE_CODE (*pc))
13192 case OMP_CLAUSE_REDUCTION:
13193 if (OMP_CLAUSE_REDUCTION_INSCAN (*pc))
13195 error_at (OMP_CLAUSE_LOCATION (*pc),
13196 "%<inscan%> %<reduction%> clause on "
13197 "%qs construct", "loop");
13198 OMP_CLAUSE_REDUCTION_INSCAN (*pc) = 0;
13200 if (OMP_CLAUSE_REDUCTION_TASK (*pc))
13202 error_at (OMP_CLAUSE_LOCATION (*pc),
13203 "invalid %<task%> reduction modifier on construct "
13204 "other than %<parallel%>, %qs or %<sections%>",
13205 lang_GNU_Fortran () ? "do" : "for");
13206 OMP_CLAUSE_REDUCTION_TASK (*pc) = 0;
13208 pc = &OMP_CLAUSE_CHAIN (*pc);
13209 break;
13210 case OMP_CLAUSE_LASTPRIVATE:
13211 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
13213 tree t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
13214 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
13215 if (OMP_CLAUSE_DECL (*pc) == TREE_OPERAND (t, 0))
13216 break;
13217 if (OMP_FOR_ORIG_DECLS (for_stmt)
13218 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
13219 i)) == TREE_LIST
13220 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
13221 i)))
13223 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
13224 if (OMP_CLAUSE_DECL (*pc) == TREE_PURPOSE (orig))
13225 break;
13228 if (i == TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)))
13230 error_at (OMP_CLAUSE_LOCATION (*pc),
13231 "%<lastprivate%> clause on a %<loop%> construct refers "
13232 "to a variable %qD which is not the loop iterator",
13233 OMP_CLAUSE_DECL (*pc));
13234 *pc = OMP_CLAUSE_CHAIN (*pc);
13235 break;
13237 pc = &OMP_CLAUSE_CHAIN (*pc);
13238 break;
13239 default:
13240 pc = &OMP_CLAUSE_CHAIN (*pc);
13241 break;
13244 TREE_SET_CODE (for_stmt, OMP_SIMD);
13246 int last;
13247 switch (kind)
13249 case OMP_CLAUSE_BIND_THREAD: last = 0; break;
13250 case OMP_CLAUSE_BIND_PARALLEL: last = 1; break;
13251 case OMP_CLAUSE_BIND_TEAMS: last = 2; break;
13253 for (int pass = 1; pass <= last; pass++)
13255 if (pass == 2)
13257 tree bind = build3 (BIND_EXPR, void_type_node, NULL, NULL, NULL);
13258 append_to_statement_list (*expr_p, &BIND_EXPR_BODY (bind));
13259 *expr_p = make_node (OMP_PARALLEL);
13260 TREE_TYPE (*expr_p) = void_type_node;
13261 OMP_PARALLEL_BODY (*expr_p) = bind;
13262 OMP_PARALLEL_COMBINED (*expr_p) = 1;
13263 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (for_stmt));
13264 tree *pc = &OMP_PARALLEL_CLAUSES (*expr_p);
13265 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
13266 if (OMP_FOR_ORIG_DECLS (for_stmt)
13267 && (TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i))
13268 == TREE_LIST))
13270 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
13271 if (TREE_PURPOSE (elt) && TREE_VALUE (elt))
13273 *pc = build_omp_clause (UNKNOWN_LOCATION,
13274 OMP_CLAUSE_FIRSTPRIVATE);
13275 OMP_CLAUSE_DECL (*pc) = TREE_VALUE (elt);
13276 pc = &OMP_CLAUSE_CHAIN (*pc);
13280 tree t = make_node (pass == 2 ? OMP_DISTRIBUTE : OMP_FOR);
13281 tree *pc = &OMP_FOR_CLAUSES (t);
13282 TREE_TYPE (t) = void_type_node;
13283 OMP_FOR_BODY (t) = *expr_p;
13284 SET_EXPR_LOCATION (t, EXPR_LOCATION (for_stmt));
13285 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
13286 switch (OMP_CLAUSE_CODE (c))
13288 case OMP_CLAUSE_BIND:
13289 case OMP_CLAUSE_ORDER:
13290 case OMP_CLAUSE_COLLAPSE:
13291 *pc = copy_node (c);
13292 pc = &OMP_CLAUSE_CHAIN (*pc);
13293 break;
13294 case OMP_CLAUSE_PRIVATE:
13295 case OMP_CLAUSE_FIRSTPRIVATE:
13296 /* Only needed on innermost. */
13297 break;
13298 case OMP_CLAUSE_LASTPRIVATE:
13299 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c) && pass != last)
13301 *pc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13302 OMP_CLAUSE_FIRSTPRIVATE);
13303 OMP_CLAUSE_DECL (*pc) = OMP_CLAUSE_DECL (c);
13304 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
13305 pc = &OMP_CLAUSE_CHAIN (*pc);
13307 *pc = copy_node (c);
13308 OMP_CLAUSE_LASTPRIVATE_STMT (*pc) = NULL_TREE;
13309 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
13310 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
13312 if (pass != last)
13313 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (*pc) = 1;
13314 else
13315 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
13316 OMP_CLAUSE_LASTPRIVATE_LOOP_IV (*pc) = 0;
13318 pc = &OMP_CLAUSE_CHAIN (*pc);
13319 break;
13320 case OMP_CLAUSE_REDUCTION:
13321 *pc = copy_node (c);
13322 OMP_CLAUSE_DECL (*pc) = unshare_expr (OMP_CLAUSE_DECL (c));
13323 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
13324 OMP_CLAUSE_REDUCTION_INIT (*pc)
13325 = unshare_expr (OMP_CLAUSE_REDUCTION_INIT (c));
13326 OMP_CLAUSE_REDUCTION_MERGE (*pc)
13327 = unshare_expr (OMP_CLAUSE_REDUCTION_MERGE (c));
13328 if (OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc))
13330 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc)
13331 = copy_node (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c));
13332 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
13333 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc)
13334 = copy_node (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c));
13335 tree nc = *pc;
13336 tree data[2] = { c, nc };
13337 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_INIT (nc),
13338 replace_reduction_placeholders,
13339 data);
13340 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_MERGE (nc),
13341 replace_reduction_placeholders,
13342 data);
13344 pc = &OMP_CLAUSE_CHAIN (*pc);
13345 break;
13346 default:
13347 gcc_unreachable ();
13349 *pc = NULL_TREE;
13350 *expr_p = t;
13352 return gimplify_omp_for (expr_p, pre_p);
13356 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
13357 of OMP_TARGET's body. */
13359 static tree
13360 find_omp_teams (tree *tp, int *walk_subtrees, void *)
13362 *walk_subtrees = 0;
13363 switch (TREE_CODE (*tp))
13365 case OMP_TEAMS:
13366 return *tp;
13367 case BIND_EXPR:
13368 case STATEMENT_LIST:
13369 *walk_subtrees = 1;
13370 break;
13371 default:
13372 break;
13374 return NULL_TREE;
13377 /* Helper function of optimize_target_teams, determine if the expression
13378 can be computed safely before the target construct on the host. */
13380 static tree
13381 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
13383 splay_tree_node n;
13385 if (TYPE_P (*tp))
13387 *walk_subtrees = 0;
13388 return NULL_TREE;
13390 switch (TREE_CODE (*tp))
13392 case VAR_DECL:
13393 case PARM_DECL:
13394 case RESULT_DECL:
13395 *walk_subtrees = 0;
13396 if (error_operand_p (*tp)
13397 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
13398 || DECL_HAS_VALUE_EXPR_P (*tp)
13399 || DECL_THREAD_LOCAL_P (*tp)
13400 || TREE_SIDE_EFFECTS (*tp)
13401 || TREE_THIS_VOLATILE (*tp))
13402 return *tp;
13403 if (is_global_var (*tp)
13404 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
13405 || lookup_attribute ("omp declare target link",
13406 DECL_ATTRIBUTES (*tp))))
13407 return *tp;
13408 if (VAR_P (*tp)
13409 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
13410 && !is_global_var (*tp)
13411 && decl_function_context (*tp) == current_function_decl)
13412 return *tp;
13413 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
13414 (splay_tree_key) *tp);
13415 if (n == NULL)
13417 if (gimplify_omp_ctxp->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
13418 return NULL_TREE;
13419 return *tp;
13421 else if (n->value & GOVD_LOCAL)
13422 return *tp;
13423 else if (n->value & GOVD_FIRSTPRIVATE)
13424 return NULL_TREE;
13425 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
13426 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
13427 return NULL_TREE;
13428 return *tp;
13429 case INTEGER_CST:
13430 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
13431 return *tp;
13432 return NULL_TREE;
13433 case TARGET_EXPR:
13434 if (TARGET_EXPR_INITIAL (*tp)
13435 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
13436 return *tp;
13437 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
13438 walk_subtrees, NULL);
13439 /* Allow some reasonable subset of integral arithmetics. */
13440 case PLUS_EXPR:
13441 case MINUS_EXPR:
13442 case MULT_EXPR:
13443 case TRUNC_DIV_EXPR:
13444 case CEIL_DIV_EXPR:
13445 case FLOOR_DIV_EXPR:
13446 case ROUND_DIV_EXPR:
13447 case TRUNC_MOD_EXPR:
13448 case CEIL_MOD_EXPR:
13449 case FLOOR_MOD_EXPR:
13450 case ROUND_MOD_EXPR:
13451 case RDIV_EXPR:
13452 case EXACT_DIV_EXPR:
13453 case MIN_EXPR:
13454 case MAX_EXPR:
13455 case LSHIFT_EXPR:
13456 case RSHIFT_EXPR:
13457 case BIT_IOR_EXPR:
13458 case BIT_XOR_EXPR:
13459 case BIT_AND_EXPR:
13460 case NEGATE_EXPR:
13461 case ABS_EXPR:
13462 case BIT_NOT_EXPR:
13463 case NON_LVALUE_EXPR:
13464 CASE_CONVERT:
13465 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
13466 return *tp;
13467 return NULL_TREE;
13468 /* And disallow anything else, except for comparisons. */
13469 default:
13470 if (COMPARISON_CLASS_P (*tp))
13471 return NULL_TREE;
13472 return *tp;
13476 /* Try to determine if the num_teams and/or thread_limit expressions
13477 can have their values determined already before entering the
13478 target construct.
13479 INTEGER_CSTs trivially are,
13480 integral decls that are firstprivate (explicitly or implicitly)
13481 or explicitly map(always, to:) or map(always, tofrom:) on the target
13482 region too, and expressions involving simple arithmetics on those
13483 too, function calls are not ok, dereferencing something neither etc.
13484 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
13485 EXPR based on what we find:
13486 0 stands for clause not specified at all, use implementation default
13487 -1 stands for value that can't be determined easily before entering
13488 the target construct.
13489 If teams construct is not present at all, use 1 for num_teams
13490 and 0 for thread_limit (only one team is involved, and the thread
13491 limit is implementation defined. */
13493 static void
13494 optimize_target_teams (tree target, gimple_seq *pre_p)
13496 tree body = OMP_BODY (target);
13497 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
13498 tree num_teams = integer_zero_node;
13499 tree thread_limit = integer_zero_node;
13500 location_t num_teams_loc = EXPR_LOCATION (target);
13501 location_t thread_limit_loc = EXPR_LOCATION (target);
13502 tree c, *p, expr;
13503 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
13505 if (teams == NULL_TREE)
13506 num_teams = integer_one_node;
13507 else
13508 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
13510 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
13512 p = &num_teams;
13513 num_teams_loc = OMP_CLAUSE_LOCATION (c);
13515 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
13517 p = &thread_limit;
13518 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
13520 else
13521 continue;
13522 expr = OMP_CLAUSE_OPERAND (c, 0);
13523 if (TREE_CODE (expr) == INTEGER_CST)
13525 *p = expr;
13526 continue;
13528 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
13530 *p = integer_minus_one_node;
13531 continue;
13533 *p = expr;
13534 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
13535 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
13536 == GS_ERROR)
13538 gimplify_omp_ctxp = target_ctx;
13539 *p = integer_minus_one_node;
13540 continue;
13542 gimplify_omp_ctxp = target_ctx;
13543 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
13544 OMP_CLAUSE_OPERAND (c, 0) = *p;
13546 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
13547 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
13548 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
13549 OMP_TARGET_CLAUSES (target) = c;
13550 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
13551 OMP_CLAUSE_NUM_TEAMS_EXPR (c) = num_teams;
13552 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
13553 OMP_TARGET_CLAUSES (target) = c;
13556 /* Gimplify the gross structure of several OMP constructs. */
13558 static void
13559 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
13561 tree expr = *expr_p;
13562 gimple *stmt;
13563 gimple_seq body = NULL;
13564 enum omp_region_type ort;
13566 switch (TREE_CODE (expr))
13568 case OMP_SECTIONS:
13569 case OMP_SINGLE:
13570 ort = ORT_WORKSHARE;
13571 break;
13572 case OMP_SCOPE:
13573 ort = ORT_TASKGROUP;
13574 break;
13575 case OMP_TARGET:
13576 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
13577 break;
13578 case OACC_KERNELS:
13579 ort = ORT_ACC_KERNELS;
13580 break;
13581 case OACC_PARALLEL:
13582 ort = ORT_ACC_PARALLEL;
13583 break;
13584 case OACC_SERIAL:
13585 ort = ORT_ACC_SERIAL;
13586 break;
13587 case OACC_DATA:
13588 ort = ORT_ACC_DATA;
13589 break;
13590 case OMP_TARGET_DATA:
13591 ort = ORT_TARGET_DATA;
13592 break;
13593 case OMP_TEAMS:
13594 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
13595 if (gimplify_omp_ctxp == NULL
13596 || gimplify_omp_ctxp->region_type == ORT_IMPLICIT_TARGET)
13597 ort = (enum omp_region_type) (ort | ORT_HOST_TEAMS);
13598 break;
13599 case OACC_HOST_DATA:
13600 ort = ORT_ACC_HOST_DATA;
13601 break;
13602 default:
13603 gcc_unreachable ();
13606 bool save_in_omp_construct = in_omp_construct;
13607 if ((ort & ORT_ACC) == 0)
13608 in_omp_construct = false;
13609 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
13610 TREE_CODE (expr));
13611 if (TREE_CODE (expr) == OMP_TARGET)
13612 optimize_target_teams (expr, pre_p);
13613 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0
13614 || (ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
13616 push_gimplify_context ();
13617 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
13618 if (gimple_code (g) == GIMPLE_BIND)
13619 pop_gimplify_context (g);
13620 else
13621 pop_gimplify_context (NULL);
13622 if ((ort & ORT_TARGET_DATA) != 0)
13624 enum built_in_function end_ix;
13625 switch (TREE_CODE (expr))
13627 case OACC_DATA:
13628 case OACC_HOST_DATA:
13629 end_ix = BUILT_IN_GOACC_DATA_END;
13630 break;
13631 case OMP_TARGET_DATA:
13632 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
13633 break;
13634 default:
13635 gcc_unreachable ();
13637 tree fn = builtin_decl_explicit (end_ix);
13638 g = gimple_build_call (fn, 0);
13639 gimple_seq cleanup = NULL;
13640 gimple_seq_add_stmt (&cleanup, g);
13641 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
13642 body = NULL;
13643 gimple_seq_add_stmt (&body, g);
13646 else
13647 gimplify_and_add (OMP_BODY (expr), &body);
13648 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
13649 TREE_CODE (expr));
13650 in_omp_construct = save_in_omp_construct;
13652 switch (TREE_CODE (expr))
13654 case OACC_DATA:
13655 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
13656 OMP_CLAUSES (expr));
13657 break;
13658 case OACC_HOST_DATA:
13659 if (omp_find_clause (OMP_CLAUSES (expr), OMP_CLAUSE_IF_PRESENT))
13661 for (tree c = OMP_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13662 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_USE_DEVICE_PTR)
13663 OMP_CLAUSE_USE_DEVICE_PTR_IF_PRESENT (c) = 1;
13666 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
13667 OMP_CLAUSES (expr));
13668 break;
13669 case OACC_KERNELS:
13670 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
13671 OMP_CLAUSES (expr));
13672 break;
13673 case OACC_PARALLEL:
13674 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
13675 OMP_CLAUSES (expr));
13676 break;
13677 case OACC_SERIAL:
13678 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_SERIAL,
13679 OMP_CLAUSES (expr));
13680 break;
13681 case OMP_SECTIONS:
13682 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
13683 break;
13684 case OMP_SINGLE:
13685 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
13686 break;
13687 case OMP_SCOPE:
13688 stmt = gimple_build_omp_scope (body, OMP_CLAUSES (expr));
13689 break;
13690 case OMP_TARGET:
13691 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
13692 OMP_CLAUSES (expr));
13693 break;
13694 case OMP_TARGET_DATA:
13695 /* Put use_device_{ptr,addr} clauses last, as map clauses are supposed
13696 to be evaluated before the use_device_{ptr,addr} clauses if they
13697 refer to the same variables. */
13699 tree use_device_clauses;
13700 tree *pc, *uc = &use_device_clauses;
13701 for (pc = &OMP_CLAUSES (expr); *pc; )
13702 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_PTR
13703 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_ADDR)
13705 *uc = *pc;
13706 *pc = OMP_CLAUSE_CHAIN (*pc);
13707 uc = &OMP_CLAUSE_CHAIN (*uc);
13709 else
13710 pc = &OMP_CLAUSE_CHAIN (*pc);
13711 *uc = NULL_TREE;
13712 *pc = use_device_clauses;
13713 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
13714 OMP_CLAUSES (expr));
13716 break;
13717 case OMP_TEAMS:
13718 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
13719 if ((ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
13720 gimple_omp_teams_set_host (as_a <gomp_teams *> (stmt), true);
13721 break;
13722 default:
13723 gcc_unreachable ();
13726 gimplify_seq_add_stmt (pre_p, stmt);
13727 *expr_p = NULL_TREE;
13730 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
13731 target update constructs. */
13733 static void
13734 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
13736 tree expr = *expr_p;
13737 int kind;
13738 gomp_target *stmt;
13739 enum omp_region_type ort = ORT_WORKSHARE;
13741 switch (TREE_CODE (expr))
13743 case OACC_ENTER_DATA:
13744 kind = GF_OMP_TARGET_KIND_OACC_ENTER_DATA;
13745 ort = ORT_ACC;
13746 break;
13747 case OACC_EXIT_DATA:
13748 kind = GF_OMP_TARGET_KIND_OACC_EXIT_DATA;
13749 ort = ORT_ACC;
13750 break;
13751 case OACC_UPDATE:
13752 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
13753 ort = ORT_ACC;
13754 break;
13755 case OMP_TARGET_UPDATE:
13756 kind = GF_OMP_TARGET_KIND_UPDATE;
13757 break;
13758 case OMP_TARGET_ENTER_DATA:
13759 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
13760 break;
13761 case OMP_TARGET_EXIT_DATA:
13762 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
13763 break;
13764 default:
13765 gcc_unreachable ();
13767 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
13768 ort, TREE_CODE (expr));
13769 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
13770 TREE_CODE (expr));
13771 if (TREE_CODE (expr) == OACC_UPDATE
13772 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
13773 OMP_CLAUSE_IF_PRESENT))
13775 /* The runtime uses GOMP_MAP_{TO,FROM} to denote the if_present
13776 clause. */
13777 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13778 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
13779 switch (OMP_CLAUSE_MAP_KIND (c))
13781 case GOMP_MAP_FORCE_TO:
13782 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TO);
13783 break;
13784 case GOMP_MAP_FORCE_FROM:
13785 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FROM);
13786 break;
13787 default:
13788 break;
13791 else if (TREE_CODE (expr) == OACC_EXIT_DATA
13792 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
13793 OMP_CLAUSE_FINALIZE))
13795 /* Use GOMP_MAP_DELETE/GOMP_MAP_FORCE_FROM to denote "finalize"
13796 semantics. */
13797 bool have_clause = false;
13798 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13799 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
13800 switch (OMP_CLAUSE_MAP_KIND (c))
13802 case GOMP_MAP_FROM:
13803 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_FROM);
13804 have_clause = true;
13805 break;
13806 case GOMP_MAP_RELEASE:
13807 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
13808 have_clause = true;
13809 break;
13810 case GOMP_MAP_TO_PSET:
13811 /* Fortran arrays with descriptors must map that descriptor when
13812 doing standalone "attach" operations (in OpenACC). In that
13813 case GOMP_MAP_TO_PSET appears by itself with no preceding
13814 clause (see trans-openmp.c:gfc_trans_omp_clauses). */
13815 break;
13816 case GOMP_MAP_POINTER:
13817 /* TODO PR92929: we may see these here, but they'll always follow
13818 one of the clauses above, and will be handled by libgomp as
13819 one group, so no handling required here. */
13820 gcc_assert (have_clause);
13821 break;
13822 case GOMP_MAP_DETACH:
13823 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_DETACH);
13824 have_clause = false;
13825 break;
13826 case GOMP_MAP_STRUCT:
13827 have_clause = false;
13828 break;
13829 default:
13830 gcc_unreachable ();
13833 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
13835 gimplify_seq_add_stmt (pre_p, stmt);
13836 *expr_p = NULL_TREE;
13839 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
13840 stabilized the lhs of the atomic operation as *ADDR. Return true if
13841 EXPR is this stabilized form. */
13843 static bool
13844 goa_lhs_expr_p (tree expr, tree addr)
13846 /* Also include casts to other type variants. The C front end is fond
13847 of adding these for e.g. volatile variables. This is like
13848 STRIP_TYPE_NOPS but includes the main variant lookup. */
13849 STRIP_USELESS_TYPE_CONVERSION (expr);
13851 if (TREE_CODE (expr) == INDIRECT_REF)
13853 expr = TREE_OPERAND (expr, 0);
13854 while (expr != addr
13855 && (CONVERT_EXPR_P (expr)
13856 || TREE_CODE (expr) == NON_LVALUE_EXPR)
13857 && TREE_CODE (expr) == TREE_CODE (addr)
13858 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
13860 expr = TREE_OPERAND (expr, 0);
13861 addr = TREE_OPERAND (addr, 0);
13863 if (expr == addr)
13864 return true;
13865 return (TREE_CODE (addr) == ADDR_EXPR
13866 && TREE_CODE (expr) == ADDR_EXPR
13867 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
13869 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
13870 return true;
13871 return false;
13874 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
13875 expression does not involve the lhs, evaluate it into a temporary.
13876 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
13877 or -1 if an error was encountered. */
13879 static int
13880 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
13881 tree lhs_var, tree &target_expr, bool rhs, int depth)
13883 tree expr = *expr_p;
13884 int saw_lhs = 0;
13886 if (goa_lhs_expr_p (expr, lhs_addr))
13888 if (pre_p)
13889 *expr_p = lhs_var;
13890 return 1;
13892 if (is_gimple_val (expr))
13893 return 0;
13895 /* Maximum depth of lhs in expression is for the
13896 __builtin_clear_padding (...), __builtin_clear_padding (...),
13897 __builtin_memcmp (&TARGET_EXPR <lhs, >, ...) == 0 ? ... : lhs; */
13898 if (++depth > 7)
13899 goto finish;
13901 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
13903 case tcc_binary:
13904 case tcc_comparison:
13905 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
13906 lhs_var, target_expr, true, depth);
13907 /* FALLTHRU */
13908 case tcc_unary:
13909 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
13910 lhs_var, target_expr, true, depth);
13911 break;
13912 case tcc_expression:
13913 switch (TREE_CODE (expr))
13915 case TRUTH_ANDIF_EXPR:
13916 case TRUTH_ORIF_EXPR:
13917 case TRUTH_AND_EXPR:
13918 case TRUTH_OR_EXPR:
13919 case TRUTH_XOR_EXPR:
13920 case BIT_INSERT_EXPR:
13921 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
13922 lhs_addr, lhs_var, target_expr, true,
13923 depth);
13924 /* FALLTHRU */
13925 case TRUTH_NOT_EXPR:
13926 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13927 lhs_addr, lhs_var, target_expr, true,
13928 depth);
13929 break;
13930 case MODIFY_EXPR:
13931 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
13932 target_expr, true, depth))
13933 break;
13934 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
13935 lhs_addr, lhs_var, target_expr, true,
13936 depth);
13937 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13938 lhs_addr, lhs_var, target_expr, false,
13939 depth);
13940 break;
13941 /* FALLTHRU */
13942 case ADDR_EXPR:
13943 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
13944 target_expr, true, depth))
13945 break;
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 case COMPOUND_EXPR:
13951 /* Break out any preevaluations from cp_build_modify_expr. */
13952 for (; TREE_CODE (expr) == COMPOUND_EXPR;
13953 expr = TREE_OPERAND (expr, 1))
13955 /* Special-case __builtin_clear_padding call before
13956 __builtin_memcmp. */
13957 if (TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR)
13959 tree fndecl = get_callee_fndecl (TREE_OPERAND (expr, 0));
13960 if (fndecl
13961 && fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING)
13962 && VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (expr, 0)))
13963 && (!pre_p
13964 || goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL,
13965 lhs_addr, lhs_var,
13966 target_expr, true, depth)))
13968 if (pre_p)
13969 *expr_p = expr;
13970 saw_lhs = goa_stabilize_expr (&TREE_OPERAND (expr, 0),
13971 pre_p, lhs_addr, lhs_var,
13972 target_expr, true, depth);
13973 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1),
13974 pre_p, lhs_addr, lhs_var,
13975 target_expr, rhs, depth);
13976 return saw_lhs;
13980 if (pre_p)
13981 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
13983 if (!pre_p)
13984 return goa_stabilize_expr (&expr, pre_p, lhs_addr, lhs_var,
13985 target_expr, rhs, depth);
13986 *expr_p = expr;
13987 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var,
13988 target_expr, rhs, depth);
13989 case COND_EXPR:
13990 if (!goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL, lhs_addr,
13991 lhs_var, target_expr, true, depth))
13992 break;
13993 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13994 lhs_addr, lhs_var, target_expr, true,
13995 depth);
13996 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
13997 lhs_addr, lhs_var, target_expr, true,
13998 depth);
13999 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 2), pre_p,
14000 lhs_addr, lhs_var, target_expr, true,
14001 depth);
14002 break;
14003 case TARGET_EXPR:
14004 if (TARGET_EXPR_INITIAL (expr))
14006 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr,
14007 lhs_var, target_expr, true,
14008 depth))
14009 break;
14010 if (expr == target_expr)
14011 saw_lhs = 1;
14012 else
14014 saw_lhs = goa_stabilize_expr (&TARGET_EXPR_INITIAL (expr),
14015 pre_p, lhs_addr, lhs_var,
14016 target_expr, true, depth);
14017 if (saw_lhs && target_expr == NULL_TREE && pre_p)
14018 target_expr = expr;
14021 break;
14022 default:
14023 break;
14025 break;
14026 case tcc_reference:
14027 if (TREE_CODE (expr) == BIT_FIELD_REF
14028 || TREE_CODE (expr) == VIEW_CONVERT_EXPR)
14029 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
14030 lhs_addr, lhs_var, target_expr, true,
14031 depth);
14032 break;
14033 case tcc_vl_exp:
14034 if (TREE_CODE (expr) == CALL_EXPR)
14036 if (tree fndecl = get_callee_fndecl (expr))
14037 if (fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING)
14038 || fndecl_built_in_p (fndecl, BUILT_IN_MEMCMP))
14040 int nargs = call_expr_nargs (expr);
14041 for (int i = 0; i < nargs; i++)
14042 saw_lhs |= goa_stabilize_expr (&CALL_EXPR_ARG (expr, i),
14043 pre_p, lhs_addr, lhs_var,
14044 target_expr, true, depth);
14047 break;
14048 default:
14049 break;
14052 finish:
14053 if (saw_lhs == 0 && pre_p)
14055 enum gimplify_status gs;
14056 if (TREE_CODE (expr) == CALL_EXPR && VOID_TYPE_P (TREE_TYPE (expr)))
14058 gimplify_stmt (&expr, pre_p);
14059 return saw_lhs;
14061 else if (rhs)
14062 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
14063 else
14064 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_lvalue, fb_lvalue);
14065 if (gs != GS_ALL_DONE)
14066 saw_lhs = -1;
14069 return saw_lhs;
14072 /* Gimplify an OMP_ATOMIC statement. */
14074 static enum gimplify_status
14075 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
14077 tree addr = TREE_OPERAND (*expr_p, 0);
14078 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
14079 ? NULL : TREE_OPERAND (*expr_p, 1);
14080 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
14081 tree tmp_load;
14082 gomp_atomic_load *loadstmt;
14083 gomp_atomic_store *storestmt;
14084 tree target_expr = NULL_TREE;
14086 tmp_load = create_tmp_reg (type);
14087 if (rhs
14088 && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load, target_expr,
14089 true, 0) < 0)
14090 return GS_ERROR;
14092 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
14093 != GS_ALL_DONE)
14094 return GS_ERROR;
14096 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr,
14097 OMP_ATOMIC_MEMORY_ORDER (*expr_p));
14098 gimplify_seq_add_stmt (pre_p, loadstmt);
14099 if (rhs)
14101 /* BIT_INSERT_EXPR is not valid for non-integral bitfield
14102 representatives. Use BIT_FIELD_REF on the lhs instead. */
14103 tree rhsarg = rhs;
14104 if (TREE_CODE (rhs) == COND_EXPR)
14105 rhsarg = TREE_OPERAND (rhs, 1);
14106 if (TREE_CODE (rhsarg) == BIT_INSERT_EXPR
14107 && !INTEGRAL_TYPE_P (TREE_TYPE (tmp_load)))
14109 tree bitpos = TREE_OPERAND (rhsarg, 2);
14110 tree op1 = TREE_OPERAND (rhsarg, 1);
14111 tree bitsize;
14112 tree tmp_store = tmp_load;
14113 if (TREE_CODE (*expr_p) == OMP_ATOMIC_CAPTURE_OLD)
14114 tmp_store = get_initialized_tmp_var (tmp_load, pre_p);
14115 if (INTEGRAL_TYPE_P (TREE_TYPE (op1)))
14116 bitsize = bitsize_int (TYPE_PRECISION (TREE_TYPE (op1)));
14117 else
14118 bitsize = TYPE_SIZE (TREE_TYPE (op1));
14119 gcc_assert (TREE_OPERAND (rhsarg, 0) == tmp_load);
14120 tree t = build2_loc (EXPR_LOCATION (rhsarg),
14121 MODIFY_EXPR, void_type_node,
14122 build3_loc (EXPR_LOCATION (rhsarg),
14123 BIT_FIELD_REF, TREE_TYPE (op1),
14124 tmp_store, bitsize, bitpos), op1);
14125 if (TREE_CODE (rhs) == COND_EXPR)
14126 t = build3_loc (EXPR_LOCATION (rhs), COND_EXPR, void_type_node,
14127 TREE_OPERAND (rhs, 0), t, void_node);
14128 gimplify_and_add (t, pre_p);
14129 rhs = tmp_store;
14131 bool save_allow_rhs_cond_expr = gimplify_ctxp->allow_rhs_cond_expr;
14132 if (TREE_CODE (rhs) == COND_EXPR)
14133 gimplify_ctxp->allow_rhs_cond_expr = true;
14134 enum gimplify_status gs = gimplify_expr (&rhs, pre_p, NULL,
14135 is_gimple_val, fb_rvalue);
14136 gimplify_ctxp->allow_rhs_cond_expr = save_allow_rhs_cond_expr;
14137 if (gs != GS_ALL_DONE)
14138 return GS_ERROR;
14141 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
14142 rhs = tmp_load;
14143 storestmt
14144 = gimple_build_omp_atomic_store (rhs, OMP_ATOMIC_MEMORY_ORDER (*expr_p));
14145 if (TREE_CODE (*expr_p) != OMP_ATOMIC_READ && OMP_ATOMIC_WEAK (*expr_p))
14147 gimple_omp_atomic_set_weak (loadstmt);
14148 gimple_omp_atomic_set_weak (storestmt);
14150 gimplify_seq_add_stmt (pre_p, storestmt);
14151 switch (TREE_CODE (*expr_p))
14153 case OMP_ATOMIC_READ:
14154 case OMP_ATOMIC_CAPTURE_OLD:
14155 *expr_p = tmp_load;
14156 gimple_omp_atomic_set_need_value (loadstmt);
14157 break;
14158 case OMP_ATOMIC_CAPTURE_NEW:
14159 *expr_p = rhs;
14160 gimple_omp_atomic_set_need_value (storestmt);
14161 break;
14162 default:
14163 *expr_p = NULL;
14164 break;
14167 return GS_ALL_DONE;
14170 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
14171 body, and adding some EH bits. */
14173 static enum gimplify_status
14174 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
14176 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
14177 gimple *body_stmt;
14178 gtransaction *trans_stmt;
14179 gimple_seq body = NULL;
14180 int subcode = 0;
14182 /* Wrap the transaction body in a BIND_EXPR so we have a context
14183 where to put decls for OMP. */
14184 if (TREE_CODE (tbody) != BIND_EXPR)
14186 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
14187 TREE_SIDE_EFFECTS (bind) = 1;
14188 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
14189 TRANSACTION_EXPR_BODY (expr) = bind;
14192 push_gimplify_context ();
14193 temp = voidify_wrapper_expr (*expr_p, NULL);
14195 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
14196 pop_gimplify_context (body_stmt);
14198 trans_stmt = gimple_build_transaction (body);
14199 if (TRANSACTION_EXPR_OUTER (expr))
14200 subcode = GTMA_IS_OUTER;
14201 else if (TRANSACTION_EXPR_RELAXED (expr))
14202 subcode = GTMA_IS_RELAXED;
14203 gimple_transaction_set_subcode (trans_stmt, subcode);
14205 gimplify_seq_add_stmt (pre_p, trans_stmt);
14207 if (temp)
14209 *expr_p = temp;
14210 return GS_OK;
14213 *expr_p = NULL_TREE;
14214 return GS_ALL_DONE;
14217 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
14218 is the OMP_BODY of the original EXPR (which has already been
14219 gimplified so it's not present in the EXPR).
14221 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
14223 static gimple *
14224 gimplify_omp_ordered (tree expr, gimple_seq body)
14226 tree c, decls;
14227 int failures = 0;
14228 unsigned int i;
14229 tree source_c = NULL_TREE;
14230 tree sink_c = NULL_TREE;
14232 if (gimplify_omp_ctxp)
14234 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
14235 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
14236 && gimplify_omp_ctxp->loop_iter_var.is_empty ()
14237 && (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK
14238 || OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE))
14240 error_at (OMP_CLAUSE_LOCATION (c),
14241 "%<ordered%> construct with %<depend%> clause must be "
14242 "closely nested inside a loop with %<ordered%> clause "
14243 "with a parameter");
14244 failures++;
14246 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
14247 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
14249 bool fail = false;
14250 for (decls = OMP_CLAUSE_DECL (c), i = 0;
14251 decls && TREE_CODE (decls) == TREE_LIST;
14252 decls = TREE_CHAIN (decls), ++i)
14253 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
14254 continue;
14255 else if (TREE_VALUE (decls)
14256 != gimplify_omp_ctxp->loop_iter_var[2 * i])
14258 error_at (OMP_CLAUSE_LOCATION (c),
14259 "variable %qE is not an iteration "
14260 "of outermost loop %d, expected %qE",
14261 TREE_VALUE (decls), i + 1,
14262 gimplify_omp_ctxp->loop_iter_var[2 * i]);
14263 fail = true;
14264 failures++;
14266 else
14267 TREE_VALUE (decls)
14268 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
14269 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
14271 error_at (OMP_CLAUSE_LOCATION (c),
14272 "number of variables in %<depend%> clause with "
14273 "%<sink%> modifier does not match number of "
14274 "iteration variables");
14275 failures++;
14277 sink_c = c;
14279 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
14280 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
14282 if (source_c)
14284 error_at (OMP_CLAUSE_LOCATION (c),
14285 "more than one %<depend%> clause with %<source%> "
14286 "modifier on an %<ordered%> construct");
14287 failures++;
14289 else
14290 source_c = c;
14293 if (source_c && sink_c)
14295 error_at (OMP_CLAUSE_LOCATION (source_c),
14296 "%<depend%> clause with %<source%> modifier specified "
14297 "together with %<depend%> clauses with %<sink%> modifier "
14298 "on the same construct");
14299 failures++;
14302 if (failures)
14303 return gimple_build_nop ();
14304 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
14307 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
14308 expression produces a value to be used as an operand inside a GIMPLE
14309 statement, the value will be stored back in *EXPR_P. This value will
14310 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
14311 an SSA_NAME. The corresponding sequence of GIMPLE statements is
14312 emitted in PRE_P and POST_P.
14314 Additionally, this process may overwrite parts of the input
14315 expression during gimplification. Ideally, it should be
14316 possible to do non-destructive gimplification.
14318 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
14319 the expression needs to evaluate to a value to be used as
14320 an operand in a GIMPLE statement, this value will be stored in
14321 *EXPR_P on exit. This happens when the caller specifies one
14322 of fb_lvalue or fb_rvalue fallback flags.
14324 PRE_P will contain the sequence of GIMPLE statements corresponding
14325 to the evaluation of EXPR and all the side-effects that must
14326 be executed before the main expression. On exit, the last
14327 statement of PRE_P is the core statement being gimplified. For
14328 instance, when gimplifying 'if (++a)' the last statement in
14329 PRE_P will be 'if (t.1)' where t.1 is the result of
14330 pre-incrementing 'a'.
14332 POST_P will contain the sequence of GIMPLE statements corresponding
14333 to the evaluation of all the side-effects that must be executed
14334 after the main expression. If this is NULL, the post
14335 side-effects are stored at the end of PRE_P.
14337 The reason why the output is split in two is to handle post
14338 side-effects explicitly. In some cases, an expression may have
14339 inner and outer post side-effects which need to be emitted in
14340 an order different from the one given by the recursive
14341 traversal. For instance, for the expression (*p--)++ the post
14342 side-effects of '--' must actually occur *after* the post
14343 side-effects of '++'. However, gimplification will first visit
14344 the inner expression, so if a separate POST sequence was not
14345 used, the resulting sequence would be:
14347 1 t.1 = *p
14348 2 p = p - 1
14349 3 t.2 = t.1 + 1
14350 4 *p = t.2
14352 However, the post-decrement operation in line #2 must not be
14353 evaluated until after the store to *p at line #4, so the
14354 correct sequence should be:
14356 1 t.1 = *p
14357 2 t.2 = t.1 + 1
14358 3 *p = t.2
14359 4 p = p - 1
14361 So, by specifying a separate post queue, it is possible
14362 to emit the post side-effects in the correct order.
14363 If POST_P is NULL, an internal queue will be used. Before
14364 returning to the caller, the sequence POST_P is appended to
14365 the main output sequence PRE_P.
14367 GIMPLE_TEST_F points to a function that takes a tree T and
14368 returns nonzero if T is in the GIMPLE form requested by the
14369 caller. The GIMPLE predicates are in gimple.c.
14371 FALLBACK tells the function what sort of a temporary we want if
14372 gimplification cannot produce an expression that complies with
14373 GIMPLE_TEST_F.
14375 fb_none means that no temporary should be generated
14376 fb_rvalue means that an rvalue is OK to generate
14377 fb_lvalue means that an lvalue is OK to generate
14378 fb_either means that either is OK, but an lvalue is preferable.
14379 fb_mayfail means that gimplification may fail (in which case
14380 GS_ERROR will be returned)
14382 The return value is either GS_ERROR or GS_ALL_DONE, since this
14383 function iterates until EXPR is completely gimplified or an error
14384 occurs. */
14386 enum gimplify_status
14387 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
14388 bool (*gimple_test_f) (tree), fallback_t fallback)
14390 tree tmp;
14391 gimple_seq internal_pre = NULL;
14392 gimple_seq internal_post = NULL;
14393 tree save_expr;
14394 bool is_statement;
14395 location_t saved_location;
14396 enum gimplify_status ret;
14397 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
14398 tree label;
14400 save_expr = *expr_p;
14401 if (save_expr == NULL_TREE)
14402 return GS_ALL_DONE;
14404 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
14405 is_statement = gimple_test_f == is_gimple_stmt;
14406 if (is_statement)
14407 gcc_assert (pre_p);
14409 /* Consistency checks. */
14410 if (gimple_test_f == is_gimple_reg)
14411 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
14412 else if (gimple_test_f == is_gimple_val
14413 || gimple_test_f == is_gimple_call_addr
14414 || gimple_test_f == is_gimple_condexpr
14415 || gimple_test_f == is_gimple_condexpr_for_cond
14416 || gimple_test_f == is_gimple_mem_rhs
14417 || gimple_test_f == is_gimple_mem_rhs_or_call
14418 || gimple_test_f == is_gimple_reg_rhs
14419 || gimple_test_f == is_gimple_reg_rhs_or_call
14420 || gimple_test_f == is_gimple_asm_val
14421 || gimple_test_f == is_gimple_mem_ref_addr)
14422 gcc_assert (fallback & fb_rvalue);
14423 else if (gimple_test_f == is_gimple_min_lval
14424 || gimple_test_f == is_gimple_lvalue)
14425 gcc_assert (fallback & fb_lvalue);
14426 else if (gimple_test_f == is_gimple_addressable)
14427 gcc_assert (fallback & fb_either);
14428 else if (gimple_test_f == is_gimple_stmt)
14429 gcc_assert (fallback == fb_none);
14430 else
14432 /* We should have recognized the GIMPLE_TEST_F predicate to
14433 know what kind of fallback to use in case a temporary is
14434 needed to hold the value or address of *EXPR_P. */
14435 gcc_unreachable ();
14438 /* We used to check the predicate here and return immediately if it
14439 succeeds. This is wrong; the design is for gimplification to be
14440 idempotent, and for the predicates to only test for valid forms, not
14441 whether they are fully simplified. */
14442 if (pre_p == NULL)
14443 pre_p = &internal_pre;
14445 if (post_p == NULL)
14446 post_p = &internal_post;
14448 /* Remember the last statements added to PRE_P and POST_P. Every
14449 new statement added by the gimplification helpers needs to be
14450 annotated with location information. To centralize the
14451 responsibility, we remember the last statement that had been
14452 added to both queues before gimplifying *EXPR_P. If
14453 gimplification produces new statements in PRE_P and POST_P, those
14454 statements will be annotated with the same location information
14455 as *EXPR_P. */
14456 pre_last_gsi = gsi_last (*pre_p);
14457 post_last_gsi = gsi_last (*post_p);
14459 saved_location = input_location;
14460 if (save_expr != error_mark_node
14461 && EXPR_HAS_LOCATION (*expr_p))
14462 input_location = EXPR_LOCATION (*expr_p);
14464 /* Loop over the specific gimplifiers until the toplevel node
14465 remains the same. */
14468 /* Strip away as many useless type conversions as possible
14469 at the toplevel. */
14470 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
14472 /* Remember the expr. */
14473 save_expr = *expr_p;
14475 /* Die, die, die, my darling. */
14476 if (error_operand_p (save_expr))
14478 ret = GS_ERROR;
14479 break;
14482 /* Do any language-specific gimplification. */
14483 ret = ((enum gimplify_status)
14484 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
14485 if (ret == GS_OK)
14487 if (*expr_p == NULL_TREE)
14488 break;
14489 if (*expr_p != save_expr)
14490 continue;
14492 else if (ret != GS_UNHANDLED)
14493 break;
14495 /* Make sure that all the cases set 'ret' appropriately. */
14496 ret = GS_UNHANDLED;
14497 switch (TREE_CODE (*expr_p))
14499 /* First deal with the special cases. */
14501 case POSTINCREMENT_EXPR:
14502 case POSTDECREMENT_EXPR:
14503 case PREINCREMENT_EXPR:
14504 case PREDECREMENT_EXPR:
14505 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
14506 fallback != fb_none,
14507 TREE_TYPE (*expr_p));
14508 break;
14510 case VIEW_CONVERT_EXPR:
14511 if ((fallback & fb_rvalue)
14512 && is_gimple_reg_type (TREE_TYPE (*expr_p))
14513 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
14515 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14516 post_p, is_gimple_val, fb_rvalue);
14517 recalculate_side_effects (*expr_p);
14518 break;
14520 /* Fallthru. */
14522 case ARRAY_REF:
14523 case ARRAY_RANGE_REF:
14524 case REALPART_EXPR:
14525 case IMAGPART_EXPR:
14526 case COMPONENT_REF:
14527 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
14528 fallback ? fallback : fb_rvalue);
14529 break;
14531 case COND_EXPR:
14532 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
14534 /* C99 code may assign to an array in a structure value of a
14535 conditional expression, and this has undefined behavior
14536 only on execution, so create a temporary if an lvalue is
14537 required. */
14538 if (fallback == fb_lvalue)
14540 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14541 mark_addressable (*expr_p);
14542 ret = GS_OK;
14544 break;
14546 case CALL_EXPR:
14547 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
14549 /* C99 code may assign to an array in a structure returned
14550 from a function, and this has undefined behavior only on
14551 execution, so create a temporary if an lvalue is
14552 required. */
14553 if (fallback == fb_lvalue)
14555 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14556 mark_addressable (*expr_p);
14557 ret = GS_OK;
14559 break;
14561 case TREE_LIST:
14562 gcc_unreachable ();
14564 case COMPOUND_EXPR:
14565 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
14566 break;
14568 case COMPOUND_LITERAL_EXPR:
14569 ret = gimplify_compound_literal_expr (expr_p, pre_p,
14570 gimple_test_f, fallback);
14571 break;
14573 case MODIFY_EXPR:
14574 case INIT_EXPR:
14575 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
14576 fallback != fb_none);
14577 break;
14579 case TRUTH_ANDIF_EXPR:
14580 case TRUTH_ORIF_EXPR:
14582 /* Preserve the original type of the expression and the
14583 source location of the outer expression. */
14584 tree org_type = TREE_TYPE (*expr_p);
14585 *expr_p = gimple_boolify (*expr_p);
14586 *expr_p = build3_loc (input_location, COND_EXPR,
14587 org_type, *expr_p,
14588 fold_convert_loc
14589 (input_location,
14590 org_type, boolean_true_node),
14591 fold_convert_loc
14592 (input_location,
14593 org_type, boolean_false_node));
14594 ret = GS_OK;
14595 break;
14598 case TRUTH_NOT_EXPR:
14600 tree type = TREE_TYPE (*expr_p);
14601 /* The parsers are careful to generate TRUTH_NOT_EXPR
14602 only with operands that are always zero or one.
14603 We do not fold here but handle the only interesting case
14604 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
14605 *expr_p = gimple_boolify (*expr_p);
14606 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
14607 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
14608 TREE_TYPE (*expr_p),
14609 TREE_OPERAND (*expr_p, 0));
14610 else
14611 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
14612 TREE_TYPE (*expr_p),
14613 TREE_OPERAND (*expr_p, 0),
14614 build_int_cst (TREE_TYPE (*expr_p), 1));
14615 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
14616 *expr_p = fold_convert_loc (input_location, type, *expr_p);
14617 ret = GS_OK;
14618 break;
14621 case ADDR_EXPR:
14622 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
14623 break;
14625 case ANNOTATE_EXPR:
14627 tree cond = TREE_OPERAND (*expr_p, 0);
14628 tree kind = TREE_OPERAND (*expr_p, 1);
14629 tree data = TREE_OPERAND (*expr_p, 2);
14630 tree type = TREE_TYPE (cond);
14631 if (!INTEGRAL_TYPE_P (type))
14633 *expr_p = cond;
14634 ret = GS_OK;
14635 break;
14637 tree tmp = create_tmp_var (type);
14638 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
14639 gcall *call
14640 = gimple_build_call_internal (IFN_ANNOTATE, 3, cond, kind, data);
14641 gimple_call_set_lhs (call, tmp);
14642 gimplify_seq_add_stmt (pre_p, call);
14643 *expr_p = tmp;
14644 ret = GS_ALL_DONE;
14645 break;
14648 case VA_ARG_EXPR:
14649 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
14650 break;
14652 CASE_CONVERT:
14653 if (IS_EMPTY_STMT (*expr_p))
14655 ret = GS_ALL_DONE;
14656 break;
14659 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
14660 || fallback == fb_none)
14662 /* Just strip a conversion to void (or in void context) and
14663 try again. */
14664 *expr_p = TREE_OPERAND (*expr_p, 0);
14665 ret = GS_OK;
14666 break;
14669 ret = gimplify_conversion (expr_p);
14670 if (ret == GS_ERROR)
14671 break;
14672 if (*expr_p != save_expr)
14673 break;
14674 /* FALLTHRU */
14676 case FIX_TRUNC_EXPR:
14677 /* unary_expr: ... | '(' cast ')' val | ... */
14678 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14679 is_gimple_val, fb_rvalue);
14680 recalculate_side_effects (*expr_p);
14681 break;
14683 case INDIRECT_REF:
14685 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
14686 bool notrap = TREE_THIS_NOTRAP (*expr_p);
14687 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
14689 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
14690 if (*expr_p != save_expr)
14692 ret = GS_OK;
14693 break;
14696 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14697 is_gimple_reg, fb_rvalue);
14698 if (ret == GS_ERROR)
14699 break;
14701 recalculate_side_effects (*expr_p);
14702 *expr_p = fold_build2_loc (input_location, MEM_REF,
14703 TREE_TYPE (*expr_p),
14704 TREE_OPERAND (*expr_p, 0),
14705 build_int_cst (saved_ptr_type, 0));
14706 TREE_THIS_VOLATILE (*expr_p) = volatilep;
14707 TREE_THIS_NOTRAP (*expr_p) = notrap;
14708 ret = GS_OK;
14709 break;
14712 /* We arrive here through the various re-gimplifcation paths. */
14713 case MEM_REF:
14714 /* First try re-folding the whole thing. */
14715 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
14716 TREE_OPERAND (*expr_p, 0),
14717 TREE_OPERAND (*expr_p, 1));
14718 if (tmp)
14720 REF_REVERSE_STORAGE_ORDER (tmp)
14721 = REF_REVERSE_STORAGE_ORDER (*expr_p);
14722 *expr_p = tmp;
14723 recalculate_side_effects (*expr_p);
14724 ret = GS_OK;
14725 break;
14727 /* Avoid re-gimplifying the address operand if it is already
14728 in suitable form. Re-gimplifying would mark the address
14729 operand addressable. Always gimplify when not in SSA form
14730 as we still may have to gimplify decls with value-exprs. */
14731 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
14732 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
14734 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14735 is_gimple_mem_ref_addr, fb_rvalue);
14736 if (ret == GS_ERROR)
14737 break;
14739 recalculate_side_effects (*expr_p);
14740 ret = GS_ALL_DONE;
14741 break;
14743 /* Constants need not be gimplified. */
14744 case INTEGER_CST:
14745 case REAL_CST:
14746 case FIXED_CST:
14747 case STRING_CST:
14748 case COMPLEX_CST:
14749 case VECTOR_CST:
14750 /* Drop the overflow flag on constants, we do not want
14751 that in the GIMPLE IL. */
14752 if (TREE_OVERFLOW_P (*expr_p))
14753 *expr_p = drop_tree_overflow (*expr_p);
14754 ret = GS_ALL_DONE;
14755 break;
14757 case CONST_DECL:
14758 /* If we require an lvalue, such as for ADDR_EXPR, retain the
14759 CONST_DECL node. Otherwise the decl is replaceable by its
14760 value. */
14761 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
14762 if (fallback & fb_lvalue)
14763 ret = GS_ALL_DONE;
14764 else
14766 *expr_p = DECL_INITIAL (*expr_p);
14767 ret = GS_OK;
14769 break;
14771 case DECL_EXPR:
14772 ret = gimplify_decl_expr (expr_p, pre_p);
14773 break;
14775 case BIND_EXPR:
14776 ret = gimplify_bind_expr (expr_p, pre_p);
14777 break;
14779 case LOOP_EXPR:
14780 ret = gimplify_loop_expr (expr_p, pre_p);
14781 break;
14783 case SWITCH_EXPR:
14784 ret = gimplify_switch_expr (expr_p, pre_p);
14785 break;
14787 case EXIT_EXPR:
14788 ret = gimplify_exit_expr (expr_p);
14789 break;
14791 case GOTO_EXPR:
14792 /* If the target is not LABEL, then it is a computed jump
14793 and the target needs to be gimplified. */
14794 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
14796 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
14797 NULL, is_gimple_val, fb_rvalue);
14798 if (ret == GS_ERROR)
14799 break;
14801 gimplify_seq_add_stmt (pre_p,
14802 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
14803 ret = GS_ALL_DONE;
14804 break;
14806 case PREDICT_EXPR:
14807 gimplify_seq_add_stmt (pre_p,
14808 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
14809 PREDICT_EXPR_OUTCOME (*expr_p)));
14810 ret = GS_ALL_DONE;
14811 break;
14813 case LABEL_EXPR:
14814 ret = gimplify_label_expr (expr_p, pre_p);
14815 label = LABEL_EXPR_LABEL (*expr_p);
14816 gcc_assert (decl_function_context (label) == current_function_decl);
14818 /* If the label is used in a goto statement, or address of the label
14819 is taken, we need to unpoison all variables that were seen so far.
14820 Doing so would prevent us from reporting a false positives. */
14821 if (asan_poisoned_variables
14822 && asan_used_labels != NULL
14823 && asan_used_labels->contains (label)
14824 && !gimplify_omp_ctxp)
14825 asan_poison_variables (asan_poisoned_variables, false, pre_p);
14826 break;
14828 case CASE_LABEL_EXPR:
14829 ret = gimplify_case_label_expr (expr_p, pre_p);
14831 if (gimplify_ctxp->live_switch_vars)
14832 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
14833 pre_p);
14834 break;
14836 case RETURN_EXPR:
14837 ret = gimplify_return_expr (*expr_p, pre_p);
14838 break;
14840 case CONSTRUCTOR:
14841 /* Don't reduce this in place; let gimplify_init_constructor work its
14842 magic. Buf if we're just elaborating this for side effects, just
14843 gimplify any element that has side-effects. */
14844 if (fallback == fb_none)
14846 unsigned HOST_WIDE_INT ix;
14847 tree val;
14848 tree temp = NULL_TREE;
14849 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
14850 if (TREE_SIDE_EFFECTS (val))
14851 append_to_statement_list (val, &temp);
14853 *expr_p = temp;
14854 ret = temp ? GS_OK : GS_ALL_DONE;
14856 /* C99 code may assign to an array in a constructed
14857 structure or union, and this has undefined behavior only
14858 on execution, so create a temporary if an lvalue is
14859 required. */
14860 else if (fallback == fb_lvalue)
14862 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14863 mark_addressable (*expr_p);
14864 ret = GS_OK;
14866 else
14867 ret = GS_ALL_DONE;
14868 break;
14870 /* The following are special cases that are not handled by the
14871 original GIMPLE grammar. */
14873 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
14874 eliminated. */
14875 case SAVE_EXPR:
14876 ret = gimplify_save_expr (expr_p, pre_p, post_p);
14877 break;
14879 case BIT_FIELD_REF:
14880 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14881 post_p, is_gimple_lvalue, fb_either);
14882 recalculate_side_effects (*expr_p);
14883 break;
14885 case TARGET_MEM_REF:
14887 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
14889 if (TMR_BASE (*expr_p))
14890 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
14891 post_p, is_gimple_mem_ref_addr, fb_either);
14892 if (TMR_INDEX (*expr_p))
14893 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
14894 post_p, is_gimple_val, fb_rvalue);
14895 if (TMR_INDEX2 (*expr_p))
14896 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
14897 post_p, is_gimple_val, fb_rvalue);
14898 /* TMR_STEP and TMR_OFFSET are always integer constants. */
14899 ret = MIN (r0, r1);
14901 break;
14903 case NON_LVALUE_EXPR:
14904 /* This should have been stripped above. */
14905 gcc_unreachable ();
14907 case ASM_EXPR:
14908 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
14909 break;
14911 case TRY_FINALLY_EXPR:
14912 case TRY_CATCH_EXPR:
14914 gimple_seq eval, cleanup;
14915 gtry *try_;
14917 /* Calls to destructors are generated automatically in FINALLY/CATCH
14918 block. They should have location as UNKNOWN_LOCATION. However,
14919 gimplify_call_expr will reset these call stmts to input_location
14920 if it finds stmt's location is unknown. To prevent resetting for
14921 destructors, we set the input_location to unknown.
14922 Note that this only affects the destructor calls in FINALLY/CATCH
14923 block, and will automatically reset to its original value by the
14924 end of gimplify_expr. */
14925 input_location = UNKNOWN_LOCATION;
14926 eval = cleanup = NULL;
14927 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
14928 if (TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
14929 && TREE_CODE (TREE_OPERAND (*expr_p, 1)) == EH_ELSE_EXPR)
14931 gimple_seq n = NULL, e = NULL;
14932 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
14933 0), &n);
14934 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
14935 1), &e);
14936 if (!gimple_seq_empty_p (n) && !gimple_seq_empty_p (e))
14938 geh_else *stmt = gimple_build_eh_else (n, e);
14939 gimple_seq_add_stmt (&cleanup, stmt);
14942 else
14943 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
14944 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
14945 if (gimple_seq_empty_p (cleanup))
14947 gimple_seq_add_seq (pre_p, eval);
14948 ret = GS_ALL_DONE;
14949 break;
14951 try_ = gimple_build_try (eval, cleanup,
14952 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
14953 ? GIMPLE_TRY_FINALLY
14954 : GIMPLE_TRY_CATCH);
14955 if (EXPR_HAS_LOCATION (save_expr))
14956 gimple_set_location (try_, EXPR_LOCATION (save_expr));
14957 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
14958 gimple_set_location (try_, saved_location);
14959 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
14960 gimple_try_set_catch_is_cleanup (try_,
14961 TRY_CATCH_IS_CLEANUP (*expr_p));
14962 gimplify_seq_add_stmt (pre_p, try_);
14963 ret = GS_ALL_DONE;
14964 break;
14967 case CLEANUP_POINT_EXPR:
14968 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
14969 break;
14971 case TARGET_EXPR:
14972 ret = gimplify_target_expr (expr_p, pre_p, post_p);
14973 break;
14975 case CATCH_EXPR:
14977 gimple *c;
14978 gimple_seq handler = NULL;
14979 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
14980 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
14981 gimplify_seq_add_stmt (pre_p, c);
14982 ret = GS_ALL_DONE;
14983 break;
14986 case EH_FILTER_EXPR:
14988 gimple *ehf;
14989 gimple_seq failure = NULL;
14991 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
14992 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
14993 copy_warning (ehf, *expr_p);
14994 gimplify_seq_add_stmt (pre_p, ehf);
14995 ret = GS_ALL_DONE;
14996 break;
14999 case OBJ_TYPE_REF:
15001 enum gimplify_status r0, r1;
15002 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
15003 post_p, is_gimple_val, fb_rvalue);
15004 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
15005 post_p, is_gimple_val, fb_rvalue);
15006 TREE_SIDE_EFFECTS (*expr_p) = 0;
15007 ret = MIN (r0, r1);
15009 break;
15011 case LABEL_DECL:
15012 /* We get here when taking the address of a label. We mark
15013 the label as "forced"; meaning it can never be removed and
15014 it is a potential target for any computed goto. */
15015 FORCED_LABEL (*expr_p) = 1;
15016 ret = GS_ALL_DONE;
15017 break;
15019 case STATEMENT_LIST:
15020 ret = gimplify_statement_list (expr_p, pre_p);
15021 break;
15023 case WITH_SIZE_EXPR:
15025 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15026 post_p == &internal_post ? NULL : post_p,
15027 gimple_test_f, fallback);
15028 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
15029 is_gimple_val, fb_rvalue);
15030 ret = GS_ALL_DONE;
15032 break;
15034 case VAR_DECL:
15035 case PARM_DECL:
15036 ret = gimplify_var_or_parm_decl (expr_p);
15037 break;
15039 case RESULT_DECL:
15040 /* When within an OMP context, notice uses of variables. */
15041 if (gimplify_omp_ctxp)
15042 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
15043 ret = GS_ALL_DONE;
15044 break;
15046 case DEBUG_EXPR_DECL:
15047 gcc_unreachable ();
15049 case DEBUG_BEGIN_STMT:
15050 gimplify_seq_add_stmt (pre_p,
15051 gimple_build_debug_begin_stmt
15052 (TREE_BLOCK (*expr_p),
15053 EXPR_LOCATION (*expr_p)));
15054 ret = GS_ALL_DONE;
15055 *expr_p = NULL;
15056 break;
15058 case SSA_NAME:
15059 /* Allow callbacks into the gimplifier during optimization. */
15060 ret = GS_ALL_DONE;
15061 break;
15063 case OMP_PARALLEL:
15064 gimplify_omp_parallel (expr_p, pre_p);
15065 ret = GS_ALL_DONE;
15066 break;
15068 case OMP_TASK:
15069 gimplify_omp_task (expr_p, pre_p);
15070 ret = GS_ALL_DONE;
15071 break;
15073 case OMP_FOR:
15074 case OMP_SIMD:
15075 case OMP_DISTRIBUTE:
15076 case OMP_TASKLOOP:
15077 case OACC_LOOP:
15078 ret = gimplify_omp_for (expr_p, pre_p);
15079 break;
15081 case OMP_LOOP:
15082 ret = gimplify_omp_loop (expr_p, pre_p);
15083 break;
15085 case OACC_CACHE:
15086 gimplify_oacc_cache (expr_p, pre_p);
15087 ret = GS_ALL_DONE;
15088 break;
15090 case OACC_DECLARE:
15091 gimplify_oacc_declare (expr_p, pre_p);
15092 ret = GS_ALL_DONE;
15093 break;
15095 case OACC_HOST_DATA:
15096 case OACC_DATA:
15097 case OACC_KERNELS:
15098 case OACC_PARALLEL:
15099 case OACC_SERIAL:
15100 case OMP_SCOPE:
15101 case OMP_SECTIONS:
15102 case OMP_SINGLE:
15103 case OMP_TARGET:
15104 case OMP_TARGET_DATA:
15105 case OMP_TEAMS:
15106 gimplify_omp_workshare (expr_p, pre_p);
15107 ret = GS_ALL_DONE;
15108 break;
15110 case OACC_ENTER_DATA:
15111 case OACC_EXIT_DATA:
15112 case OACC_UPDATE:
15113 case OMP_TARGET_UPDATE:
15114 case OMP_TARGET_ENTER_DATA:
15115 case OMP_TARGET_EXIT_DATA:
15116 gimplify_omp_target_update (expr_p, pre_p);
15117 ret = GS_ALL_DONE;
15118 break;
15120 case OMP_SECTION:
15121 case OMP_MASTER:
15122 case OMP_MASKED:
15123 case OMP_ORDERED:
15124 case OMP_CRITICAL:
15125 case OMP_SCAN:
15127 gimple_seq body = NULL;
15128 gimple *g;
15129 bool saved_in_omp_construct = in_omp_construct;
15131 in_omp_construct = true;
15132 gimplify_and_add (OMP_BODY (*expr_p), &body);
15133 in_omp_construct = saved_in_omp_construct;
15134 switch (TREE_CODE (*expr_p))
15136 case OMP_SECTION:
15137 g = gimple_build_omp_section (body);
15138 break;
15139 case OMP_MASTER:
15140 g = gimple_build_omp_master (body);
15141 break;
15142 case OMP_ORDERED:
15143 g = gimplify_omp_ordered (*expr_p, body);
15144 break;
15145 case OMP_MASKED:
15146 gimplify_scan_omp_clauses (&OMP_MASKED_CLAUSES (*expr_p),
15147 pre_p, ORT_WORKSHARE, OMP_MASKED);
15148 gimplify_adjust_omp_clauses (pre_p, body,
15149 &OMP_MASKED_CLAUSES (*expr_p),
15150 OMP_MASKED);
15151 g = gimple_build_omp_masked (body,
15152 OMP_MASKED_CLAUSES (*expr_p));
15153 break;
15154 case OMP_CRITICAL:
15155 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
15156 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
15157 gimplify_adjust_omp_clauses (pre_p, body,
15158 &OMP_CRITICAL_CLAUSES (*expr_p),
15159 OMP_CRITICAL);
15160 g = gimple_build_omp_critical (body,
15161 OMP_CRITICAL_NAME (*expr_p),
15162 OMP_CRITICAL_CLAUSES (*expr_p));
15163 break;
15164 case OMP_SCAN:
15165 gimplify_scan_omp_clauses (&OMP_SCAN_CLAUSES (*expr_p),
15166 pre_p, ORT_WORKSHARE, OMP_SCAN);
15167 gimplify_adjust_omp_clauses (pre_p, body,
15168 &OMP_SCAN_CLAUSES (*expr_p),
15169 OMP_SCAN);
15170 g = gimple_build_omp_scan (body, OMP_SCAN_CLAUSES (*expr_p));
15171 break;
15172 default:
15173 gcc_unreachable ();
15175 gimplify_seq_add_stmt (pre_p, g);
15176 ret = GS_ALL_DONE;
15177 break;
15180 case OMP_TASKGROUP:
15182 gimple_seq body = NULL;
15184 tree *pclauses = &OMP_TASKGROUP_CLAUSES (*expr_p);
15185 bool saved_in_omp_construct = in_omp_construct;
15186 gimplify_scan_omp_clauses (pclauses, pre_p, ORT_TASKGROUP,
15187 OMP_TASKGROUP);
15188 gimplify_adjust_omp_clauses (pre_p, NULL, pclauses, OMP_TASKGROUP);
15190 in_omp_construct = true;
15191 gimplify_and_add (OMP_BODY (*expr_p), &body);
15192 in_omp_construct = saved_in_omp_construct;
15193 gimple_seq cleanup = NULL;
15194 tree fn = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
15195 gimple *g = gimple_build_call (fn, 0);
15196 gimple_seq_add_stmt (&cleanup, g);
15197 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
15198 body = NULL;
15199 gimple_seq_add_stmt (&body, g);
15200 g = gimple_build_omp_taskgroup (body, *pclauses);
15201 gimplify_seq_add_stmt (pre_p, g);
15202 ret = GS_ALL_DONE;
15203 break;
15206 case OMP_ATOMIC:
15207 case OMP_ATOMIC_READ:
15208 case OMP_ATOMIC_CAPTURE_OLD:
15209 case OMP_ATOMIC_CAPTURE_NEW:
15210 ret = gimplify_omp_atomic (expr_p, pre_p);
15211 break;
15213 case TRANSACTION_EXPR:
15214 ret = gimplify_transaction (expr_p, pre_p);
15215 break;
15217 case TRUTH_AND_EXPR:
15218 case TRUTH_OR_EXPR:
15219 case TRUTH_XOR_EXPR:
15221 tree orig_type = TREE_TYPE (*expr_p);
15222 tree new_type, xop0, xop1;
15223 *expr_p = gimple_boolify (*expr_p);
15224 new_type = TREE_TYPE (*expr_p);
15225 if (!useless_type_conversion_p (orig_type, new_type))
15227 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
15228 ret = GS_OK;
15229 break;
15232 /* Boolified binary truth expressions are semantically equivalent
15233 to bitwise binary expressions. Canonicalize them to the
15234 bitwise variant. */
15235 switch (TREE_CODE (*expr_p))
15237 case TRUTH_AND_EXPR:
15238 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
15239 break;
15240 case TRUTH_OR_EXPR:
15241 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
15242 break;
15243 case TRUTH_XOR_EXPR:
15244 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
15245 break;
15246 default:
15247 break;
15249 /* Now make sure that operands have compatible type to
15250 expression's new_type. */
15251 xop0 = TREE_OPERAND (*expr_p, 0);
15252 xop1 = TREE_OPERAND (*expr_p, 1);
15253 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
15254 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
15255 new_type,
15256 xop0);
15257 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
15258 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
15259 new_type,
15260 xop1);
15261 /* Continue classified as tcc_binary. */
15262 goto expr_2;
15265 case VEC_COND_EXPR:
15266 goto expr_3;
15268 case VEC_PERM_EXPR:
15269 /* Classified as tcc_expression. */
15270 goto expr_3;
15272 case BIT_INSERT_EXPR:
15273 /* Argument 3 is a constant. */
15274 goto expr_2;
15276 case POINTER_PLUS_EXPR:
15278 enum gimplify_status r0, r1;
15279 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15280 post_p, is_gimple_val, fb_rvalue);
15281 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
15282 post_p, is_gimple_val, fb_rvalue);
15283 recalculate_side_effects (*expr_p);
15284 ret = MIN (r0, r1);
15285 break;
15288 default:
15289 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
15291 case tcc_comparison:
15292 /* Handle comparison of objects of non scalar mode aggregates
15293 with a call to memcmp. It would be nice to only have to do
15294 this for variable-sized objects, but then we'd have to allow
15295 the same nest of reference nodes we allow for MODIFY_EXPR and
15296 that's too complex.
15298 Compare scalar mode aggregates as scalar mode values. Using
15299 memcmp for them would be very inefficient at best, and is
15300 plain wrong if bitfields are involved. */
15302 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
15304 /* Vector comparisons need no boolification. */
15305 if (TREE_CODE (type) == VECTOR_TYPE)
15306 goto expr_2;
15307 else if (!AGGREGATE_TYPE_P (type))
15309 tree org_type = TREE_TYPE (*expr_p);
15310 *expr_p = gimple_boolify (*expr_p);
15311 if (!useless_type_conversion_p (org_type,
15312 TREE_TYPE (*expr_p)))
15314 *expr_p = fold_convert_loc (input_location,
15315 org_type, *expr_p);
15316 ret = GS_OK;
15318 else
15319 goto expr_2;
15321 else if (TYPE_MODE (type) != BLKmode)
15322 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
15323 else
15324 ret = gimplify_variable_sized_compare (expr_p);
15326 break;
15329 /* If *EXPR_P does not need to be special-cased, handle it
15330 according to its class. */
15331 case tcc_unary:
15332 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15333 post_p, is_gimple_val, fb_rvalue);
15334 break;
15336 case tcc_binary:
15337 expr_2:
15339 enum gimplify_status r0, r1;
15341 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15342 post_p, is_gimple_val, fb_rvalue);
15343 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
15344 post_p, is_gimple_val, fb_rvalue);
15346 ret = MIN (r0, r1);
15347 break;
15350 expr_3:
15352 enum gimplify_status r0, r1, r2;
15354 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15355 post_p, is_gimple_val, fb_rvalue);
15356 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
15357 post_p, is_gimple_val, fb_rvalue);
15358 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
15359 post_p, is_gimple_val, fb_rvalue);
15361 ret = MIN (MIN (r0, r1), r2);
15362 break;
15365 case tcc_declaration:
15366 case tcc_constant:
15367 ret = GS_ALL_DONE;
15368 goto dont_recalculate;
15370 default:
15371 gcc_unreachable ();
15374 recalculate_side_effects (*expr_p);
15376 dont_recalculate:
15377 break;
15380 gcc_assert (*expr_p || ret != GS_OK);
15382 while (ret == GS_OK);
15384 /* If we encountered an error_mark somewhere nested inside, either
15385 stub out the statement or propagate the error back out. */
15386 if (ret == GS_ERROR)
15388 if (is_statement)
15389 *expr_p = NULL;
15390 goto out;
15393 /* This was only valid as a return value from the langhook, which
15394 we handled. Make sure it doesn't escape from any other context. */
15395 gcc_assert (ret != GS_UNHANDLED);
15397 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
15399 /* We aren't looking for a value, and we don't have a valid
15400 statement. If it doesn't have side-effects, throw it away.
15401 We can also get here with code such as "*&&L;", where L is
15402 a LABEL_DECL that is marked as FORCED_LABEL. */
15403 if (TREE_CODE (*expr_p) == LABEL_DECL
15404 || !TREE_SIDE_EFFECTS (*expr_p))
15405 *expr_p = NULL;
15406 else if (!TREE_THIS_VOLATILE (*expr_p))
15408 /* This is probably a _REF that contains something nested that
15409 has side effects. Recurse through the operands to find it. */
15410 enum tree_code code = TREE_CODE (*expr_p);
15412 switch (code)
15414 case COMPONENT_REF:
15415 case REALPART_EXPR:
15416 case IMAGPART_EXPR:
15417 case VIEW_CONVERT_EXPR:
15418 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
15419 gimple_test_f, fallback);
15420 break;
15422 case ARRAY_REF:
15423 case ARRAY_RANGE_REF:
15424 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
15425 gimple_test_f, fallback);
15426 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
15427 gimple_test_f, fallback);
15428 break;
15430 default:
15431 /* Anything else with side-effects must be converted to
15432 a valid statement before we get here. */
15433 gcc_unreachable ();
15436 *expr_p = NULL;
15438 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
15439 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode
15440 && !is_empty_type (TREE_TYPE (*expr_p)))
15442 /* Historically, the compiler has treated a bare reference
15443 to a non-BLKmode volatile lvalue as forcing a load. */
15444 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
15446 /* Normally, we do not want to create a temporary for a
15447 TREE_ADDRESSABLE type because such a type should not be
15448 copied by bitwise-assignment. However, we make an
15449 exception here, as all we are doing here is ensuring that
15450 we read the bytes that make up the type. We use
15451 create_tmp_var_raw because create_tmp_var will abort when
15452 given a TREE_ADDRESSABLE type. */
15453 tree tmp = create_tmp_var_raw (type, "vol");
15454 gimple_add_tmp_var (tmp);
15455 gimplify_assign (tmp, *expr_p, pre_p);
15456 *expr_p = NULL;
15458 else
15459 /* We can't do anything useful with a volatile reference to
15460 an incomplete type, so just throw it away. Likewise for
15461 a BLKmode type, since any implicit inner load should
15462 already have been turned into an explicit one by the
15463 gimplification process. */
15464 *expr_p = NULL;
15467 /* If we are gimplifying at the statement level, we're done. Tack
15468 everything together and return. */
15469 if (fallback == fb_none || is_statement)
15471 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
15472 it out for GC to reclaim it. */
15473 *expr_p = NULL_TREE;
15475 if (!gimple_seq_empty_p (internal_pre)
15476 || !gimple_seq_empty_p (internal_post))
15478 gimplify_seq_add_seq (&internal_pre, internal_post);
15479 gimplify_seq_add_seq (pre_p, internal_pre);
15482 /* The result of gimplifying *EXPR_P is going to be the last few
15483 statements in *PRE_P and *POST_P. Add location information
15484 to all the statements that were added by the gimplification
15485 helpers. */
15486 if (!gimple_seq_empty_p (*pre_p))
15487 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
15489 if (!gimple_seq_empty_p (*post_p))
15490 annotate_all_with_location_after (*post_p, post_last_gsi,
15491 input_location);
15493 goto out;
15496 #ifdef ENABLE_GIMPLE_CHECKING
15497 if (*expr_p)
15499 enum tree_code code = TREE_CODE (*expr_p);
15500 /* These expressions should already be in gimple IR form. */
15501 gcc_assert (code != MODIFY_EXPR
15502 && code != ASM_EXPR
15503 && code != BIND_EXPR
15504 && code != CATCH_EXPR
15505 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
15506 && code != EH_FILTER_EXPR
15507 && code != GOTO_EXPR
15508 && code != LABEL_EXPR
15509 && code != LOOP_EXPR
15510 && code != SWITCH_EXPR
15511 && code != TRY_FINALLY_EXPR
15512 && code != EH_ELSE_EXPR
15513 && code != OACC_PARALLEL
15514 && code != OACC_KERNELS
15515 && code != OACC_SERIAL
15516 && code != OACC_DATA
15517 && code != OACC_HOST_DATA
15518 && code != OACC_DECLARE
15519 && code != OACC_UPDATE
15520 && code != OACC_ENTER_DATA
15521 && code != OACC_EXIT_DATA
15522 && code != OACC_CACHE
15523 && code != OMP_CRITICAL
15524 && code != OMP_FOR
15525 && code != OACC_LOOP
15526 && code != OMP_MASTER
15527 && code != OMP_MASKED
15528 && code != OMP_TASKGROUP
15529 && code != OMP_ORDERED
15530 && code != OMP_PARALLEL
15531 && code != OMP_SCAN
15532 && code != OMP_SECTIONS
15533 && code != OMP_SECTION
15534 && code != OMP_SINGLE
15535 && code != OMP_SCOPE);
15537 #endif
15539 /* Otherwise we're gimplifying a subexpression, so the resulting
15540 value is interesting. If it's a valid operand that matches
15541 GIMPLE_TEST_F, we're done. Unless we are handling some
15542 post-effects internally; if that's the case, we need to copy into
15543 a temporary before adding the post-effects to POST_P. */
15544 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
15545 goto out;
15547 /* Otherwise, we need to create a new temporary for the gimplified
15548 expression. */
15550 /* We can't return an lvalue if we have an internal postqueue. The
15551 object the lvalue refers to would (probably) be modified by the
15552 postqueue; we need to copy the value out first, which means an
15553 rvalue. */
15554 if ((fallback & fb_lvalue)
15555 && gimple_seq_empty_p (internal_post)
15556 && is_gimple_addressable (*expr_p))
15558 /* An lvalue will do. Take the address of the expression, store it
15559 in a temporary, and replace the expression with an INDIRECT_REF of
15560 that temporary. */
15561 tree ref_alias_type = reference_alias_ptr_type (*expr_p);
15562 unsigned int ref_align = get_object_alignment (*expr_p);
15563 tree ref_type = TREE_TYPE (*expr_p);
15564 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
15565 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
15566 if (TYPE_ALIGN (ref_type) != ref_align)
15567 ref_type = build_aligned_type (ref_type, ref_align);
15568 *expr_p = build2 (MEM_REF, ref_type,
15569 tmp, build_zero_cst (ref_alias_type));
15571 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
15573 /* An rvalue will do. Assign the gimplified expression into a
15574 new temporary TMP and replace the original expression with
15575 TMP. First, make sure that the expression has a type so that
15576 it can be assigned into a temporary. */
15577 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
15578 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
15580 else
15582 #ifdef ENABLE_GIMPLE_CHECKING
15583 if (!(fallback & fb_mayfail))
15585 fprintf (stderr, "gimplification failed:\n");
15586 print_generic_expr (stderr, *expr_p);
15587 debug_tree (*expr_p);
15588 internal_error ("gimplification failed");
15590 #endif
15591 gcc_assert (fallback & fb_mayfail);
15593 /* If this is an asm statement, and the user asked for the
15594 impossible, don't die. Fail and let gimplify_asm_expr
15595 issue an error. */
15596 ret = GS_ERROR;
15597 goto out;
15600 /* Make sure the temporary matches our predicate. */
15601 gcc_assert ((*gimple_test_f) (*expr_p));
15603 if (!gimple_seq_empty_p (internal_post))
15605 annotate_all_with_location (internal_post, input_location);
15606 gimplify_seq_add_seq (pre_p, internal_post);
15609 out:
15610 input_location = saved_location;
15611 return ret;
15614 /* Like gimplify_expr but make sure the gimplified result is not itself
15615 a SSA name (but a decl if it were). Temporaries required by
15616 evaluating *EXPR_P may be still SSA names. */
15618 static enum gimplify_status
15619 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
15620 bool (*gimple_test_f) (tree), fallback_t fallback,
15621 bool allow_ssa)
15623 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
15624 gimple_test_f, fallback);
15625 if (! allow_ssa
15626 && TREE_CODE (*expr_p) == SSA_NAME)
15627 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
15628 return ret;
15631 /* Look through TYPE for variable-sized objects and gimplify each such
15632 size that we find. Add to LIST_P any statements generated. */
15634 void
15635 gimplify_type_sizes (tree type, gimple_seq *list_p)
15637 if (type == NULL || type == error_mark_node)
15638 return;
15640 const bool ignored_p
15641 = TYPE_NAME (type)
15642 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
15643 && DECL_IGNORED_P (TYPE_NAME (type));
15644 tree t;
15646 /* We first do the main variant, then copy into any other variants. */
15647 type = TYPE_MAIN_VARIANT (type);
15649 /* Avoid infinite recursion. */
15650 if (TYPE_SIZES_GIMPLIFIED (type))
15651 return;
15653 TYPE_SIZES_GIMPLIFIED (type) = 1;
15655 switch (TREE_CODE (type))
15657 case INTEGER_TYPE:
15658 case ENUMERAL_TYPE:
15659 case BOOLEAN_TYPE:
15660 case REAL_TYPE:
15661 case FIXED_POINT_TYPE:
15662 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
15663 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
15665 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
15667 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
15668 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
15670 break;
15672 case ARRAY_TYPE:
15673 /* These types may not have declarations, so handle them here. */
15674 gimplify_type_sizes (TREE_TYPE (type), list_p);
15675 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
15676 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
15677 with assigned stack slots, for -O1+ -g they should be tracked
15678 by VTA. */
15679 if (!ignored_p
15680 && TYPE_DOMAIN (type)
15681 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
15683 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
15684 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
15685 DECL_IGNORED_P (t) = 0;
15686 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
15687 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
15688 DECL_IGNORED_P (t) = 0;
15690 break;
15692 case RECORD_TYPE:
15693 case UNION_TYPE:
15694 case QUAL_UNION_TYPE:
15695 for (tree field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
15696 if (TREE_CODE (field) == FIELD_DECL)
15698 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
15699 /* Likewise, ensure variable offsets aren't removed. */
15700 if (!ignored_p
15701 && (t = DECL_FIELD_OFFSET (field))
15702 && VAR_P (t)
15703 && DECL_ARTIFICIAL (t))
15704 DECL_IGNORED_P (t) = 0;
15705 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
15706 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
15707 gimplify_type_sizes (TREE_TYPE (field), list_p);
15709 break;
15711 case POINTER_TYPE:
15712 case REFERENCE_TYPE:
15713 /* We used to recurse on the pointed-to type here, which turned out to
15714 be incorrect because its definition might refer to variables not
15715 yet initialized at this point if a forward declaration is involved.
15717 It was actually useful for anonymous pointed-to types to ensure
15718 that the sizes evaluation dominates every possible later use of the
15719 values. Restricting to such types here would be safe since there
15720 is no possible forward declaration around, but would introduce an
15721 undesirable middle-end semantic to anonymity. We then defer to
15722 front-ends the responsibility of ensuring that the sizes are
15723 evaluated both early and late enough, e.g. by attaching artificial
15724 type declarations to the tree. */
15725 break;
15727 default:
15728 break;
15731 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
15732 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
15734 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
15736 TYPE_SIZE (t) = TYPE_SIZE (type);
15737 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
15738 TYPE_SIZES_GIMPLIFIED (t) = 1;
15742 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
15743 a size or position, has had all of its SAVE_EXPRs evaluated.
15744 We add any required statements to *STMT_P. */
15746 void
15747 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
15749 tree expr = *expr_p;
15751 /* We don't do anything if the value isn't there, is constant, or contains
15752 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
15753 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
15754 will want to replace it with a new variable, but that will cause problems
15755 if this type is from outside the function. It's OK to have that here. */
15756 if (expr == NULL_TREE
15757 || is_gimple_constant (expr)
15758 || TREE_CODE (expr) == VAR_DECL
15759 || CONTAINS_PLACEHOLDER_P (expr))
15760 return;
15762 *expr_p = unshare_expr (expr);
15764 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
15765 if the def vanishes. */
15766 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
15768 /* If expr wasn't already is_gimple_sizepos or is_gimple_constant from the
15769 FE, ensure that it is a VAR_DECL, otherwise we might handle some decls
15770 as gimplify_vla_decl even when they would have all sizes INTEGER_CSTs. */
15771 if (is_gimple_constant (*expr_p))
15772 *expr_p = get_initialized_tmp_var (*expr_p, stmt_p, NULL, false);
15775 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
15776 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
15777 is true, also gimplify the parameters. */
15779 gbind *
15780 gimplify_body (tree fndecl, bool do_parms)
15782 location_t saved_location = input_location;
15783 gimple_seq parm_stmts, parm_cleanup = NULL, seq;
15784 gimple *outer_stmt;
15785 gbind *outer_bind;
15787 timevar_push (TV_TREE_GIMPLIFY);
15789 init_tree_ssa (cfun);
15791 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
15792 gimplification. */
15793 default_rtl_profile ();
15795 gcc_assert (gimplify_ctxp == NULL);
15796 push_gimplify_context (true);
15798 if (flag_openacc || flag_openmp)
15800 gcc_assert (gimplify_omp_ctxp == NULL);
15801 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
15802 gimplify_omp_ctxp = new_omp_context (ORT_IMPLICIT_TARGET);
15805 /* Unshare most shared trees in the body and in that of any nested functions.
15806 It would seem we don't have to do this for nested functions because
15807 they are supposed to be output and then the outer function gimplified
15808 first, but the g++ front end doesn't always do it that way. */
15809 unshare_body (fndecl);
15810 unvisit_body (fndecl);
15812 /* Make sure input_location isn't set to something weird. */
15813 input_location = DECL_SOURCE_LOCATION (fndecl);
15815 /* Resolve callee-copies. This has to be done before processing
15816 the body so that DECL_VALUE_EXPR gets processed correctly. */
15817 parm_stmts = do_parms ? gimplify_parameters (&parm_cleanup) : NULL;
15819 /* Gimplify the function's body. */
15820 seq = NULL;
15821 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
15822 outer_stmt = gimple_seq_first_nondebug_stmt (seq);
15823 if (!outer_stmt)
15825 outer_stmt = gimple_build_nop ();
15826 gimplify_seq_add_stmt (&seq, outer_stmt);
15829 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
15830 not the case, wrap everything in a GIMPLE_BIND to make it so. */
15831 if (gimple_code (outer_stmt) == GIMPLE_BIND
15832 && (gimple_seq_first_nondebug_stmt (seq)
15833 == gimple_seq_last_nondebug_stmt (seq)))
15835 outer_bind = as_a <gbind *> (outer_stmt);
15836 if (gimple_seq_first_stmt (seq) != outer_stmt
15837 || gimple_seq_last_stmt (seq) != outer_stmt)
15839 /* If there are debug stmts before or after outer_stmt, move them
15840 inside of outer_bind body. */
15841 gimple_stmt_iterator gsi = gsi_for_stmt (outer_stmt, &seq);
15842 gimple_seq second_seq = NULL;
15843 if (gimple_seq_first_stmt (seq) != outer_stmt
15844 && gimple_seq_last_stmt (seq) != outer_stmt)
15846 second_seq = gsi_split_seq_after (gsi);
15847 gsi_remove (&gsi, false);
15849 else if (gimple_seq_first_stmt (seq) != outer_stmt)
15850 gsi_remove (&gsi, false);
15851 else
15853 gsi_remove (&gsi, false);
15854 second_seq = seq;
15855 seq = NULL;
15857 gimple_seq_add_seq_without_update (&seq,
15858 gimple_bind_body (outer_bind));
15859 gimple_seq_add_seq_without_update (&seq, second_seq);
15860 gimple_bind_set_body (outer_bind, seq);
15863 else
15864 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
15866 DECL_SAVED_TREE (fndecl) = NULL_TREE;
15868 /* If we had callee-copies statements, insert them at the beginning
15869 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
15870 if (!gimple_seq_empty_p (parm_stmts))
15872 tree parm;
15874 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
15875 if (parm_cleanup)
15877 gtry *g = gimple_build_try (parm_stmts, parm_cleanup,
15878 GIMPLE_TRY_FINALLY);
15879 parm_stmts = NULL;
15880 gimple_seq_add_stmt (&parm_stmts, g);
15882 gimple_bind_set_body (outer_bind, parm_stmts);
15884 for (parm = DECL_ARGUMENTS (current_function_decl);
15885 parm; parm = DECL_CHAIN (parm))
15886 if (DECL_HAS_VALUE_EXPR_P (parm))
15888 DECL_HAS_VALUE_EXPR_P (parm) = 0;
15889 DECL_IGNORED_P (parm) = 0;
15893 if ((flag_openacc || flag_openmp || flag_openmp_simd)
15894 && gimplify_omp_ctxp)
15896 delete_omp_context (gimplify_omp_ctxp);
15897 gimplify_omp_ctxp = NULL;
15900 pop_gimplify_context (outer_bind);
15901 gcc_assert (gimplify_ctxp == NULL);
15903 if (flag_checking && !seen_error ())
15904 verify_gimple_in_seq (gimple_bind_body (outer_bind));
15906 timevar_pop (TV_TREE_GIMPLIFY);
15907 input_location = saved_location;
15909 return outer_bind;
15912 typedef char *char_p; /* For DEF_VEC_P. */
15914 /* Return whether we should exclude FNDECL from instrumentation. */
15916 static bool
15917 flag_instrument_functions_exclude_p (tree fndecl)
15919 vec<char_p> *v;
15921 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
15922 if (v && v->length () > 0)
15924 const char *name;
15925 int i;
15926 char *s;
15928 name = lang_hooks.decl_printable_name (fndecl, 1);
15929 FOR_EACH_VEC_ELT (*v, i, s)
15930 if (strstr (name, s) != NULL)
15931 return true;
15934 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
15935 if (v && v->length () > 0)
15937 const char *name;
15938 int i;
15939 char *s;
15941 name = DECL_SOURCE_FILE (fndecl);
15942 FOR_EACH_VEC_ELT (*v, i, s)
15943 if (strstr (name, s) != NULL)
15944 return true;
15947 return false;
15950 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
15951 node for the function we want to gimplify.
15953 Return the sequence of GIMPLE statements corresponding to the body
15954 of FNDECL. */
15956 void
15957 gimplify_function_tree (tree fndecl)
15959 gimple_seq seq;
15960 gbind *bind;
15962 gcc_assert (!gimple_body (fndecl));
15964 if (DECL_STRUCT_FUNCTION (fndecl))
15965 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
15966 else
15967 push_struct_function (fndecl);
15969 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
15970 if necessary. */
15971 cfun->curr_properties |= PROP_gimple_lva;
15973 if (asan_sanitize_use_after_scope ())
15974 asan_poisoned_variables = new hash_set<tree> ();
15975 bind = gimplify_body (fndecl, true);
15976 if (asan_poisoned_variables)
15978 delete asan_poisoned_variables;
15979 asan_poisoned_variables = NULL;
15982 /* The tree body of the function is no longer needed, replace it
15983 with the new GIMPLE body. */
15984 seq = NULL;
15985 gimple_seq_add_stmt (&seq, bind);
15986 gimple_set_body (fndecl, seq);
15988 /* If we're instrumenting function entry/exit, then prepend the call to
15989 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
15990 catch the exit hook. */
15991 /* ??? Add some way to ignore exceptions for this TFE. */
15992 if (flag_instrument_function_entry_exit
15993 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
15994 /* Do not instrument extern inline functions. */
15995 && !(DECL_DECLARED_INLINE_P (fndecl)
15996 && DECL_EXTERNAL (fndecl)
15997 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
15998 && !flag_instrument_functions_exclude_p (fndecl))
16000 tree x;
16001 gbind *new_bind;
16002 gimple *tf;
16003 gimple_seq cleanup = NULL, body = NULL;
16004 tree tmp_var, this_fn_addr;
16005 gcall *call;
16007 /* The instrumentation hooks aren't going to call the instrumented
16008 function and the address they receive is expected to be matchable
16009 against symbol addresses. Make sure we don't create a trampoline,
16010 in case the current function is nested. */
16011 this_fn_addr = build_fold_addr_expr (current_function_decl);
16012 TREE_NO_TRAMPOLINE (this_fn_addr) = 1;
16014 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
16015 call = gimple_build_call (x, 1, integer_zero_node);
16016 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
16017 gimple_call_set_lhs (call, tmp_var);
16018 gimplify_seq_add_stmt (&cleanup, call);
16019 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
16020 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
16021 gimplify_seq_add_stmt (&cleanup, call);
16022 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
16024 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
16025 call = gimple_build_call (x, 1, integer_zero_node);
16026 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
16027 gimple_call_set_lhs (call, tmp_var);
16028 gimplify_seq_add_stmt (&body, call);
16029 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
16030 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
16031 gimplify_seq_add_stmt (&body, call);
16032 gimplify_seq_add_stmt (&body, tf);
16033 new_bind = gimple_build_bind (NULL, body, NULL);
16035 /* Replace the current function body with the body
16036 wrapped in the try/finally TF. */
16037 seq = NULL;
16038 gimple_seq_add_stmt (&seq, new_bind);
16039 gimple_set_body (fndecl, seq);
16040 bind = new_bind;
16043 if (sanitize_flags_p (SANITIZE_THREAD)
16044 && param_tsan_instrument_func_entry_exit)
16046 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
16047 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
16048 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
16049 /* Replace the current function body with the body
16050 wrapped in the try/finally TF. */
16051 seq = NULL;
16052 gimple_seq_add_stmt (&seq, new_bind);
16053 gimple_set_body (fndecl, seq);
16056 DECL_SAVED_TREE (fndecl) = NULL_TREE;
16057 cfun->curr_properties |= PROP_gimple_any;
16059 pop_cfun ();
16061 dump_function (TDI_gimple, fndecl);
16064 /* Return a dummy expression of type TYPE in order to keep going after an
16065 error. */
16067 static tree
16068 dummy_object (tree type)
16070 tree t = build_int_cst (build_pointer_type (type), 0);
16071 return build2 (MEM_REF, type, t, t);
16074 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
16075 builtin function, but a very special sort of operator. */
16077 enum gimplify_status
16078 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
16079 gimple_seq *post_p ATTRIBUTE_UNUSED)
16081 tree promoted_type, have_va_type;
16082 tree valist = TREE_OPERAND (*expr_p, 0);
16083 tree type = TREE_TYPE (*expr_p);
16084 tree t, tag, aptag;
16085 location_t loc = EXPR_LOCATION (*expr_p);
16087 /* Verify that valist is of the proper type. */
16088 have_va_type = TREE_TYPE (valist);
16089 if (have_va_type == error_mark_node)
16090 return GS_ERROR;
16091 have_va_type = targetm.canonical_va_list_type (have_va_type);
16092 if (have_va_type == NULL_TREE
16093 && POINTER_TYPE_P (TREE_TYPE (valist)))
16094 /* Handle 'Case 1: Not an array type' from c-common.c/build_va_arg. */
16095 have_va_type
16096 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
16097 gcc_assert (have_va_type != NULL_TREE);
16099 /* Generate a diagnostic for requesting data of a type that cannot
16100 be passed through `...' due to type promotion at the call site. */
16101 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
16102 != type)
16104 static bool gave_help;
16105 bool warned;
16106 /* Use the expansion point to handle cases such as passing bool (defined
16107 in a system header) through `...'. */
16108 location_t xloc
16109 = expansion_point_location_if_in_system_header (loc);
16111 /* Unfortunately, this is merely undefined, rather than a constraint
16112 violation, so we cannot make this an error. If this call is never
16113 executed, the program is still strictly conforming. */
16114 auto_diagnostic_group d;
16115 warned = warning_at (xloc, 0,
16116 "%qT is promoted to %qT when passed through %<...%>",
16117 type, promoted_type);
16118 if (!gave_help && warned)
16120 gave_help = true;
16121 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
16122 promoted_type, type);
16125 /* We can, however, treat "undefined" any way we please.
16126 Call abort to encourage the user to fix the program. */
16127 if (warned)
16128 inform (xloc, "if this code is reached, the program will abort");
16129 /* Before the abort, allow the evaluation of the va_list
16130 expression to exit or longjmp. */
16131 gimplify_and_add (valist, pre_p);
16132 t = build_call_expr_loc (loc,
16133 builtin_decl_implicit (BUILT_IN_TRAP), 0);
16134 gimplify_and_add (t, pre_p);
16136 /* This is dead code, but go ahead and finish so that the
16137 mode of the result comes out right. */
16138 *expr_p = dummy_object (type);
16139 return GS_ALL_DONE;
16142 tag = build_int_cst (build_pointer_type (type), 0);
16143 aptag = build_int_cst (TREE_TYPE (valist), 0);
16145 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
16146 valist, tag, aptag);
16148 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
16149 needs to be expanded. */
16150 cfun->curr_properties &= ~PROP_gimple_lva;
16152 return GS_OK;
16155 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
16157 DST/SRC are the destination and source respectively. You can pass
16158 ungimplified trees in DST or SRC, in which case they will be
16159 converted to a gimple operand if necessary.
16161 This function returns the newly created GIMPLE_ASSIGN tuple. */
16163 gimple *
16164 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
16166 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
16167 gimplify_and_add (t, seq_p);
16168 ggc_free (t);
16169 return gimple_seq_last_stmt (*seq_p);
16172 inline hashval_t
16173 gimplify_hasher::hash (const elt_t *p)
16175 tree t = p->val;
16176 return iterative_hash_expr (t, 0);
16179 inline bool
16180 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
16182 tree t1 = p1->val;
16183 tree t2 = p2->val;
16184 enum tree_code code = TREE_CODE (t1);
16186 if (TREE_CODE (t2) != code
16187 || TREE_TYPE (t1) != TREE_TYPE (t2))
16188 return false;
16190 if (!operand_equal_p (t1, t2, 0))
16191 return false;
16193 /* Only allow them to compare equal if they also hash equal; otherwise
16194 results are nondeterminate, and we fail bootstrap comparison. */
16195 gcc_checking_assert (hash (p1) == hash (p2));
16197 return true;