c++: top level bind when rewriting coroutines [PR106188]
[official-gcc.git] / gcc / gimplify.cc
blobdcdc8523ff55e751d4f5dad2d81d40ada7bbf7d9
1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2022 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-iterator.h"
46 #include "gimple-fold.h"
47 #include "tree-eh.h"
48 #include "gimplify.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 "tree-hash-traits.h"
57 #include "omp-general.h"
58 #include "omp-low.h"
59 #include "gimple-low.h"
60 #include "gomp-constants.h"
61 #include "splay-tree.h"
62 #include "gimple-walk.h"
63 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
64 #include "builtins.h"
65 #include "stringpool.h"
66 #include "attribs.h"
67 #include "asan.h"
68 #include "dbgcnt.h"
69 #include "omp-offload.h"
70 #include "context.h"
71 #include "tree-nested.h"
73 /* Hash set of poisoned variables in a bind expr. */
74 static hash_set<tree> *asan_poisoned_variables = NULL;
76 enum gimplify_omp_var_data
78 GOVD_SEEN = 0x000001,
79 GOVD_EXPLICIT = 0x000002,
80 GOVD_SHARED = 0x000004,
81 GOVD_PRIVATE = 0x000008,
82 GOVD_FIRSTPRIVATE = 0x000010,
83 GOVD_LASTPRIVATE = 0x000020,
84 GOVD_REDUCTION = 0x000040,
85 GOVD_LOCAL = 0x00080,
86 GOVD_MAP = 0x000100,
87 GOVD_DEBUG_PRIVATE = 0x000200,
88 GOVD_PRIVATE_OUTER_REF = 0x000400,
89 GOVD_LINEAR = 0x000800,
90 GOVD_ALIGNED = 0x001000,
92 /* Flag for GOVD_MAP: don't copy back. */
93 GOVD_MAP_TO_ONLY = 0x002000,
95 /* Flag for GOVD_LINEAR or GOVD_LASTPRIVATE: no outer reference. */
96 GOVD_LINEAR_LASTPRIVATE_NO_OUTER = 0x004000,
98 GOVD_MAP_0LEN_ARRAY = 0x008000,
100 /* Flag for GOVD_MAP, if it is always, to or always, tofrom mapping. */
101 GOVD_MAP_ALWAYS_TO = 0x010000,
103 /* Flag for shared vars that are or might be stored to in the region. */
104 GOVD_WRITTEN = 0x020000,
106 /* Flag for GOVD_MAP, if it is a forced mapping. */
107 GOVD_MAP_FORCE = 0x040000,
109 /* Flag for GOVD_MAP: must be present already. */
110 GOVD_MAP_FORCE_PRESENT = 0x080000,
112 /* Flag for GOVD_MAP: only allocate. */
113 GOVD_MAP_ALLOC_ONLY = 0x100000,
115 /* Flag for GOVD_MAP: only copy back. */
116 GOVD_MAP_FROM_ONLY = 0x200000,
118 GOVD_NONTEMPORAL = 0x400000,
120 /* Flag for GOVD_LASTPRIVATE: conditional modifier. */
121 GOVD_LASTPRIVATE_CONDITIONAL = 0x800000,
123 GOVD_CONDTEMP = 0x1000000,
125 /* Flag for GOVD_REDUCTION: inscan seen in {in,ex}clusive clause. */
126 GOVD_REDUCTION_INSCAN = 0x2000000,
128 /* Flag for GOVD_MAP: (struct) vars that have pointer attachments for
129 fields. */
130 GOVD_MAP_HAS_ATTACHMENTS = 0x4000000,
132 /* Flag for GOVD_FIRSTPRIVATE: OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT. */
133 GOVD_FIRSTPRIVATE_IMPLICIT = 0x8000000,
135 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
136 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
137 | GOVD_LOCAL)
141 enum omp_region_type
143 ORT_WORKSHARE = 0x00,
144 ORT_TASKGROUP = 0x01,
145 ORT_SIMD = 0x04,
147 ORT_PARALLEL = 0x08,
148 ORT_COMBINED_PARALLEL = ORT_PARALLEL | 1,
150 ORT_TASK = 0x10,
151 ORT_UNTIED_TASK = ORT_TASK | 1,
152 ORT_TASKLOOP = ORT_TASK | 2,
153 ORT_UNTIED_TASKLOOP = ORT_UNTIED_TASK | 2,
155 ORT_TEAMS = 0x20,
156 ORT_COMBINED_TEAMS = ORT_TEAMS | 1,
157 ORT_HOST_TEAMS = ORT_TEAMS | 2,
158 ORT_COMBINED_HOST_TEAMS = ORT_COMBINED_TEAMS | 2,
160 /* Data region. */
161 ORT_TARGET_DATA = 0x40,
163 /* Data region with offloading. */
164 ORT_TARGET = 0x80,
165 ORT_COMBINED_TARGET = ORT_TARGET | 1,
166 ORT_IMPLICIT_TARGET = ORT_TARGET | 2,
168 /* OpenACC variants. */
169 ORT_ACC = 0x100, /* A generic OpenACC region. */
170 ORT_ACC_DATA = ORT_ACC | ORT_TARGET_DATA, /* Data construct. */
171 ORT_ACC_PARALLEL = ORT_ACC | ORT_TARGET, /* Parallel construct */
172 ORT_ACC_KERNELS = ORT_ACC | ORT_TARGET | 2, /* Kernels construct. */
173 ORT_ACC_SERIAL = ORT_ACC | ORT_TARGET | 4, /* Serial construct. */
174 ORT_ACC_HOST_DATA = ORT_ACC | ORT_TARGET_DATA | 2, /* Host data. */
176 /* Dummy OpenMP region, used to disable expansion of
177 DECL_VALUE_EXPRs in taskloop pre body. */
178 ORT_NONE = 0x200
181 /* Gimplify hashtable helper. */
183 struct gimplify_hasher : free_ptr_hash <elt_t>
185 static inline hashval_t hash (const elt_t *);
186 static inline bool equal (const elt_t *, const elt_t *);
189 struct gimplify_ctx
191 struct gimplify_ctx *prev_context;
193 vec<gbind *> bind_expr_stack;
194 tree temps;
195 gimple_seq conditional_cleanups;
196 tree exit_label;
197 tree return_temp;
199 vec<tree> case_labels;
200 hash_set<tree> *live_switch_vars;
201 /* The formal temporary table. Should this be persistent? */
202 hash_table<gimplify_hasher> *temp_htab;
204 int conditions;
205 unsigned into_ssa : 1;
206 unsigned allow_rhs_cond_expr : 1;
207 unsigned in_cleanup_point_expr : 1;
208 unsigned keep_stack : 1;
209 unsigned save_stack : 1;
210 unsigned in_switch_expr : 1;
213 enum gimplify_defaultmap_kind
215 GDMK_SCALAR,
216 GDMK_SCALAR_TARGET, /* w/ Fortran's target attr, implicit mapping, only. */
217 GDMK_AGGREGATE,
218 GDMK_ALLOCATABLE,
219 GDMK_POINTER
222 struct gimplify_omp_ctx
224 struct gimplify_omp_ctx *outer_context;
225 splay_tree variables;
226 hash_set<tree> *privatized_types;
227 tree clauses;
228 /* Iteration variables in an OMP_FOR. */
229 vec<tree> loop_iter_var;
230 location_t location;
231 enum omp_clause_default_kind default_kind;
232 enum omp_region_type region_type;
233 enum tree_code code;
234 bool combined_loop;
235 bool distribute;
236 bool target_firstprivatize_array_bases;
237 bool add_safelen1;
238 bool order_concurrent;
239 bool has_depend;
240 bool in_for_exprs;
241 int defaultmap[5];
244 static struct gimplify_ctx *gimplify_ctxp;
245 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
246 static bool in_omp_construct;
248 /* Forward declaration. */
249 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
250 static hash_map<tree, tree> *oacc_declare_returns;
251 static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
252 bool (*) (tree), fallback_t, bool);
253 static void prepare_gimple_addressable (tree *, gimple_seq *);
255 /* Shorter alias name for the above function for use in gimplify.cc
256 only. */
258 static inline void
259 gimplify_seq_add_stmt (gimple_seq *seq_p, gimple *gs)
261 gimple_seq_add_stmt_without_update (seq_p, gs);
264 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
265 NULL, a new sequence is allocated. This function is
266 similar to gimple_seq_add_seq, but does not scan the operands.
267 During gimplification, we need to manipulate statement sequences
268 before the def/use vectors have been constructed. */
270 static void
271 gimplify_seq_add_seq (gimple_seq *dst_p, gimple_seq src)
273 gimple_stmt_iterator si;
275 if (src == NULL)
276 return;
278 si = gsi_last (*dst_p);
279 gsi_insert_seq_after_without_update (&si, src, GSI_NEW_STMT);
283 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
284 and popping gimplify contexts. */
286 static struct gimplify_ctx *ctx_pool = NULL;
288 /* Return a gimplify context struct from the pool. */
290 static inline struct gimplify_ctx *
291 ctx_alloc (void)
293 struct gimplify_ctx * c = ctx_pool;
295 if (c)
296 ctx_pool = c->prev_context;
297 else
298 c = XNEW (struct gimplify_ctx);
300 memset (c, '\0', sizeof (*c));
301 return c;
304 /* Put gimplify context C back into the pool. */
306 static inline void
307 ctx_free (struct gimplify_ctx *c)
309 c->prev_context = ctx_pool;
310 ctx_pool = c;
313 /* Free allocated ctx stack memory. */
315 void
316 free_gimplify_stack (void)
318 struct gimplify_ctx *c;
320 while ((c = ctx_pool))
322 ctx_pool = c->prev_context;
323 free (c);
328 /* Set up a context for the gimplifier. */
330 void
331 push_gimplify_context (bool in_ssa, bool rhs_cond_ok)
333 struct gimplify_ctx *c = ctx_alloc ();
335 c->prev_context = gimplify_ctxp;
336 gimplify_ctxp = c;
337 gimplify_ctxp->into_ssa = in_ssa;
338 gimplify_ctxp->allow_rhs_cond_expr = rhs_cond_ok;
341 /* Tear down a context for the gimplifier. If BODY is non-null, then
342 put the temporaries into the outer BIND_EXPR. Otherwise, put them
343 in the local_decls.
345 BODY is not a sequence, but the first tuple in a sequence. */
347 void
348 pop_gimplify_context (gimple *body)
350 struct gimplify_ctx *c = gimplify_ctxp;
352 gcc_assert (c
353 && (!c->bind_expr_stack.exists ()
354 || c->bind_expr_stack.is_empty ()));
355 c->bind_expr_stack.release ();
356 gimplify_ctxp = c->prev_context;
358 if (body)
359 declare_vars (c->temps, body, false);
360 else
361 record_vars (c->temps);
363 delete c->temp_htab;
364 c->temp_htab = NULL;
365 ctx_free (c);
368 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
370 static void
371 gimple_push_bind_expr (gbind *bind_stmt)
373 gimplify_ctxp->bind_expr_stack.reserve (8);
374 gimplify_ctxp->bind_expr_stack.safe_push (bind_stmt);
377 /* Pop the first element off the stack of bindings. */
379 static void
380 gimple_pop_bind_expr (void)
382 gimplify_ctxp->bind_expr_stack.pop ();
385 /* Return the first element of the stack of bindings. */
387 gbind *
388 gimple_current_bind_expr (void)
390 return gimplify_ctxp->bind_expr_stack.last ();
393 /* Return the stack of bindings created during gimplification. */
395 vec<gbind *>
396 gimple_bind_expr_stack (void)
398 return gimplify_ctxp->bind_expr_stack;
401 /* Return true iff there is a COND_EXPR between us and the innermost
402 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
404 static bool
405 gimple_conditional_context (void)
407 return gimplify_ctxp->conditions > 0;
410 /* Note that we've entered a COND_EXPR. */
412 static void
413 gimple_push_condition (void)
415 #ifdef ENABLE_GIMPLE_CHECKING
416 if (gimplify_ctxp->conditions == 0)
417 gcc_assert (gimple_seq_empty_p (gimplify_ctxp->conditional_cleanups));
418 #endif
419 ++(gimplify_ctxp->conditions);
422 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
423 now, add any conditional cleanups we've seen to the prequeue. */
425 static void
426 gimple_pop_condition (gimple_seq *pre_p)
428 int conds = --(gimplify_ctxp->conditions);
430 gcc_assert (conds >= 0);
431 if (conds == 0)
433 gimplify_seq_add_seq (pre_p, gimplify_ctxp->conditional_cleanups);
434 gimplify_ctxp->conditional_cleanups = NULL;
438 /* A stable comparison routine for use with splay trees and DECLs. */
440 static int
441 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
443 tree a = (tree) xa;
444 tree b = (tree) xb;
446 return DECL_UID (a) - DECL_UID (b);
449 /* Create a new omp construct that deals with variable remapping. */
451 static struct gimplify_omp_ctx *
452 new_omp_context (enum omp_region_type region_type)
454 struct gimplify_omp_ctx *c;
456 c = XCNEW (struct gimplify_omp_ctx);
457 c->outer_context = gimplify_omp_ctxp;
458 c->variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
459 c->privatized_types = new hash_set<tree>;
460 c->location = input_location;
461 c->region_type = region_type;
462 if ((region_type & ORT_TASK) == 0)
463 c->default_kind = OMP_CLAUSE_DEFAULT_SHARED;
464 else
465 c->default_kind = OMP_CLAUSE_DEFAULT_UNSPECIFIED;
466 c->defaultmap[GDMK_SCALAR] = GOVD_MAP;
467 c->defaultmap[GDMK_SCALAR_TARGET] = GOVD_MAP;
468 c->defaultmap[GDMK_AGGREGATE] = GOVD_MAP;
469 c->defaultmap[GDMK_ALLOCATABLE] = GOVD_MAP;
470 c->defaultmap[GDMK_POINTER] = GOVD_MAP;
472 return c;
475 /* Destroy an omp construct that deals with variable remapping. */
477 static void
478 delete_omp_context (struct gimplify_omp_ctx *c)
480 splay_tree_delete (c->variables);
481 delete c->privatized_types;
482 c->loop_iter_var.release ();
483 XDELETE (c);
486 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
487 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
489 /* Both gimplify the statement T and append it to *SEQ_P. This function
490 behaves exactly as gimplify_stmt, but you don't have to pass T as a
491 reference. */
493 void
494 gimplify_and_add (tree t, gimple_seq *seq_p)
496 gimplify_stmt (&t, seq_p);
499 /* Gimplify statement T into sequence *SEQ_P, and return the first
500 tuple in the sequence of generated tuples for this statement.
501 Return NULL if gimplifying T produced no tuples. */
503 static gimple *
504 gimplify_and_return_first (tree t, gimple_seq *seq_p)
506 gimple_stmt_iterator last = gsi_last (*seq_p);
508 gimplify_and_add (t, seq_p);
510 if (!gsi_end_p (last))
512 gsi_next (&last);
513 return gsi_stmt (last);
515 else
516 return gimple_seq_first_stmt (*seq_p);
519 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
520 LHS, or for a call argument. */
522 static bool
523 is_gimple_mem_rhs (tree t)
525 /* If we're dealing with a renamable type, either source or dest must be
526 a renamed variable. */
527 if (is_gimple_reg_type (TREE_TYPE (t)))
528 return is_gimple_val (t);
529 else
530 return is_gimple_val (t) || is_gimple_lvalue (t);
533 /* Return true if T is a CALL_EXPR or an expression that can be
534 assigned to a temporary. Note that this predicate should only be
535 used during gimplification. See the rationale for this in
536 gimplify_modify_expr. */
538 static bool
539 is_gimple_reg_rhs_or_call (tree t)
541 return (get_gimple_rhs_class (TREE_CODE (t)) != GIMPLE_INVALID_RHS
542 || TREE_CODE (t) == CALL_EXPR);
545 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
546 this predicate should only be used during gimplification. See the
547 rationale for this in gimplify_modify_expr. */
549 static bool
550 is_gimple_mem_rhs_or_call (tree t)
552 /* If we're dealing with a renamable type, either source or dest must be
553 a renamed variable. */
554 if (is_gimple_reg_type (TREE_TYPE (t)))
555 return is_gimple_val (t);
556 else
557 return (is_gimple_val (t)
558 || is_gimple_lvalue (t)
559 || TREE_CLOBBER_P (t)
560 || TREE_CODE (t) == CALL_EXPR);
563 /* Create a temporary with a name derived from VAL. Subroutine of
564 lookup_tmp_var; nobody else should call this function. */
566 static inline tree
567 create_tmp_from_val (tree val)
569 /* Drop all qualifiers and address-space information from the value type. */
570 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (val));
571 tree var = create_tmp_var (type, get_name (val));
572 return var;
575 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
576 an existing expression temporary. If NOT_GIMPLE_REG, mark it as such. */
578 static tree
579 lookup_tmp_var (tree val, bool is_formal, bool not_gimple_reg)
581 tree ret;
583 /* We cannot mark a formal temporary with DECL_NOT_GIMPLE_REG_P. */
584 gcc_assert (!is_formal || !not_gimple_reg);
586 /* If not optimizing, never really reuse a temporary. local-alloc
587 won't allocate any variable that is used in more than one basic
588 block, which means it will go into memory, causing much extra
589 work in reload and final and poorer code generation, outweighing
590 the extra memory allocation here. */
591 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
593 ret = create_tmp_from_val (val);
594 DECL_NOT_GIMPLE_REG_P (ret) = not_gimple_reg;
596 else
598 elt_t elt, *elt_p;
599 elt_t **slot;
601 elt.val = val;
602 if (!gimplify_ctxp->temp_htab)
603 gimplify_ctxp->temp_htab = new hash_table<gimplify_hasher> (1000);
604 slot = gimplify_ctxp->temp_htab->find_slot (&elt, INSERT);
605 if (*slot == NULL)
607 elt_p = XNEW (elt_t);
608 elt_p->val = val;
609 elt_p->temp = ret = create_tmp_from_val (val);
610 *slot = elt_p;
612 else
614 elt_p = *slot;
615 ret = elt_p->temp;
619 return ret;
622 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
624 static tree
625 internal_get_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
626 bool is_formal, bool allow_ssa, bool not_gimple_reg)
628 tree t, mod;
630 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
631 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
632 gimplify_expr (&val, pre_p, post_p, is_gimple_reg_rhs_or_call,
633 fb_rvalue);
635 if (allow_ssa
636 && gimplify_ctxp->into_ssa
637 && is_gimple_reg_type (TREE_TYPE (val)))
639 t = make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val)));
640 if (! gimple_in_ssa_p (cfun))
642 const char *name = get_name (val);
643 if (name)
644 SET_SSA_NAME_VAR_OR_IDENTIFIER (t, create_tmp_var_name (name));
647 else
648 t = lookup_tmp_var (val, is_formal, not_gimple_reg);
650 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
652 SET_EXPR_LOCATION (mod, EXPR_LOC_OR_LOC (val, input_location));
654 /* gimplify_modify_expr might want to reduce this further. */
655 gimplify_and_add (mod, pre_p);
656 ggc_free (mod);
658 return t;
661 /* Return a formal temporary variable initialized with VAL. PRE_P is as
662 in gimplify_expr. Only use this function if:
664 1) The value of the unfactored expression represented by VAL will not
665 change between the initialization and use of the temporary, and
666 2) The temporary will not be otherwise modified.
668 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
669 and #2 means it is inappropriate for && temps.
671 For other cases, use get_initialized_tmp_var instead. */
673 tree
674 get_formal_tmp_var (tree val, gimple_seq *pre_p)
676 return internal_get_tmp_var (val, pre_p, NULL, true, true, false);
679 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
680 are as in gimplify_expr. */
682 tree
683 get_initialized_tmp_var (tree val, gimple_seq *pre_p,
684 gimple_seq *post_p /* = NULL */,
685 bool allow_ssa /* = true */)
687 return internal_get_tmp_var (val, pre_p, post_p, false, allow_ssa, false);
690 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
691 generate debug info for them; otherwise don't. */
693 void
694 declare_vars (tree vars, gimple *gs, bool debug_info)
696 tree last = vars;
697 if (last)
699 tree temps, block;
701 gbind *scope = as_a <gbind *> (gs);
703 temps = nreverse (last);
705 block = gimple_bind_block (scope);
706 gcc_assert (!block || TREE_CODE (block) == BLOCK);
707 if (!block || !debug_info)
709 DECL_CHAIN (last) = gimple_bind_vars (scope);
710 gimple_bind_set_vars (scope, temps);
712 else
714 /* We need to attach the nodes both to the BIND_EXPR and to its
715 associated BLOCK for debugging purposes. The key point here
716 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
717 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
718 if (BLOCK_VARS (block))
719 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
720 else
722 gimple_bind_set_vars (scope,
723 chainon (gimple_bind_vars (scope), temps));
724 BLOCK_VARS (block) = temps;
730 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
731 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
732 no such upper bound can be obtained. */
734 static void
735 force_constant_size (tree var)
737 /* The only attempt we make is by querying the maximum size of objects
738 of the variable's type. */
740 HOST_WIDE_INT max_size;
742 gcc_assert (VAR_P (var));
744 max_size = max_int_size_in_bytes (TREE_TYPE (var));
746 gcc_assert (max_size >= 0);
748 DECL_SIZE_UNIT (var)
749 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
750 DECL_SIZE (var)
751 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
754 /* Push the temporary variable TMP into the current binding. */
756 void
757 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
759 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
761 /* Later processing assumes that the object size is constant, which might
762 not be true at this point. Force the use of a constant upper bound in
763 this case. */
764 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
765 force_constant_size (tmp);
767 DECL_CONTEXT (tmp) = fn->decl;
768 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
770 record_vars_into (tmp, fn->decl);
773 /* Push the temporary variable TMP into the current binding. */
775 void
776 gimple_add_tmp_var (tree tmp)
778 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
780 /* Later processing assumes that the object size is constant, which might
781 not be true at this point. Force the use of a constant upper bound in
782 this case. */
783 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
784 force_constant_size (tmp);
786 DECL_CONTEXT (tmp) = current_function_decl;
787 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
789 if (gimplify_ctxp)
791 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
792 gimplify_ctxp->temps = tmp;
794 /* Mark temporaries local within the nearest enclosing parallel. */
795 if (gimplify_omp_ctxp)
797 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
798 int flag = GOVD_LOCAL | GOVD_SEEN;
799 while (ctx
800 && (ctx->region_type == ORT_WORKSHARE
801 || ctx->region_type == ORT_TASKGROUP
802 || ctx->region_type == ORT_SIMD
803 || ctx->region_type == ORT_ACC))
805 if (ctx->region_type == ORT_SIMD
806 && TREE_ADDRESSABLE (tmp)
807 && !TREE_STATIC (tmp))
809 if (TREE_CODE (DECL_SIZE_UNIT (tmp)) != INTEGER_CST)
810 ctx->add_safelen1 = true;
811 else if (ctx->in_for_exprs)
812 flag = GOVD_PRIVATE;
813 else
814 flag = GOVD_PRIVATE | GOVD_SEEN;
815 break;
817 ctx = ctx->outer_context;
819 if (ctx)
820 omp_add_variable (ctx, tmp, flag);
823 else if (cfun)
824 record_vars (tmp);
825 else
827 gimple_seq body_seq;
829 /* This case is for nested functions. We need to expose the locals
830 they create. */
831 body_seq = gimple_body (current_function_decl);
832 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
838 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
839 nodes that are referenced more than once in GENERIC functions. This is
840 necessary because gimplification (translation into GIMPLE) is performed
841 by modifying tree nodes in-place, so gimplication of a shared node in a
842 first context could generate an invalid GIMPLE form in a second context.
844 This is achieved with a simple mark/copy/unmark algorithm that walks the
845 GENERIC representation top-down, marks nodes with TREE_VISITED the first
846 time it encounters them, duplicates them if they already have TREE_VISITED
847 set, and finally removes the TREE_VISITED marks it has set.
849 The algorithm works only at the function level, i.e. it generates a GENERIC
850 representation of a function with no nodes shared within the function when
851 passed a GENERIC function (except for nodes that are allowed to be shared).
853 At the global level, it is also necessary to unshare tree nodes that are
854 referenced in more than one function, for the same aforementioned reason.
855 This requires some cooperation from the front-end. There are 2 strategies:
857 1. Manual unsharing. The front-end needs to call unshare_expr on every
858 expression that might end up being shared across functions.
860 2. Deep unsharing. This is an extension of regular unsharing. Instead
861 of calling unshare_expr on expressions that might be shared across
862 functions, the front-end pre-marks them with TREE_VISITED. This will
863 ensure that they are unshared on the first reference within functions
864 when the regular unsharing algorithm runs. The counterpart is that
865 this algorithm must look deeper than for manual unsharing, which is
866 specified by LANG_HOOKS_DEEP_UNSHARING.
868 If there are only few specific cases of node sharing across functions, it is
869 probably easier for a front-end to unshare the expressions manually. On the
870 contrary, if the expressions generated at the global level are as widespread
871 as expressions generated within functions, deep unsharing is very likely the
872 way to go. */
874 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
875 These nodes model computations that must be done once. If we were to
876 unshare something like SAVE_EXPR(i++), the gimplification process would
877 create wrong code. However, if DATA is non-null, it must hold a pointer
878 set that is used to unshare the subtrees of these nodes. */
880 static tree
881 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
883 tree t = *tp;
884 enum tree_code code = TREE_CODE (t);
886 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
887 copy their subtrees if we can make sure to do it only once. */
888 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
890 if (data && !((hash_set<tree> *)data)->add (t))
892 else
893 *walk_subtrees = 0;
896 /* Stop at types, decls, constants like copy_tree_r. */
897 else if (TREE_CODE_CLASS (code) == tcc_type
898 || TREE_CODE_CLASS (code) == tcc_declaration
899 || TREE_CODE_CLASS (code) == tcc_constant)
900 *walk_subtrees = 0;
902 /* Cope with the statement expression extension. */
903 else if (code == STATEMENT_LIST)
906 /* Leave the bulk of the work to copy_tree_r itself. */
907 else
908 copy_tree_r (tp, walk_subtrees, NULL);
910 return NULL_TREE;
913 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
914 If *TP has been visited already, then *TP is deeply copied by calling
915 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
917 static tree
918 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
920 tree t = *tp;
921 enum tree_code code = TREE_CODE (t);
923 /* Skip types, decls, and constants. But we do want to look at their
924 types and the bounds of types. Mark them as visited so we properly
925 unmark their subtrees on the unmark pass. If we've already seen them,
926 don't look down further. */
927 if (TREE_CODE_CLASS (code) == tcc_type
928 || TREE_CODE_CLASS (code) == tcc_declaration
929 || TREE_CODE_CLASS (code) == tcc_constant)
931 if (TREE_VISITED (t))
932 *walk_subtrees = 0;
933 else
934 TREE_VISITED (t) = 1;
937 /* If this node has been visited already, unshare it and don't look
938 any deeper. */
939 else if (TREE_VISITED (t))
941 walk_tree (tp, mostly_copy_tree_r, data, NULL);
942 *walk_subtrees = 0;
945 /* Otherwise, mark the node as visited and keep looking. */
946 else
947 TREE_VISITED (t) = 1;
949 return NULL_TREE;
952 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
953 copy_if_shared_r callback unmodified. */
955 void
956 copy_if_shared (tree *tp, void *data)
958 walk_tree (tp, copy_if_shared_r, data, NULL);
961 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
962 any nested functions. */
964 static void
965 unshare_body (tree fndecl)
967 struct cgraph_node *cgn = cgraph_node::get (fndecl);
968 /* If the language requires deep unsharing, we need a pointer set to make
969 sure we don't repeatedly unshare subtrees of unshareable nodes. */
970 hash_set<tree> *visited
971 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
973 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
974 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
975 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
977 delete visited;
979 if (cgn)
980 for (cgn = first_nested_function (cgn); cgn;
981 cgn = next_nested_function (cgn))
982 unshare_body (cgn->decl);
985 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
986 Subtrees are walked until the first unvisited node is encountered. */
988 static tree
989 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
991 tree t = *tp;
993 /* If this node has been visited, unmark it and keep looking. */
994 if (TREE_VISITED (t))
995 TREE_VISITED (t) = 0;
997 /* Otherwise, don't look any deeper. */
998 else
999 *walk_subtrees = 0;
1001 return NULL_TREE;
1004 /* Unmark the visited trees rooted at *TP. */
1006 static inline void
1007 unmark_visited (tree *tp)
1009 walk_tree (tp, unmark_visited_r, NULL, NULL);
1012 /* Likewise, but mark all trees as not visited. */
1014 static void
1015 unvisit_body (tree fndecl)
1017 struct cgraph_node *cgn = cgraph_node::get (fndecl);
1019 unmark_visited (&DECL_SAVED_TREE (fndecl));
1020 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
1021 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
1023 if (cgn)
1024 for (cgn = first_nested_function (cgn);
1025 cgn; cgn = next_nested_function (cgn))
1026 unvisit_body (cgn->decl);
1029 /* Unconditionally make an unshared copy of EXPR. This is used when using
1030 stored expressions which span multiple functions, such as BINFO_VTABLE,
1031 as the normal unsharing process can't tell that they're shared. */
1033 tree
1034 unshare_expr (tree expr)
1036 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1037 return expr;
1040 /* Worker for unshare_expr_without_location. */
1042 static tree
1043 prune_expr_location (tree *tp, int *walk_subtrees, void *)
1045 if (EXPR_P (*tp))
1046 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
1047 else
1048 *walk_subtrees = 0;
1049 return NULL_TREE;
1052 /* Similar to unshare_expr but also prune all expression locations
1053 from EXPR. */
1055 tree
1056 unshare_expr_without_location (tree expr)
1058 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1059 if (EXPR_P (expr))
1060 walk_tree (&expr, prune_expr_location, NULL, NULL);
1061 return expr;
1064 /* Return the EXPR_LOCATION of EXPR, if it (maybe recursively) has
1065 one, OR_ELSE otherwise. The location of a STATEMENT_LISTs
1066 comprising at least one DEBUG_BEGIN_STMT followed by exactly one
1067 EXPR is the location of the EXPR. */
1069 static location_t
1070 rexpr_location (tree expr, location_t or_else = UNKNOWN_LOCATION)
1072 if (!expr)
1073 return or_else;
1075 if (EXPR_HAS_LOCATION (expr))
1076 return EXPR_LOCATION (expr);
1078 if (TREE_CODE (expr) != STATEMENT_LIST)
1079 return or_else;
1081 tree_stmt_iterator i = tsi_start (expr);
1083 bool found = false;
1084 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
1086 found = true;
1087 tsi_next (&i);
1090 if (!found || !tsi_one_before_end_p (i))
1091 return or_else;
1093 return rexpr_location (tsi_stmt (i), or_else);
1096 /* Return TRUE iff EXPR (maybe recursively) has a location; see
1097 rexpr_location for the potential recursion. */
1099 static inline bool
1100 rexpr_has_location (tree expr)
1102 return rexpr_location (expr) != UNKNOWN_LOCATION;
1106 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
1107 contain statements and have a value. Assign its value to a temporary
1108 and give it void_type_node. Return the temporary, or NULL_TREE if
1109 WRAPPER was already void. */
1111 tree
1112 voidify_wrapper_expr (tree wrapper, tree temp)
1114 tree type = TREE_TYPE (wrapper);
1115 if (type && !VOID_TYPE_P (type))
1117 tree *p;
1119 /* Set p to point to the body of the wrapper. Loop until we find
1120 something that isn't a wrapper. */
1121 for (p = &wrapper; p && *p; )
1123 switch (TREE_CODE (*p))
1125 case BIND_EXPR:
1126 TREE_SIDE_EFFECTS (*p) = 1;
1127 TREE_TYPE (*p) = void_type_node;
1128 /* For a BIND_EXPR, the body is operand 1. */
1129 p = &BIND_EXPR_BODY (*p);
1130 break;
1132 case CLEANUP_POINT_EXPR:
1133 case TRY_FINALLY_EXPR:
1134 case TRY_CATCH_EXPR:
1135 TREE_SIDE_EFFECTS (*p) = 1;
1136 TREE_TYPE (*p) = void_type_node;
1137 p = &TREE_OPERAND (*p, 0);
1138 break;
1140 case STATEMENT_LIST:
1142 tree_stmt_iterator i = tsi_last (*p);
1143 TREE_SIDE_EFFECTS (*p) = 1;
1144 TREE_TYPE (*p) = void_type_node;
1145 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
1147 break;
1149 case COMPOUND_EXPR:
1150 /* Advance to the last statement. Set all container types to
1151 void. */
1152 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
1154 TREE_SIDE_EFFECTS (*p) = 1;
1155 TREE_TYPE (*p) = void_type_node;
1157 break;
1159 case TRANSACTION_EXPR:
1160 TREE_SIDE_EFFECTS (*p) = 1;
1161 TREE_TYPE (*p) = void_type_node;
1162 p = &TRANSACTION_EXPR_BODY (*p);
1163 break;
1165 default:
1166 /* Assume that any tree upon which voidify_wrapper_expr is
1167 directly called is a wrapper, and that its body is op0. */
1168 if (p == &wrapper)
1170 TREE_SIDE_EFFECTS (*p) = 1;
1171 TREE_TYPE (*p) = void_type_node;
1172 p = &TREE_OPERAND (*p, 0);
1173 break;
1175 goto out;
1179 out:
1180 if (p == NULL || IS_EMPTY_STMT (*p))
1181 temp = NULL_TREE;
1182 else if (temp)
1184 /* The wrapper is on the RHS of an assignment that we're pushing
1185 down. */
1186 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1187 || TREE_CODE (temp) == MODIFY_EXPR);
1188 TREE_OPERAND (temp, 1) = *p;
1189 *p = temp;
1191 else
1193 temp = create_tmp_var (type, "retval");
1194 *p = build2 (INIT_EXPR, type, temp, *p);
1197 return temp;
1200 return NULL_TREE;
1203 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1204 a temporary through which they communicate. */
1206 static void
1207 build_stack_save_restore (gcall **save, gcall **restore)
1209 tree tmp_var;
1211 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1212 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1213 gimple_call_set_lhs (*save, tmp_var);
1215 *restore
1216 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1217 1, tmp_var);
1220 /* Generate IFN_ASAN_MARK call that poisons shadow of a for DECL variable. */
1222 static tree
1223 build_asan_poison_call_expr (tree decl)
1225 /* Do not poison variables that have size equal to zero. */
1226 tree unit_size = DECL_SIZE_UNIT (decl);
1227 if (zerop (unit_size))
1228 return NULL_TREE;
1230 tree base = build_fold_addr_expr (decl);
1232 return build_call_expr_internal_loc (UNKNOWN_LOCATION, IFN_ASAN_MARK,
1233 void_type_node, 3,
1234 build_int_cst (integer_type_node,
1235 ASAN_MARK_POISON),
1236 base, unit_size);
1239 /* Generate IFN_ASAN_MARK call that would poison or unpoison, depending
1240 on POISON flag, shadow memory of a DECL variable. The call will be
1241 put on location identified by IT iterator, where BEFORE flag drives
1242 position where the stmt will be put. */
1244 static void
1245 asan_poison_variable (tree decl, bool poison, gimple_stmt_iterator *it,
1246 bool before)
1248 tree unit_size = DECL_SIZE_UNIT (decl);
1249 tree base = build_fold_addr_expr (decl);
1251 /* Do not poison variables that have size equal to zero. */
1252 if (zerop (unit_size))
1253 return;
1255 /* It's necessary to have all stack variables aligned to ASAN granularity
1256 bytes. */
1257 gcc_assert (!hwasan_sanitize_p () || hwasan_sanitize_stack_p ());
1258 unsigned shadow_granularity
1259 = hwasan_sanitize_p () ? HWASAN_TAG_GRANULE_SIZE : ASAN_SHADOW_GRANULARITY;
1260 if (DECL_ALIGN_UNIT (decl) <= shadow_granularity)
1261 SET_DECL_ALIGN (decl, BITS_PER_UNIT * shadow_granularity);
1263 HOST_WIDE_INT flags = poison ? ASAN_MARK_POISON : ASAN_MARK_UNPOISON;
1265 gimple *g
1266 = gimple_build_call_internal (IFN_ASAN_MARK, 3,
1267 build_int_cst (integer_type_node, flags),
1268 base, unit_size);
1270 if (before)
1271 gsi_insert_before (it, g, GSI_NEW_STMT);
1272 else
1273 gsi_insert_after (it, g, GSI_NEW_STMT);
1276 /* Generate IFN_ASAN_MARK internal call that depending on POISON flag
1277 either poisons or unpoisons a DECL. Created statement is appended
1278 to SEQ_P gimple sequence. */
1280 static void
1281 asan_poison_variable (tree decl, bool poison, gimple_seq *seq_p)
1283 gimple_stmt_iterator it = gsi_last (*seq_p);
1284 bool before = false;
1286 if (gsi_end_p (it))
1287 before = true;
1289 asan_poison_variable (decl, poison, &it, before);
1292 /* Sort pair of VAR_DECLs A and B by DECL_UID. */
1294 static int
1295 sort_by_decl_uid (const void *a, const void *b)
1297 const tree *t1 = (const tree *)a;
1298 const tree *t2 = (const tree *)b;
1300 int uid1 = DECL_UID (*t1);
1301 int uid2 = DECL_UID (*t2);
1303 if (uid1 < uid2)
1304 return -1;
1305 else if (uid1 > uid2)
1306 return 1;
1307 else
1308 return 0;
1311 /* Generate IFN_ASAN_MARK internal call for all VARIABLES
1312 depending on POISON flag. Created statement is appended
1313 to SEQ_P gimple sequence. */
1315 static void
1316 asan_poison_variables (hash_set<tree> *variables, bool poison, gimple_seq *seq_p)
1318 unsigned c = variables->elements ();
1319 if (c == 0)
1320 return;
1322 auto_vec<tree> sorted_variables (c);
1324 for (hash_set<tree>::iterator it = variables->begin ();
1325 it != variables->end (); ++it)
1326 sorted_variables.safe_push (*it);
1328 sorted_variables.qsort (sort_by_decl_uid);
1330 unsigned i;
1331 tree var;
1332 FOR_EACH_VEC_ELT (sorted_variables, i, var)
1334 asan_poison_variable (var, poison, seq_p);
1336 /* Add use_after_scope_memory attribute for the variable in order
1337 to prevent re-written into SSA. */
1338 if (!lookup_attribute (ASAN_USE_AFTER_SCOPE_ATTRIBUTE,
1339 DECL_ATTRIBUTES (var)))
1340 DECL_ATTRIBUTES (var)
1341 = tree_cons (get_identifier (ASAN_USE_AFTER_SCOPE_ATTRIBUTE),
1342 integer_one_node,
1343 DECL_ATTRIBUTES (var));
1347 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1349 static enum gimplify_status
1350 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1352 tree bind_expr = *expr_p;
1353 bool old_keep_stack = gimplify_ctxp->keep_stack;
1354 bool old_save_stack = gimplify_ctxp->save_stack;
1355 tree t;
1356 gbind *bind_stmt;
1357 gimple_seq body, cleanup;
1358 gcall *stack_save;
1359 location_t start_locus = 0, end_locus = 0;
1360 tree ret_clauses = NULL;
1362 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1364 /* Mark variables seen in this bind expr. */
1365 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1367 if (VAR_P (t))
1369 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1371 /* Mark variable as local. */
1372 if (ctx && ctx->region_type != ORT_NONE && !DECL_EXTERNAL (t))
1374 if (! DECL_SEEN_IN_BIND_EXPR_P (t)
1375 || splay_tree_lookup (ctx->variables,
1376 (splay_tree_key) t) == NULL)
1378 int flag = GOVD_LOCAL;
1379 if (ctx->region_type == ORT_SIMD
1380 && TREE_ADDRESSABLE (t)
1381 && !TREE_STATIC (t))
1383 if (TREE_CODE (DECL_SIZE_UNIT (t)) != INTEGER_CST)
1384 ctx->add_safelen1 = true;
1385 else
1386 flag = GOVD_PRIVATE;
1388 omp_add_variable (ctx, t, flag | GOVD_SEEN);
1390 /* Static locals inside of target construct or offloaded
1391 routines need to be "omp declare target". */
1392 if (TREE_STATIC (t))
1393 for (; ctx; ctx = ctx->outer_context)
1394 if ((ctx->region_type & ORT_TARGET) != 0)
1396 if (!lookup_attribute ("omp declare target",
1397 DECL_ATTRIBUTES (t)))
1399 tree id = get_identifier ("omp declare target");
1400 DECL_ATTRIBUTES (t)
1401 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (t));
1402 varpool_node *node = varpool_node::get (t);
1403 if (node)
1405 node->offloadable = 1;
1406 if (ENABLE_OFFLOADING && !DECL_EXTERNAL (t))
1408 g->have_offload = true;
1409 if (!in_lto_p)
1410 vec_safe_push (offload_vars, t);
1414 break;
1418 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1420 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1421 cfun->has_local_explicit_reg_vars = true;
1425 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1426 BIND_EXPR_BLOCK (bind_expr));
1427 gimple_push_bind_expr (bind_stmt);
1429 gimplify_ctxp->keep_stack = false;
1430 gimplify_ctxp->save_stack = false;
1432 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1433 body = NULL;
1434 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1435 gimple_bind_set_body (bind_stmt, body);
1437 /* Source location wise, the cleanup code (stack_restore and clobbers)
1438 belongs to the end of the block, so propagate what we have. The
1439 stack_save operation belongs to the beginning of block, which we can
1440 infer from the bind_expr directly if the block has no explicit
1441 assignment. */
1442 if (BIND_EXPR_BLOCK (bind_expr))
1444 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1445 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1447 if (start_locus == 0)
1448 start_locus = EXPR_LOCATION (bind_expr);
1450 cleanup = NULL;
1451 stack_save = NULL;
1453 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1454 the stack space allocated to the VLAs. */
1455 if (gimplify_ctxp->save_stack && !gimplify_ctxp->keep_stack)
1457 gcall *stack_restore;
1459 /* Save stack on entry and restore it on exit. Add a try_finally
1460 block to achieve this. */
1461 build_stack_save_restore (&stack_save, &stack_restore);
1463 gimple_set_location (stack_save, start_locus);
1464 gimple_set_location (stack_restore, end_locus);
1466 gimplify_seq_add_stmt (&cleanup, stack_restore);
1469 /* Add clobbers for all variables that go out of scope. */
1470 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1472 if (VAR_P (t)
1473 && !is_global_var (t)
1474 && DECL_CONTEXT (t) == current_function_decl)
1476 if (!DECL_HARD_REGISTER (t)
1477 && !TREE_THIS_VOLATILE (t)
1478 && !DECL_HAS_VALUE_EXPR_P (t)
1479 /* Only care for variables that have to be in memory. Others
1480 will be rewritten into SSA names, hence moved to the
1481 top-level. */
1482 && !is_gimple_reg (t)
1483 && flag_stack_reuse != SR_NONE)
1485 tree clobber = build_clobber (TREE_TYPE (t), CLOBBER_EOL);
1486 gimple *clobber_stmt;
1487 clobber_stmt = gimple_build_assign (t, clobber);
1488 gimple_set_location (clobber_stmt, end_locus);
1489 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1492 if (flag_openacc && oacc_declare_returns != NULL)
1494 tree key = t;
1495 if (DECL_HAS_VALUE_EXPR_P (key))
1497 key = DECL_VALUE_EXPR (key);
1498 if (TREE_CODE (key) == INDIRECT_REF)
1499 key = TREE_OPERAND (key, 0);
1501 tree *c = oacc_declare_returns->get (key);
1502 if (c != NULL)
1504 if (ret_clauses)
1505 OMP_CLAUSE_CHAIN (*c) = ret_clauses;
1507 ret_clauses = unshare_expr (*c);
1509 oacc_declare_returns->remove (key);
1511 if (oacc_declare_returns->is_empty ())
1513 delete oacc_declare_returns;
1514 oacc_declare_returns = NULL;
1520 if (asan_poisoned_variables != NULL
1521 && asan_poisoned_variables->contains (t))
1523 asan_poisoned_variables->remove (t);
1524 asan_poison_variable (t, true, &cleanup);
1527 if (gimplify_ctxp->live_switch_vars != NULL
1528 && gimplify_ctxp->live_switch_vars->contains (t))
1529 gimplify_ctxp->live_switch_vars->remove (t);
1532 if (ret_clauses)
1534 gomp_target *stmt;
1535 gimple_stmt_iterator si = gsi_start (cleanup);
1537 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
1538 ret_clauses);
1539 gsi_insert_seq_before_without_update (&si, stmt, GSI_NEW_STMT);
1542 if (cleanup)
1544 gtry *gs;
1545 gimple_seq new_body;
1547 new_body = NULL;
1548 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1549 GIMPLE_TRY_FINALLY);
1551 if (stack_save)
1552 gimplify_seq_add_stmt (&new_body, stack_save);
1553 gimplify_seq_add_stmt (&new_body, gs);
1554 gimple_bind_set_body (bind_stmt, new_body);
1557 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1558 if (!gimplify_ctxp->keep_stack)
1559 gimplify_ctxp->keep_stack = old_keep_stack;
1560 gimplify_ctxp->save_stack = old_save_stack;
1562 gimple_pop_bind_expr ();
1564 gimplify_seq_add_stmt (pre_p, bind_stmt);
1566 if (temp)
1568 *expr_p = temp;
1569 return GS_OK;
1572 *expr_p = NULL_TREE;
1573 return GS_ALL_DONE;
1576 /* Maybe add early return predict statement to PRE_P sequence. */
1578 static void
1579 maybe_add_early_return_predict_stmt (gimple_seq *pre_p)
1581 /* If we are not in a conditional context, add PREDICT statement. */
1582 if (gimple_conditional_context ())
1584 gimple *predict = gimple_build_predict (PRED_TREE_EARLY_RETURN,
1585 NOT_TAKEN);
1586 gimplify_seq_add_stmt (pre_p, predict);
1590 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1591 GIMPLE value, it is assigned to a new temporary and the statement is
1592 re-written to return the temporary.
1594 PRE_P points to the sequence where side effects that must happen before
1595 STMT should be stored. */
1597 static enum gimplify_status
1598 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1600 greturn *ret;
1601 tree ret_expr = TREE_OPERAND (stmt, 0);
1602 tree result_decl, result;
1604 if (ret_expr == error_mark_node)
1605 return GS_ERROR;
1607 if (!ret_expr
1608 || TREE_CODE (ret_expr) == RESULT_DECL)
1610 maybe_add_early_return_predict_stmt (pre_p);
1611 greturn *ret = gimple_build_return (ret_expr);
1612 copy_warning (ret, stmt);
1613 gimplify_seq_add_stmt (pre_p, ret);
1614 return GS_ALL_DONE;
1617 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1618 result_decl = NULL_TREE;
1619 else if (TREE_CODE (ret_expr) == COMPOUND_EXPR)
1621 /* Used in C++ for handling EH cleanup of the return value if a local
1622 cleanup throws. Assume the front-end knows what it's doing. */
1623 result_decl = DECL_RESULT (current_function_decl);
1624 /* But crash if we end up trying to modify ret_expr below. */
1625 ret_expr = NULL_TREE;
1627 else
1629 result_decl = TREE_OPERAND (ret_expr, 0);
1631 /* See through a return by reference. */
1632 if (TREE_CODE (result_decl) == INDIRECT_REF)
1633 result_decl = TREE_OPERAND (result_decl, 0);
1635 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1636 || TREE_CODE (ret_expr) == INIT_EXPR)
1637 && TREE_CODE (result_decl) == RESULT_DECL);
1640 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1641 Recall that aggregate_value_p is FALSE for any aggregate type that is
1642 returned in registers. If we're returning values in registers, then
1643 we don't want to extend the lifetime of the RESULT_DECL, particularly
1644 across another call. In addition, for those aggregates for which
1645 hard_function_value generates a PARALLEL, we'll die during normal
1646 expansion of structure assignments; there's special code in expand_return
1647 to handle this case that does not exist in expand_expr. */
1648 if (!result_decl)
1649 result = NULL_TREE;
1650 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1652 if (!poly_int_tree_p (DECL_SIZE (result_decl)))
1654 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1655 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1656 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1657 should be effectively allocated by the caller, i.e. all calls to
1658 this function must be subject to the Return Slot Optimization. */
1659 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1660 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1662 result = result_decl;
1664 else if (gimplify_ctxp->return_temp)
1665 result = gimplify_ctxp->return_temp;
1666 else
1668 result = create_tmp_reg (TREE_TYPE (result_decl));
1670 /* ??? With complex control flow (usually involving abnormal edges),
1671 we can wind up warning about an uninitialized value for this. Due
1672 to how this variable is constructed and initialized, this is never
1673 true. Give up and never warn. */
1674 suppress_warning (result, OPT_Wuninitialized);
1676 gimplify_ctxp->return_temp = result;
1679 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1680 Then gimplify the whole thing. */
1681 if (result != result_decl)
1682 TREE_OPERAND (ret_expr, 0) = result;
1684 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1686 maybe_add_early_return_predict_stmt (pre_p);
1687 ret = gimple_build_return (result);
1688 copy_warning (ret, stmt);
1689 gimplify_seq_add_stmt (pre_p, ret);
1691 return GS_ALL_DONE;
1694 /* Gimplify a variable-length array DECL. */
1696 static void
1697 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1699 /* This is a variable-sized decl. Simplify its size and mark it
1700 for deferred expansion. */
1701 tree t, addr, ptr_type;
1703 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1704 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1706 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1707 if (DECL_HAS_VALUE_EXPR_P (decl))
1708 return;
1710 /* All occurrences of this decl in final gimplified code will be
1711 replaced by indirection. Setting DECL_VALUE_EXPR does two
1712 things: First, it lets the rest of the gimplifier know what
1713 replacement to use. Second, it lets the debug info know
1714 where to find the value. */
1715 ptr_type = build_pointer_type (TREE_TYPE (decl));
1716 addr = create_tmp_var (ptr_type, get_name (decl));
1717 DECL_IGNORED_P (addr) = 0;
1718 t = build_fold_indirect_ref (addr);
1719 TREE_THIS_NOTRAP (t) = 1;
1720 SET_DECL_VALUE_EXPR (decl, t);
1721 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1723 t = build_alloca_call_expr (DECL_SIZE_UNIT (decl), DECL_ALIGN (decl),
1724 max_int_size_in_bytes (TREE_TYPE (decl)));
1725 /* The call has been built for a variable-sized object. */
1726 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1727 t = fold_convert (ptr_type, t);
1728 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1730 gimplify_and_add (t, seq_p);
1732 /* Record the dynamic allocation associated with DECL if requested. */
1733 if (flag_callgraph_info & CALLGRAPH_INFO_DYNAMIC_ALLOC)
1734 record_dynamic_alloc (decl);
1737 /* A helper function to be called via walk_tree. Mark all labels under *TP
1738 as being forced. To be called for DECL_INITIAL of static variables. */
1740 static tree
1741 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1743 if (TYPE_P (*tp))
1744 *walk_subtrees = 0;
1745 if (TREE_CODE (*tp) == LABEL_DECL)
1747 FORCED_LABEL (*tp) = 1;
1748 cfun->has_forced_label_in_static = 1;
1751 return NULL_TREE;
1754 /* Generate an initialization to automatic variable DECL based on INIT_TYPE.
1755 Build a call to internal const function DEFERRED_INIT:
1756 1st argument: SIZE of the DECL;
1757 2nd argument: INIT_TYPE;
1758 3rd argument: NAME of the DECL;
1760 as LHS = DEFERRED_INIT (SIZE of the DECL, INIT_TYPE, NAME of the DECL). */
1762 static void
1763 gimple_add_init_for_auto_var (tree decl,
1764 enum auto_init_type init_type,
1765 gimple_seq *seq_p)
1767 gcc_assert (auto_var_p (decl));
1768 gcc_assert (init_type > AUTO_INIT_UNINITIALIZED);
1769 location_t loc = EXPR_LOCATION (decl);
1770 tree decl_size = TYPE_SIZE_UNIT (TREE_TYPE (decl));
1772 tree init_type_node
1773 = build_int_cst (integer_type_node, (int) init_type);
1775 tree decl_name = NULL_TREE;
1776 if (DECL_NAME (decl))
1778 decl_name = build_string_literal (IDENTIFIER_LENGTH (DECL_NAME (decl)) + 1,
1779 IDENTIFIER_POINTER (DECL_NAME (decl)));
1781 else
1783 char *decl_name_anonymous = xasprintf ("D.%u", DECL_UID (decl));
1784 decl_name = build_string_literal (strlen (decl_name_anonymous) + 1,
1785 decl_name_anonymous);
1786 free (decl_name_anonymous);
1789 tree call = build_call_expr_internal_loc (loc, IFN_DEFERRED_INIT,
1790 TREE_TYPE (decl), 3,
1791 decl_size, init_type_node,
1792 decl_name);
1794 gimplify_assign (decl, call, seq_p);
1797 /* Generate padding initialization for automatic vairable DECL.
1798 C guarantees that brace-init with fewer initializers than members
1799 aggregate will initialize the rest of the aggregate as-if it were
1800 static initialization. In turn static initialization guarantees
1801 that padding is initialized to zero. So, we always initialize paddings
1802 to zeroes regardless INIT_TYPE.
1803 To do the padding initialization, we insert a call to
1804 __builtin_clear_padding (&decl, 0, for_auto_init = true).
1805 Note, we add an additional dummy argument for __builtin_clear_padding,
1806 'for_auto_init' to distinguish whether this call is for automatic
1807 variable initialization or not.
1809 static void
1810 gimple_add_padding_init_for_auto_var (tree decl, bool is_vla,
1811 gimple_seq *seq_p)
1813 tree addr_of_decl = NULL_TREE;
1814 tree fn = builtin_decl_explicit (BUILT_IN_CLEAR_PADDING);
1816 if (is_vla)
1818 /* The temporary address variable for this vla should be
1819 created in gimplify_vla_decl. */
1820 gcc_assert (DECL_HAS_VALUE_EXPR_P (decl));
1821 gcc_assert (TREE_CODE (DECL_VALUE_EXPR (decl)) == INDIRECT_REF);
1822 addr_of_decl = TREE_OPERAND (DECL_VALUE_EXPR (decl), 0);
1824 else
1826 mark_addressable (decl);
1827 addr_of_decl = build_fold_addr_expr (decl);
1830 gimple *call = gimple_build_call (fn, 2, addr_of_decl,
1831 build_one_cst (TREE_TYPE (addr_of_decl)));
1832 gimplify_seq_add_stmt (seq_p, call);
1835 /* Return true if the DECL need to be automaticly initialized by the
1836 compiler. */
1837 static bool
1838 is_var_need_auto_init (tree decl)
1840 if (auto_var_p (decl)
1841 && (TREE_CODE (decl) != VAR_DECL
1842 || !DECL_HARD_REGISTER (decl))
1843 && (flag_auto_var_init > AUTO_INIT_UNINITIALIZED)
1844 && (!lookup_attribute ("uninitialized", DECL_ATTRIBUTES (decl)))
1845 && !OPAQUE_TYPE_P (TREE_TYPE (decl))
1846 && !is_empty_type (TREE_TYPE (decl)))
1847 return true;
1848 return false;
1851 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1852 and initialization explicit. */
1854 static enum gimplify_status
1855 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1857 tree stmt = *stmt_p;
1858 tree decl = DECL_EXPR_DECL (stmt);
1860 *stmt_p = NULL_TREE;
1862 if (TREE_TYPE (decl) == error_mark_node)
1863 return GS_ERROR;
1865 if ((TREE_CODE (decl) == TYPE_DECL
1866 || VAR_P (decl))
1867 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1869 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1870 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
1871 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
1874 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1875 in case its size expressions contain problematic nodes like CALL_EXPR. */
1876 if (TREE_CODE (decl) == TYPE_DECL
1877 && DECL_ORIGINAL_TYPE (decl)
1878 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1880 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1881 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
1882 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
1885 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
1887 tree init = DECL_INITIAL (decl);
1888 bool is_vla = false;
1889 /* Check whether a decl has FE created VALUE_EXPR here BEFORE
1890 gimplify_vla_decl creates VALUE_EXPR for a vla decl.
1891 If the decl has VALUE_EXPR that was created by FE (usually
1892 C++FE), it's a proxy varaible, and FE already initialized
1893 the VALUE_EXPR of it, we should not initialize it anymore. */
1894 bool decl_had_value_expr_p = DECL_HAS_VALUE_EXPR_P (decl);
1896 poly_uint64 size;
1897 if (!poly_int_tree_p (DECL_SIZE_UNIT (decl), &size)
1898 || (!TREE_STATIC (decl)
1899 && flag_stack_check == GENERIC_STACK_CHECK
1900 && maybe_gt (size,
1901 (unsigned HOST_WIDE_INT) STACK_CHECK_MAX_VAR_SIZE)))
1903 gimplify_vla_decl (decl, seq_p);
1904 is_vla = true;
1907 if (asan_poisoned_variables
1908 && !is_vla
1909 && TREE_ADDRESSABLE (decl)
1910 && !TREE_STATIC (decl)
1911 && !DECL_HAS_VALUE_EXPR_P (decl)
1912 && DECL_ALIGN (decl) <= MAX_SUPPORTED_STACK_ALIGNMENT
1913 && dbg_cnt (asan_use_after_scope)
1914 && !gimplify_omp_ctxp
1915 /* GNAT introduces temporaries to hold return values of calls in
1916 initializers of variables defined in other units, so the
1917 declaration of the variable is discarded completely. We do not
1918 want to issue poison calls for such dropped variables. */
1919 && (DECL_SEEN_IN_BIND_EXPR_P (decl)
1920 || (DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)))
1922 asan_poisoned_variables->add (decl);
1923 asan_poison_variable (decl, false, seq_p);
1924 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
1925 gimplify_ctxp->live_switch_vars->add (decl);
1928 /* Some front ends do not explicitly declare all anonymous
1929 artificial variables. We compensate here by declaring the
1930 variables, though it would be better if the front ends would
1931 explicitly declare them. */
1932 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1933 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1934 gimple_add_tmp_var (decl);
1936 if (init && init != error_mark_node)
1938 if (!TREE_STATIC (decl))
1940 DECL_INITIAL (decl) = NULL_TREE;
1941 init = build2 (INIT_EXPR, void_type_node, decl, init);
1942 gimplify_and_add (init, seq_p);
1943 ggc_free (init);
1944 /* Clear TREE_READONLY if we really have an initialization. */
1945 if (!DECL_INITIAL (decl)
1946 && !omp_privatize_by_reference (decl))
1947 TREE_READONLY (decl) = 0;
1949 else
1950 /* We must still examine initializers for static variables
1951 as they may contain a label address. */
1952 walk_tree (&init, force_labels_r, NULL, NULL);
1954 /* When there is no explicit initializer, if the user requested,
1955 We should insert an artifical initializer for this automatic
1956 variable. */
1957 else if (is_var_need_auto_init (decl)
1958 && !decl_had_value_expr_p)
1960 gimple_add_init_for_auto_var (decl,
1961 flag_auto_var_init,
1962 seq_p);
1963 /* The expanding of a call to the above .DEFERRED_INIT will apply
1964 block initialization to the whole space covered by this variable.
1965 As a result, all the paddings will be initialized to zeroes
1966 for zero initialization and 0xFE byte-repeatable patterns for
1967 pattern initialization.
1968 In order to make the paddings as zeroes for pattern init, We
1969 should add a call to __builtin_clear_padding to clear the
1970 paddings to zero in compatiple with CLANG.
1971 We cannot insert this call if the variable is a gimple register
1972 since __builtin_clear_padding will take the address of the
1973 variable. As a result, if a long double/_Complex long double
1974 variable will spilled into stack later, its padding is 0XFE. */
1975 if (flag_auto_var_init == AUTO_INIT_PATTERN
1976 && !is_gimple_reg (decl)
1977 && clear_padding_type_may_have_padding_p (TREE_TYPE (decl)))
1978 gimple_add_padding_init_for_auto_var (decl, is_vla, seq_p);
1982 return GS_ALL_DONE;
1985 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1986 and replacing the LOOP_EXPR with goto, but if the loop contains an
1987 EXIT_EXPR, we need to append a label for it to jump to. */
1989 static enum gimplify_status
1990 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1992 tree saved_label = gimplify_ctxp->exit_label;
1993 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1995 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1997 gimplify_ctxp->exit_label = NULL_TREE;
1999 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
2001 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
2003 if (gimplify_ctxp->exit_label)
2004 gimplify_seq_add_stmt (pre_p,
2005 gimple_build_label (gimplify_ctxp->exit_label));
2007 gimplify_ctxp->exit_label = saved_label;
2009 *expr_p = NULL;
2010 return GS_ALL_DONE;
2013 /* Gimplify a statement list onto a sequence. These may be created either
2014 by an enlightened front-end, or by shortcut_cond_expr. */
2016 static enum gimplify_status
2017 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
2019 tree temp = voidify_wrapper_expr (*expr_p, NULL);
2021 tree_stmt_iterator i = tsi_start (*expr_p);
2023 while (!tsi_end_p (i))
2025 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
2026 tsi_delink (&i);
2029 if (temp)
2031 *expr_p = temp;
2032 return GS_OK;
2035 return GS_ALL_DONE;
2039 /* Emit warning for the unreachable statment STMT if needed.
2040 Return the gimple itself when the warning is emitted, otherwise
2041 return NULL. */
2042 static gimple *
2043 emit_warn_switch_unreachable (gimple *stmt)
2045 if (gimple_code (stmt) == GIMPLE_GOTO
2046 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
2047 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
2048 /* Don't warn for compiler-generated gotos. These occur
2049 in Duff's devices, for example. */
2050 return NULL;
2051 else if ((flag_auto_var_init > AUTO_INIT_UNINITIALIZED)
2052 && ((gimple_call_internal_p (stmt, IFN_DEFERRED_INIT))
2053 || (gimple_call_builtin_p (stmt, BUILT_IN_CLEAR_PADDING)
2054 && (bool) TREE_INT_CST_LOW (gimple_call_arg (stmt, 1)))
2055 || (is_gimple_assign (stmt)
2056 && gimple_assign_single_p (stmt)
2057 && (TREE_CODE (gimple_assign_rhs1 (stmt)) == SSA_NAME)
2058 && gimple_call_internal_p (
2059 SSA_NAME_DEF_STMT (gimple_assign_rhs1 (stmt)),
2060 IFN_DEFERRED_INIT))))
2061 /* Don't warn for compiler-generated initializations for
2062 -ftrivial-auto-var-init.
2063 There are 3 cases:
2064 case 1: a call to .DEFERRED_INIT;
2065 case 2: a call to __builtin_clear_padding with the 2nd argument is
2066 present and non-zero;
2067 case 3: a gimple assign store right after the call to .DEFERRED_INIT
2068 that has the LHS of .DEFERRED_INIT as the RHS as following:
2069 _1 = .DEFERRED_INIT (4, 2, &"i1"[0]);
2070 i1 = _1. */
2071 return NULL;
2072 else
2073 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
2074 "statement will never be executed");
2075 return stmt;
2078 /* Callback for walk_gimple_seq. */
2080 static tree
2081 warn_switch_unreachable_and_auto_init_r (gimple_stmt_iterator *gsi_p,
2082 bool *handled_ops_p,
2083 struct walk_stmt_info *wi)
2085 gimple *stmt = gsi_stmt (*gsi_p);
2086 bool unreachable_issued = wi->info != NULL;
2088 *handled_ops_p = true;
2089 switch (gimple_code (stmt))
2091 case GIMPLE_TRY:
2092 /* A compiler-generated cleanup or a user-written try block.
2093 If it's empty, don't dive into it--that would result in
2094 worse location info. */
2095 if (gimple_try_eval (stmt) == NULL)
2097 if (warn_switch_unreachable && !unreachable_issued)
2098 wi->info = emit_warn_switch_unreachable (stmt);
2100 /* Stop when auto var init warning is not on. */
2101 if (!warn_trivial_auto_var_init)
2102 return integer_zero_node;
2104 /* Fall through. */
2105 case GIMPLE_BIND:
2106 case GIMPLE_CATCH:
2107 case GIMPLE_EH_FILTER:
2108 case GIMPLE_TRANSACTION:
2109 /* Walk the sub-statements. */
2110 *handled_ops_p = false;
2111 break;
2113 case GIMPLE_DEBUG:
2114 /* Ignore these. We may generate them before declarations that
2115 are never executed. If there's something to warn about,
2116 there will be non-debug stmts too, and we'll catch those. */
2117 break;
2119 case GIMPLE_LABEL:
2120 /* Stop till the first Label. */
2121 return integer_zero_node;
2122 case GIMPLE_CALL:
2123 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2125 *handled_ops_p = false;
2126 break;
2128 if (warn_trivial_auto_var_init
2129 && flag_auto_var_init > AUTO_INIT_UNINITIALIZED
2130 && gimple_call_internal_p (stmt, IFN_DEFERRED_INIT))
2132 /* Get the variable name from the 3rd argument of call. */
2133 tree var_name = gimple_call_arg (stmt, 2);
2134 var_name = TREE_OPERAND (TREE_OPERAND (var_name, 0), 0);
2135 const char *var_name_str = TREE_STRING_POINTER (var_name);
2137 warning_at (gimple_location (stmt), OPT_Wtrivial_auto_var_init,
2138 "%qs cannot be initialized with"
2139 "%<-ftrivial-auto-var_init%>",
2140 var_name_str);
2141 break;
2144 /* Fall through. */
2145 default:
2146 /* check the first "real" statement (not a decl/lexical scope/...), issue
2147 warning if needed. */
2148 if (warn_switch_unreachable && !unreachable_issued)
2149 wi->info = emit_warn_switch_unreachable (stmt);
2150 /* Stop when auto var init warning is not on. */
2151 if (!warn_trivial_auto_var_init)
2152 return integer_zero_node;
2153 break;
2155 return NULL_TREE;
2159 /* Possibly warn about unreachable statements between switch's controlling
2160 expression and the first case. Also warn about -ftrivial-auto-var-init
2161 cannot initialize the auto variable under such situation.
2162 SEQ is the body of a switch expression. */
2164 static void
2165 maybe_warn_switch_unreachable_and_auto_init (gimple_seq seq)
2167 if ((!warn_switch_unreachable && !warn_trivial_auto_var_init)
2168 /* This warning doesn't play well with Fortran when optimizations
2169 are on. */
2170 || lang_GNU_Fortran ()
2171 || seq == NULL)
2172 return;
2174 struct walk_stmt_info wi;
2176 memset (&wi, 0, sizeof (wi));
2177 walk_gimple_seq (seq, warn_switch_unreachable_and_auto_init_r, NULL, &wi);
2181 /* A label entry that pairs label and a location. */
2182 struct label_entry
2184 tree label;
2185 location_t loc;
2188 /* Find LABEL in vector of label entries VEC. */
2190 static struct label_entry *
2191 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
2193 unsigned int i;
2194 struct label_entry *l;
2196 FOR_EACH_VEC_ELT (*vec, i, l)
2197 if (l->label == label)
2198 return l;
2199 return NULL;
2202 /* Return true if LABEL, a LABEL_DECL, represents a case label
2203 in a vector of labels CASES. */
2205 static bool
2206 case_label_p (const vec<tree> *cases, tree label)
2208 unsigned int i;
2209 tree l;
2211 FOR_EACH_VEC_ELT (*cases, i, l)
2212 if (CASE_LABEL (l) == label)
2213 return true;
2214 return false;
2217 /* Find the last nondebug statement in a scope STMT. */
2219 static gimple *
2220 last_stmt_in_scope (gimple *stmt)
2222 if (!stmt)
2223 return NULL;
2225 switch (gimple_code (stmt))
2227 case GIMPLE_BIND:
2229 gbind *bind = as_a <gbind *> (stmt);
2230 stmt = gimple_seq_last_nondebug_stmt (gimple_bind_body (bind));
2231 return last_stmt_in_scope (stmt);
2234 case GIMPLE_TRY:
2236 gtry *try_stmt = as_a <gtry *> (stmt);
2237 stmt = gimple_seq_last_nondebug_stmt (gimple_try_eval (try_stmt));
2238 gimple *last_eval = last_stmt_in_scope (stmt);
2239 if (gimple_stmt_may_fallthru (last_eval)
2240 && (last_eval == NULL
2241 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
2242 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
2244 stmt = gimple_seq_last_nondebug_stmt (gimple_try_cleanup (try_stmt));
2245 return last_stmt_in_scope (stmt);
2247 else
2248 return last_eval;
2251 case GIMPLE_DEBUG:
2252 gcc_unreachable ();
2254 default:
2255 return stmt;
2259 /* Collect labels that may fall through into LABELS and return the statement
2260 preceding another case label, or a user-defined label. Store a location
2261 useful to give warnings at *PREVLOC (usually the location of the returned
2262 statement or of its surrounding scope). */
2264 static gimple *
2265 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
2266 auto_vec <struct label_entry> *labels,
2267 location_t *prevloc)
2269 gimple *prev = NULL;
2271 *prevloc = UNKNOWN_LOCATION;
2274 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND)
2276 /* Recognize the special GIMPLE_BIND added by gimplify_switch_expr,
2277 which starts on a GIMPLE_SWITCH and ends with a break label.
2278 Handle that as a single statement that can fall through. */
2279 gbind *bind = as_a <gbind *> (gsi_stmt (*gsi_p));
2280 gimple *first = gimple_seq_first_stmt (gimple_bind_body (bind));
2281 gimple *last = gimple_seq_last_stmt (gimple_bind_body (bind));
2282 if (last
2283 && gimple_code (first) == GIMPLE_SWITCH
2284 && gimple_code (last) == GIMPLE_LABEL)
2286 tree label = gimple_label_label (as_a <glabel *> (last));
2287 if (SWITCH_BREAK_LABEL_P (label))
2289 prev = bind;
2290 gsi_next (gsi_p);
2291 continue;
2295 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
2296 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
2298 /* Nested scope. Only look at the last statement of
2299 the innermost scope. */
2300 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
2301 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
2302 if (last)
2304 prev = last;
2305 /* It might be a label without a location. Use the
2306 location of the scope then. */
2307 if (!gimple_has_location (prev))
2308 *prevloc = bind_loc;
2310 gsi_next (gsi_p);
2311 continue;
2314 /* Ifs are tricky. */
2315 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
2317 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
2318 tree false_lab = gimple_cond_false_label (cond_stmt);
2319 location_t if_loc = gimple_location (cond_stmt);
2321 /* If we have e.g.
2322 if (i > 1) goto <D.2259>; else goto D;
2323 we can't do much with the else-branch. */
2324 if (!DECL_ARTIFICIAL (false_lab))
2325 break;
2327 /* Go on until the false label, then one step back. */
2328 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
2330 gimple *stmt = gsi_stmt (*gsi_p);
2331 if (gimple_code (stmt) == GIMPLE_LABEL
2332 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
2333 break;
2336 /* Not found? Oops. */
2337 if (gsi_end_p (*gsi_p))
2338 break;
2340 /* A dead label can't fall through. */
2341 if (!UNUSED_LABEL_P (false_lab))
2343 struct label_entry l = { false_lab, if_loc };
2344 labels->safe_push (l);
2347 /* Go to the last statement of the then branch. */
2348 gsi_prev (gsi_p);
2350 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
2351 <D.1759>:
2352 <stmt>;
2353 goto <D.1761>;
2354 <D.1760>:
2356 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
2357 && !gimple_has_location (gsi_stmt (*gsi_p)))
2359 /* Look at the statement before, it might be
2360 attribute fallthrough, in which case don't warn. */
2361 gsi_prev (gsi_p);
2362 bool fallthru_before_dest
2363 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
2364 gsi_next (gsi_p);
2365 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
2366 if (!fallthru_before_dest)
2368 struct label_entry l = { goto_dest, if_loc };
2369 labels->safe_push (l);
2372 /* This case is about
2373 if (1 != 0) goto <D.2022>; else goto <D.2023>;
2374 <D.2022>:
2375 n = n + 1; // #1
2376 <D.2023>: // #2
2377 <D.1988>: // #3
2378 where #2 is UNUSED_LABEL_P and we want to warn about #1 falling
2379 through to #3. So set PREV to #1. */
2380 else if (UNUSED_LABEL_P (false_lab))
2381 prev = gsi_stmt (*gsi_p);
2383 /* And move back. */
2384 gsi_next (gsi_p);
2387 /* Remember the last statement. Skip labels that are of no interest
2388 to us. */
2389 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2391 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
2392 if (find_label_entry (labels, label))
2393 prev = gsi_stmt (*gsi_p);
2395 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
2397 else if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_PREDICT)
2399 else if (!is_gimple_debug (gsi_stmt (*gsi_p)))
2400 prev = gsi_stmt (*gsi_p);
2401 gsi_next (gsi_p);
2403 while (!gsi_end_p (*gsi_p)
2404 /* Stop if we find a case or a user-defined label. */
2405 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
2406 || !gimple_has_location (gsi_stmt (*gsi_p))));
2408 if (prev && gimple_has_location (prev))
2409 *prevloc = gimple_location (prev);
2410 return prev;
2413 /* Return true if the switch fallthough warning should occur. LABEL is
2414 the label statement that we're falling through to. */
2416 static bool
2417 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
2419 gimple_stmt_iterator gsi = *gsi_p;
2421 /* Don't warn if the label is marked with a "falls through" comment. */
2422 if (FALLTHROUGH_LABEL_P (label))
2423 return false;
2425 /* Don't warn for non-case labels followed by a statement:
2426 case 0:
2427 foo ();
2428 label:
2429 bar ();
2430 as these are likely intentional. */
2431 if (!case_label_p (&gimplify_ctxp->case_labels, label))
2433 tree l;
2434 while (!gsi_end_p (gsi)
2435 && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2436 && (l = gimple_label_label (as_a <glabel *> (gsi_stmt (gsi))))
2437 && !case_label_p (&gimplify_ctxp->case_labels, l))
2438 gsi_next_nondebug (&gsi);
2439 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
2440 return false;
2443 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2444 immediately breaks. */
2445 gsi = *gsi_p;
2447 /* Skip all immediately following labels. */
2448 while (!gsi_end_p (gsi)
2449 && (gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2450 || gimple_code (gsi_stmt (gsi)) == GIMPLE_PREDICT))
2451 gsi_next_nondebug (&gsi);
2453 /* { ... something; default:; } */
2454 if (gsi_end_p (gsi)
2455 /* { ... something; default: break; } or
2456 { ... something; default: goto L; } */
2457 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2458 /* { ... something; default: return; } */
2459 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2460 return false;
2462 return true;
2465 /* Callback for walk_gimple_seq. */
2467 static tree
2468 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2469 struct walk_stmt_info *)
2471 gimple *stmt = gsi_stmt (*gsi_p);
2473 *handled_ops_p = true;
2474 switch (gimple_code (stmt))
2476 case GIMPLE_TRY:
2477 case GIMPLE_BIND:
2478 case GIMPLE_CATCH:
2479 case GIMPLE_EH_FILTER:
2480 case GIMPLE_TRANSACTION:
2481 /* Walk the sub-statements. */
2482 *handled_ops_p = false;
2483 break;
2485 /* Find a sequence of form:
2487 GIMPLE_LABEL
2488 [...]
2489 <may fallthru stmt>
2490 GIMPLE_LABEL
2492 and possibly warn. */
2493 case GIMPLE_LABEL:
2495 /* Found a label. Skip all immediately following labels. */
2496 while (!gsi_end_p (*gsi_p)
2497 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2498 gsi_next_nondebug (gsi_p);
2500 /* There might be no more statements. */
2501 if (gsi_end_p (*gsi_p))
2502 return integer_zero_node;
2504 /* Vector of labels that fall through. */
2505 auto_vec <struct label_entry> labels;
2506 location_t prevloc;
2507 gimple *prev = collect_fallthrough_labels (gsi_p, &labels, &prevloc);
2509 /* There might be no more statements. */
2510 if (gsi_end_p (*gsi_p))
2511 return integer_zero_node;
2513 gimple *next = gsi_stmt (*gsi_p);
2514 tree label;
2515 /* If what follows is a label, then we may have a fallthrough. */
2516 if (gimple_code (next) == GIMPLE_LABEL
2517 && gimple_has_location (next)
2518 && (label = gimple_label_label (as_a <glabel *> (next)))
2519 && prev != NULL)
2521 struct label_entry *l;
2522 bool warned_p = false;
2523 auto_diagnostic_group d;
2524 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2525 /* Quiet. */;
2526 else if (gimple_code (prev) == GIMPLE_LABEL
2527 && (label = gimple_label_label (as_a <glabel *> (prev)))
2528 && (l = find_label_entry (&labels, label)))
2529 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2530 "this statement may fall through");
2531 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2532 /* Try to be clever and don't warn when the statement
2533 can't actually fall through. */
2534 && gimple_stmt_may_fallthru (prev)
2535 && prevloc != UNKNOWN_LOCATION)
2536 warned_p = warning_at (prevloc,
2537 OPT_Wimplicit_fallthrough_,
2538 "this statement may fall through");
2539 if (warned_p)
2540 inform (gimple_location (next), "here");
2542 /* Mark this label as processed so as to prevent multiple
2543 warnings in nested switches. */
2544 FALLTHROUGH_LABEL_P (label) = true;
2546 /* So that next warn_implicit_fallthrough_r will start looking for
2547 a new sequence starting with this label. */
2548 gsi_prev (gsi_p);
2551 break;
2552 default:
2553 break;
2555 return NULL_TREE;
2558 /* Warn when a switch case falls through. */
2560 static void
2561 maybe_warn_implicit_fallthrough (gimple_seq seq)
2563 if (!warn_implicit_fallthrough)
2564 return;
2566 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2567 if (!(lang_GNU_C ()
2568 || lang_GNU_CXX ()
2569 || lang_GNU_OBJC ()))
2570 return;
2572 struct walk_stmt_info wi;
2573 memset (&wi, 0, sizeof (wi));
2574 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2577 /* Callback for walk_gimple_seq. */
2579 static tree
2580 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2581 struct walk_stmt_info *wi)
2583 gimple *stmt = gsi_stmt (*gsi_p);
2585 *handled_ops_p = true;
2586 switch (gimple_code (stmt))
2588 case GIMPLE_TRY:
2589 case GIMPLE_BIND:
2590 case GIMPLE_CATCH:
2591 case GIMPLE_EH_FILTER:
2592 case GIMPLE_TRANSACTION:
2593 /* Walk the sub-statements. */
2594 *handled_ops_p = false;
2595 break;
2596 case GIMPLE_CALL:
2597 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2599 gsi_remove (gsi_p, true);
2600 if (gsi_end_p (*gsi_p))
2602 *static_cast<location_t *>(wi->info) = gimple_location (stmt);
2603 return integer_zero_node;
2606 bool found = false;
2607 location_t loc = gimple_location (stmt);
2609 gimple_stmt_iterator gsi2 = *gsi_p;
2610 stmt = gsi_stmt (gsi2);
2611 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2613 /* Go on until the artificial label. */
2614 tree goto_dest = gimple_goto_dest (stmt);
2615 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2617 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2618 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2619 == goto_dest)
2620 break;
2623 /* Not found? Stop. */
2624 if (gsi_end_p (gsi2))
2625 break;
2627 /* Look one past it. */
2628 gsi_next (&gsi2);
2631 /* We're looking for a case label or default label here. */
2632 while (!gsi_end_p (gsi2))
2634 stmt = gsi_stmt (gsi2);
2635 if (gimple_code (stmt) == GIMPLE_LABEL)
2637 tree label = gimple_label_label (as_a <glabel *> (stmt));
2638 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2640 found = true;
2641 break;
2644 else if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2646 else if (!is_gimple_debug (stmt))
2647 /* Anything else is not expected. */
2648 break;
2649 gsi_next (&gsi2);
2651 if (!found)
2652 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2653 "a case label or default label");
2655 break;
2656 default:
2657 break;
2659 return NULL_TREE;
2662 /* Expand all FALLTHROUGH () calls in SEQ. */
2664 static void
2665 expand_FALLTHROUGH (gimple_seq *seq_p)
2667 struct walk_stmt_info wi;
2668 location_t loc;
2669 memset (&wi, 0, sizeof (wi));
2670 wi.info = (void *) &loc;
2671 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2672 if (wi.callback_result == integer_zero_node)
2673 /* We've found [[fallthrough]]; at the end of a switch, which the C++
2674 standard says is ill-formed; see [dcl.attr.fallthrough]. */
2675 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2676 "a case label or default label");
2680 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2681 branch to. */
2683 static enum gimplify_status
2684 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2686 tree switch_expr = *expr_p;
2687 gimple_seq switch_body_seq = NULL;
2688 enum gimplify_status ret;
2689 tree index_type = TREE_TYPE (switch_expr);
2690 if (index_type == NULL_TREE)
2691 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2693 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2694 fb_rvalue);
2695 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2696 return ret;
2698 if (SWITCH_BODY (switch_expr))
2700 vec<tree> labels;
2701 vec<tree> saved_labels;
2702 hash_set<tree> *saved_live_switch_vars = NULL;
2703 tree default_case = NULL_TREE;
2704 gswitch *switch_stmt;
2706 /* Save old labels, get new ones from body, then restore the old
2707 labels. Save all the things from the switch body to append after. */
2708 saved_labels = gimplify_ctxp->case_labels;
2709 gimplify_ctxp->case_labels.create (8);
2711 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2712 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2713 tree_code body_type = TREE_CODE (SWITCH_BODY (switch_expr));
2714 if (body_type == BIND_EXPR || body_type == STATEMENT_LIST)
2715 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2716 else
2717 gimplify_ctxp->live_switch_vars = NULL;
2719 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2720 gimplify_ctxp->in_switch_expr = true;
2722 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2724 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2725 maybe_warn_switch_unreachable_and_auto_init (switch_body_seq);
2726 maybe_warn_implicit_fallthrough (switch_body_seq);
2727 /* Only do this for the outermost GIMPLE_SWITCH. */
2728 if (!gimplify_ctxp->in_switch_expr)
2729 expand_FALLTHROUGH (&switch_body_seq);
2731 labels = gimplify_ctxp->case_labels;
2732 gimplify_ctxp->case_labels = saved_labels;
2734 if (gimplify_ctxp->live_switch_vars)
2736 gcc_assert (gimplify_ctxp->live_switch_vars->is_empty ());
2737 delete gimplify_ctxp->live_switch_vars;
2739 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2741 preprocess_case_label_vec_for_gimple (labels, index_type,
2742 &default_case);
2744 bool add_bind = false;
2745 if (!default_case)
2747 glabel *new_default;
2749 default_case
2750 = build_case_label (NULL_TREE, NULL_TREE,
2751 create_artificial_label (UNKNOWN_LOCATION));
2752 if (old_in_switch_expr)
2754 SWITCH_BREAK_LABEL_P (CASE_LABEL (default_case)) = 1;
2755 add_bind = true;
2757 new_default = gimple_build_label (CASE_LABEL (default_case));
2758 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2760 else if (old_in_switch_expr)
2762 gimple *last = gimple_seq_last_stmt (switch_body_seq);
2763 if (last && gimple_code (last) == GIMPLE_LABEL)
2765 tree label = gimple_label_label (as_a <glabel *> (last));
2766 if (SWITCH_BREAK_LABEL_P (label))
2767 add_bind = true;
2771 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2772 default_case, labels);
2773 /* For the benefit of -Wimplicit-fallthrough, if switch_body_seq
2774 ends with a GIMPLE_LABEL holding SWITCH_BREAK_LABEL_P LABEL_DECL,
2775 wrap the GIMPLE_SWITCH up to that GIMPLE_LABEL into a GIMPLE_BIND,
2776 so that we can easily find the start and end of the switch
2777 statement. */
2778 if (add_bind)
2780 gimple_seq bind_body = NULL;
2781 gimplify_seq_add_stmt (&bind_body, switch_stmt);
2782 gimple_seq_add_seq (&bind_body, switch_body_seq);
2783 gbind *bind = gimple_build_bind (NULL_TREE, bind_body, NULL_TREE);
2784 gimple_set_location (bind, EXPR_LOCATION (switch_expr));
2785 gimplify_seq_add_stmt (pre_p, bind);
2787 else
2789 gimplify_seq_add_stmt (pre_p, switch_stmt);
2790 gimplify_seq_add_seq (pre_p, switch_body_seq);
2792 labels.release ();
2794 else
2795 gcc_unreachable ();
2797 return GS_ALL_DONE;
2800 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
2802 static enum gimplify_status
2803 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
2805 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
2806 == current_function_decl);
2808 tree label = LABEL_EXPR_LABEL (*expr_p);
2809 glabel *label_stmt = gimple_build_label (label);
2810 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2811 gimplify_seq_add_stmt (pre_p, label_stmt);
2813 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2814 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2815 NOT_TAKEN));
2816 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2817 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2818 TAKEN));
2820 return GS_ALL_DONE;
2823 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
2825 static enum gimplify_status
2826 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
2828 struct gimplify_ctx *ctxp;
2829 glabel *label_stmt;
2831 /* Invalid programs can play Duff's Device type games with, for example,
2832 #pragma omp parallel. At least in the C front end, we don't
2833 detect such invalid branches until after gimplification, in the
2834 diagnose_omp_blocks pass. */
2835 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
2836 if (ctxp->case_labels.exists ())
2837 break;
2839 tree label = CASE_LABEL (*expr_p);
2840 label_stmt = gimple_build_label (label);
2841 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2842 ctxp->case_labels.safe_push (*expr_p);
2843 gimplify_seq_add_stmt (pre_p, label_stmt);
2845 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2846 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2847 NOT_TAKEN));
2848 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2849 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2850 TAKEN));
2852 return GS_ALL_DONE;
2855 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
2856 if necessary. */
2858 tree
2859 build_and_jump (tree *label_p)
2861 if (label_p == NULL)
2862 /* If there's nowhere to jump, just fall through. */
2863 return NULL_TREE;
2865 if (*label_p == NULL_TREE)
2867 tree label = create_artificial_label (UNKNOWN_LOCATION);
2868 *label_p = label;
2871 return build1 (GOTO_EXPR, void_type_node, *label_p);
2874 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
2875 This also involves building a label to jump to and communicating it to
2876 gimplify_loop_expr through gimplify_ctxp->exit_label. */
2878 static enum gimplify_status
2879 gimplify_exit_expr (tree *expr_p)
2881 tree cond = TREE_OPERAND (*expr_p, 0);
2882 tree expr;
2884 expr = build_and_jump (&gimplify_ctxp->exit_label);
2885 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
2886 *expr_p = expr;
2888 return GS_OK;
2891 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
2892 different from its canonical type, wrap the whole thing inside a
2893 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
2894 type.
2896 The canonical type of a COMPONENT_REF is the type of the field being
2897 referenced--unless the field is a bit-field which can be read directly
2898 in a smaller mode, in which case the canonical type is the
2899 sign-appropriate type corresponding to that mode. */
2901 static void
2902 canonicalize_component_ref (tree *expr_p)
2904 tree expr = *expr_p;
2905 tree type;
2907 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
2909 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
2910 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
2911 else
2912 type = TREE_TYPE (TREE_OPERAND (expr, 1));
2914 /* One could argue that all the stuff below is not necessary for
2915 the non-bitfield case and declare it a FE error if type
2916 adjustment would be needed. */
2917 if (TREE_TYPE (expr) != type)
2919 #ifdef ENABLE_TYPES_CHECKING
2920 tree old_type = TREE_TYPE (expr);
2921 #endif
2922 int type_quals;
2924 /* We need to preserve qualifiers and propagate them from
2925 operand 0. */
2926 type_quals = TYPE_QUALS (type)
2927 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
2928 if (TYPE_QUALS (type) != type_quals)
2929 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
2931 /* Set the type of the COMPONENT_REF to the underlying type. */
2932 TREE_TYPE (expr) = type;
2934 #ifdef ENABLE_TYPES_CHECKING
2935 /* It is now a FE error, if the conversion from the canonical
2936 type to the original expression type is not useless. */
2937 gcc_assert (useless_type_conversion_p (old_type, type));
2938 #endif
2942 /* If a NOP conversion is changing a pointer to array of foo to a pointer
2943 to foo, embed that change in the ADDR_EXPR by converting
2944 T array[U];
2945 (T *)&array
2947 &array[L]
2948 where L is the lower bound. For simplicity, only do this for constant
2949 lower bound.
2950 The constraint is that the type of &array[L] is trivially convertible
2951 to T *. */
2953 static void
2954 canonicalize_addr_expr (tree *expr_p)
2956 tree expr = *expr_p;
2957 tree addr_expr = TREE_OPERAND (expr, 0);
2958 tree datype, ddatype, pddatype;
2960 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
2961 if (!POINTER_TYPE_P (TREE_TYPE (expr))
2962 || TREE_CODE (addr_expr) != ADDR_EXPR)
2963 return;
2965 /* The addr_expr type should be a pointer to an array. */
2966 datype = TREE_TYPE (TREE_TYPE (addr_expr));
2967 if (TREE_CODE (datype) != ARRAY_TYPE)
2968 return;
2970 /* The pointer to element type shall be trivially convertible to
2971 the expression pointer type. */
2972 ddatype = TREE_TYPE (datype);
2973 pddatype = build_pointer_type (ddatype);
2974 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
2975 pddatype))
2976 return;
2978 /* The lower bound and element sizes must be constant. */
2979 if (!TYPE_SIZE_UNIT (ddatype)
2980 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
2981 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
2982 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
2983 return;
2985 /* All checks succeeded. Build a new node to merge the cast. */
2986 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
2987 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
2988 NULL_TREE, NULL_TREE);
2989 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
2991 /* We can have stripped a required restrict qualifier above. */
2992 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
2993 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
2996 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
2997 underneath as appropriate. */
2999 static enum gimplify_status
3000 gimplify_conversion (tree *expr_p)
3002 location_t loc = EXPR_LOCATION (*expr_p);
3003 gcc_assert (CONVERT_EXPR_P (*expr_p));
3005 /* Then strip away all but the outermost conversion. */
3006 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
3008 /* And remove the outermost conversion if it's useless. */
3009 if (tree_ssa_useless_type_conversion (*expr_p))
3010 *expr_p = TREE_OPERAND (*expr_p, 0);
3012 /* If we still have a conversion at the toplevel,
3013 then canonicalize some constructs. */
3014 if (CONVERT_EXPR_P (*expr_p))
3016 tree sub = TREE_OPERAND (*expr_p, 0);
3018 /* If a NOP conversion is changing the type of a COMPONENT_REF
3019 expression, then canonicalize its type now in order to expose more
3020 redundant conversions. */
3021 if (TREE_CODE (sub) == COMPONENT_REF)
3022 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
3024 /* If a NOP conversion is changing a pointer to array of foo
3025 to a pointer to foo, embed that change in the ADDR_EXPR. */
3026 else if (TREE_CODE (sub) == ADDR_EXPR)
3027 canonicalize_addr_expr (expr_p);
3030 /* If we have a conversion to a non-register type force the
3031 use of a VIEW_CONVERT_EXPR instead. */
3032 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
3033 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
3034 TREE_OPERAND (*expr_p, 0));
3036 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
3037 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
3038 TREE_SET_CODE (*expr_p, NOP_EXPR);
3040 return GS_OK;
3043 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
3044 DECL_VALUE_EXPR, and it's worth re-examining things. */
3046 static enum gimplify_status
3047 gimplify_var_or_parm_decl (tree *expr_p)
3049 tree decl = *expr_p;
3051 /* ??? If this is a local variable, and it has not been seen in any
3052 outer BIND_EXPR, then it's probably the result of a duplicate
3053 declaration, for which we've already issued an error. It would
3054 be really nice if the front end wouldn't leak these at all.
3055 Currently the only known culprit is C++ destructors, as seen
3056 in g++.old-deja/g++.jason/binding.C.
3057 Another possible culpit are size expressions for variably modified
3058 types which are lost in the FE or not gimplified correctly. */
3059 if (VAR_P (decl)
3060 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
3061 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
3062 && decl_function_context (decl) == current_function_decl)
3064 gcc_assert (seen_error ());
3065 return GS_ERROR;
3068 /* When within an OMP context, notice uses of variables. */
3069 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
3070 return GS_ALL_DONE;
3072 /* If the decl is an alias for another expression, substitute it now. */
3073 if (DECL_HAS_VALUE_EXPR_P (decl))
3075 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
3076 return GS_OK;
3079 return GS_ALL_DONE;
3082 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
3084 static void
3085 recalculate_side_effects (tree t)
3087 enum tree_code code = TREE_CODE (t);
3088 int len = TREE_OPERAND_LENGTH (t);
3089 int i;
3091 switch (TREE_CODE_CLASS (code))
3093 case tcc_expression:
3094 switch (code)
3096 case INIT_EXPR:
3097 case MODIFY_EXPR:
3098 case VA_ARG_EXPR:
3099 case PREDECREMENT_EXPR:
3100 case PREINCREMENT_EXPR:
3101 case POSTDECREMENT_EXPR:
3102 case POSTINCREMENT_EXPR:
3103 /* All of these have side-effects, no matter what their
3104 operands are. */
3105 return;
3107 default:
3108 break;
3110 /* Fall through. */
3112 case tcc_comparison: /* a comparison expression */
3113 case tcc_unary: /* a unary arithmetic expression */
3114 case tcc_binary: /* a binary arithmetic expression */
3115 case tcc_reference: /* a reference */
3116 case tcc_vl_exp: /* a function call */
3117 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
3118 for (i = 0; i < len; ++i)
3120 tree op = TREE_OPERAND (t, i);
3121 if (op && TREE_SIDE_EFFECTS (op))
3122 TREE_SIDE_EFFECTS (t) = 1;
3124 break;
3126 case tcc_constant:
3127 /* No side-effects. */
3128 return;
3130 default:
3131 gcc_unreachable ();
3135 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
3136 node *EXPR_P.
3138 compound_lval
3139 : min_lval '[' val ']'
3140 | min_lval '.' ID
3141 | compound_lval '[' val ']'
3142 | compound_lval '.' ID
3144 This is not part of the original SIMPLE definition, which separates
3145 array and member references, but it seems reasonable to handle them
3146 together. Also, this way we don't run into problems with union
3147 aliasing; gcc requires that for accesses through a union to alias, the
3148 union reference must be explicit, which was not always the case when we
3149 were splitting up array and member refs.
3151 PRE_P points to the sequence where side effects that must happen before
3152 *EXPR_P should be stored.
3154 POST_P points to the sequence where side effects that must happen after
3155 *EXPR_P should be stored. */
3157 static enum gimplify_status
3158 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3159 fallback_t fallback)
3161 tree *p;
3162 enum gimplify_status ret = GS_ALL_DONE, tret;
3163 int i;
3164 location_t loc = EXPR_LOCATION (*expr_p);
3165 tree expr = *expr_p;
3167 /* Create a stack of the subexpressions so later we can walk them in
3168 order from inner to outer. */
3169 auto_vec<tree, 10> expr_stack;
3171 /* We can handle anything that get_inner_reference can deal with. */
3172 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
3174 restart:
3175 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
3176 if (TREE_CODE (*p) == INDIRECT_REF)
3177 *p = fold_indirect_ref_loc (loc, *p);
3179 if (handled_component_p (*p))
3181 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
3182 additional COMPONENT_REFs. */
3183 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
3184 && gimplify_var_or_parm_decl (p) == GS_OK)
3185 goto restart;
3186 else
3187 break;
3189 expr_stack.safe_push (*p);
3192 gcc_assert (expr_stack.length ());
3194 /* Now EXPR_STACK is a stack of pointers to all the refs we've
3195 walked through and P points to the innermost expression.
3197 Java requires that we elaborated nodes in source order. That
3198 means we must gimplify the inner expression followed by each of
3199 the indices, in order. But we can't gimplify the inner
3200 expression until we deal with any variable bounds, sizes, or
3201 positions in order to deal with PLACEHOLDER_EXPRs.
3203 The base expression may contain a statement expression that
3204 has declarations used in size expressions, so has to be
3205 gimplified before gimplifying the size expressions.
3207 So we do this in three steps. First we deal with variable
3208 bounds, sizes, and positions, then we gimplify the base and
3209 ensure it is memory if needed, then we deal with the annotations
3210 for any variables in the components and any indices, from left
3211 to right. */
3213 bool need_non_reg = false;
3214 for (i = expr_stack.length () - 1; i >= 0; i--)
3216 tree t = expr_stack[i];
3218 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3220 /* Deal with the low bound and element type size and put them into
3221 the ARRAY_REF. If these values are set, they have already been
3222 gimplified. */
3223 if (TREE_OPERAND (t, 2) == NULL_TREE)
3225 tree low = unshare_expr (array_ref_low_bound (t));
3226 if (!is_gimple_min_invariant (low))
3228 TREE_OPERAND (t, 2) = low;
3232 if (TREE_OPERAND (t, 3) == NULL_TREE)
3234 tree elmt_size = array_ref_element_size (t);
3235 if (!is_gimple_min_invariant (elmt_size))
3237 elmt_size = unshare_expr (elmt_size);
3238 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
3239 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
3241 /* Divide the element size by the alignment of the element
3242 type (above). */
3243 elmt_size = size_binop_loc (loc, EXACT_DIV_EXPR,
3244 elmt_size, factor);
3246 TREE_OPERAND (t, 3) = elmt_size;
3249 need_non_reg = true;
3251 else if (TREE_CODE (t) == COMPONENT_REF)
3253 /* Set the field offset into T and gimplify it. */
3254 if (TREE_OPERAND (t, 2) == NULL_TREE)
3256 tree offset = component_ref_field_offset (t);
3257 if (!is_gimple_min_invariant (offset))
3259 offset = unshare_expr (offset);
3260 tree field = TREE_OPERAND (t, 1);
3261 tree factor
3262 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
3264 /* Divide the offset by its alignment. */
3265 offset = size_binop_loc (loc, EXACT_DIV_EXPR,
3266 offset, factor);
3268 TREE_OPERAND (t, 2) = offset;
3271 need_non_reg = true;
3275 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
3276 so as to match the min_lval predicate. Failure to do so may result
3277 in the creation of large aggregate temporaries. */
3278 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
3279 fallback | fb_lvalue);
3280 ret = MIN (ret, tret);
3282 /* Step 2a: if we have component references we do not support on
3283 registers then make sure the base isn't a register. Of course
3284 we can only do so if an rvalue is OK. */
3285 if (need_non_reg && (fallback & fb_rvalue))
3286 prepare_gimple_addressable (p, pre_p);
3288 /* Step 3: gimplify size expressions and the indices and operands of
3289 ARRAY_REF. During this loop we also remove any useless conversions. */
3291 for (; expr_stack.length () > 0; )
3293 tree t = expr_stack.pop ();
3295 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3297 /* Gimplify the low bound and element type size. */
3298 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3299 is_gimple_reg, fb_rvalue);
3300 ret = MIN (ret, tret);
3302 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
3303 is_gimple_reg, fb_rvalue);
3304 ret = MIN (ret, tret);
3306 /* Gimplify the dimension. */
3307 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
3308 is_gimple_val, fb_rvalue);
3309 ret = MIN (ret, tret);
3311 else if (TREE_CODE (t) == COMPONENT_REF)
3313 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3314 is_gimple_reg, fb_rvalue);
3315 ret = MIN (ret, tret);
3318 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
3320 /* The innermost expression P may have originally had
3321 TREE_SIDE_EFFECTS set which would have caused all the outer
3322 expressions in *EXPR_P leading to P to also have had
3323 TREE_SIDE_EFFECTS set. */
3324 recalculate_side_effects (t);
3327 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
3328 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
3330 canonicalize_component_ref (expr_p);
3333 expr_stack.release ();
3335 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
3337 return ret;
3340 /* Gimplify the self modifying expression pointed to by EXPR_P
3341 (++, --, +=, -=).
3343 PRE_P points to the list where side effects that must happen before
3344 *EXPR_P should be stored.
3346 POST_P points to the list where side effects that must happen after
3347 *EXPR_P should be stored.
3349 WANT_VALUE is nonzero iff we want to use the value of this expression
3350 in another expression.
3352 ARITH_TYPE is the type the computation should be performed in. */
3354 enum gimplify_status
3355 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3356 bool want_value, tree arith_type)
3358 enum tree_code code;
3359 tree lhs, lvalue, rhs, t1;
3360 gimple_seq post = NULL, *orig_post_p = post_p;
3361 bool postfix;
3362 enum tree_code arith_code;
3363 enum gimplify_status ret;
3364 location_t loc = EXPR_LOCATION (*expr_p);
3366 code = TREE_CODE (*expr_p);
3368 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
3369 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
3371 /* Prefix or postfix? */
3372 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
3373 /* Faster to treat as prefix if result is not used. */
3374 postfix = want_value;
3375 else
3376 postfix = false;
3378 /* For postfix, make sure the inner expression's post side effects
3379 are executed after side effects from this expression. */
3380 if (postfix)
3381 post_p = &post;
3383 /* Add or subtract? */
3384 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
3385 arith_code = PLUS_EXPR;
3386 else
3387 arith_code = MINUS_EXPR;
3389 /* Gimplify the LHS into a GIMPLE lvalue. */
3390 lvalue = TREE_OPERAND (*expr_p, 0);
3391 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3392 if (ret == GS_ERROR)
3393 return ret;
3395 /* Extract the operands to the arithmetic operation. */
3396 lhs = lvalue;
3397 rhs = TREE_OPERAND (*expr_p, 1);
3399 /* For postfix operator, we evaluate the LHS to an rvalue and then use
3400 that as the result value and in the postqueue operation. */
3401 if (postfix)
3403 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
3404 if (ret == GS_ERROR)
3405 return ret;
3407 lhs = get_initialized_tmp_var (lhs, pre_p);
3410 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
3411 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
3413 rhs = convert_to_ptrofftype_loc (loc, rhs);
3414 if (arith_code == MINUS_EXPR)
3415 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
3416 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
3418 else
3419 t1 = fold_convert (TREE_TYPE (*expr_p),
3420 fold_build2 (arith_code, arith_type,
3421 fold_convert (arith_type, lhs),
3422 fold_convert (arith_type, rhs)));
3424 if (postfix)
3426 gimplify_assign (lvalue, t1, pre_p);
3427 gimplify_seq_add_seq (orig_post_p, post);
3428 *expr_p = lhs;
3429 return GS_ALL_DONE;
3431 else
3433 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
3434 return GS_OK;
3438 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
3440 static void
3441 maybe_with_size_expr (tree *expr_p)
3443 tree expr = *expr_p;
3444 tree type = TREE_TYPE (expr);
3445 tree size;
3447 /* If we've already wrapped this or the type is error_mark_node, we can't do
3448 anything. */
3449 if (TREE_CODE (expr) == WITH_SIZE_EXPR
3450 || type == error_mark_node)
3451 return;
3453 /* If the size isn't known or is a constant, we have nothing to do. */
3454 size = TYPE_SIZE_UNIT (type);
3455 if (!size || poly_int_tree_p (size))
3456 return;
3458 /* Otherwise, make a WITH_SIZE_EXPR. */
3459 size = unshare_expr (size);
3460 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
3461 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
3464 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
3465 Store any side-effects in PRE_P. CALL_LOCATION is the location of
3466 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
3467 gimplified to an SSA name. */
3469 enum gimplify_status
3470 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3471 bool allow_ssa)
3473 bool (*test) (tree);
3474 fallback_t fb;
3476 /* In general, we allow lvalues for function arguments to avoid
3477 extra overhead of copying large aggregates out of even larger
3478 aggregates into temporaries only to copy the temporaries to
3479 the argument list. Make optimizers happy by pulling out to
3480 temporaries those types that fit in registers. */
3481 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3482 test = is_gimple_val, fb = fb_rvalue;
3483 else
3485 test = is_gimple_lvalue, fb = fb_either;
3486 /* Also strip a TARGET_EXPR that would force an extra copy. */
3487 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3489 tree init = TARGET_EXPR_INITIAL (*arg_p);
3490 if (init
3491 && !VOID_TYPE_P (TREE_TYPE (init)))
3492 *arg_p = init;
3496 /* If this is a variable sized type, we must remember the size. */
3497 maybe_with_size_expr (arg_p);
3499 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3500 /* Make sure arguments have the same location as the function call
3501 itself. */
3502 protected_set_expr_location (*arg_p, call_location);
3504 /* There is a sequence point before a function call. Side effects in
3505 the argument list must occur before the actual call. So, when
3506 gimplifying arguments, force gimplify_expr to use an internal
3507 post queue which is then appended to the end of PRE_P. */
3508 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3511 /* Don't fold inside offloading or taskreg regions: it can break code by
3512 adding decl references that weren't in the source. We'll do it during
3513 omplower pass instead. */
3515 static bool
3516 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3518 struct gimplify_omp_ctx *ctx;
3519 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3520 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3521 return false;
3522 else if ((ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
3523 return false;
3524 /* Delay folding of builtins until the IL is in consistent state
3525 so the diagnostic machinery can do a better job. */
3526 if (gimple_call_builtin_p (gsi_stmt (*gsi)))
3527 return false;
3528 return fold_stmt (gsi);
3531 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3532 WANT_VALUE is true if the result of the call is desired. */
3534 static enum gimplify_status
3535 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3537 tree fndecl, parms, p, fnptrtype;
3538 enum gimplify_status ret;
3539 int i, nargs;
3540 gcall *call;
3541 bool builtin_va_start_p = false;
3542 location_t loc = EXPR_LOCATION (*expr_p);
3544 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3546 /* For reliable diagnostics during inlining, it is necessary that
3547 every call_expr be annotated with file and line. */
3548 if (! EXPR_HAS_LOCATION (*expr_p))
3549 SET_EXPR_LOCATION (*expr_p, input_location);
3551 /* Gimplify internal functions created in the FEs. */
3552 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3554 if (want_value)
3555 return GS_ALL_DONE;
3557 nargs = call_expr_nargs (*expr_p);
3558 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3559 auto_vec<tree> vargs (nargs);
3561 for (i = 0; i < nargs; i++)
3563 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3564 EXPR_LOCATION (*expr_p));
3565 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3568 gcall *call = gimple_build_call_internal_vec (ifn, vargs);
3569 gimple_call_set_nothrow (call, TREE_NOTHROW (*expr_p));
3570 gimplify_seq_add_stmt (pre_p, call);
3571 return GS_ALL_DONE;
3574 /* This may be a call to a builtin function.
3576 Builtin function calls may be transformed into different
3577 (and more efficient) builtin function calls under certain
3578 circumstances. Unfortunately, gimplification can muck things
3579 up enough that the builtin expanders are not aware that certain
3580 transformations are still valid.
3582 So we attempt transformation/gimplification of the call before
3583 we gimplify the CALL_EXPR. At this time we do not manage to
3584 transform all calls in the same manner as the expanders do, but
3585 we do transform most of them. */
3586 fndecl = get_callee_fndecl (*expr_p);
3587 if (fndecl && fndecl_built_in_p (fndecl, BUILT_IN_NORMAL))
3588 switch (DECL_FUNCTION_CODE (fndecl))
3590 CASE_BUILT_IN_ALLOCA:
3591 /* If the call has been built for a variable-sized object, then we
3592 want to restore the stack level when the enclosing BIND_EXPR is
3593 exited to reclaim the allocated space; otherwise, we precisely
3594 need to do the opposite and preserve the latest stack level. */
3595 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3596 gimplify_ctxp->save_stack = true;
3597 else
3598 gimplify_ctxp->keep_stack = true;
3599 break;
3601 case BUILT_IN_VA_START:
3603 builtin_va_start_p = TRUE;
3604 if (call_expr_nargs (*expr_p) < 2)
3606 error ("too few arguments to function %<va_start%>");
3607 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3608 return GS_OK;
3611 if (fold_builtin_next_arg (*expr_p, true))
3613 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3614 return GS_OK;
3616 break;
3619 case BUILT_IN_EH_RETURN:
3620 cfun->calls_eh_return = true;
3621 break;
3623 case BUILT_IN_CLEAR_PADDING:
3624 if (call_expr_nargs (*expr_p) == 1)
3626 /* Remember the original type of the argument in an internal
3627 dummy second argument, as in GIMPLE pointer conversions are
3628 useless. Also mark this call as not for automatic
3629 initialization in the internal dummy third argument. */
3630 p = CALL_EXPR_ARG (*expr_p, 0);
3631 *expr_p
3632 = build_call_expr_loc (EXPR_LOCATION (*expr_p), fndecl, 2, p,
3633 build_zero_cst (TREE_TYPE (p)));
3634 return GS_OK;
3636 break;
3638 default:
3641 if (fndecl && fndecl_built_in_p (fndecl))
3643 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3644 if (new_tree && new_tree != *expr_p)
3646 /* There was a transformation of this call which computes the
3647 same value, but in a more efficient way. Return and try
3648 again. */
3649 *expr_p = new_tree;
3650 return GS_OK;
3654 /* Remember the original function pointer type. */
3655 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3657 if (flag_openmp
3658 && fndecl
3659 && cfun
3660 && (cfun->curr_properties & PROP_gimple_any) == 0)
3662 tree variant = omp_resolve_declare_variant (fndecl);
3663 if (variant != fndecl)
3664 CALL_EXPR_FN (*expr_p) = build1 (ADDR_EXPR, fnptrtype, variant);
3667 /* There is a sequence point before the call, so any side effects in
3668 the calling expression must occur before the actual call. Force
3669 gimplify_expr to use an internal post queue. */
3670 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3671 is_gimple_call_addr, fb_rvalue);
3673 nargs = call_expr_nargs (*expr_p);
3675 /* Get argument types for verification. */
3676 fndecl = get_callee_fndecl (*expr_p);
3677 parms = NULL_TREE;
3678 if (fndecl)
3679 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3680 else
3681 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3683 if (fndecl && DECL_ARGUMENTS (fndecl))
3684 p = DECL_ARGUMENTS (fndecl);
3685 else if (parms)
3686 p = parms;
3687 else
3688 p = NULL_TREE;
3689 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3692 /* If the last argument is __builtin_va_arg_pack () and it is not
3693 passed as a named argument, decrease the number of CALL_EXPR
3694 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3695 if (!p
3696 && i < nargs
3697 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3699 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3700 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3702 if (last_arg_fndecl
3703 && fndecl_built_in_p (last_arg_fndecl, BUILT_IN_VA_ARG_PACK))
3705 tree call = *expr_p;
3707 --nargs;
3708 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
3709 CALL_EXPR_FN (call),
3710 nargs, CALL_EXPR_ARGP (call));
3712 /* Copy all CALL_EXPR flags, location and block, except
3713 CALL_EXPR_VA_ARG_PACK flag. */
3714 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
3715 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
3716 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
3717 = CALL_EXPR_RETURN_SLOT_OPT (call);
3718 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
3719 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
3721 /* Set CALL_EXPR_VA_ARG_PACK. */
3722 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
3726 /* If the call returns twice then after building the CFG the call
3727 argument computations will no longer dominate the call because
3728 we add an abnormal incoming edge to the call. So do not use SSA
3729 vars there. */
3730 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
3732 /* Gimplify the function arguments. */
3733 if (nargs > 0)
3735 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
3736 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
3737 PUSH_ARGS_REVERSED ? i-- : i++)
3739 enum gimplify_status t;
3741 /* Avoid gimplifying the second argument to va_start, which needs to
3742 be the plain PARM_DECL. */
3743 if ((i != 1) || !builtin_va_start_p)
3745 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3746 EXPR_LOCATION (*expr_p), ! returns_twice);
3748 if (t == GS_ERROR)
3749 ret = GS_ERROR;
3754 /* Gimplify the static chain. */
3755 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
3757 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
3758 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
3759 else
3761 enum gimplify_status t;
3762 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
3763 EXPR_LOCATION (*expr_p), ! returns_twice);
3764 if (t == GS_ERROR)
3765 ret = GS_ERROR;
3769 /* Verify the function result. */
3770 if (want_value && fndecl
3771 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
3773 error_at (loc, "using result of function returning %<void%>");
3774 ret = GS_ERROR;
3777 /* Try this again in case gimplification exposed something. */
3778 if (ret != GS_ERROR)
3780 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3782 if (new_tree && new_tree != *expr_p)
3784 /* There was a transformation of this call which computes the
3785 same value, but in a more efficient way. Return and try
3786 again. */
3787 *expr_p = new_tree;
3788 return GS_OK;
3791 else
3793 *expr_p = error_mark_node;
3794 return GS_ERROR;
3797 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
3798 decl. This allows us to eliminate redundant or useless
3799 calls to "const" functions. */
3800 if (TREE_CODE (*expr_p) == CALL_EXPR)
3802 int flags = call_expr_flags (*expr_p);
3803 if (flags & (ECF_CONST | ECF_PURE)
3804 /* An infinite loop is considered a side effect. */
3805 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
3806 TREE_SIDE_EFFECTS (*expr_p) = 0;
3809 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
3810 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
3811 form and delegate the creation of a GIMPLE_CALL to
3812 gimplify_modify_expr. This is always possible because when
3813 WANT_VALUE is true, the caller wants the result of this call into
3814 a temporary, which means that we will emit an INIT_EXPR in
3815 internal_get_tmp_var which will then be handled by
3816 gimplify_modify_expr. */
3817 if (!want_value)
3819 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
3820 have to do is replicate it as a GIMPLE_CALL tuple. */
3821 gimple_stmt_iterator gsi;
3822 call = gimple_build_call_from_tree (*expr_p, fnptrtype);
3823 notice_special_calls (call);
3824 gimplify_seq_add_stmt (pre_p, call);
3825 gsi = gsi_last (*pre_p);
3826 maybe_fold_stmt (&gsi);
3827 *expr_p = NULL_TREE;
3829 else
3830 /* Remember the original function type. */
3831 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
3832 CALL_EXPR_FN (*expr_p));
3834 return ret;
3837 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
3838 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
3840 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
3841 condition is true or false, respectively. If null, we should generate
3842 our own to skip over the evaluation of this specific expression.
3844 LOCUS is the source location of the COND_EXPR.
3846 This function is the tree equivalent of do_jump.
3848 shortcut_cond_r should only be called by shortcut_cond_expr. */
3850 static tree
3851 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
3852 location_t locus)
3854 tree local_label = NULL_TREE;
3855 tree t, expr = NULL;
3857 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
3858 retain the shortcut semantics. Just insert the gotos here;
3859 shortcut_cond_expr will append the real blocks later. */
3860 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3862 location_t new_locus;
3864 /* Turn if (a && b) into
3866 if (a); else goto no;
3867 if (b) goto yes; else goto no;
3868 (no:) */
3870 if (false_label_p == NULL)
3871 false_label_p = &local_label;
3873 /* Keep the original source location on the first 'if'. */
3874 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
3875 append_to_statement_list (t, &expr);
3877 /* Set the source location of the && on the second 'if'. */
3878 new_locus = rexpr_location (pred, locus);
3879 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3880 new_locus);
3881 append_to_statement_list (t, &expr);
3883 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3885 location_t new_locus;
3887 /* Turn if (a || b) into
3889 if (a) goto yes;
3890 if (b) goto yes; else goto no;
3891 (yes:) */
3893 if (true_label_p == NULL)
3894 true_label_p = &local_label;
3896 /* Keep the original source location on the first 'if'. */
3897 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
3898 append_to_statement_list (t, &expr);
3900 /* Set the source location of the || on the second 'if'. */
3901 new_locus = rexpr_location (pred, locus);
3902 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3903 new_locus);
3904 append_to_statement_list (t, &expr);
3906 else if (TREE_CODE (pred) == COND_EXPR
3907 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
3908 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
3910 location_t new_locus;
3912 /* As long as we're messing with gotos, turn if (a ? b : c) into
3913 if (a)
3914 if (b) goto yes; else goto no;
3915 else
3916 if (c) goto yes; else goto no;
3918 Don't do this if one of the arms has void type, which can happen
3919 in C++ when the arm is throw. */
3921 /* Keep the original source location on the first 'if'. Set the source
3922 location of the ? on the second 'if'. */
3923 new_locus = rexpr_location (pred, locus);
3924 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
3925 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
3926 false_label_p, locus),
3927 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
3928 false_label_p, new_locus));
3930 else
3932 expr = build3 (COND_EXPR, void_type_node, pred,
3933 build_and_jump (true_label_p),
3934 build_and_jump (false_label_p));
3935 SET_EXPR_LOCATION (expr, locus);
3938 if (local_label)
3940 t = build1 (LABEL_EXPR, void_type_node, local_label);
3941 append_to_statement_list (t, &expr);
3944 return expr;
3947 /* If EXPR is a GOTO_EXPR, return it. If it is a STATEMENT_LIST, skip
3948 any of its leading DEBUG_BEGIN_STMTS and recurse on the subsequent
3949 statement, if it is the last one. Otherwise, return NULL. */
3951 static tree
3952 find_goto (tree expr)
3954 if (!expr)
3955 return NULL_TREE;
3957 if (TREE_CODE (expr) == GOTO_EXPR)
3958 return expr;
3960 if (TREE_CODE (expr) != STATEMENT_LIST)
3961 return NULL_TREE;
3963 tree_stmt_iterator i = tsi_start (expr);
3965 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
3966 tsi_next (&i);
3968 if (!tsi_one_before_end_p (i))
3969 return NULL_TREE;
3971 return find_goto (tsi_stmt (i));
3974 /* Same as find_goto, except that it returns NULL if the destination
3975 is not a LABEL_DECL. */
3977 static inline tree
3978 find_goto_label (tree expr)
3980 tree dest = find_goto (expr);
3981 if (dest && TREE_CODE (GOTO_DESTINATION (dest)) == LABEL_DECL)
3982 return dest;
3983 return NULL_TREE;
3986 /* Given a conditional expression EXPR with short-circuit boolean
3987 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
3988 predicate apart into the equivalent sequence of conditionals. */
3990 static tree
3991 shortcut_cond_expr (tree expr)
3993 tree pred = TREE_OPERAND (expr, 0);
3994 tree then_ = TREE_OPERAND (expr, 1);
3995 tree else_ = TREE_OPERAND (expr, 2);
3996 tree true_label, false_label, end_label, t;
3997 tree *true_label_p;
3998 tree *false_label_p;
3999 bool emit_end, emit_false, jump_over_else;
4000 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
4001 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
4003 /* First do simple transformations. */
4004 if (!else_se)
4006 /* If there is no 'else', turn
4007 if (a && b) then c
4008 into
4009 if (a) if (b) then c. */
4010 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
4012 /* Keep the original source location on the first 'if'. */
4013 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
4014 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
4015 /* Set the source location of the && on the second 'if'. */
4016 if (rexpr_has_location (pred))
4017 SET_EXPR_LOCATION (expr, rexpr_location (pred));
4018 then_ = shortcut_cond_expr (expr);
4019 then_se = then_ && TREE_SIDE_EFFECTS (then_);
4020 pred = TREE_OPERAND (pred, 0);
4021 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
4022 SET_EXPR_LOCATION (expr, locus);
4026 if (!then_se)
4028 /* If there is no 'then', turn
4029 if (a || b); else d
4030 into
4031 if (a); else if (b); else d. */
4032 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
4034 /* Keep the original source location on the first 'if'. */
4035 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
4036 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
4037 /* Set the source location of the || on the second 'if'. */
4038 if (rexpr_has_location (pred))
4039 SET_EXPR_LOCATION (expr, rexpr_location (pred));
4040 else_ = shortcut_cond_expr (expr);
4041 else_se = else_ && TREE_SIDE_EFFECTS (else_);
4042 pred = TREE_OPERAND (pred, 0);
4043 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
4044 SET_EXPR_LOCATION (expr, locus);
4048 /* If we're done, great. */
4049 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
4050 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
4051 return expr;
4053 /* Otherwise we need to mess with gotos. Change
4054 if (a) c; else d;
4056 if (a); else goto no;
4057 c; goto end;
4058 no: d; end:
4059 and recursively gimplify the condition. */
4061 true_label = false_label = end_label = NULL_TREE;
4063 /* If our arms just jump somewhere, hijack those labels so we don't
4064 generate jumps to jumps. */
4066 if (tree then_goto = find_goto_label (then_))
4068 true_label = GOTO_DESTINATION (then_goto);
4069 then_ = NULL;
4070 then_se = false;
4073 if (tree else_goto = find_goto_label (else_))
4075 false_label = GOTO_DESTINATION (else_goto);
4076 else_ = NULL;
4077 else_se = false;
4080 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
4081 if (true_label)
4082 true_label_p = &true_label;
4083 else
4084 true_label_p = NULL;
4086 /* The 'else' branch also needs a label if it contains interesting code. */
4087 if (false_label || else_se)
4088 false_label_p = &false_label;
4089 else
4090 false_label_p = NULL;
4092 /* If there was nothing else in our arms, just forward the label(s). */
4093 if (!then_se && !else_se)
4094 return shortcut_cond_r (pred, true_label_p, false_label_p,
4095 EXPR_LOC_OR_LOC (expr, input_location));
4097 /* If our last subexpression already has a terminal label, reuse it. */
4098 if (else_se)
4099 t = expr_last (else_);
4100 else if (then_se)
4101 t = expr_last (then_);
4102 else
4103 t = NULL;
4104 if (t && TREE_CODE (t) == LABEL_EXPR)
4105 end_label = LABEL_EXPR_LABEL (t);
4107 /* If we don't care about jumping to the 'else' branch, jump to the end
4108 if the condition is false. */
4109 if (!false_label_p)
4110 false_label_p = &end_label;
4112 /* We only want to emit these labels if we aren't hijacking them. */
4113 emit_end = (end_label == NULL_TREE);
4114 emit_false = (false_label == NULL_TREE);
4116 /* We only emit the jump over the else clause if we have to--if the
4117 then clause may fall through. Otherwise we can wind up with a
4118 useless jump and a useless label at the end of gimplified code,
4119 which will cause us to think that this conditional as a whole
4120 falls through even if it doesn't. If we then inline a function
4121 which ends with such a condition, that can cause us to issue an
4122 inappropriate warning about control reaching the end of a
4123 non-void function. */
4124 jump_over_else = block_may_fallthru (then_);
4126 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
4127 EXPR_LOC_OR_LOC (expr, input_location));
4129 expr = NULL;
4130 append_to_statement_list (pred, &expr);
4132 append_to_statement_list (then_, &expr);
4133 if (else_se)
4135 if (jump_over_else)
4137 tree last = expr_last (expr);
4138 t = build_and_jump (&end_label);
4139 if (rexpr_has_location (last))
4140 SET_EXPR_LOCATION (t, rexpr_location (last));
4141 append_to_statement_list (t, &expr);
4143 if (emit_false)
4145 t = build1 (LABEL_EXPR, void_type_node, false_label);
4146 append_to_statement_list (t, &expr);
4148 append_to_statement_list (else_, &expr);
4150 if (emit_end && end_label)
4152 t = build1 (LABEL_EXPR, void_type_node, end_label);
4153 append_to_statement_list (t, &expr);
4156 return expr;
4159 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
4161 tree
4162 gimple_boolify (tree expr)
4164 tree type = TREE_TYPE (expr);
4165 location_t loc = EXPR_LOCATION (expr);
4167 if (TREE_CODE (expr) == NE_EXPR
4168 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
4169 && integer_zerop (TREE_OPERAND (expr, 1)))
4171 tree call = TREE_OPERAND (expr, 0);
4172 tree fn = get_callee_fndecl (call);
4174 /* For __builtin_expect ((long) (x), y) recurse into x as well
4175 if x is truth_value_p. */
4176 if (fn
4177 && fndecl_built_in_p (fn, BUILT_IN_EXPECT)
4178 && call_expr_nargs (call) == 2)
4180 tree arg = CALL_EXPR_ARG (call, 0);
4181 if (arg)
4183 if (TREE_CODE (arg) == NOP_EXPR
4184 && TREE_TYPE (arg) == TREE_TYPE (call))
4185 arg = TREE_OPERAND (arg, 0);
4186 if (truth_value_p (TREE_CODE (arg)))
4188 arg = gimple_boolify (arg);
4189 CALL_EXPR_ARG (call, 0)
4190 = fold_convert_loc (loc, TREE_TYPE (call), arg);
4196 switch (TREE_CODE (expr))
4198 case TRUTH_AND_EXPR:
4199 case TRUTH_OR_EXPR:
4200 case TRUTH_XOR_EXPR:
4201 case TRUTH_ANDIF_EXPR:
4202 case TRUTH_ORIF_EXPR:
4203 /* Also boolify the arguments of truth exprs. */
4204 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
4205 /* FALLTHRU */
4207 case TRUTH_NOT_EXPR:
4208 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4210 /* These expressions always produce boolean results. */
4211 if (TREE_CODE (type) != BOOLEAN_TYPE)
4212 TREE_TYPE (expr) = boolean_type_node;
4213 return expr;
4215 case ANNOTATE_EXPR:
4216 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
4218 case annot_expr_ivdep_kind:
4219 case annot_expr_unroll_kind:
4220 case annot_expr_no_vector_kind:
4221 case annot_expr_vector_kind:
4222 case annot_expr_parallel_kind:
4223 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4224 if (TREE_CODE (type) != BOOLEAN_TYPE)
4225 TREE_TYPE (expr) = boolean_type_node;
4226 return expr;
4227 default:
4228 gcc_unreachable ();
4231 default:
4232 if (COMPARISON_CLASS_P (expr))
4234 /* There expressions always prduce boolean results. */
4235 if (TREE_CODE (type) != BOOLEAN_TYPE)
4236 TREE_TYPE (expr) = boolean_type_node;
4237 return expr;
4239 /* Other expressions that get here must have boolean values, but
4240 might need to be converted to the appropriate mode. */
4241 if (TREE_CODE (type) == BOOLEAN_TYPE)
4242 return expr;
4243 return fold_convert_loc (loc, boolean_type_node, expr);
4247 /* Given a conditional expression *EXPR_P without side effects, gimplify
4248 its operands. New statements are inserted to PRE_P. */
4250 static enum gimplify_status
4251 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
4253 tree expr = *expr_p, cond;
4254 enum gimplify_status ret, tret;
4255 enum tree_code code;
4257 cond = gimple_boolify (COND_EXPR_COND (expr));
4259 /* We need to handle && and || specially, as their gimplification
4260 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
4261 code = TREE_CODE (cond);
4262 if (code == TRUTH_ANDIF_EXPR)
4263 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
4264 else if (code == TRUTH_ORIF_EXPR)
4265 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
4266 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_val, fb_rvalue);
4267 COND_EXPR_COND (*expr_p) = cond;
4269 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
4270 is_gimple_val, fb_rvalue);
4271 ret = MIN (ret, tret);
4272 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
4273 is_gimple_val, fb_rvalue);
4275 return MIN (ret, tret);
4278 /* Return true if evaluating EXPR could trap.
4279 EXPR is GENERIC, while tree_could_trap_p can be called
4280 only on GIMPLE. */
4282 bool
4283 generic_expr_could_trap_p (tree expr)
4285 unsigned i, n;
4287 if (!expr || is_gimple_val (expr))
4288 return false;
4290 if (!EXPR_P (expr) || tree_could_trap_p (expr))
4291 return true;
4293 n = TREE_OPERAND_LENGTH (expr);
4294 for (i = 0; i < n; i++)
4295 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
4296 return true;
4298 return false;
4301 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
4302 into
4304 if (p) if (p)
4305 t1 = a; a;
4306 else or else
4307 t1 = b; b;
4310 The second form is used when *EXPR_P is of type void.
4312 PRE_P points to the list where side effects that must happen before
4313 *EXPR_P should be stored. */
4315 static enum gimplify_status
4316 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
4318 tree expr = *expr_p;
4319 tree type = TREE_TYPE (expr);
4320 location_t loc = EXPR_LOCATION (expr);
4321 tree tmp, arm1, arm2;
4322 enum gimplify_status ret;
4323 tree label_true, label_false, label_cont;
4324 bool have_then_clause_p, have_else_clause_p;
4325 gcond *cond_stmt;
4326 enum tree_code pred_code;
4327 gimple_seq seq = NULL;
4329 /* If this COND_EXPR has a value, copy the values into a temporary within
4330 the arms. */
4331 if (!VOID_TYPE_P (type))
4333 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
4334 tree result;
4336 /* If either an rvalue is ok or we do not require an lvalue, create the
4337 temporary. But we cannot do that if the type is addressable. */
4338 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
4339 && !TREE_ADDRESSABLE (type))
4341 if (gimplify_ctxp->allow_rhs_cond_expr
4342 /* If either branch has side effects or could trap, it can't be
4343 evaluated unconditionally. */
4344 && !TREE_SIDE_EFFECTS (then_)
4345 && !generic_expr_could_trap_p (then_)
4346 && !TREE_SIDE_EFFECTS (else_)
4347 && !generic_expr_could_trap_p (else_))
4348 return gimplify_pure_cond_expr (expr_p, pre_p);
4350 tmp = create_tmp_var (type, "iftmp");
4351 result = tmp;
4354 /* Otherwise, only create and copy references to the values. */
4355 else
4357 type = build_pointer_type (type);
4359 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4360 then_ = build_fold_addr_expr_loc (loc, then_);
4362 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4363 else_ = build_fold_addr_expr_loc (loc, else_);
4365 expr
4366 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
4368 tmp = create_tmp_var (type, "iftmp");
4369 result = build_simple_mem_ref_loc (loc, tmp);
4372 /* Build the new then clause, `tmp = then_;'. But don't build the
4373 assignment if the value is void; in C++ it can be if it's a throw. */
4374 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4375 TREE_OPERAND (expr, 1) = build2 (INIT_EXPR, type, tmp, then_);
4377 /* Similarly, build the new else clause, `tmp = else_;'. */
4378 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4379 TREE_OPERAND (expr, 2) = build2 (INIT_EXPR, type, tmp, else_);
4381 TREE_TYPE (expr) = void_type_node;
4382 recalculate_side_effects (expr);
4384 /* Move the COND_EXPR to the prequeue. */
4385 gimplify_stmt (&expr, pre_p);
4387 *expr_p = result;
4388 return GS_ALL_DONE;
4391 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
4392 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
4393 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
4394 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
4396 /* Make sure the condition has BOOLEAN_TYPE. */
4397 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4399 /* Break apart && and || conditions. */
4400 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
4401 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
4403 expr = shortcut_cond_expr (expr);
4405 if (expr != *expr_p)
4407 *expr_p = expr;
4409 /* We can't rely on gimplify_expr to re-gimplify the expanded
4410 form properly, as cleanups might cause the target labels to be
4411 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
4412 set up a conditional context. */
4413 gimple_push_condition ();
4414 gimplify_stmt (expr_p, &seq);
4415 gimple_pop_condition (pre_p);
4416 gimple_seq_add_seq (pre_p, seq);
4418 return GS_ALL_DONE;
4422 /* Now do the normal gimplification. */
4424 /* Gimplify condition. */
4425 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
4426 is_gimple_condexpr_for_cond, fb_rvalue);
4427 if (ret == GS_ERROR)
4428 return GS_ERROR;
4429 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
4431 gimple_push_condition ();
4433 have_then_clause_p = have_else_clause_p = false;
4434 label_true = find_goto_label (TREE_OPERAND (expr, 1));
4435 if (label_true
4436 && DECL_CONTEXT (GOTO_DESTINATION (label_true)) == current_function_decl
4437 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4438 have different locations, otherwise we end up with incorrect
4439 location information on the branches. */
4440 && (optimize
4441 || !EXPR_HAS_LOCATION (expr)
4442 || !rexpr_has_location (label_true)
4443 || EXPR_LOCATION (expr) == rexpr_location (label_true)))
4445 have_then_clause_p = true;
4446 label_true = GOTO_DESTINATION (label_true);
4448 else
4449 label_true = create_artificial_label (UNKNOWN_LOCATION);
4450 label_false = find_goto_label (TREE_OPERAND (expr, 2));
4451 if (label_false
4452 && DECL_CONTEXT (GOTO_DESTINATION (label_false)) == current_function_decl
4453 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4454 have different locations, otherwise we end up with incorrect
4455 location information on the branches. */
4456 && (optimize
4457 || !EXPR_HAS_LOCATION (expr)
4458 || !rexpr_has_location (label_false)
4459 || EXPR_LOCATION (expr) == rexpr_location (label_false)))
4461 have_else_clause_p = true;
4462 label_false = GOTO_DESTINATION (label_false);
4464 else
4465 label_false = create_artificial_label (UNKNOWN_LOCATION);
4467 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
4468 &arm2);
4469 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
4470 label_false);
4471 gimple_set_location (cond_stmt, EXPR_LOCATION (expr));
4472 copy_warning (cond_stmt, COND_EXPR_COND (expr));
4473 gimplify_seq_add_stmt (&seq, cond_stmt);
4474 gimple_stmt_iterator gsi = gsi_last (seq);
4475 maybe_fold_stmt (&gsi);
4477 label_cont = NULL_TREE;
4478 if (!have_then_clause_p)
4480 /* For if (...) {} else { code; } put label_true after
4481 the else block. */
4482 if (TREE_OPERAND (expr, 1) == NULL_TREE
4483 && !have_else_clause_p
4484 && TREE_OPERAND (expr, 2) != NULL_TREE)
4486 /* For if (0) {} else { code; } tell -Wimplicit-fallthrough
4487 handling that label_cont == label_true can be only reached
4488 through fallthrough from { code; }. */
4489 if (integer_zerop (COND_EXPR_COND (expr)))
4490 UNUSED_LABEL_P (label_true) = 1;
4491 label_cont = label_true;
4493 else
4495 bool then_side_effects
4496 = (TREE_OPERAND (expr, 1)
4497 && TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 1)));
4498 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
4499 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
4500 /* For if (...) { code; } else {} or
4501 if (...) { code; } else goto label; or
4502 if (...) { code; return; } else { ... }
4503 label_cont isn't needed. */
4504 if (!have_else_clause_p
4505 && TREE_OPERAND (expr, 2) != NULL_TREE
4506 && gimple_seq_may_fallthru (seq))
4508 gimple *g;
4509 label_cont = create_artificial_label (UNKNOWN_LOCATION);
4511 /* For if (0) { non-side-effect-code } else { code }
4512 tell -Wimplicit-fallthrough handling that label_cont can
4513 be only reached through fallthrough from { code }. */
4514 if (integer_zerop (COND_EXPR_COND (expr)))
4516 UNUSED_LABEL_P (label_true) = 1;
4517 if (!then_side_effects)
4518 UNUSED_LABEL_P (label_cont) = 1;
4521 g = gimple_build_goto (label_cont);
4523 /* GIMPLE_COND's are very low level; they have embedded
4524 gotos. This particular embedded goto should not be marked
4525 with the location of the original COND_EXPR, as it would
4526 correspond to the COND_EXPR's condition, not the ELSE or the
4527 THEN arms. To avoid marking it with the wrong location, flag
4528 it as "no location". */
4529 gimple_set_do_not_emit_location (g);
4531 gimplify_seq_add_stmt (&seq, g);
4535 if (!have_else_clause_p)
4537 /* For if (1) { code } or if (1) { code } else { non-side-effect-code }
4538 tell -Wimplicit-fallthrough handling that label_false can be only
4539 reached through fallthrough from { code }. */
4540 if (integer_nonzerop (COND_EXPR_COND (expr))
4541 && (TREE_OPERAND (expr, 2) == NULL_TREE
4542 || !TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 2))))
4543 UNUSED_LABEL_P (label_false) = 1;
4544 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
4545 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
4547 if (label_cont)
4548 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
4550 gimple_pop_condition (pre_p);
4551 gimple_seq_add_seq (pre_p, seq);
4553 if (ret == GS_ERROR)
4554 ; /* Do nothing. */
4555 else if (have_then_clause_p || have_else_clause_p)
4556 ret = GS_ALL_DONE;
4557 else
4559 /* Both arms are empty; replace the COND_EXPR with its predicate. */
4560 expr = TREE_OPERAND (expr, 0);
4561 gimplify_stmt (&expr, pre_p);
4564 *expr_p = NULL;
4565 return ret;
4568 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4569 to be marked addressable.
4571 We cannot rely on such an expression being directly markable if a temporary
4572 has been created by the gimplification. In this case, we create another
4573 temporary and initialize it with a copy, which will become a store after we
4574 mark it addressable. This can happen if the front-end passed us something
4575 that it could not mark addressable yet, like a Fortran pass-by-reference
4576 parameter (int) floatvar. */
4578 static void
4579 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4581 while (handled_component_p (*expr_p))
4582 expr_p = &TREE_OPERAND (*expr_p, 0);
4584 /* Do not allow an SSA name as the temporary. */
4585 if (is_gimple_reg (*expr_p))
4586 *expr_p = internal_get_tmp_var (*expr_p, seq_p, NULL, false, false, true);
4589 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4590 a call to __builtin_memcpy. */
4592 static enum gimplify_status
4593 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4594 gimple_seq *seq_p)
4596 tree t, to, to_ptr, from, from_ptr;
4597 gcall *gs;
4598 location_t loc = EXPR_LOCATION (*expr_p);
4600 to = TREE_OPERAND (*expr_p, 0);
4601 from = TREE_OPERAND (*expr_p, 1);
4603 /* Mark the RHS addressable. Beware that it may not be possible to do so
4604 directly if a temporary has been created by the gimplification. */
4605 prepare_gimple_addressable (&from, seq_p);
4607 mark_addressable (from);
4608 from_ptr = build_fold_addr_expr_loc (loc, from);
4609 gimplify_arg (&from_ptr, seq_p, loc);
4611 mark_addressable (to);
4612 to_ptr = build_fold_addr_expr_loc (loc, to);
4613 gimplify_arg (&to_ptr, seq_p, loc);
4615 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4617 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4618 gimple_call_set_alloca_for_var (gs, true);
4620 if (want_value)
4622 /* tmp = memcpy() */
4623 t = create_tmp_var (TREE_TYPE (to_ptr));
4624 gimple_call_set_lhs (gs, t);
4625 gimplify_seq_add_stmt (seq_p, gs);
4627 *expr_p = build_simple_mem_ref (t);
4628 return GS_ALL_DONE;
4631 gimplify_seq_add_stmt (seq_p, gs);
4632 *expr_p = NULL;
4633 return GS_ALL_DONE;
4636 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4637 a call to __builtin_memset. In this case we know that the RHS is
4638 a CONSTRUCTOR with an empty element list. */
4640 static enum gimplify_status
4641 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4642 gimple_seq *seq_p)
4644 tree t, from, to, to_ptr;
4645 gcall *gs;
4646 location_t loc = EXPR_LOCATION (*expr_p);
4648 /* Assert our assumptions, to abort instead of producing wrong code
4649 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4650 not be immediately exposed. */
4651 from = TREE_OPERAND (*expr_p, 1);
4652 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4653 from = TREE_OPERAND (from, 0);
4655 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4656 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4658 /* Now proceed. */
4659 to = TREE_OPERAND (*expr_p, 0);
4661 to_ptr = build_fold_addr_expr_loc (loc, to);
4662 gimplify_arg (&to_ptr, seq_p, loc);
4663 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4665 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4667 if (want_value)
4669 /* tmp = memset() */
4670 t = create_tmp_var (TREE_TYPE (to_ptr));
4671 gimple_call_set_lhs (gs, t);
4672 gimplify_seq_add_stmt (seq_p, gs);
4674 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4675 return GS_ALL_DONE;
4678 gimplify_seq_add_stmt (seq_p, gs);
4679 *expr_p = NULL;
4680 return GS_ALL_DONE;
4683 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4684 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4685 assignment. Return non-null if we detect a potential overlap. */
4687 struct gimplify_init_ctor_preeval_data
4689 /* The base decl of the lhs object. May be NULL, in which case we
4690 have to assume the lhs is indirect. */
4691 tree lhs_base_decl;
4693 /* The alias set of the lhs object. */
4694 alias_set_type lhs_alias_set;
4697 static tree
4698 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4700 struct gimplify_init_ctor_preeval_data *data
4701 = (struct gimplify_init_ctor_preeval_data *) xdata;
4702 tree t = *tp;
4704 /* If we find the base object, obviously we have overlap. */
4705 if (data->lhs_base_decl == t)
4706 return t;
4708 /* If the constructor component is indirect, determine if we have a
4709 potential overlap with the lhs. The only bits of information we
4710 have to go on at this point are addressability and alias sets. */
4711 if ((INDIRECT_REF_P (t)
4712 || TREE_CODE (t) == MEM_REF)
4713 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4714 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
4715 return t;
4717 /* If the constructor component is a call, determine if it can hide a
4718 potential overlap with the lhs through an INDIRECT_REF like above.
4719 ??? Ugh - this is completely broken. In fact this whole analysis
4720 doesn't look conservative. */
4721 if (TREE_CODE (t) == CALL_EXPR)
4723 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
4725 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
4726 if (POINTER_TYPE_P (TREE_VALUE (type))
4727 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4728 && alias_sets_conflict_p (data->lhs_alias_set,
4729 get_alias_set
4730 (TREE_TYPE (TREE_VALUE (type)))))
4731 return t;
4734 if (IS_TYPE_OR_DECL_P (t))
4735 *walk_subtrees = 0;
4736 return NULL;
4739 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
4740 force values that overlap with the lhs (as described by *DATA)
4741 into temporaries. */
4743 static void
4744 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4745 struct gimplify_init_ctor_preeval_data *data)
4747 enum gimplify_status one;
4749 /* If the value is constant, then there's nothing to pre-evaluate. */
4750 if (TREE_CONSTANT (*expr_p))
4752 /* Ensure it does not have side effects, it might contain a reference to
4753 the object we're initializing. */
4754 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
4755 return;
4758 /* If the type has non-trivial constructors, we can't pre-evaluate. */
4759 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
4760 return;
4762 /* Recurse for nested constructors. */
4763 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
4765 unsigned HOST_WIDE_INT ix;
4766 constructor_elt *ce;
4767 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
4769 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
4770 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
4772 return;
4775 /* If this is a variable sized type, we must remember the size. */
4776 maybe_with_size_expr (expr_p);
4778 /* Gimplify the constructor element to something appropriate for the rhs
4779 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
4780 the gimplifier will consider this a store to memory. Doing this
4781 gimplification now means that we won't have to deal with complicated
4782 language-specific trees, nor trees like SAVE_EXPR that can induce
4783 exponential search behavior. */
4784 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
4785 if (one == GS_ERROR)
4787 *expr_p = NULL;
4788 return;
4791 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
4792 with the lhs, since "a = { .x=a }" doesn't make sense. This will
4793 always be true for all scalars, since is_gimple_mem_rhs insists on a
4794 temporary variable for them. */
4795 if (DECL_P (*expr_p))
4796 return;
4798 /* If this is of variable size, we have no choice but to assume it doesn't
4799 overlap since we can't make a temporary for it. */
4800 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
4801 return;
4803 /* Otherwise, we must search for overlap ... */
4804 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
4805 return;
4807 /* ... and if found, force the value into a temporary. */
4808 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
4811 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
4812 a RANGE_EXPR in a CONSTRUCTOR for an array.
4814 var = lower;
4815 loop_entry:
4816 object[var] = value;
4817 if (var == upper)
4818 goto loop_exit;
4819 var = var + 1;
4820 goto loop_entry;
4821 loop_exit:
4823 We increment var _after_ the loop exit check because we might otherwise
4824 fail if upper == TYPE_MAX_VALUE (type for upper).
4826 Note that we never have to deal with SAVE_EXPRs here, because this has
4827 already been taken care of for us, in gimplify_init_ctor_preeval(). */
4829 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
4830 gimple_seq *, bool);
4832 static void
4833 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
4834 tree value, tree array_elt_type,
4835 gimple_seq *pre_p, bool cleared)
4837 tree loop_entry_label, loop_exit_label, fall_thru_label;
4838 tree var, var_type, cref, tmp;
4840 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
4841 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
4842 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
4844 /* Create and initialize the index variable. */
4845 var_type = TREE_TYPE (upper);
4846 var = create_tmp_var (var_type);
4847 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
4849 /* Add the loop entry label. */
4850 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
4852 /* Build the reference. */
4853 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4854 var, NULL_TREE, NULL_TREE);
4856 /* If we are a constructor, just call gimplify_init_ctor_eval to do
4857 the store. Otherwise just assign value to the reference. */
4859 if (TREE_CODE (value) == CONSTRUCTOR)
4860 /* NB we might have to call ourself recursively through
4861 gimplify_init_ctor_eval if the value is a constructor. */
4862 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4863 pre_p, cleared);
4864 else
4866 if (gimplify_expr (&value, pre_p, NULL, is_gimple_val, fb_rvalue)
4867 != GS_ERROR)
4868 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
4871 /* We exit the loop when the index var is equal to the upper bound. */
4872 gimplify_seq_add_stmt (pre_p,
4873 gimple_build_cond (EQ_EXPR, var, upper,
4874 loop_exit_label, fall_thru_label));
4876 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
4878 /* Otherwise, increment the index var... */
4879 tmp = build2 (PLUS_EXPR, var_type, var,
4880 fold_convert (var_type, integer_one_node));
4881 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
4883 /* ...and jump back to the loop entry. */
4884 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
4886 /* Add the loop exit label. */
4887 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
4890 /* A subroutine of gimplify_init_constructor. Generate individual
4891 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
4892 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
4893 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
4894 zeroed first. */
4896 static void
4897 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
4898 gimple_seq *pre_p, bool cleared)
4900 tree array_elt_type = NULL;
4901 unsigned HOST_WIDE_INT ix;
4902 tree purpose, value;
4904 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
4905 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
4907 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
4909 tree cref;
4911 /* NULL values are created above for gimplification errors. */
4912 if (value == NULL)
4913 continue;
4915 if (cleared && initializer_zerop (value))
4916 continue;
4918 /* ??? Here's to hoping the front end fills in all of the indices,
4919 so we don't have to figure out what's missing ourselves. */
4920 gcc_assert (purpose);
4922 /* Skip zero-sized fields, unless value has side-effects. This can
4923 happen with calls to functions returning a empty type, which
4924 we shouldn't discard. As a number of downstream passes don't
4925 expect sets of empty type fields, we rely on the gimplification of
4926 the MODIFY_EXPR we make below to drop the assignment statement. */
4927 if (!TREE_SIDE_EFFECTS (value)
4928 && TREE_CODE (purpose) == FIELD_DECL
4929 && is_empty_type (TREE_TYPE (purpose)))
4930 continue;
4932 /* If we have a RANGE_EXPR, we have to build a loop to assign the
4933 whole range. */
4934 if (TREE_CODE (purpose) == RANGE_EXPR)
4936 tree lower = TREE_OPERAND (purpose, 0);
4937 tree upper = TREE_OPERAND (purpose, 1);
4939 /* If the lower bound is equal to upper, just treat it as if
4940 upper was the index. */
4941 if (simple_cst_equal (lower, upper))
4942 purpose = upper;
4943 else
4945 gimplify_init_ctor_eval_range (object, lower, upper, value,
4946 array_elt_type, pre_p, cleared);
4947 continue;
4951 if (array_elt_type)
4953 /* Do not use bitsizetype for ARRAY_REF indices. */
4954 if (TYPE_DOMAIN (TREE_TYPE (object)))
4955 purpose
4956 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
4957 purpose);
4958 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4959 purpose, NULL_TREE, NULL_TREE);
4961 else
4963 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
4964 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
4965 unshare_expr (object), purpose, NULL_TREE);
4968 if (TREE_CODE (value) == CONSTRUCTOR
4969 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
4970 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4971 pre_p, cleared);
4972 else
4974 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
4975 gimplify_and_add (init, pre_p);
4976 ggc_free (init);
4981 /* Return the appropriate RHS predicate for this LHS. */
4983 gimple_predicate
4984 rhs_predicate_for (tree lhs)
4986 if (is_gimple_reg (lhs))
4987 return is_gimple_reg_rhs_or_call;
4988 else
4989 return is_gimple_mem_rhs_or_call;
4992 /* Return the initial guess for an appropriate RHS predicate for this LHS,
4993 before the LHS has been gimplified. */
4995 static gimple_predicate
4996 initial_rhs_predicate_for (tree lhs)
4998 if (is_gimple_reg_type (TREE_TYPE (lhs)))
4999 return is_gimple_reg_rhs_or_call;
5000 else
5001 return is_gimple_mem_rhs_or_call;
5004 /* Gimplify a C99 compound literal expression. This just means adding
5005 the DECL_EXPR before the current statement and using its anonymous
5006 decl instead. */
5008 static enum gimplify_status
5009 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
5010 bool (*gimple_test_f) (tree),
5011 fallback_t fallback)
5013 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
5014 tree decl = DECL_EXPR_DECL (decl_s);
5015 tree init = DECL_INITIAL (decl);
5016 /* Mark the decl as addressable if the compound literal
5017 expression is addressable now, otherwise it is marked too late
5018 after we gimplify the initialization expression. */
5019 if (TREE_ADDRESSABLE (*expr_p))
5020 TREE_ADDRESSABLE (decl) = 1;
5021 /* Otherwise, if we don't need an lvalue and have a literal directly
5022 substitute it. Check if it matches the gimple predicate, as
5023 otherwise we'd generate a new temporary, and we can as well just
5024 use the decl we already have. */
5025 else if (!TREE_ADDRESSABLE (decl)
5026 && !TREE_THIS_VOLATILE (decl)
5027 && init
5028 && (fallback & fb_lvalue) == 0
5029 && gimple_test_f (init))
5031 *expr_p = init;
5032 return GS_OK;
5035 /* If the decl is not addressable, then it is being used in some
5036 expression or on the right hand side of a statement, and it can
5037 be put into a readonly data section. */
5038 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
5039 TREE_READONLY (decl) = 1;
5041 /* This decl isn't mentioned in the enclosing block, so add it to the
5042 list of temps. FIXME it seems a bit of a kludge to say that
5043 anonymous artificial vars aren't pushed, but everything else is. */
5044 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
5045 gimple_add_tmp_var (decl);
5047 gimplify_and_add (decl_s, pre_p);
5048 *expr_p = decl;
5049 return GS_OK;
5052 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
5053 return a new CONSTRUCTOR if something changed. */
5055 static tree
5056 optimize_compound_literals_in_ctor (tree orig_ctor)
5058 tree ctor = orig_ctor;
5059 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
5060 unsigned int idx, num = vec_safe_length (elts);
5062 for (idx = 0; idx < num; idx++)
5064 tree value = (*elts)[idx].value;
5065 tree newval = value;
5066 if (TREE_CODE (value) == CONSTRUCTOR)
5067 newval = optimize_compound_literals_in_ctor (value);
5068 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
5070 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
5071 tree decl = DECL_EXPR_DECL (decl_s);
5072 tree init = DECL_INITIAL (decl);
5074 if (!TREE_ADDRESSABLE (value)
5075 && !TREE_ADDRESSABLE (decl)
5076 && init
5077 && TREE_CODE (init) == CONSTRUCTOR)
5078 newval = optimize_compound_literals_in_ctor (init);
5080 if (newval == value)
5081 continue;
5083 if (ctor == orig_ctor)
5085 ctor = copy_node (orig_ctor);
5086 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
5087 elts = CONSTRUCTOR_ELTS (ctor);
5089 (*elts)[idx].value = newval;
5091 return ctor;
5094 /* A subroutine of gimplify_modify_expr. Break out elements of a
5095 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
5097 Note that we still need to clear any elements that don't have explicit
5098 initializers, so if not all elements are initialized we keep the
5099 original MODIFY_EXPR, we just remove all of the constructor elements.
5101 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
5102 GS_ERROR if we would have to create a temporary when gimplifying
5103 this constructor. Otherwise, return GS_OK.
5105 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
5107 static enum gimplify_status
5108 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5109 bool want_value, bool notify_temp_creation)
5111 tree object, ctor, type;
5112 enum gimplify_status ret;
5113 vec<constructor_elt, va_gc> *elts;
5114 bool cleared = false;
5115 bool is_empty_ctor = false;
5116 bool is_init_expr = (TREE_CODE (*expr_p) == INIT_EXPR);
5118 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
5120 if (!notify_temp_creation)
5122 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5123 is_gimple_lvalue, fb_lvalue);
5124 if (ret == GS_ERROR)
5125 return ret;
5128 object = TREE_OPERAND (*expr_p, 0);
5129 ctor = TREE_OPERAND (*expr_p, 1)
5130 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
5131 type = TREE_TYPE (ctor);
5132 elts = CONSTRUCTOR_ELTS (ctor);
5133 ret = GS_ALL_DONE;
5135 switch (TREE_CODE (type))
5137 case RECORD_TYPE:
5138 case UNION_TYPE:
5139 case QUAL_UNION_TYPE:
5140 case ARRAY_TYPE:
5142 /* Use readonly data for initializers of this or smaller size
5143 regardless of the num_nonzero_elements / num_unique_nonzero_elements
5144 ratio. */
5145 const HOST_WIDE_INT min_unique_size = 64;
5146 /* If num_nonzero_elements / num_unique_nonzero_elements ratio
5147 is smaller than this, use readonly data. */
5148 const int unique_nonzero_ratio = 8;
5149 /* True if a single access of the object must be ensured. This is the
5150 case if the target is volatile, the type is non-addressable and more
5151 than one field need to be assigned. */
5152 const bool ensure_single_access
5153 = TREE_THIS_VOLATILE (object)
5154 && !TREE_ADDRESSABLE (type)
5155 && vec_safe_length (elts) > 1;
5156 struct gimplify_init_ctor_preeval_data preeval_data;
5157 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
5158 HOST_WIDE_INT num_unique_nonzero_elements;
5159 bool complete_p, valid_const_initializer;
5161 /* Aggregate types must lower constructors to initialization of
5162 individual elements. The exception is that a CONSTRUCTOR node
5163 with no elements indicates zero-initialization of the whole. */
5164 if (vec_safe_is_empty (elts))
5166 if (notify_temp_creation)
5167 return GS_OK;
5169 /* The var will be initialized and so appear on lhs of
5170 assignment, it can't be TREE_READONLY anymore. */
5171 if (VAR_P (object))
5172 TREE_READONLY (object) = 0;
5174 is_empty_ctor = true;
5175 break;
5178 /* Fetch information about the constructor to direct later processing.
5179 We might want to make static versions of it in various cases, and
5180 can only do so if it known to be a valid constant initializer. */
5181 valid_const_initializer
5182 = categorize_ctor_elements (ctor, &num_nonzero_elements,
5183 &num_unique_nonzero_elements,
5184 &num_ctor_elements, &complete_p);
5186 /* If a const aggregate variable is being initialized, then it
5187 should never be a lose to promote the variable to be static. */
5188 if (valid_const_initializer
5189 && num_nonzero_elements > 1
5190 && TREE_READONLY (object)
5191 && VAR_P (object)
5192 && !DECL_REGISTER (object)
5193 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object))
5194 /* For ctors that have many repeated nonzero elements
5195 represented through RANGE_EXPRs, prefer initializing
5196 those through runtime loops over copies of large amounts
5197 of data from readonly data section. */
5198 && (num_unique_nonzero_elements
5199 > num_nonzero_elements / unique_nonzero_ratio
5200 || ((unsigned HOST_WIDE_INT) int_size_in_bytes (type)
5201 <= (unsigned HOST_WIDE_INT) min_unique_size)))
5203 if (notify_temp_creation)
5204 return GS_ERROR;
5206 DECL_INITIAL (object) = ctor;
5207 TREE_STATIC (object) = 1;
5208 if (!DECL_NAME (object))
5209 DECL_NAME (object) = create_tmp_var_name ("C");
5210 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
5212 /* ??? C++ doesn't automatically append a .<number> to the
5213 assembler name, and even when it does, it looks at FE private
5214 data structures to figure out what that number should be,
5215 which are not set for this variable. I suppose this is
5216 important for local statics for inline functions, which aren't
5217 "local" in the object file sense. So in order to get a unique
5218 TU-local symbol, we must invoke the lhd version now. */
5219 lhd_set_decl_assembler_name (object);
5221 *expr_p = NULL_TREE;
5222 break;
5225 /* The var will be initialized and so appear on lhs of
5226 assignment, it can't be TREE_READONLY anymore. */
5227 if (VAR_P (object) && !notify_temp_creation)
5228 TREE_READONLY (object) = 0;
5230 /* If there are "lots" of initialized elements, even discounting
5231 those that are not address constants (and thus *must* be
5232 computed at runtime), then partition the constructor into
5233 constant and non-constant parts. Block copy the constant
5234 parts in, then generate code for the non-constant parts. */
5235 /* TODO. There's code in cp/typeck.cc to do this. */
5237 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
5238 /* store_constructor will ignore the clearing of variable-sized
5239 objects. Initializers for such objects must explicitly set
5240 every field that needs to be set. */
5241 cleared = false;
5242 else if (!complete_p)
5243 /* If the constructor isn't complete, clear the whole object
5244 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
5246 ??? This ought not to be needed. For any element not present
5247 in the initializer, we should simply set them to zero. Except
5248 we'd need to *find* the elements that are not present, and that
5249 requires trickery to avoid quadratic compile-time behavior in
5250 large cases or excessive memory use in small cases. */
5251 cleared = !CONSTRUCTOR_NO_CLEARING (ctor);
5252 else if (num_ctor_elements - num_nonzero_elements
5253 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
5254 && num_nonzero_elements < num_ctor_elements / 4)
5255 /* If there are "lots" of zeros, it's more efficient to clear
5256 the memory and then set the nonzero elements. */
5257 cleared = true;
5258 else if (ensure_single_access && num_nonzero_elements == 0)
5259 /* If a single access to the target must be ensured and all elements
5260 are zero, then it's optimal to clear whatever their number. */
5261 cleared = true;
5262 else
5263 cleared = false;
5265 /* If there are "lots" of initialized elements, and all of them
5266 are valid address constants, then the entire initializer can
5267 be dropped to memory, and then memcpy'd out. Don't do this
5268 for sparse arrays, though, as it's more efficient to follow
5269 the standard CONSTRUCTOR behavior of memset followed by
5270 individual element initialization. Also don't do this for small
5271 all-zero initializers (which aren't big enough to merit
5272 clearing), and don't try to make bitwise copies of
5273 TREE_ADDRESSABLE types. */
5274 if (valid_const_initializer
5275 && complete_p
5276 && !(cleared || num_nonzero_elements == 0)
5277 && !TREE_ADDRESSABLE (type))
5279 HOST_WIDE_INT size = int_size_in_bytes (type);
5280 unsigned int align;
5282 /* ??? We can still get unbounded array types, at least
5283 from the C++ front end. This seems wrong, but attempt
5284 to work around it for now. */
5285 if (size < 0)
5287 size = int_size_in_bytes (TREE_TYPE (object));
5288 if (size >= 0)
5289 TREE_TYPE (ctor) = type = TREE_TYPE (object);
5292 /* Find the maximum alignment we can assume for the object. */
5293 /* ??? Make use of DECL_OFFSET_ALIGN. */
5294 if (DECL_P (object))
5295 align = DECL_ALIGN (object);
5296 else
5297 align = TYPE_ALIGN (type);
5299 /* Do a block move either if the size is so small as to make
5300 each individual move a sub-unit move on average, or if it
5301 is so large as to make individual moves inefficient. */
5302 if (size > 0
5303 && num_nonzero_elements > 1
5304 /* For ctors that have many repeated nonzero elements
5305 represented through RANGE_EXPRs, prefer initializing
5306 those through runtime loops over copies of large amounts
5307 of data from readonly data section. */
5308 && (num_unique_nonzero_elements
5309 > num_nonzero_elements / unique_nonzero_ratio
5310 || size <= min_unique_size)
5311 && (size < num_nonzero_elements
5312 || !can_move_by_pieces (size, align)))
5314 if (notify_temp_creation)
5315 return GS_ERROR;
5317 walk_tree (&ctor, force_labels_r, NULL, NULL);
5318 ctor = tree_output_constant_def (ctor);
5319 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
5320 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
5321 TREE_OPERAND (*expr_p, 1) = ctor;
5323 /* This is no longer an assignment of a CONSTRUCTOR, but
5324 we still may have processing to do on the LHS. So
5325 pretend we didn't do anything here to let that happen. */
5326 return GS_UNHANDLED;
5330 /* If a single access to the target must be ensured and there are
5331 nonzero elements or the zero elements are not assigned en masse,
5332 initialize the target from a temporary. */
5333 if (ensure_single_access && (num_nonzero_elements > 0 || !cleared))
5335 if (notify_temp_creation)
5336 return GS_ERROR;
5338 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
5339 TREE_OPERAND (*expr_p, 0) = temp;
5340 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
5341 *expr_p,
5342 build2 (MODIFY_EXPR, void_type_node,
5343 object, temp));
5344 return GS_OK;
5347 if (notify_temp_creation)
5348 return GS_OK;
5350 /* If there are nonzero elements and if needed, pre-evaluate to capture
5351 elements overlapping with the lhs into temporaries. We must do this
5352 before clearing to fetch the values before they are zeroed-out. */
5353 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
5355 preeval_data.lhs_base_decl = get_base_address (object);
5356 if (!DECL_P (preeval_data.lhs_base_decl))
5357 preeval_data.lhs_base_decl = NULL;
5358 preeval_data.lhs_alias_set = get_alias_set (object);
5360 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
5361 pre_p, post_p, &preeval_data);
5364 bool ctor_has_side_effects_p
5365 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
5367 if (cleared)
5369 /* Zap the CONSTRUCTOR element list, which simplifies this case.
5370 Note that we still have to gimplify, in order to handle the
5371 case of variable sized types. Avoid shared tree structures. */
5372 CONSTRUCTOR_ELTS (ctor) = NULL;
5373 TREE_SIDE_EFFECTS (ctor) = 0;
5374 object = unshare_expr (object);
5375 gimplify_stmt (expr_p, pre_p);
5378 /* If we have not block cleared the object, or if there are nonzero
5379 elements in the constructor, or if the constructor has side effects,
5380 add assignments to the individual scalar fields of the object. */
5381 if (!cleared
5382 || num_nonzero_elements > 0
5383 || ctor_has_side_effects_p)
5384 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
5386 *expr_p = NULL_TREE;
5388 break;
5390 case COMPLEX_TYPE:
5392 tree r, i;
5394 if (notify_temp_creation)
5395 return GS_OK;
5397 /* Extract the real and imaginary parts out of the ctor. */
5398 gcc_assert (elts->length () == 2);
5399 r = (*elts)[0].value;
5400 i = (*elts)[1].value;
5401 if (r == NULL || i == NULL)
5403 tree zero = build_zero_cst (TREE_TYPE (type));
5404 if (r == NULL)
5405 r = zero;
5406 if (i == NULL)
5407 i = zero;
5410 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
5411 represent creation of a complex value. */
5412 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
5414 ctor = build_complex (type, r, i);
5415 TREE_OPERAND (*expr_p, 1) = ctor;
5417 else
5419 ctor = build2 (COMPLEX_EXPR, type, r, i);
5420 TREE_OPERAND (*expr_p, 1) = ctor;
5421 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
5422 pre_p,
5423 post_p,
5424 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
5425 fb_rvalue);
5428 break;
5430 case VECTOR_TYPE:
5432 unsigned HOST_WIDE_INT ix;
5433 constructor_elt *ce;
5435 if (notify_temp_creation)
5436 return GS_OK;
5438 /* Vector types use CONSTRUCTOR all the way through gimple
5439 compilation as a general initializer. */
5440 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
5442 enum gimplify_status tret;
5443 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
5444 fb_rvalue);
5445 if (tret == GS_ERROR)
5446 ret = GS_ERROR;
5447 else if (TREE_STATIC (ctor)
5448 && !initializer_constant_valid_p (ce->value,
5449 TREE_TYPE (ce->value)))
5450 TREE_STATIC (ctor) = 0;
5452 recompute_constructor_flags (ctor);
5454 /* Go ahead and simplify constant constructors to VECTOR_CST. */
5455 if (TREE_CONSTANT (ctor))
5457 bool constant_p = true;
5458 tree value;
5460 /* Even when ctor is constant, it might contain non-*_CST
5461 elements, such as addresses or trapping values like
5462 1.0/0.0 - 1.0/0.0. Such expressions don't belong
5463 in VECTOR_CST nodes. */
5464 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
5465 if (!CONSTANT_CLASS_P (value))
5467 constant_p = false;
5468 break;
5471 if (constant_p)
5473 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
5474 break;
5478 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
5479 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
5481 break;
5483 default:
5484 /* So how did we get a CONSTRUCTOR for a scalar type? */
5485 gcc_unreachable ();
5488 if (ret == GS_ERROR)
5489 return GS_ERROR;
5490 /* If we have gimplified both sides of the initializer but have
5491 not emitted an assignment, do so now. */
5492 if (*expr_p
5493 /* If the type is an empty type, we don't need to emit the
5494 assignment. */
5495 && !is_empty_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
5497 tree lhs = TREE_OPERAND (*expr_p, 0);
5498 tree rhs = TREE_OPERAND (*expr_p, 1);
5499 if (want_value && object == lhs)
5500 lhs = unshare_expr (lhs);
5501 gassign *init = gimple_build_assign (lhs, rhs);
5502 gimplify_seq_add_stmt (pre_p, init);
5504 if (want_value)
5506 *expr_p = object;
5507 ret = GS_OK;
5509 else
5511 *expr_p = NULL;
5512 ret = GS_ALL_DONE;
5515 /* If the user requests to initialize automatic variables, we
5516 should initialize paddings inside the variable. Add a call to
5517 __builtin_clear_pading (&object, 0, for_auto_init = true) to
5518 initialize paddings of object always to zero regardless of
5519 INIT_TYPE. Note, we will not insert this call if the aggregate
5520 variable has be completely cleared already or it's initialized
5521 with an empty constructor. We cannot insert this call if the
5522 variable is a gimple register since __builtin_clear_padding will take
5523 the address of the variable. As a result, if a long double/_Complex long
5524 double variable will be spilled into stack later, its padding cannot
5525 be cleared with __builtin_clear_padding. We should clear its padding
5526 when it is spilled into memory. */
5527 if (is_init_expr
5528 && !is_gimple_reg (object)
5529 && clear_padding_type_may_have_padding_p (type)
5530 && ((AGGREGATE_TYPE_P (type) && !cleared && !is_empty_ctor)
5531 || !AGGREGATE_TYPE_P (type))
5532 && is_var_need_auto_init (object))
5533 gimple_add_padding_init_for_auto_var (object, false, pre_p);
5535 return ret;
5538 /* Given a pointer value OP0, return a simplified version of an
5539 indirection through OP0, or NULL_TREE if no simplification is
5540 possible. This may only be applied to a rhs of an expression.
5541 Note that the resulting type may be different from the type pointed
5542 to in the sense that it is still compatible from the langhooks
5543 point of view. */
5545 static tree
5546 gimple_fold_indirect_ref_rhs (tree t)
5548 return gimple_fold_indirect_ref (t);
5551 /* Subroutine of gimplify_modify_expr to do simplifications of
5552 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
5553 something changes. */
5555 static enum gimplify_status
5556 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
5557 gimple_seq *pre_p, gimple_seq *post_p,
5558 bool want_value)
5560 enum gimplify_status ret = GS_UNHANDLED;
5561 bool changed;
5565 changed = false;
5566 switch (TREE_CODE (*from_p))
5568 case VAR_DECL:
5569 /* If we're assigning from a read-only variable initialized with
5570 a constructor and not volatile, do the direct assignment from
5571 the constructor, but only if the target is not volatile either
5572 since this latter assignment might end up being done on a per
5573 field basis. However, if the target is volatile and the type
5574 is aggregate and non-addressable, gimplify_init_constructor
5575 knows that it needs to ensure a single access to the target
5576 and it will return GS_OK only in this case. */
5577 if (TREE_READONLY (*from_p)
5578 && DECL_INITIAL (*from_p)
5579 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR
5580 && !TREE_THIS_VOLATILE (*from_p)
5581 && (!TREE_THIS_VOLATILE (*to_p)
5582 || (AGGREGATE_TYPE_P (TREE_TYPE (*to_p))
5583 && !TREE_ADDRESSABLE (TREE_TYPE (*to_p)))))
5585 tree old_from = *from_p;
5586 enum gimplify_status subret;
5588 /* Move the constructor into the RHS. */
5589 *from_p = unshare_expr (DECL_INITIAL (*from_p));
5591 /* Let's see if gimplify_init_constructor will need to put
5592 it in memory. */
5593 subret = gimplify_init_constructor (expr_p, NULL, NULL,
5594 false, true);
5595 if (subret == GS_ERROR)
5597 /* If so, revert the change. */
5598 *from_p = old_from;
5600 else
5602 ret = GS_OK;
5603 changed = true;
5606 break;
5607 case INDIRECT_REF:
5609 /* If we have code like
5611 *(const A*)(A*)&x
5613 where the type of "x" is a (possibly cv-qualified variant
5614 of "A"), treat the entire expression as identical to "x".
5615 This kind of code arises in C++ when an object is bound
5616 to a const reference, and if "x" is a TARGET_EXPR we want
5617 to take advantage of the optimization below. */
5618 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5619 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
5620 if (t)
5622 if (TREE_THIS_VOLATILE (t) != volatile_p)
5624 if (DECL_P (t))
5625 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5626 build_fold_addr_expr (t));
5627 if (REFERENCE_CLASS_P (t))
5628 TREE_THIS_VOLATILE (t) = volatile_p;
5630 *from_p = t;
5631 ret = GS_OK;
5632 changed = true;
5634 break;
5637 case TARGET_EXPR:
5639 /* If we are initializing something from a TARGET_EXPR, strip the
5640 TARGET_EXPR and initialize it directly, if possible. This can't
5641 be done if the initializer is void, since that implies that the
5642 temporary is set in some non-trivial way.
5644 ??? What about code that pulls out the temp and uses it
5645 elsewhere? I think that such code never uses the TARGET_EXPR as
5646 an initializer. If I'm wrong, we'll die because the temp won't
5647 have any RTL. In that case, I guess we'll need to replace
5648 references somehow. */
5649 tree init = TARGET_EXPR_INITIAL (*from_p);
5651 if (init
5652 && (TREE_CODE (*expr_p) != MODIFY_EXPR
5653 || !TARGET_EXPR_NO_ELIDE (*from_p))
5654 && !VOID_TYPE_P (TREE_TYPE (init)))
5656 *from_p = init;
5657 ret = GS_OK;
5658 changed = true;
5661 break;
5663 case COMPOUND_EXPR:
5664 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5665 caught. */
5666 gimplify_compound_expr (from_p, pre_p, true);
5667 ret = GS_OK;
5668 changed = true;
5669 break;
5671 case CONSTRUCTOR:
5672 /* If we already made some changes, let the front end have a
5673 crack at this before we break it down. */
5674 if (ret != GS_UNHANDLED)
5675 break;
5677 /* If we're initializing from a CONSTRUCTOR, break this into
5678 individual MODIFY_EXPRs. */
5679 ret = gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5680 false);
5681 return ret;
5683 case COND_EXPR:
5684 /* If we're assigning to a non-register type, push the assignment
5685 down into the branches. This is mandatory for ADDRESSABLE types,
5686 since we cannot generate temporaries for such, but it saves a
5687 copy in other cases as well. */
5688 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5690 /* This code should mirror the code in gimplify_cond_expr. */
5691 enum tree_code code = TREE_CODE (*expr_p);
5692 tree cond = *from_p;
5693 tree result = *to_p;
5695 ret = gimplify_expr (&result, pre_p, post_p,
5696 is_gimple_lvalue, fb_lvalue);
5697 if (ret != GS_ERROR)
5698 ret = GS_OK;
5700 /* If we are going to write RESULT more than once, clear
5701 TREE_READONLY flag, otherwise we might incorrectly promote
5702 the variable to static const and initialize it at compile
5703 time in one of the branches. */
5704 if (VAR_P (result)
5705 && TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node
5706 && TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5707 TREE_READONLY (result) = 0;
5708 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
5709 TREE_OPERAND (cond, 1)
5710 = build2 (code, void_type_node, result,
5711 TREE_OPERAND (cond, 1));
5712 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5713 TREE_OPERAND (cond, 2)
5714 = build2 (code, void_type_node, unshare_expr (result),
5715 TREE_OPERAND (cond, 2));
5717 TREE_TYPE (cond) = void_type_node;
5718 recalculate_side_effects (cond);
5720 if (want_value)
5722 gimplify_and_add (cond, pre_p);
5723 *expr_p = unshare_expr (result);
5725 else
5726 *expr_p = cond;
5727 return ret;
5729 break;
5731 case CALL_EXPR:
5732 /* For calls that return in memory, give *to_p as the CALL_EXPR's
5733 return slot so that we don't generate a temporary. */
5734 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
5735 && aggregate_value_p (*from_p, *from_p))
5737 bool use_target;
5739 if (!(rhs_predicate_for (*to_p))(*from_p))
5740 /* If we need a temporary, *to_p isn't accurate. */
5741 use_target = false;
5742 /* It's OK to use the return slot directly unless it's an NRV. */
5743 else if (TREE_CODE (*to_p) == RESULT_DECL
5744 && DECL_NAME (*to_p) == NULL_TREE
5745 && needs_to_live_in_memory (*to_p))
5746 use_target = true;
5747 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
5748 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
5749 /* Don't force regs into memory. */
5750 use_target = false;
5751 else if (TREE_CODE (*expr_p) == INIT_EXPR)
5752 /* It's OK to use the target directly if it's being
5753 initialized. */
5754 use_target = true;
5755 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
5756 != INTEGER_CST)
5757 /* Always use the target and thus RSO for variable-sized types.
5758 GIMPLE cannot deal with a variable-sized assignment
5759 embedded in a call statement. */
5760 use_target = true;
5761 else if (TREE_CODE (*to_p) != SSA_NAME
5762 && (!is_gimple_variable (*to_p)
5763 || needs_to_live_in_memory (*to_p)))
5764 /* Don't use the original target if it's already addressable;
5765 if its address escapes, and the called function uses the
5766 NRV optimization, a conforming program could see *to_p
5767 change before the called function returns; see c++/19317.
5768 When optimizing, the return_slot pass marks more functions
5769 as safe after we have escape info. */
5770 use_target = false;
5771 else
5772 use_target = true;
5774 if (use_target)
5776 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
5777 mark_addressable (*to_p);
5780 break;
5782 case WITH_SIZE_EXPR:
5783 /* Likewise for calls that return an aggregate of non-constant size,
5784 since we would not be able to generate a temporary at all. */
5785 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
5787 *from_p = TREE_OPERAND (*from_p, 0);
5788 /* We don't change ret in this case because the
5789 WITH_SIZE_EXPR might have been added in
5790 gimplify_modify_expr, so returning GS_OK would lead to an
5791 infinite loop. */
5792 changed = true;
5794 break;
5796 /* If we're initializing from a container, push the initialization
5797 inside it. */
5798 case CLEANUP_POINT_EXPR:
5799 case BIND_EXPR:
5800 case STATEMENT_LIST:
5802 tree wrap = *from_p;
5803 tree t;
5805 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
5806 fb_lvalue);
5807 if (ret != GS_ERROR)
5808 ret = GS_OK;
5810 t = voidify_wrapper_expr (wrap, *expr_p);
5811 gcc_assert (t == *expr_p);
5813 if (want_value)
5815 gimplify_and_add (wrap, pre_p);
5816 *expr_p = unshare_expr (*to_p);
5818 else
5819 *expr_p = wrap;
5820 return GS_OK;
5823 case NOP_EXPR:
5824 /* Pull out compound literal expressions from a NOP_EXPR.
5825 Those are created in the C FE to drop qualifiers during
5826 lvalue conversion. */
5827 if ((TREE_CODE (TREE_OPERAND (*from_p, 0)) == COMPOUND_LITERAL_EXPR)
5828 && tree_ssa_useless_type_conversion (*from_p))
5830 *from_p = TREE_OPERAND (*from_p, 0);
5831 ret = GS_OK;
5832 changed = true;
5834 break;
5836 case COMPOUND_LITERAL_EXPR:
5838 tree complit = TREE_OPERAND (*expr_p, 1);
5839 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
5840 tree decl = DECL_EXPR_DECL (decl_s);
5841 tree init = DECL_INITIAL (decl);
5843 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
5844 into struct T x = { 0, 1, 2 } if the address of the
5845 compound literal has never been taken. */
5846 if (!TREE_ADDRESSABLE (complit)
5847 && !TREE_ADDRESSABLE (decl)
5848 && init)
5850 *expr_p = copy_node (*expr_p);
5851 TREE_OPERAND (*expr_p, 1) = init;
5852 return GS_OK;
5856 default:
5857 break;
5860 while (changed);
5862 return ret;
5866 /* Return true if T looks like a valid GIMPLE statement. */
5868 static bool
5869 is_gimple_stmt (tree t)
5871 const enum tree_code code = TREE_CODE (t);
5873 switch (code)
5875 case NOP_EXPR:
5876 /* The only valid NOP_EXPR is the empty statement. */
5877 return IS_EMPTY_STMT (t);
5879 case BIND_EXPR:
5880 case COND_EXPR:
5881 /* These are only valid if they're void. */
5882 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
5884 case SWITCH_EXPR:
5885 case GOTO_EXPR:
5886 case RETURN_EXPR:
5887 case LABEL_EXPR:
5888 case CASE_LABEL_EXPR:
5889 case TRY_CATCH_EXPR:
5890 case TRY_FINALLY_EXPR:
5891 case EH_FILTER_EXPR:
5892 case CATCH_EXPR:
5893 case ASM_EXPR:
5894 case STATEMENT_LIST:
5895 case OACC_PARALLEL:
5896 case OACC_KERNELS:
5897 case OACC_SERIAL:
5898 case OACC_DATA:
5899 case OACC_HOST_DATA:
5900 case OACC_DECLARE:
5901 case OACC_UPDATE:
5902 case OACC_ENTER_DATA:
5903 case OACC_EXIT_DATA:
5904 case OACC_CACHE:
5905 case OMP_PARALLEL:
5906 case OMP_FOR:
5907 case OMP_SIMD:
5908 case OMP_DISTRIBUTE:
5909 case OMP_LOOP:
5910 case OACC_LOOP:
5911 case OMP_SCAN:
5912 case OMP_SCOPE:
5913 case OMP_SECTIONS:
5914 case OMP_SECTION:
5915 case OMP_SINGLE:
5916 case OMP_MASTER:
5917 case OMP_MASKED:
5918 case OMP_TASKGROUP:
5919 case OMP_ORDERED:
5920 case OMP_CRITICAL:
5921 case OMP_TASK:
5922 case OMP_TARGET:
5923 case OMP_TARGET_DATA:
5924 case OMP_TARGET_UPDATE:
5925 case OMP_TARGET_ENTER_DATA:
5926 case OMP_TARGET_EXIT_DATA:
5927 case OMP_TASKLOOP:
5928 case OMP_TEAMS:
5929 /* These are always void. */
5930 return true;
5932 case CALL_EXPR:
5933 case MODIFY_EXPR:
5934 case PREDICT_EXPR:
5935 /* These are valid regardless of their type. */
5936 return true;
5938 default:
5939 return false;
5944 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
5945 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a gimple register.
5947 IMPORTANT NOTE: This promotion is performed by introducing a load of the
5948 other, unmodified part of the complex object just before the total store.
5949 As a consequence, if the object is still uninitialized, an undefined value
5950 will be loaded into a register, which may result in a spurious exception
5951 if the register is floating-point and the value happens to be a signaling
5952 NaN for example. Then the fully-fledged complex operations lowering pass
5953 followed by a DCE pass are necessary in order to fix things up. */
5955 static enum gimplify_status
5956 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
5957 bool want_value)
5959 enum tree_code code, ocode;
5960 tree lhs, rhs, new_rhs, other, realpart, imagpart;
5962 lhs = TREE_OPERAND (*expr_p, 0);
5963 rhs = TREE_OPERAND (*expr_p, 1);
5964 code = TREE_CODE (lhs);
5965 lhs = TREE_OPERAND (lhs, 0);
5967 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
5968 other = build1 (ocode, TREE_TYPE (rhs), lhs);
5969 suppress_warning (other);
5970 other = get_formal_tmp_var (other, pre_p);
5972 realpart = code == REALPART_EXPR ? rhs : other;
5973 imagpart = code == REALPART_EXPR ? other : rhs;
5975 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
5976 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
5977 else
5978 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
5980 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
5981 *expr_p = (want_value) ? rhs : NULL_TREE;
5983 return GS_ALL_DONE;
5986 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
5988 modify_expr
5989 : varname '=' rhs
5990 | '*' ID '=' rhs
5992 PRE_P points to the list where side effects that must happen before
5993 *EXPR_P should be stored.
5995 POST_P points to the list where side effects that must happen after
5996 *EXPR_P should be stored.
5998 WANT_VALUE is nonzero iff we want to use the value of this expression
5999 in another expression. */
6001 static enum gimplify_status
6002 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
6003 bool want_value)
6005 tree *from_p = &TREE_OPERAND (*expr_p, 1);
6006 tree *to_p = &TREE_OPERAND (*expr_p, 0);
6007 enum gimplify_status ret = GS_UNHANDLED;
6008 gimple *assign;
6009 location_t loc = EXPR_LOCATION (*expr_p);
6010 gimple_stmt_iterator gsi;
6012 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
6013 || TREE_CODE (*expr_p) == INIT_EXPR);
6015 /* Trying to simplify a clobber using normal logic doesn't work,
6016 so handle it here. */
6017 if (TREE_CLOBBER_P (*from_p))
6019 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
6020 if (ret == GS_ERROR)
6021 return ret;
6022 gcc_assert (!want_value);
6023 if (!VAR_P (*to_p) && TREE_CODE (*to_p) != MEM_REF)
6025 tree addr = get_initialized_tmp_var (build_fold_addr_expr (*to_p),
6026 pre_p, post_p);
6027 *to_p = build_simple_mem_ref_loc (EXPR_LOCATION (*to_p), addr);
6029 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
6030 *expr_p = NULL;
6031 return GS_ALL_DONE;
6034 /* Convert initialization from an empty variable-size CONSTRUCTOR to
6035 memset. */
6036 if (TREE_TYPE (*from_p) != error_mark_node
6037 && TYPE_SIZE_UNIT (TREE_TYPE (*from_p))
6038 && !poly_int_tree_p (TYPE_SIZE_UNIT (TREE_TYPE (*from_p)))
6039 && TREE_CODE (*from_p) == CONSTRUCTOR
6040 && CONSTRUCTOR_NELTS (*from_p) == 0)
6042 maybe_with_size_expr (from_p);
6043 gcc_assert (TREE_CODE (*from_p) == WITH_SIZE_EXPR);
6044 return gimplify_modify_expr_to_memset (expr_p,
6045 TREE_OPERAND (*from_p, 1),
6046 want_value, pre_p);
6049 /* Insert pointer conversions required by the middle-end that are not
6050 required by the frontend. This fixes middle-end type checking for
6051 for example gcc.dg/redecl-6.c. */
6052 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
6054 STRIP_USELESS_TYPE_CONVERSION (*from_p);
6055 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
6056 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
6059 /* See if any simplifications can be done based on what the RHS is. */
6060 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
6061 want_value);
6062 if (ret != GS_UNHANDLED)
6063 return ret;
6065 /* For empty types only gimplify the left hand side and right hand
6066 side as statements and throw away the assignment. Do this after
6067 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
6068 types properly. */
6069 if (is_empty_type (TREE_TYPE (*from_p))
6070 && !want_value
6071 /* Don't do this for calls that return addressable types, expand_call
6072 relies on those having a lhs. */
6073 && !(TREE_ADDRESSABLE (TREE_TYPE (*from_p))
6074 && TREE_CODE (*from_p) == CALL_EXPR))
6076 gimplify_stmt (from_p, pre_p);
6077 gimplify_stmt (to_p, pre_p);
6078 *expr_p = NULL_TREE;
6079 return GS_ALL_DONE;
6082 /* If the value being copied is of variable width, compute the length
6083 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
6084 before gimplifying any of the operands so that we can resolve any
6085 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
6086 the size of the expression to be copied, not of the destination, so
6087 that is what we must do here. */
6088 maybe_with_size_expr (from_p);
6090 /* As a special case, we have to temporarily allow for assignments
6091 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
6092 a toplevel statement, when gimplifying the GENERIC expression
6093 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
6094 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
6096 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
6097 prevent gimplify_expr from trying to create a new temporary for
6098 foo's LHS, we tell it that it should only gimplify until it
6099 reaches the CALL_EXPR. On return from gimplify_expr, the newly
6100 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
6101 and all we need to do here is set 'a' to be its LHS. */
6103 /* Gimplify the RHS first for C++17 and bug 71104. */
6104 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
6105 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
6106 if (ret == GS_ERROR)
6107 return ret;
6109 /* Then gimplify the LHS. */
6110 /* If we gimplified the RHS to a CALL_EXPR and that call may return
6111 twice we have to make sure to gimplify into non-SSA as otherwise
6112 the abnormal edge added later will make those defs not dominate
6113 their uses.
6114 ??? Technically this applies only to the registers used in the
6115 resulting non-register *TO_P. */
6116 bool saved_into_ssa = gimplify_ctxp->into_ssa;
6117 if (saved_into_ssa
6118 && TREE_CODE (*from_p) == CALL_EXPR
6119 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
6120 gimplify_ctxp->into_ssa = false;
6121 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
6122 gimplify_ctxp->into_ssa = saved_into_ssa;
6123 if (ret == GS_ERROR)
6124 return ret;
6126 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
6127 guess for the predicate was wrong. */
6128 gimple_predicate final_pred = rhs_predicate_for (*to_p);
6129 if (final_pred != initial_pred)
6131 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
6132 if (ret == GS_ERROR)
6133 return ret;
6136 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
6137 size as argument to the call. */
6138 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
6140 tree call = TREE_OPERAND (*from_p, 0);
6141 tree vlasize = TREE_OPERAND (*from_p, 1);
6143 if (TREE_CODE (call) == CALL_EXPR
6144 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
6146 int nargs = call_expr_nargs (call);
6147 tree type = TREE_TYPE (call);
6148 tree ap = CALL_EXPR_ARG (call, 0);
6149 tree tag = CALL_EXPR_ARG (call, 1);
6150 tree aptag = CALL_EXPR_ARG (call, 2);
6151 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
6152 IFN_VA_ARG, type,
6153 nargs + 1, ap, tag,
6154 aptag, vlasize);
6155 TREE_OPERAND (*from_p, 0) = newcall;
6159 /* Now see if the above changed *from_p to something we handle specially. */
6160 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
6161 want_value);
6162 if (ret != GS_UNHANDLED)
6163 return ret;
6165 /* If we've got a variable sized assignment between two lvalues (i.e. does
6166 not involve a call), then we can make things a bit more straightforward
6167 by converting the assignment to memcpy or memset. */
6168 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
6170 tree from = TREE_OPERAND (*from_p, 0);
6171 tree size = TREE_OPERAND (*from_p, 1);
6173 if (TREE_CODE (from) == CONSTRUCTOR)
6174 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
6176 if (is_gimple_addressable (from))
6178 *from_p = from;
6179 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
6180 pre_p);
6184 /* Transform partial stores to non-addressable complex variables into
6185 total stores. This allows us to use real instead of virtual operands
6186 for these variables, which improves optimization. */
6187 if ((TREE_CODE (*to_p) == REALPART_EXPR
6188 || TREE_CODE (*to_p) == IMAGPART_EXPR)
6189 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
6190 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
6192 /* Try to alleviate the effects of the gimplification creating artificial
6193 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
6194 make sure not to create DECL_DEBUG_EXPR links across functions. */
6195 if (!gimplify_ctxp->into_ssa
6196 && VAR_P (*from_p)
6197 && DECL_IGNORED_P (*from_p)
6198 && DECL_P (*to_p)
6199 && !DECL_IGNORED_P (*to_p)
6200 && decl_function_context (*to_p) == current_function_decl
6201 && decl_function_context (*from_p) == current_function_decl)
6203 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
6204 DECL_NAME (*from_p)
6205 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
6206 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
6207 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
6210 if (want_value && TREE_THIS_VOLATILE (*to_p))
6211 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
6213 if (TREE_CODE (*from_p) == CALL_EXPR)
6215 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
6216 instead of a GIMPLE_ASSIGN. */
6217 gcall *call_stmt;
6218 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
6220 /* Gimplify internal functions created in the FEs. */
6221 int nargs = call_expr_nargs (*from_p), i;
6222 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
6223 auto_vec<tree> vargs (nargs);
6225 for (i = 0; i < nargs; i++)
6227 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
6228 EXPR_LOCATION (*from_p));
6229 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
6231 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
6232 gimple_call_set_nothrow (call_stmt, TREE_NOTHROW (*from_p));
6233 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
6235 else
6237 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
6238 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
6239 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
6240 tree fndecl = get_callee_fndecl (*from_p);
6241 if (fndecl
6242 && fndecl_built_in_p (fndecl, BUILT_IN_EXPECT)
6243 && call_expr_nargs (*from_p) == 3)
6244 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
6245 CALL_EXPR_ARG (*from_p, 0),
6246 CALL_EXPR_ARG (*from_p, 1),
6247 CALL_EXPR_ARG (*from_p, 2));
6248 else
6250 call_stmt = gimple_build_call_from_tree (*from_p, fnptrtype);
6253 notice_special_calls (call_stmt);
6254 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
6255 gimple_call_set_lhs (call_stmt, *to_p);
6256 else if (TREE_CODE (*to_p) == SSA_NAME)
6257 /* The above is somewhat premature, avoid ICEing later for a
6258 SSA name w/o a definition. We may have uses in the GIMPLE IL.
6259 ??? This doesn't make it a default-def. */
6260 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
6262 assign = call_stmt;
6264 else
6266 assign = gimple_build_assign (*to_p, *from_p);
6267 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
6268 if (COMPARISON_CLASS_P (*from_p))
6269 copy_warning (assign, *from_p);
6272 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
6274 /* We should have got an SSA name from the start. */
6275 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
6276 || ! gimple_in_ssa_p (cfun));
6279 gimplify_seq_add_stmt (pre_p, assign);
6280 gsi = gsi_last (*pre_p);
6281 maybe_fold_stmt (&gsi);
6283 if (want_value)
6285 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
6286 return GS_OK;
6288 else
6289 *expr_p = NULL;
6291 return GS_ALL_DONE;
6294 /* Gimplify a comparison between two variable-sized objects. Do this
6295 with a call to BUILT_IN_MEMCMP. */
6297 static enum gimplify_status
6298 gimplify_variable_sized_compare (tree *expr_p)
6300 location_t loc = EXPR_LOCATION (*expr_p);
6301 tree op0 = TREE_OPERAND (*expr_p, 0);
6302 tree op1 = TREE_OPERAND (*expr_p, 1);
6303 tree t, arg, dest, src, expr;
6305 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
6306 arg = unshare_expr (arg);
6307 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
6308 src = build_fold_addr_expr_loc (loc, op1);
6309 dest = build_fold_addr_expr_loc (loc, op0);
6310 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
6311 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
6313 expr
6314 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
6315 SET_EXPR_LOCATION (expr, loc);
6316 *expr_p = expr;
6318 return GS_OK;
6321 /* Gimplify a comparison between two aggregate objects of integral scalar
6322 mode as a comparison between the bitwise equivalent scalar values. */
6324 static enum gimplify_status
6325 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
6327 location_t loc = EXPR_LOCATION (*expr_p);
6328 tree op0 = TREE_OPERAND (*expr_p, 0);
6329 tree op1 = TREE_OPERAND (*expr_p, 1);
6331 tree type = TREE_TYPE (op0);
6332 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
6334 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
6335 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
6337 *expr_p
6338 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
6340 return GS_OK;
6343 /* Gimplify an expression sequence. This function gimplifies each
6344 expression and rewrites the original expression with the last
6345 expression of the sequence in GIMPLE form.
6347 PRE_P points to the list where the side effects for all the
6348 expressions in the sequence will be emitted.
6350 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
6352 static enum gimplify_status
6353 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
6355 tree t = *expr_p;
6359 tree *sub_p = &TREE_OPERAND (t, 0);
6361 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
6362 gimplify_compound_expr (sub_p, pre_p, false);
6363 else
6364 gimplify_stmt (sub_p, pre_p);
6366 t = TREE_OPERAND (t, 1);
6368 while (TREE_CODE (t) == COMPOUND_EXPR);
6370 *expr_p = t;
6371 if (want_value)
6372 return GS_OK;
6373 else
6375 gimplify_stmt (expr_p, pre_p);
6376 return GS_ALL_DONE;
6380 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
6381 gimplify. After gimplification, EXPR_P will point to a new temporary
6382 that holds the original value of the SAVE_EXPR node.
6384 PRE_P points to the list where side effects that must happen before
6385 *EXPR_P should be stored. */
6387 static enum gimplify_status
6388 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6390 enum gimplify_status ret = GS_ALL_DONE;
6391 tree val;
6393 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
6394 val = TREE_OPERAND (*expr_p, 0);
6396 if (TREE_TYPE (val) == error_mark_node)
6397 return GS_ERROR;
6399 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
6400 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
6402 /* The operand may be a void-valued expression. It is
6403 being executed only for its side-effects. */
6404 if (TREE_TYPE (val) == void_type_node)
6406 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
6407 is_gimple_stmt, fb_none);
6408 val = NULL;
6410 else
6411 /* The temporary may not be an SSA name as later abnormal and EH
6412 control flow may invalidate use/def domination. When in SSA
6413 form then assume there are no such issues and SAVE_EXPRs only
6414 appear via GENERIC foldings. */
6415 val = get_initialized_tmp_var (val, pre_p, post_p,
6416 gimple_in_ssa_p (cfun));
6418 TREE_OPERAND (*expr_p, 0) = val;
6419 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
6422 *expr_p = val;
6424 return ret;
6427 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
6429 unary_expr
6430 : ...
6431 | '&' varname
6434 PRE_P points to the list where side effects that must happen before
6435 *EXPR_P should be stored.
6437 POST_P points to the list where side effects that must happen after
6438 *EXPR_P should be stored. */
6440 static enum gimplify_status
6441 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6443 tree expr = *expr_p;
6444 tree op0 = TREE_OPERAND (expr, 0);
6445 enum gimplify_status ret;
6446 location_t loc = EXPR_LOCATION (*expr_p);
6448 switch (TREE_CODE (op0))
6450 case INDIRECT_REF:
6451 do_indirect_ref:
6452 /* Check if we are dealing with an expression of the form '&*ptr'.
6453 While the front end folds away '&*ptr' into 'ptr', these
6454 expressions may be generated internally by the compiler (e.g.,
6455 builtins like __builtin_va_end). */
6456 /* Caution: the silent array decomposition semantics we allow for
6457 ADDR_EXPR means we can't always discard the pair. */
6458 /* Gimplification of the ADDR_EXPR operand may drop
6459 cv-qualification conversions, so make sure we add them if
6460 needed. */
6462 tree op00 = TREE_OPERAND (op0, 0);
6463 tree t_expr = TREE_TYPE (expr);
6464 tree t_op00 = TREE_TYPE (op00);
6466 if (!useless_type_conversion_p (t_expr, t_op00))
6467 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
6468 *expr_p = op00;
6469 ret = GS_OK;
6471 break;
6473 case VIEW_CONVERT_EXPR:
6474 /* Take the address of our operand and then convert it to the type of
6475 this ADDR_EXPR.
6477 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
6478 all clear. The impact of this transformation is even less clear. */
6480 /* If the operand is a useless conversion, look through it. Doing so
6481 guarantees that the ADDR_EXPR and its operand will remain of the
6482 same type. */
6483 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
6484 op0 = TREE_OPERAND (op0, 0);
6486 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
6487 build_fold_addr_expr_loc (loc,
6488 TREE_OPERAND (op0, 0)));
6489 ret = GS_OK;
6490 break;
6492 case MEM_REF:
6493 if (integer_zerop (TREE_OPERAND (op0, 1)))
6494 goto do_indirect_ref;
6496 /* fall through */
6498 default:
6499 /* If we see a call to a declared builtin or see its address
6500 being taken (we can unify those cases here) then we can mark
6501 the builtin for implicit generation by GCC. */
6502 if (TREE_CODE (op0) == FUNCTION_DECL
6503 && fndecl_built_in_p (op0, BUILT_IN_NORMAL)
6504 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
6505 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
6507 /* We use fb_either here because the C frontend sometimes takes
6508 the address of a call that returns a struct; see
6509 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
6510 the implied temporary explicit. */
6512 /* Make the operand addressable. */
6513 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
6514 is_gimple_addressable, fb_either);
6515 if (ret == GS_ERROR)
6516 break;
6518 /* Then mark it. Beware that it may not be possible to do so directly
6519 if a temporary has been created by the gimplification. */
6520 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
6522 op0 = TREE_OPERAND (expr, 0);
6524 /* For various reasons, the gimplification of the expression
6525 may have made a new INDIRECT_REF. */
6526 if (TREE_CODE (op0) == INDIRECT_REF
6527 || (TREE_CODE (op0) == MEM_REF
6528 && integer_zerop (TREE_OPERAND (op0, 1))))
6529 goto do_indirect_ref;
6531 mark_addressable (TREE_OPERAND (expr, 0));
6533 /* The FEs may end up building ADDR_EXPRs early on a decl with
6534 an incomplete type. Re-build ADDR_EXPRs in canonical form
6535 here. */
6536 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
6537 *expr_p = build_fold_addr_expr (op0);
6539 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
6540 recompute_tree_invariant_for_addr_expr (*expr_p);
6542 /* If we re-built the ADDR_EXPR add a conversion to the original type
6543 if required. */
6544 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
6545 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
6547 break;
6550 return ret;
6553 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
6554 value; output operands should be a gimple lvalue. */
6556 static enum gimplify_status
6557 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6559 tree expr;
6560 int noutputs;
6561 const char **oconstraints;
6562 int i;
6563 tree link;
6564 const char *constraint;
6565 bool allows_mem, allows_reg, is_inout;
6566 enum gimplify_status ret, tret;
6567 gasm *stmt;
6568 vec<tree, va_gc> *inputs;
6569 vec<tree, va_gc> *outputs;
6570 vec<tree, va_gc> *clobbers;
6571 vec<tree, va_gc> *labels;
6572 tree link_next;
6574 expr = *expr_p;
6575 noutputs = list_length (ASM_OUTPUTS (expr));
6576 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
6578 inputs = NULL;
6579 outputs = NULL;
6580 clobbers = NULL;
6581 labels = NULL;
6583 ret = GS_ALL_DONE;
6584 link_next = NULL_TREE;
6585 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
6587 bool ok;
6588 size_t constraint_len;
6590 link_next = TREE_CHAIN (link);
6592 oconstraints[i]
6593 = constraint
6594 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6595 constraint_len = strlen (constraint);
6596 if (constraint_len == 0)
6597 continue;
6599 ok = parse_output_constraint (&constraint, i, 0, 0,
6600 &allows_mem, &allows_reg, &is_inout);
6601 if (!ok)
6603 ret = GS_ERROR;
6604 is_inout = false;
6607 /* If we can't make copies, we can only accept memory.
6608 Similarly for VLAs. */
6609 tree outtype = TREE_TYPE (TREE_VALUE (link));
6610 if (outtype != error_mark_node
6611 && (TREE_ADDRESSABLE (outtype)
6612 || !COMPLETE_TYPE_P (outtype)
6613 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (outtype))))
6615 if (allows_mem)
6616 allows_reg = 0;
6617 else
6619 error ("impossible constraint in %<asm%>");
6620 error ("non-memory output %d must stay in memory", i);
6621 return GS_ERROR;
6625 if (!allows_reg && allows_mem)
6626 mark_addressable (TREE_VALUE (link));
6628 tree orig = TREE_VALUE (link);
6629 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6630 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
6631 fb_lvalue | fb_mayfail);
6632 if (tret == GS_ERROR)
6634 if (orig != error_mark_node)
6635 error ("invalid lvalue in %<asm%> output %d", i);
6636 ret = tret;
6639 /* If the constraint does not allow memory make sure we gimplify
6640 it to a register if it is not already but its base is. This
6641 happens for complex and vector components. */
6642 if (!allows_mem)
6644 tree op = TREE_VALUE (link);
6645 if (! is_gimple_val (op)
6646 && is_gimple_reg_type (TREE_TYPE (op))
6647 && is_gimple_reg (get_base_address (op)))
6649 tree tem = create_tmp_reg (TREE_TYPE (op));
6650 tree ass;
6651 if (is_inout)
6653 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
6654 tem, unshare_expr (op));
6655 gimplify_and_add (ass, pre_p);
6657 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
6658 gimplify_and_add (ass, post_p);
6660 TREE_VALUE (link) = tem;
6661 tret = GS_OK;
6665 vec_safe_push (outputs, link);
6666 TREE_CHAIN (link) = NULL_TREE;
6668 if (is_inout)
6670 /* An input/output operand. To give the optimizers more
6671 flexibility, split it into separate input and output
6672 operands. */
6673 tree input;
6674 /* Buffer big enough to format a 32-bit UINT_MAX into. */
6675 char buf[11];
6677 /* Turn the in/out constraint into an output constraint. */
6678 char *p = xstrdup (constraint);
6679 p[0] = '=';
6680 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
6682 /* And add a matching input constraint. */
6683 if (allows_reg)
6685 sprintf (buf, "%u", i);
6687 /* If there are multiple alternatives in the constraint,
6688 handle each of them individually. Those that allow register
6689 will be replaced with operand number, the others will stay
6690 unchanged. */
6691 if (strchr (p, ',') != NULL)
6693 size_t len = 0, buflen = strlen (buf);
6694 char *beg, *end, *str, *dst;
6696 for (beg = p + 1;;)
6698 end = strchr (beg, ',');
6699 if (end == NULL)
6700 end = strchr (beg, '\0');
6701 if ((size_t) (end - beg) < buflen)
6702 len += buflen + 1;
6703 else
6704 len += end - beg + 1;
6705 if (*end)
6706 beg = end + 1;
6707 else
6708 break;
6711 str = (char *) alloca (len);
6712 for (beg = p + 1, dst = str;;)
6714 const char *tem;
6715 bool mem_p, reg_p, inout_p;
6717 end = strchr (beg, ',');
6718 if (end)
6719 *end = '\0';
6720 beg[-1] = '=';
6721 tem = beg - 1;
6722 parse_output_constraint (&tem, i, 0, 0,
6723 &mem_p, &reg_p, &inout_p);
6724 if (dst != str)
6725 *dst++ = ',';
6726 if (reg_p)
6728 memcpy (dst, buf, buflen);
6729 dst += buflen;
6731 else
6733 if (end)
6734 len = end - beg;
6735 else
6736 len = strlen (beg);
6737 memcpy (dst, beg, len);
6738 dst += len;
6740 if (end)
6741 beg = end + 1;
6742 else
6743 break;
6745 *dst = '\0';
6746 input = build_string (dst - str, str);
6748 else
6749 input = build_string (strlen (buf), buf);
6751 else
6752 input = build_string (constraint_len - 1, constraint + 1);
6754 free (p);
6756 input = build_tree_list (build_tree_list (NULL_TREE, input),
6757 unshare_expr (TREE_VALUE (link)));
6758 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
6762 link_next = NULL_TREE;
6763 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
6765 link_next = TREE_CHAIN (link);
6766 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6767 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
6768 oconstraints, &allows_mem, &allows_reg);
6770 /* If we can't make copies, we can only accept memory. */
6771 tree intype = TREE_TYPE (TREE_VALUE (link));
6772 if (intype != error_mark_node
6773 && (TREE_ADDRESSABLE (intype)
6774 || !COMPLETE_TYPE_P (intype)
6775 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (intype))))
6777 if (allows_mem)
6778 allows_reg = 0;
6779 else
6781 error ("impossible constraint in %<asm%>");
6782 error ("non-memory input %d must stay in memory", i);
6783 return GS_ERROR;
6787 /* If the operand is a memory input, it should be an lvalue. */
6788 if (!allows_reg && allows_mem)
6790 tree inputv = TREE_VALUE (link);
6791 STRIP_NOPS (inputv);
6792 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
6793 || TREE_CODE (inputv) == PREINCREMENT_EXPR
6794 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
6795 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
6796 || TREE_CODE (inputv) == MODIFY_EXPR)
6797 TREE_VALUE (link) = error_mark_node;
6798 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6799 is_gimple_lvalue, fb_lvalue | fb_mayfail);
6800 if (tret != GS_ERROR)
6802 /* Unlike output operands, memory inputs are not guaranteed
6803 to be lvalues by the FE, and while the expressions are
6804 marked addressable there, if it is e.g. a statement
6805 expression, temporaries in it might not end up being
6806 addressable. They might be already used in the IL and thus
6807 it is too late to make them addressable now though. */
6808 tree x = TREE_VALUE (link);
6809 while (handled_component_p (x))
6810 x = TREE_OPERAND (x, 0);
6811 if (TREE_CODE (x) == MEM_REF
6812 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
6813 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
6814 if ((VAR_P (x)
6815 || TREE_CODE (x) == PARM_DECL
6816 || TREE_CODE (x) == RESULT_DECL)
6817 && !TREE_ADDRESSABLE (x)
6818 && is_gimple_reg (x))
6820 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
6821 input_location), 0,
6822 "memory input %d is not directly addressable",
6824 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
6827 mark_addressable (TREE_VALUE (link));
6828 if (tret == GS_ERROR)
6830 if (inputv != error_mark_node)
6831 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
6832 "memory input %d is not directly addressable", i);
6833 ret = tret;
6836 else
6838 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6839 is_gimple_asm_val, fb_rvalue);
6840 if (tret == GS_ERROR)
6841 ret = tret;
6844 TREE_CHAIN (link) = NULL_TREE;
6845 vec_safe_push (inputs, link);
6848 link_next = NULL_TREE;
6849 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
6851 link_next = TREE_CHAIN (link);
6852 TREE_CHAIN (link) = NULL_TREE;
6853 vec_safe_push (clobbers, link);
6856 link_next = NULL_TREE;
6857 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
6859 link_next = TREE_CHAIN (link);
6860 TREE_CHAIN (link) = NULL_TREE;
6861 vec_safe_push (labels, link);
6864 /* Do not add ASMs with errors to the gimple IL stream. */
6865 if (ret != GS_ERROR)
6867 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
6868 inputs, outputs, clobbers, labels);
6870 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
6871 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
6872 gimple_asm_set_inline (stmt, ASM_INLINE_P (expr));
6874 gimplify_seq_add_stmt (pre_p, stmt);
6877 return ret;
6880 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
6881 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
6882 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
6883 return to this function.
6885 FIXME should we complexify the prequeue handling instead? Or use flags
6886 for all the cleanups and let the optimizer tighten them up? The current
6887 code seems pretty fragile; it will break on a cleanup within any
6888 non-conditional nesting. But any such nesting would be broken, anyway;
6889 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
6890 and continues out of it. We can do that at the RTL level, though, so
6891 having an optimizer to tighten up try/finally regions would be a Good
6892 Thing. */
6894 static enum gimplify_status
6895 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
6897 gimple_stmt_iterator iter;
6898 gimple_seq body_sequence = NULL;
6900 tree temp = voidify_wrapper_expr (*expr_p, NULL);
6902 /* We only care about the number of conditions between the innermost
6903 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
6904 any cleanups collected outside the CLEANUP_POINT_EXPR. */
6905 int old_conds = gimplify_ctxp->conditions;
6906 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
6907 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
6908 gimplify_ctxp->conditions = 0;
6909 gimplify_ctxp->conditional_cleanups = NULL;
6910 gimplify_ctxp->in_cleanup_point_expr = true;
6912 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
6914 gimplify_ctxp->conditions = old_conds;
6915 gimplify_ctxp->conditional_cleanups = old_cleanups;
6916 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
6918 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
6920 gimple *wce = gsi_stmt (iter);
6922 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
6924 if (gsi_one_before_end_p (iter))
6926 /* Note that gsi_insert_seq_before and gsi_remove do not
6927 scan operands, unlike some other sequence mutators. */
6928 if (!gimple_wce_cleanup_eh_only (wce))
6929 gsi_insert_seq_before_without_update (&iter,
6930 gimple_wce_cleanup (wce),
6931 GSI_SAME_STMT);
6932 gsi_remove (&iter, true);
6933 break;
6935 else
6937 gtry *gtry;
6938 gimple_seq seq;
6939 enum gimple_try_flags kind;
6941 if (gimple_wce_cleanup_eh_only (wce))
6942 kind = GIMPLE_TRY_CATCH;
6943 else
6944 kind = GIMPLE_TRY_FINALLY;
6945 seq = gsi_split_seq_after (iter);
6947 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
6948 /* Do not use gsi_replace here, as it may scan operands.
6949 We want to do a simple structural modification only. */
6950 gsi_set_stmt (&iter, gtry);
6951 iter = gsi_start (gtry->eval);
6954 else
6955 gsi_next (&iter);
6958 gimplify_seq_add_seq (pre_p, body_sequence);
6959 if (temp)
6961 *expr_p = temp;
6962 return GS_OK;
6964 else
6966 *expr_p = NULL;
6967 return GS_ALL_DONE;
6971 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
6972 is the cleanup action required. EH_ONLY is true if the cleanup should
6973 only be executed if an exception is thrown, not on normal exit.
6974 If FORCE_UNCOND is true perform the cleanup unconditionally; this is
6975 only valid for clobbers. */
6977 static void
6978 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p,
6979 bool force_uncond = false)
6981 gimple *wce;
6982 gimple_seq cleanup_stmts = NULL;
6984 /* Errors can result in improperly nested cleanups. Which results in
6985 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
6986 if (seen_error ())
6987 return;
6989 if (gimple_conditional_context ())
6991 /* If we're in a conditional context, this is more complex. We only
6992 want to run the cleanup if we actually ran the initialization that
6993 necessitates it, but we want to run it after the end of the
6994 conditional context. So we wrap the try/finally around the
6995 condition and use a flag to determine whether or not to actually
6996 run the destructor. Thus
6998 test ? f(A()) : 0
7000 becomes (approximately)
7002 flag = 0;
7003 try {
7004 if (test) { A::A(temp); flag = 1; val = f(temp); }
7005 else { val = 0; }
7006 } finally {
7007 if (flag) A::~A(temp);
7011 if (force_uncond)
7013 gimplify_stmt (&cleanup, &cleanup_stmts);
7014 wce = gimple_build_wce (cleanup_stmts);
7015 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
7017 else
7019 tree flag = create_tmp_var (boolean_type_node, "cleanup");
7020 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
7021 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
7023 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
7024 gimplify_stmt (&cleanup, &cleanup_stmts);
7025 wce = gimple_build_wce (cleanup_stmts);
7026 gimple_wce_set_cleanup_eh_only (wce, eh_only);
7028 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
7029 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
7030 gimplify_seq_add_stmt (pre_p, ftrue);
7032 /* Because of this manipulation, and the EH edges that jump
7033 threading cannot redirect, the temporary (VAR) will appear
7034 to be used uninitialized. Don't warn. */
7035 suppress_warning (var, OPT_Wuninitialized);
7038 else
7040 gimplify_stmt (&cleanup, &cleanup_stmts);
7041 wce = gimple_build_wce (cleanup_stmts);
7042 gimple_wce_set_cleanup_eh_only (wce, eh_only);
7043 gimplify_seq_add_stmt (pre_p, wce);
7047 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
7049 static enum gimplify_status
7050 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
7052 tree targ = *expr_p;
7053 tree temp = TARGET_EXPR_SLOT (targ);
7054 tree init = TARGET_EXPR_INITIAL (targ);
7055 enum gimplify_status ret;
7057 bool unpoison_empty_seq = false;
7058 gimple_stmt_iterator unpoison_it;
7060 if (init)
7062 gimple_seq init_pre_p = NULL;
7064 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
7065 to the temps list. Handle also variable length TARGET_EXPRs. */
7066 if (!poly_int_tree_p (DECL_SIZE (temp)))
7068 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
7069 gimplify_type_sizes (TREE_TYPE (temp), &init_pre_p);
7070 /* FIXME: this is correct only when the size of the type does
7071 not depend on expressions evaluated in init. */
7072 gimplify_vla_decl (temp, &init_pre_p);
7074 else
7076 /* Save location where we need to place unpoisoning. It's possible
7077 that a variable will be converted to needs_to_live_in_memory. */
7078 unpoison_it = gsi_last (*pre_p);
7079 unpoison_empty_seq = gsi_end_p (unpoison_it);
7081 gimple_add_tmp_var (temp);
7084 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
7085 expression is supposed to initialize the slot. */
7086 if (VOID_TYPE_P (TREE_TYPE (init)))
7087 ret = gimplify_expr (&init, &init_pre_p, post_p, is_gimple_stmt,
7088 fb_none);
7089 else
7091 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
7092 init = init_expr;
7093 ret = gimplify_expr (&init, &init_pre_p, post_p, is_gimple_stmt,
7094 fb_none);
7095 init = NULL;
7096 ggc_free (init_expr);
7098 if (ret == GS_ERROR)
7100 /* PR c++/28266 Make sure this is expanded only once. */
7101 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
7102 return GS_ERROR;
7105 if (init)
7106 gimplify_and_add (init, &init_pre_p);
7108 /* Add a clobber for the temporary going out of scope, like
7109 gimplify_bind_expr. */
7110 if (gimplify_ctxp->in_cleanup_point_expr
7111 && needs_to_live_in_memory (temp))
7113 if (flag_stack_reuse == SR_ALL)
7115 tree clobber = build_clobber (TREE_TYPE (temp), CLOBBER_EOL);
7116 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
7117 gimple_push_cleanup (temp, clobber, false, pre_p, true);
7119 if (asan_poisoned_variables
7120 && DECL_ALIGN (temp) <= MAX_SUPPORTED_STACK_ALIGNMENT
7121 && !TREE_STATIC (temp)
7122 && dbg_cnt (asan_use_after_scope)
7123 && !gimplify_omp_ctxp)
7125 tree asan_cleanup = build_asan_poison_call_expr (temp);
7126 if (asan_cleanup)
7128 if (unpoison_empty_seq)
7129 unpoison_it = gsi_start (*pre_p);
7131 asan_poison_variable (temp, false, &unpoison_it,
7132 unpoison_empty_seq);
7133 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
7138 gimple_seq_add_seq (pre_p, init_pre_p);
7140 /* If needed, push the cleanup for the temp. */
7141 if (TARGET_EXPR_CLEANUP (targ))
7142 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
7143 CLEANUP_EH_ONLY (targ), pre_p);
7145 /* Only expand this once. */
7146 TREE_OPERAND (targ, 3) = init;
7147 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
7149 else
7150 /* We should have expanded this before. */
7151 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
7153 *expr_p = temp;
7154 return GS_OK;
7157 /* Gimplification of expression trees. */
7159 /* Gimplify an expression which appears at statement context. The
7160 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
7161 NULL, a new sequence is allocated.
7163 Return true if we actually added a statement to the queue. */
7165 bool
7166 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
7168 gimple_seq_node last;
7170 last = gimple_seq_last (*seq_p);
7171 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
7172 return last != gimple_seq_last (*seq_p);
7175 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
7176 to CTX. If entries already exist, force them to be some flavor of private.
7177 If there is no enclosing parallel, do nothing. */
7179 void
7180 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
7182 splay_tree_node n;
7184 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
7185 return;
7189 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7190 if (n != NULL)
7192 if (n->value & GOVD_SHARED)
7193 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
7194 else if (n->value & GOVD_MAP)
7195 n->value |= GOVD_MAP_TO_ONLY;
7196 else
7197 return;
7199 else if ((ctx->region_type & ORT_TARGET) != 0)
7201 if (ctx->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
7202 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7203 else
7204 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
7206 else if (ctx->region_type != ORT_WORKSHARE
7207 && ctx->region_type != ORT_TASKGROUP
7208 && ctx->region_type != ORT_SIMD
7209 && ctx->region_type != ORT_ACC
7210 && !(ctx->region_type & ORT_TARGET_DATA))
7211 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7213 ctx = ctx->outer_context;
7215 while (ctx);
7218 /* Similarly for each of the type sizes of TYPE. */
7220 static void
7221 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
7223 if (type == NULL || type == error_mark_node)
7224 return;
7225 type = TYPE_MAIN_VARIANT (type);
7227 if (ctx->privatized_types->add (type))
7228 return;
7230 switch (TREE_CODE (type))
7232 case INTEGER_TYPE:
7233 case ENUMERAL_TYPE:
7234 case BOOLEAN_TYPE:
7235 case REAL_TYPE:
7236 case FIXED_POINT_TYPE:
7237 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
7238 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
7239 break;
7241 case ARRAY_TYPE:
7242 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7243 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
7244 break;
7246 case RECORD_TYPE:
7247 case UNION_TYPE:
7248 case QUAL_UNION_TYPE:
7250 tree field;
7251 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
7252 if (TREE_CODE (field) == FIELD_DECL)
7254 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
7255 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
7258 break;
7260 case POINTER_TYPE:
7261 case REFERENCE_TYPE:
7262 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7263 break;
7265 default:
7266 break;
7269 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
7270 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
7271 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
7274 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
7276 static void
7277 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
7279 splay_tree_node n;
7280 unsigned int nflags;
7281 tree t;
7283 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
7284 return;
7286 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
7287 there are constructors involved somewhere. Exception is a shared clause,
7288 there is nothing privatized in that case. */
7289 if ((flags & GOVD_SHARED) == 0
7290 && (TREE_ADDRESSABLE (TREE_TYPE (decl))
7291 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl))))
7292 flags |= GOVD_SEEN;
7294 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7295 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7297 /* We shouldn't be re-adding the decl with the same data
7298 sharing class. */
7299 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
7300 nflags = n->value | flags;
7301 /* The only combination of data sharing classes we should see is
7302 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
7303 reduction variables to be used in data sharing clauses. */
7304 gcc_assert ((ctx->region_type & ORT_ACC) != 0
7305 || ((nflags & GOVD_DATA_SHARE_CLASS)
7306 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
7307 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
7308 n->value = nflags;
7309 return;
7312 /* When adding a variable-sized variable, we have to handle all sorts
7313 of additional bits of data: the pointer replacement variable, and
7314 the parameters of the type. */
7315 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7317 /* Add the pointer replacement variable as PRIVATE if the variable
7318 replacement is private, else FIRSTPRIVATE since we'll need the
7319 address of the original variable either for SHARED, or for the
7320 copy into or out of the context. */
7321 if (!(flags & GOVD_LOCAL) && ctx->region_type != ORT_TASKGROUP)
7323 if (flags & GOVD_MAP)
7324 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
7325 else if (flags & GOVD_PRIVATE)
7326 nflags = GOVD_PRIVATE;
7327 else if (((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7328 && (flags & GOVD_FIRSTPRIVATE))
7329 || (ctx->region_type == ORT_TARGET_DATA
7330 && (flags & GOVD_DATA_SHARE_CLASS) == 0))
7331 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
7332 else
7333 nflags = GOVD_FIRSTPRIVATE;
7334 nflags |= flags & GOVD_SEEN;
7335 t = DECL_VALUE_EXPR (decl);
7336 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7337 t = TREE_OPERAND (t, 0);
7338 gcc_assert (DECL_P (t));
7339 omp_add_variable (ctx, t, nflags);
7342 /* Add all of the variable and type parameters (which should have
7343 been gimplified to a formal temporary) as FIRSTPRIVATE. */
7344 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
7345 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
7346 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7348 /* The variable-sized variable itself is never SHARED, only some form
7349 of PRIVATE. The sharing would take place via the pointer variable
7350 which we remapped above. */
7351 if (flags & GOVD_SHARED)
7352 flags = GOVD_SHARED | GOVD_DEBUG_PRIVATE
7353 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
7355 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
7356 alloca statement we generate for the variable, so make sure it
7357 is available. This isn't automatically needed for the SHARED
7358 case, since we won't be allocating local storage then.
7359 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
7360 in this case omp_notice_variable will be called later
7361 on when it is gimplified. */
7362 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
7363 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
7364 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
7366 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
7367 && omp_privatize_by_reference (decl))
7369 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7371 /* Similar to the direct variable sized case above, we'll need the
7372 size of references being privatized. */
7373 if ((flags & GOVD_SHARED) == 0)
7375 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7376 if (t && DECL_P (t))
7377 omp_notice_variable (ctx, t, true);
7381 if (n != NULL)
7382 n->value |= flags;
7383 else
7384 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
7386 /* For reductions clauses in OpenACC loop directives, by default create a
7387 copy clause on the enclosing parallel construct for carrying back the
7388 results. */
7389 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
7391 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
7392 while (outer_ctx)
7394 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
7395 if (n != NULL)
7397 /* Ignore local variables and explicitly declared clauses. */
7398 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
7399 break;
7400 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
7402 /* According to the OpenACC spec, such a reduction variable
7403 should already have a copy map on a kernels construct,
7404 verify that here. */
7405 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
7406 && (n->value & GOVD_MAP));
7408 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7410 /* Remove firstprivate and make it a copy map. */
7411 n->value &= ~GOVD_FIRSTPRIVATE;
7412 n->value |= GOVD_MAP;
7415 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7417 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
7418 GOVD_MAP | GOVD_SEEN);
7419 break;
7421 outer_ctx = outer_ctx->outer_context;
7426 /* Notice a threadprivate variable DECL used in OMP context CTX.
7427 This just prints out diagnostics about threadprivate variable uses
7428 in untied tasks. If DECL2 is non-NULL, prevent this warning
7429 on that variable. */
7431 static bool
7432 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
7433 tree decl2)
7435 splay_tree_node n;
7436 struct gimplify_omp_ctx *octx;
7438 for (octx = ctx; octx; octx = octx->outer_context)
7439 if ((octx->region_type & ORT_TARGET) != 0
7440 || octx->order_concurrent)
7442 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
7443 if (n == NULL)
7445 if (octx->order_concurrent)
7447 error ("threadprivate variable %qE used in a region with"
7448 " %<order(concurrent)%> clause", DECL_NAME (decl));
7449 inform (octx->location, "enclosing region");
7451 else
7453 error ("threadprivate variable %qE used in target region",
7454 DECL_NAME (decl));
7455 inform (octx->location, "enclosing target region");
7457 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
7459 if (decl2)
7460 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
7463 if (ctx->region_type != ORT_UNTIED_TASK)
7464 return false;
7465 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7466 if (n == NULL)
7468 error ("threadprivate variable %qE used in untied task",
7469 DECL_NAME (decl));
7470 inform (ctx->location, "enclosing task");
7471 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
7473 if (decl2)
7474 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
7475 return false;
7478 /* Return true if global var DECL is device resident. */
7480 static bool
7481 device_resident_p (tree decl)
7483 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
7485 if (!attr)
7486 return false;
7488 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
7490 tree c = TREE_VALUE (t);
7491 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
7492 return true;
7495 return false;
7498 /* Return true if DECL has an ACC DECLARE attribute. */
7500 static bool
7501 is_oacc_declared (tree decl)
7503 tree t = TREE_CODE (decl) == MEM_REF ? TREE_OPERAND (decl, 0) : decl;
7504 tree declared = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (t));
7505 return declared != NULL_TREE;
7508 /* Determine outer default flags for DECL mentioned in an OMP region
7509 but not declared in an enclosing clause.
7511 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
7512 remapped firstprivate instead of shared. To some extent this is
7513 addressed in omp_firstprivatize_type_sizes, but not
7514 effectively. */
7516 static unsigned
7517 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
7518 bool in_code, unsigned flags)
7520 enum omp_clause_default_kind default_kind = ctx->default_kind;
7521 enum omp_clause_default_kind kind;
7523 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
7524 if (ctx->region_type & ORT_TASK)
7526 tree detach_clause = omp_find_clause (ctx->clauses, OMP_CLAUSE_DETACH);
7528 /* The event-handle specified by a detach clause should always be firstprivate,
7529 regardless of the current default. */
7530 if (detach_clause && OMP_CLAUSE_DECL (detach_clause) == decl)
7531 kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
7533 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
7534 default_kind = kind;
7535 else if (VAR_P (decl) && TREE_STATIC (decl) && DECL_IN_CONSTANT_POOL (decl))
7536 default_kind = OMP_CLAUSE_DEFAULT_SHARED;
7537 /* For C/C++ default({,first}private), variables with static storage duration
7538 declared in a namespace or global scope and referenced in construct
7539 must be explicitly specified, i.e. acts as default(none). */
7540 else if ((default_kind == OMP_CLAUSE_DEFAULT_PRIVATE
7541 || default_kind == OMP_CLAUSE_DEFAULT_FIRSTPRIVATE)
7542 && VAR_P (decl)
7543 && is_global_var (decl)
7544 && (DECL_FILE_SCOPE_P (decl)
7545 || (DECL_CONTEXT (decl)
7546 && TREE_CODE (DECL_CONTEXT (decl)) == NAMESPACE_DECL))
7547 && !lang_GNU_Fortran ())
7548 default_kind = OMP_CLAUSE_DEFAULT_NONE;
7550 switch (default_kind)
7552 case OMP_CLAUSE_DEFAULT_NONE:
7554 const char *rtype;
7556 if (ctx->region_type & ORT_PARALLEL)
7557 rtype = "parallel";
7558 else if ((ctx->region_type & ORT_TASKLOOP) == ORT_TASKLOOP)
7559 rtype = "taskloop";
7560 else if (ctx->region_type & ORT_TASK)
7561 rtype = "task";
7562 else if (ctx->region_type & ORT_TEAMS)
7563 rtype = "teams";
7564 else
7565 gcc_unreachable ();
7567 error ("%qE not specified in enclosing %qs",
7568 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
7569 inform (ctx->location, "enclosing %qs", rtype);
7571 /* FALLTHRU */
7572 case OMP_CLAUSE_DEFAULT_SHARED:
7573 flags |= GOVD_SHARED;
7574 break;
7575 case OMP_CLAUSE_DEFAULT_PRIVATE:
7576 flags |= GOVD_PRIVATE;
7577 break;
7578 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
7579 flags |= GOVD_FIRSTPRIVATE;
7580 break;
7581 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
7582 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
7583 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
7584 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
7586 omp_notice_variable (octx, decl, in_code);
7587 for (; octx; octx = octx->outer_context)
7589 splay_tree_node n2;
7591 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
7592 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
7593 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
7594 continue;
7595 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
7597 flags |= GOVD_FIRSTPRIVATE;
7598 goto found_outer;
7600 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
7602 flags |= GOVD_SHARED;
7603 goto found_outer;
7608 if (TREE_CODE (decl) == PARM_DECL
7609 || (!is_global_var (decl)
7610 && DECL_CONTEXT (decl) == current_function_decl))
7611 flags |= GOVD_FIRSTPRIVATE;
7612 else
7613 flags |= GOVD_SHARED;
7614 found_outer:
7615 break;
7617 default:
7618 gcc_unreachable ();
7621 return flags;
7625 /* Determine outer default flags for DECL mentioned in an OACC region
7626 but not declared in an enclosing clause. */
7628 static unsigned
7629 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
7631 const char *rkind;
7632 bool on_device = false;
7633 bool is_private = false;
7634 bool declared = is_oacc_declared (decl);
7635 tree type = TREE_TYPE (decl);
7637 if (omp_privatize_by_reference (decl))
7638 type = TREE_TYPE (type);
7640 /* For Fortran COMMON blocks, only used variables in those blocks are
7641 transfered and remapped. The block itself will have a private clause to
7642 avoid transfering the data twice.
7643 The hook evaluates to false by default. For a variable in Fortran's COMMON
7644 or EQUIVALENCE block, returns 'true' (as we have shared=false) - as only
7645 the variables in such a COMMON/EQUIVALENCE block shall be privatized not
7646 the whole block. For C++ and Fortran, it can also be true under certain
7647 other conditions, if DECL_HAS_VALUE_EXPR. */
7648 if (RECORD_OR_UNION_TYPE_P (type))
7649 is_private = lang_hooks.decls.omp_disregard_value_expr (decl, false);
7651 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
7652 && is_global_var (decl)
7653 && device_resident_p (decl)
7654 && !is_private)
7656 on_device = true;
7657 flags |= GOVD_MAP_TO_ONLY;
7660 switch (ctx->region_type)
7662 case ORT_ACC_KERNELS:
7663 rkind = "kernels";
7665 if (is_private)
7666 flags |= GOVD_FIRSTPRIVATE;
7667 else if (AGGREGATE_TYPE_P (type))
7669 /* Aggregates default to 'present_or_copy', or 'present'. */
7670 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7671 flags |= GOVD_MAP;
7672 else
7673 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7675 else
7676 /* Scalars default to 'copy'. */
7677 flags |= GOVD_MAP | GOVD_MAP_FORCE;
7679 break;
7681 case ORT_ACC_PARALLEL:
7682 case ORT_ACC_SERIAL:
7683 rkind = ctx->region_type == ORT_ACC_PARALLEL ? "parallel" : "serial";
7685 if (is_private)
7686 flags |= GOVD_FIRSTPRIVATE;
7687 else if (on_device || declared)
7688 flags |= GOVD_MAP;
7689 else if (AGGREGATE_TYPE_P (type))
7691 /* Aggregates default to 'present_or_copy', or 'present'. */
7692 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7693 flags |= GOVD_MAP;
7694 else
7695 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7697 else
7698 /* Scalars default to 'firstprivate'. */
7699 flags |= GOVD_FIRSTPRIVATE;
7701 break;
7703 default:
7704 gcc_unreachable ();
7707 if (DECL_ARTIFICIAL (decl))
7708 ; /* We can get compiler-generated decls, and should not complain
7709 about them. */
7710 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_NONE)
7712 error ("%qE not specified in enclosing OpenACC %qs construct",
7713 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rkind);
7714 inform (ctx->location, "enclosing OpenACC %qs construct", rkind);
7716 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_PRESENT)
7717 ; /* Handled above. */
7718 else
7719 gcc_checking_assert (ctx->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
7721 return flags;
7724 /* Record the fact that DECL was used within the OMP context CTX.
7725 IN_CODE is true when real code uses DECL, and false when we should
7726 merely emit default(none) errors. Return true if DECL is going to
7727 be remapped and thus DECL shouldn't be gimplified into its
7728 DECL_VALUE_EXPR (if any). */
7730 static bool
7731 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
7733 splay_tree_node n;
7734 unsigned flags = in_code ? GOVD_SEEN : 0;
7735 bool ret = false, shared;
7737 if (error_operand_p (decl))
7738 return false;
7740 if (ctx->region_type == ORT_NONE)
7741 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
7743 if (is_global_var (decl))
7745 /* Threadprivate variables are predetermined. */
7746 if (DECL_THREAD_LOCAL_P (decl))
7747 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
7749 if (DECL_HAS_VALUE_EXPR_P (decl))
7751 if (ctx->region_type & ORT_ACC)
7752 /* For OpenACC, defer expansion of value to avoid transfering
7753 privatized common block data instead of im-/explicitly transfered
7754 variables which are in common blocks. */
7756 else
7758 tree value = get_base_address (DECL_VALUE_EXPR (decl));
7760 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
7761 return omp_notice_threadprivate_variable (ctx, decl, value);
7765 if (gimplify_omp_ctxp->outer_context == NULL
7766 && VAR_P (decl)
7767 && oacc_get_fn_attrib (current_function_decl))
7769 location_t loc = DECL_SOURCE_LOCATION (decl);
7771 if (lookup_attribute ("omp declare target link",
7772 DECL_ATTRIBUTES (decl)))
7774 error_at (loc,
7775 "%qE with %<link%> clause used in %<routine%> function",
7776 DECL_NAME (decl));
7777 return false;
7779 else if (!lookup_attribute ("omp declare target",
7780 DECL_ATTRIBUTES (decl)))
7782 error_at (loc,
7783 "%qE requires a %<declare%> directive for use "
7784 "in a %<routine%> function", DECL_NAME (decl));
7785 return false;
7790 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7791 if ((ctx->region_type & ORT_TARGET) != 0)
7793 if (ctx->region_type & ORT_ACC)
7794 /* For OpenACC, as remarked above, defer expansion. */
7795 shared = false;
7796 else
7797 shared = true;
7799 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7800 if (n == NULL)
7802 unsigned nflags = flags;
7803 if ((ctx->region_type & ORT_ACC) == 0)
7805 bool is_declare_target = false;
7806 if (is_global_var (decl)
7807 && varpool_node::get_create (decl)->offloadable)
7809 struct gimplify_omp_ctx *octx;
7810 for (octx = ctx->outer_context;
7811 octx; octx = octx->outer_context)
7813 n = splay_tree_lookup (octx->variables,
7814 (splay_tree_key)decl);
7815 if (n
7816 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
7817 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7818 break;
7820 is_declare_target = octx == NULL;
7822 if (!is_declare_target)
7824 int gdmk;
7825 enum omp_clause_defaultmap_kind kind;
7826 if (lang_hooks.decls.omp_allocatable_p (decl))
7827 gdmk = GDMK_ALLOCATABLE;
7828 else if (lang_hooks.decls.omp_scalar_target_p (decl))
7829 gdmk = GDMK_SCALAR_TARGET;
7830 else if (lang_hooks.decls.omp_scalar_p (decl, false))
7831 gdmk = GDMK_SCALAR;
7832 else if (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
7833 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
7834 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
7835 == POINTER_TYPE)))
7836 gdmk = GDMK_POINTER;
7837 else
7838 gdmk = GDMK_AGGREGATE;
7839 kind = lang_hooks.decls.omp_predetermined_mapping (decl);
7840 if (kind != OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED)
7842 if (kind == OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE)
7843 nflags |= GOVD_FIRSTPRIVATE;
7844 else if (kind == OMP_CLAUSE_DEFAULTMAP_TO)
7845 nflags |= GOVD_MAP | GOVD_MAP_TO_ONLY;
7846 else
7847 gcc_unreachable ();
7849 else if (ctx->defaultmap[gdmk] == 0)
7851 tree d = lang_hooks.decls.omp_report_decl (decl);
7852 error ("%qE not specified in enclosing %<target%>",
7853 DECL_NAME (d));
7854 inform (ctx->location, "enclosing %<target%>");
7856 else if (ctx->defaultmap[gdmk]
7857 & (GOVD_MAP_0LEN_ARRAY | GOVD_FIRSTPRIVATE))
7858 nflags |= ctx->defaultmap[gdmk];
7859 else
7861 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
7862 nflags |= ctx->defaultmap[gdmk] & ~GOVD_MAP;
7867 struct gimplify_omp_ctx *octx = ctx->outer_context;
7868 if ((ctx->region_type & ORT_ACC) && octx)
7870 /* Look in outer OpenACC contexts, to see if there's a
7871 data attribute for this variable. */
7872 omp_notice_variable (octx, decl, in_code);
7874 for (; octx; octx = octx->outer_context)
7876 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
7877 break;
7878 splay_tree_node n2
7879 = splay_tree_lookup (octx->variables,
7880 (splay_tree_key) decl);
7881 if (n2)
7883 if (octx->region_type == ORT_ACC_HOST_DATA)
7884 error ("variable %qE declared in enclosing "
7885 "%<host_data%> region", DECL_NAME (decl));
7886 nflags |= GOVD_MAP;
7887 if (octx->region_type == ORT_ACC_DATA
7888 && (n2->value & GOVD_MAP_0LEN_ARRAY))
7889 nflags |= GOVD_MAP_0LEN_ARRAY;
7890 goto found_outer;
7895 if ((nflags & ~(GOVD_MAP_TO_ONLY | GOVD_MAP_FROM_ONLY
7896 | GOVD_MAP_ALLOC_ONLY)) == flags)
7898 tree type = TREE_TYPE (decl);
7900 if (gimplify_omp_ctxp->target_firstprivatize_array_bases
7901 && omp_privatize_by_reference (decl))
7902 type = TREE_TYPE (type);
7903 if (!omp_mappable_type (type))
7905 error ("%qD referenced in target region does not have "
7906 "a mappable type", decl);
7907 nflags |= GOVD_MAP | GOVD_EXPLICIT;
7909 else
7911 if ((ctx->region_type & ORT_ACC) != 0)
7912 nflags = oacc_default_clause (ctx, decl, flags);
7913 else
7914 nflags |= GOVD_MAP;
7917 found_outer:
7918 omp_add_variable (ctx, decl, nflags);
7920 else
7922 /* If nothing changed, there's nothing left to do. */
7923 if ((n->value & flags) == flags)
7924 return ret;
7925 flags |= n->value;
7926 n->value = flags;
7928 goto do_outer;
7931 if (n == NULL)
7933 if (ctx->region_type == ORT_WORKSHARE
7934 || ctx->region_type == ORT_TASKGROUP
7935 || ctx->region_type == ORT_SIMD
7936 || ctx->region_type == ORT_ACC
7937 || (ctx->region_type & ORT_TARGET_DATA) != 0)
7938 goto do_outer;
7940 flags = omp_default_clause (ctx, decl, in_code, flags);
7942 if ((flags & GOVD_PRIVATE)
7943 && lang_hooks.decls.omp_private_outer_ref (decl))
7944 flags |= GOVD_PRIVATE_OUTER_REF;
7946 omp_add_variable (ctx, decl, flags);
7948 shared = (flags & GOVD_SHARED) != 0;
7949 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7950 goto do_outer;
7953 /* Don't mark as GOVD_SEEN addressable temporaries seen only in simd
7954 lb, b or incr expressions, those shouldn't be turned into simd arrays. */
7955 if (ctx->region_type == ORT_SIMD
7956 && ctx->in_for_exprs
7957 && ((n->value & (GOVD_PRIVATE | GOVD_SEEN | GOVD_EXPLICIT))
7958 == GOVD_PRIVATE))
7959 flags &= ~GOVD_SEEN;
7961 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
7962 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
7963 && DECL_SIZE (decl))
7965 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7967 splay_tree_node n2;
7968 tree t = DECL_VALUE_EXPR (decl);
7969 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7970 t = TREE_OPERAND (t, 0);
7971 gcc_assert (DECL_P (t));
7972 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7973 n2->value |= GOVD_SEEN;
7975 else if (omp_privatize_by_reference (decl)
7976 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
7977 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
7978 != INTEGER_CST))
7980 splay_tree_node n2;
7981 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7982 gcc_assert (DECL_P (t));
7983 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7984 if (n2)
7985 omp_notice_variable (ctx, t, true);
7989 if (ctx->region_type & ORT_ACC)
7990 /* For OpenACC, as remarked above, defer expansion. */
7991 shared = false;
7992 else
7993 shared = ((flags | n->value) & GOVD_SHARED) != 0;
7994 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7996 /* If nothing changed, there's nothing left to do. */
7997 if ((n->value & flags) == flags)
7998 return ret;
7999 flags |= n->value;
8000 n->value = flags;
8002 do_outer:
8003 /* If the variable is private in the current context, then we don't
8004 need to propagate anything to an outer context. */
8005 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
8006 return ret;
8007 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8008 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8009 return ret;
8010 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
8011 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8012 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8013 return ret;
8014 if (ctx->outer_context
8015 && omp_notice_variable (ctx->outer_context, decl, in_code))
8016 return true;
8017 return ret;
8020 /* Verify that DECL is private within CTX. If there's specific information
8021 to the contrary in the innermost scope, generate an error. */
8023 static bool
8024 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
8026 splay_tree_node n;
8028 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
8029 if (n != NULL)
8031 if (n->value & GOVD_SHARED)
8033 if (ctx == gimplify_omp_ctxp)
8035 if (simd)
8036 error ("iteration variable %qE is predetermined linear",
8037 DECL_NAME (decl));
8038 else
8039 error ("iteration variable %qE should be private",
8040 DECL_NAME (decl));
8041 n->value = GOVD_PRIVATE;
8042 return true;
8044 else
8045 return false;
8047 else if ((n->value & GOVD_EXPLICIT) != 0
8048 && (ctx == gimplify_omp_ctxp
8049 || (ctx->region_type == ORT_COMBINED_PARALLEL
8050 && gimplify_omp_ctxp->outer_context == ctx)))
8052 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
8053 error ("iteration variable %qE should not be firstprivate",
8054 DECL_NAME (decl));
8055 else if ((n->value & GOVD_REDUCTION) != 0)
8056 error ("iteration variable %qE should not be reduction",
8057 DECL_NAME (decl));
8058 else if (simd != 1 && (n->value & GOVD_LINEAR) != 0)
8059 error ("iteration variable %qE should not be linear",
8060 DECL_NAME (decl));
8062 return (ctx == gimplify_omp_ctxp
8063 || (ctx->region_type == ORT_COMBINED_PARALLEL
8064 && gimplify_omp_ctxp->outer_context == ctx));
8067 if (ctx->region_type != ORT_WORKSHARE
8068 && ctx->region_type != ORT_TASKGROUP
8069 && ctx->region_type != ORT_SIMD
8070 && ctx->region_type != ORT_ACC)
8071 return false;
8072 else if (ctx->outer_context)
8073 return omp_is_private (ctx->outer_context, decl, simd);
8074 return false;
8077 /* Return true if DECL is private within a parallel region
8078 that binds to the current construct's context or in parallel
8079 region's REDUCTION clause. */
8081 static bool
8082 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
8084 splay_tree_node n;
8088 ctx = ctx->outer_context;
8089 if (ctx == NULL)
8091 if (is_global_var (decl))
8092 return false;
8094 /* References might be private, but might be shared too,
8095 when checking for copyprivate, assume they might be
8096 private, otherwise assume they might be shared. */
8097 if (copyprivate)
8098 return true;
8100 if (omp_privatize_by_reference (decl))
8101 return false;
8103 /* Treat C++ privatized non-static data members outside
8104 of the privatization the same. */
8105 if (omp_member_access_dummy_var (decl))
8106 return false;
8108 return true;
8111 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8113 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
8114 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
8116 if ((ctx->region_type & ORT_TARGET_DATA) != 0
8117 || n == NULL
8118 || (n->value & GOVD_MAP) == 0)
8119 continue;
8120 return false;
8123 if (n != NULL)
8125 if ((n->value & GOVD_LOCAL) != 0
8126 && omp_member_access_dummy_var (decl))
8127 return false;
8128 return (n->value & GOVD_SHARED) == 0;
8131 if (ctx->region_type == ORT_WORKSHARE
8132 || ctx->region_type == ORT_TASKGROUP
8133 || ctx->region_type == ORT_SIMD
8134 || ctx->region_type == ORT_ACC)
8135 continue;
8137 break;
8139 while (1);
8140 return false;
8143 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
8145 static tree
8146 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
8148 tree t = *tp;
8150 /* If this node has been visited, unmark it and keep looking. */
8151 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
8152 return t;
8154 if (IS_TYPE_OR_DECL_P (t))
8155 *walk_subtrees = 0;
8156 return NULL_TREE;
8160 /* Gimplify the affinity clause but effectively ignore it.
8161 Generate:
8162 var = begin;
8163 if ((step > 1) ? var <= end : var > end)
8164 locatator_var_expr; */
8166 static void
8167 gimplify_omp_affinity (tree *list_p, gimple_seq *pre_p)
8169 tree last_iter = NULL_TREE;
8170 tree last_bind = NULL_TREE;
8171 tree label = NULL_TREE;
8172 tree *last_body = NULL;
8173 for (tree c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8174 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_AFFINITY)
8176 tree t = OMP_CLAUSE_DECL (c);
8177 if (TREE_CODE (t) == TREE_LIST
8178 && TREE_PURPOSE (t)
8179 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8181 if (TREE_VALUE (t) == null_pointer_node)
8182 continue;
8183 if (TREE_PURPOSE (t) != last_iter)
8185 if (last_bind)
8187 append_to_statement_list (label, last_body);
8188 gimplify_and_add (last_bind, pre_p);
8189 last_bind = NULL_TREE;
8191 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8193 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8194 is_gimple_val, fb_rvalue) == GS_ERROR
8195 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8196 is_gimple_val, fb_rvalue) == GS_ERROR
8197 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8198 is_gimple_val, fb_rvalue) == GS_ERROR
8199 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8200 is_gimple_val, fb_rvalue)
8201 == GS_ERROR))
8202 return;
8204 last_iter = TREE_PURPOSE (t);
8205 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8206 last_bind = build3 (BIND_EXPR, void_type_node, BLOCK_VARS (block),
8207 NULL, block);
8208 last_body = &BIND_EXPR_BODY (last_bind);
8209 tree cond = NULL_TREE;
8210 location_t loc = OMP_CLAUSE_LOCATION (c);
8211 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8213 tree var = TREE_VEC_ELT (it, 0);
8214 tree begin = TREE_VEC_ELT (it, 1);
8215 tree end = TREE_VEC_ELT (it, 2);
8216 tree step = TREE_VEC_ELT (it, 3);
8217 loc = DECL_SOURCE_LOCATION (var);
8218 tree tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8219 var, begin);
8220 append_to_statement_list_force (tem, last_body);
8222 tree cond1 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8223 step, build_zero_cst (TREE_TYPE (step)));
8224 tree cond2 = fold_build2_loc (loc, LE_EXPR, boolean_type_node,
8225 var, end);
8226 tree cond3 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8227 var, end);
8228 cond1 = fold_build3_loc (loc, COND_EXPR, boolean_type_node,
8229 cond1, cond2, cond3);
8230 if (cond)
8231 cond = fold_build2_loc (loc, TRUTH_AND_EXPR,
8232 boolean_type_node, cond, cond1);
8233 else
8234 cond = cond1;
8236 tree cont_label = create_artificial_label (loc);
8237 label = build1 (LABEL_EXPR, void_type_node, cont_label);
8238 tree tem = fold_build3_loc (loc, COND_EXPR, void_type_node, cond,
8239 void_node,
8240 build_and_jump (&cont_label));
8241 append_to_statement_list_force (tem, last_body);
8243 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8245 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t), 0),
8246 last_body);
8247 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8249 if (error_operand_p (TREE_VALUE (t)))
8250 return;
8251 append_to_statement_list_force (TREE_VALUE (t), last_body);
8252 TREE_VALUE (t) = null_pointer_node;
8254 else
8256 if (last_bind)
8258 append_to_statement_list (label, last_body);
8259 gimplify_and_add (last_bind, pre_p);
8260 last_bind = NULL_TREE;
8262 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8264 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8265 NULL, is_gimple_val, fb_rvalue);
8266 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8268 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8269 return;
8270 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8271 is_gimple_lvalue, fb_lvalue) == GS_ERROR)
8272 return;
8273 gimplify_and_add (OMP_CLAUSE_DECL (c), pre_p);
8276 if (last_bind)
8278 append_to_statement_list (label, last_body);
8279 gimplify_and_add (last_bind, pre_p);
8281 return;
8284 /* If *LIST_P contains any OpenMP depend clauses with iterators,
8285 lower all the depend clauses by populating corresponding depend
8286 array. Returns 0 if there are no such depend clauses, or
8287 2 if all depend clauses should be removed, 1 otherwise. */
8289 static int
8290 gimplify_omp_depend (tree *list_p, gimple_seq *pre_p)
8292 tree c;
8293 gimple *g;
8294 size_t n[5] = { 0, 0, 0, 0, 0 };
8295 bool unused[5];
8296 tree counts[5] = { NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE };
8297 tree last_iter = NULL_TREE, last_count = NULL_TREE;
8298 size_t i, j;
8299 location_t first_loc = UNKNOWN_LOCATION;
8301 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8302 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8304 switch (OMP_CLAUSE_DEPEND_KIND (c))
8306 case OMP_CLAUSE_DEPEND_IN:
8307 i = 2;
8308 break;
8309 case OMP_CLAUSE_DEPEND_OUT:
8310 case OMP_CLAUSE_DEPEND_INOUT:
8311 i = 0;
8312 break;
8313 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8314 i = 1;
8315 break;
8316 case OMP_CLAUSE_DEPEND_DEPOBJ:
8317 i = 3;
8318 break;
8319 case OMP_CLAUSE_DEPEND_INOUTSET:
8320 i = 4;
8321 break;
8322 default:
8323 gcc_unreachable ();
8325 tree t = OMP_CLAUSE_DECL (c);
8326 if (first_loc == UNKNOWN_LOCATION)
8327 first_loc = OMP_CLAUSE_LOCATION (c);
8328 if (TREE_CODE (t) == TREE_LIST
8329 && TREE_PURPOSE (t)
8330 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8332 if (TREE_PURPOSE (t) != last_iter)
8334 tree tcnt = size_one_node;
8335 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8337 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8338 is_gimple_val, fb_rvalue) == GS_ERROR
8339 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8340 is_gimple_val, fb_rvalue) == GS_ERROR
8341 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8342 is_gimple_val, fb_rvalue) == GS_ERROR
8343 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8344 is_gimple_val, fb_rvalue)
8345 == GS_ERROR))
8346 return 2;
8347 tree var = TREE_VEC_ELT (it, 0);
8348 tree begin = TREE_VEC_ELT (it, 1);
8349 tree end = TREE_VEC_ELT (it, 2);
8350 tree step = TREE_VEC_ELT (it, 3);
8351 tree orig_step = TREE_VEC_ELT (it, 4);
8352 tree type = TREE_TYPE (var);
8353 tree stype = TREE_TYPE (step);
8354 location_t loc = DECL_SOURCE_LOCATION (var);
8355 tree endmbegin;
8356 /* Compute count for this iterator as
8357 orig_step > 0
8358 ? (begin < end ? (end - begin + (step - 1)) / step : 0)
8359 : (begin > end ? (end - begin + (step + 1)) / step : 0)
8360 and compute product of those for the entire depend
8361 clause. */
8362 if (POINTER_TYPE_P (type))
8363 endmbegin = fold_build2_loc (loc, POINTER_DIFF_EXPR,
8364 stype, end, begin);
8365 else
8366 endmbegin = fold_build2_loc (loc, MINUS_EXPR, type,
8367 end, begin);
8368 tree stepm1 = fold_build2_loc (loc, MINUS_EXPR, stype,
8369 step,
8370 build_int_cst (stype, 1));
8371 tree stepp1 = fold_build2_loc (loc, PLUS_EXPR, stype, step,
8372 build_int_cst (stype, 1));
8373 tree pos = fold_build2_loc (loc, PLUS_EXPR, stype,
8374 unshare_expr (endmbegin),
8375 stepm1);
8376 pos = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8377 pos, step);
8378 tree neg = fold_build2_loc (loc, PLUS_EXPR, stype,
8379 endmbegin, stepp1);
8380 if (TYPE_UNSIGNED (stype))
8382 neg = fold_build1_loc (loc, NEGATE_EXPR, stype, neg);
8383 step = fold_build1_loc (loc, NEGATE_EXPR, stype, step);
8385 neg = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8386 neg, step);
8387 step = NULL_TREE;
8388 tree cond = fold_build2_loc (loc, LT_EXPR,
8389 boolean_type_node,
8390 begin, end);
8391 pos = fold_build3_loc (loc, COND_EXPR, stype, cond, pos,
8392 build_int_cst (stype, 0));
8393 cond = fold_build2_loc (loc, LT_EXPR, boolean_type_node,
8394 end, begin);
8395 neg = fold_build3_loc (loc, COND_EXPR, stype, cond, neg,
8396 build_int_cst (stype, 0));
8397 tree osteptype = TREE_TYPE (orig_step);
8398 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8399 orig_step,
8400 build_int_cst (osteptype, 0));
8401 tree cnt = fold_build3_loc (loc, COND_EXPR, stype,
8402 cond, pos, neg);
8403 cnt = fold_convert_loc (loc, sizetype, cnt);
8404 if (gimplify_expr (&cnt, pre_p, NULL, is_gimple_val,
8405 fb_rvalue) == GS_ERROR)
8406 return 2;
8407 tcnt = size_binop_loc (loc, MULT_EXPR, tcnt, cnt);
8409 if (gimplify_expr (&tcnt, pre_p, NULL, is_gimple_val,
8410 fb_rvalue) == GS_ERROR)
8411 return 2;
8412 last_iter = TREE_PURPOSE (t);
8413 last_count = tcnt;
8415 if (counts[i] == NULL_TREE)
8416 counts[i] = last_count;
8417 else
8418 counts[i] = size_binop_loc (OMP_CLAUSE_LOCATION (c),
8419 PLUS_EXPR, counts[i], last_count);
8421 else
8422 n[i]++;
8424 for (i = 0; i < 5; i++)
8425 if (counts[i])
8426 break;
8427 if (i == 5)
8428 return 0;
8430 tree total = size_zero_node;
8431 for (i = 0; i < 5; i++)
8433 unused[i] = counts[i] == NULL_TREE && n[i] == 0;
8434 if (counts[i] == NULL_TREE)
8435 counts[i] = size_zero_node;
8436 if (n[i])
8437 counts[i] = size_binop (PLUS_EXPR, counts[i], size_int (n[i]));
8438 if (gimplify_expr (&counts[i], pre_p, NULL, is_gimple_val,
8439 fb_rvalue) == GS_ERROR)
8440 return 2;
8441 total = size_binop (PLUS_EXPR, total, counts[i]);
8444 if (gimplify_expr (&total, pre_p, NULL, is_gimple_val, fb_rvalue)
8445 == GS_ERROR)
8446 return 2;
8447 bool is_old = unused[1] && unused[3] && unused[4];
8448 tree totalpx = size_binop (PLUS_EXPR, unshare_expr (total),
8449 size_int (is_old ? 1 : 4));
8450 if (!unused[4])
8451 totalpx = size_binop (PLUS_EXPR, totalpx,
8452 size_binop (MULT_EXPR, counts[4], size_int (2)));
8453 tree type = build_array_type (ptr_type_node, build_index_type (totalpx));
8454 tree array = create_tmp_var_raw (type);
8455 TREE_ADDRESSABLE (array) = 1;
8456 if (!poly_int_tree_p (totalpx))
8458 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (array)))
8459 gimplify_type_sizes (TREE_TYPE (array), pre_p);
8460 if (gimplify_omp_ctxp)
8462 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8463 while (ctx
8464 && (ctx->region_type == ORT_WORKSHARE
8465 || ctx->region_type == ORT_TASKGROUP
8466 || ctx->region_type == ORT_SIMD
8467 || ctx->region_type == ORT_ACC))
8468 ctx = ctx->outer_context;
8469 if (ctx)
8470 omp_add_variable (ctx, array, GOVD_LOCAL | GOVD_SEEN);
8472 gimplify_vla_decl (array, pre_p);
8474 else
8475 gimple_add_tmp_var (array);
8476 tree r = build4 (ARRAY_REF, ptr_type_node, array, size_int (0), NULL_TREE,
8477 NULL_TREE);
8478 tree tem;
8479 if (!is_old)
8481 tem = build2 (MODIFY_EXPR, void_type_node, r,
8482 build_int_cst (ptr_type_node, 0));
8483 gimplify_and_add (tem, pre_p);
8484 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (1), NULL_TREE,
8485 NULL_TREE);
8487 tem = build2 (MODIFY_EXPR, void_type_node, r,
8488 fold_convert (ptr_type_node, total));
8489 gimplify_and_add (tem, pre_p);
8490 for (i = 1; i < (is_old ? 2 : 4); i++)
8492 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (i + !is_old),
8493 NULL_TREE, NULL_TREE);
8494 tem = build2 (MODIFY_EXPR, void_type_node, r, counts[i - 1]);
8495 gimplify_and_add (tem, pre_p);
8498 tree cnts[6];
8499 for (j = 5; j; j--)
8500 if (!unused[j - 1])
8501 break;
8502 for (i = 0; i < 5; i++)
8504 if (i && (i >= j || unused[i - 1]))
8506 cnts[i] = cnts[i - 1];
8507 continue;
8509 cnts[i] = create_tmp_var (sizetype);
8510 if (i == 0)
8511 g = gimple_build_assign (cnts[i], size_int (is_old ? 2 : 5));
8512 else
8514 tree t;
8515 if (is_old)
8516 t = size_binop (PLUS_EXPR, counts[0], size_int (2));
8517 else
8518 t = size_binop (PLUS_EXPR, cnts[i - 1], counts[i - 1]);
8519 if (gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue)
8520 == GS_ERROR)
8521 return 2;
8522 g = gimple_build_assign (cnts[i], t);
8524 gimple_seq_add_stmt (pre_p, g);
8526 if (unused[4])
8527 cnts[5] = NULL_TREE;
8528 else
8530 tree t = size_binop (PLUS_EXPR, total, size_int (5));
8531 cnts[5] = create_tmp_var (sizetype);
8532 g = gimple_build_assign (cnts[i], t);
8533 gimple_seq_add_stmt (pre_p, g);
8536 last_iter = NULL_TREE;
8537 tree last_bind = NULL_TREE;
8538 tree *last_body = NULL;
8539 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8540 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8542 switch (OMP_CLAUSE_DEPEND_KIND (c))
8544 case OMP_CLAUSE_DEPEND_IN:
8545 i = 2;
8546 break;
8547 case OMP_CLAUSE_DEPEND_OUT:
8548 case OMP_CLAUSE_DEPEND_INOUT:
8549 i = 0;
8550 break;
8551 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8552 i = 1;
8553 break;
8554 case OMP_CLAUSE_DEPEND_DEPOBJ:
8555 i = 3;
8556 break;
8557 case OMP_CLAUSE_DEPEND_INOUTSET:
8558 i = 4;
8559 break;
8560 default:
8561 gcc_unreachable ();
8563 tree t = OMP_CLAUSE_DECL (c);
8564 if (TREE_CODE (t) == TREE_LIST
8565 && TREE_PURPOSE (t)
8566 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8568 if (TREE_PURPOSE (t) != last_iter)
8570 if (last_bind)
8571 gimplify_and_add (last_bind, pre_p);
8572 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8573 last_bind = build3 (BIND_EXPR, void_type_node,
8574 BLOCK_VARS (block), NULL, block);
8575 TREE_SIDE_EFFECTS (last_bind) = 1;
8576 SET_EXPR_LOCATION (last_bind, OMP_CLAUSE_LOCATION (c));
8577 tree *p = &BIND_EXPR_BODY (last_bind);
8578 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8580 tree var = TREE_VEC_ELT (it, 0);
8581 tree begin = TREE_VEC_ELT (it, 1);
8582 tree end = TREE_VEC_ELT (it, 2);
8583 tree step = TREE_VEC_ELT (it, 3);
8584 tree orig_step = TREE_VEC_ELT (it, 4);
8585 tree type = TREE_TYPE (var);
8586 location_t loc = DECL_SOURCE_LOCATION (var);
8587 /* Emit:
8588 var = begin;
8589 goto cond_label;
8590 beg_label:
8592 var = var + step;
8593 cond_label:
8594 if (orig_step > 0) {
8595 if (var < end) goto beg_label;
8596 } else {
8597 if (var > end) goto beg_label;
8599 for each iterator, with inner iterators added to
8600 the ... above. */
8601 tree beg_label = create_artificial_label (loc);
8602 tree cond_label = NULL_TREE;
8603 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8604 var, begin);
8605 append_to_statement_list_force (tem, p);
8606 tem = build_and_jump (&cond_label);
8607 append_to_statement_list_force (tem, p);
8608 tem = build1 (LABEL_EXPR, void_type_node, beg_label);
8609 append_to_statement_list (tem, p);
8610 tree bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
8611 NULL_TREE, NULL_TREE);
8612 TREE_SIDE_EFFECTS (bind) = 1;
8613 SET_EXPR_LOCATION (bind, loc);
8614 append_to_statement_list_force (bind, p);
8615 if (POINTER_TYPE_P (type))
8616 tem = build2_loc (loc, POINTER_PLUS_EXPR, type,
8617 var, fold_convert_loc (loc, sizetype,
8618 step));
8619 else
8620 tem = build2_loc (loc, PLUS_EXPR, type, var, step);
8621 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8622 var, tem);
8623 append_to_statement_list_force (tem, p);
8624 tem = build1 (LABEL_EXPR, void_type_node, cond_label);
8625 append_to_statement_list (tem, p);
8626 tree cond = fold_build2_loc (loc, LT_EXPR,
8627 boolean_type_node,
8628 var, end);
8629 tree pos
8630 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8631 cond, build_and_jump (&beg_label),
8632 void_node);
8633 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8634 var, end);
8635 tree neg
8636 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8637 cond, build_and_jump (&beg_label),
8638 void_node);
8639 tree osteptype = TREE_TYPE (orig_step);
8640 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8641 orig_step,
8642 build_int_cst (osteptype, 0));
8643 tem = fold_build3_loc (loc, COND_EXPR, void_type_node,
8644 cond, pos, neg);
8645 append_to_statement_list_force (tem, p);
8646 p = &BIND_EXPR_BODY (bind);
8648 last_body = p;
8650 last_iter = TREE_PURPOSE (t);
8651 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8653 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t),
8654 0), last_body);
8655 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8657 if (error_operand_p (TREE_VALUE (t)))
8658 return 2;
8659 if (TREE_VALUE (t) != null_pointer_node)
8660 TREE_VALUE (t) = build_fold_addr_expr (TREE_VALUE (t));
8661 if (i == 4)
8663 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8664 NULL_TREE, NULL_TREE);
8665 tree r2 = build4 (ARRAY_REF, ptr_type_node, array, cnts[5],
8666 NULL_TREE, NULL_TREE);
8667 r2 = build_fold_addr_expr_with_type (r2, ptr_type_node);
8668 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8669 void_type_node, r, r2);
8670 append_to_statement_list_force (tem, last_body);
8671 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8672 void_type_node, cnts[i],
8673 size_binop (PLUS_EXPR, cnts[i],
8674 size_int (1)));
8675 append_to_statement_list_force (tem, last_body);
8676 i = 5;
8678 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8679 NULL_TREE, NULL_TREE);
8680 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8681 void_type_node, r, TREE_VALUE (t));
8682 append_to_statement_list_force (tem, last_body);
8683 if (i == 5)
8685 r = build4 (ARRAY_REF, ptr_type_node, array,
8686 size_binop (PLUS_EXPR, cnts[i], size_int (1)),
8687 NULL_TREE, NULL_TREE);
8688 tem = build_int_cst (ptr_type_node, GOMP_DEPEND_INOUTSET);
8689 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8690 void_type_node, r, tem);
8691 append_to_statement_list_force (tem, last_body);
8693 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8694 void_type_node, cnts[i],
8695 size_binop (PLUS_EXPR, cnts[i],
8696 size_int (1 + (i == 5))));
8697 append_to_statement_list_force (tem, last_body);
8698 TREE_VALUE (t) = null_pointer_node;
8700 else
8702 if (last_bind)
8704 gimplify_and_add (last_bind, pre_p);
8705 last_bind = NULL_TREE;
8707 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8709 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8710 NULL, is_gimple_val, fb_rvalue);
8711 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8713 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8714 return 2;
8715 if (OMP_CLAUSE_DECL (c) != null_pointer_node)
8716 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
8717 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8718 is_gimple_val, fb_rvalue) == GS_ERROR)
8719 return 2;
8720 if (i == 4)
8722 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8723 NULL_TREE, NULL_TREE);
8724 tree r2 = build4 (ARRAY_REF, ptr_type_node, array, cnts[5],
8725 NULL_TREE, NULL_TREE);
8726 r2 = build_fold_addr_expr_with_type (r2, ptr_type_node);
8727 tem = build2 (MODIFY_EXPR, void_type_node, r, r2);
8728 gimplify_and_add (tem, pre_p);
8729 g = gimple_build_assign (cnts[i], size_binop (PLUS_EXPR,
8730 cnts[i],
8731 size_int (1)));
8732 gimple_seq_add_stmt (pre_p, g);
8733 i = 5;
8735 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8736 NULL_TREE, NULL_TREE);
8737 tem = build2 (MODIFY_EXPR, void_type_node, r, OMP_CLAUSE_DECL (c));
8738 gimplify_and_add (tem, pre_p);
8739 if (i == 5)
8741 r = build4 (ARRAY_REF, ptr_type_node, array,
8742 size_binop (PLUS_EXPR, cnts[i], size_int (1)),
8743 NULL_TREE, NULL_TREE);
8744 tem = build_int_cst (ptr_type_node, GOMP_DEPEND_INOUTSET);
8745 tem = build2 (MODIFY_EXPR, void_type_node, r, tem);
8746 append_to_statement_list_force (tem, last_body);
8747 gimplify_and_add (tem, pre_p);
8749 g = gimple_build_assign (cnts[i],
8750 size_binop (PLUS_EXPR, cnts[i],
8751 size_int (1 + (i == 5))));
8752 gimple_seq_add_stmt (pre_p, g);
8755 if (last_bind)
8756 gimplify_and_add (last_bind, pre_p);
8757 tree cond = boolean_false_node;
8758 if (is_old)
8760 if (!unused[0])
8761 cond = build2_loc (first_loc, NE_EXPR, boolean_type_node, cnts[0],
8762 size_binop_loc (first_loc, PLUS_EXPR, counts[0],
8763 size_int (2)));
8764 if (!unused[2])
8765 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8766 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8767 cnts[2],
8768 size_binop_loc (first_loc, PLUS_EXPR,
8769 totalpx,
8770 size_int (1))));
8772 else
8774 tree prev = size_int (5);
8775 for (i = 0; i < 5; i++)
8777 if (unused[i])
8778 continue;
8779 prev = size_binop_loc (first_loc, PLUS_EXPR, counts[i], prev);
8780 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8781 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8782 cnts[i], unshare_expr (prev)));
8785 tem = build3_loc (first_loc, COND_EXPR, void_type_node, cond,
8786 build_call_expr_loc (first_loc,
8787 builtin_decl_explicit (BUILT_IN_TRAP),
8788 0), void_node);
8789 gimplify_and_add (tem, pre_p);
8790 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_DEPEND);
8791 OMP_CLAUSE_DEPEND_KIND (c) = OMP_CLAUSE_DEPEND_LAST;
8792 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (array);
8793 OMP_CLAUSE_CHAIN (c) = *list_p;
8794 *list_p = c;
8795 return 1;
8798 /* Insert a GOMP_MAP_ALLOC or GOMP_MAP_RELEASE node following a
8799 GOMP_MAP_STRUCT mapping. C is an always_pointer mapping. STRUCT_NODE is
8800 the struct node to insert the new mapping after (when the struct node is
8801 initially created). PREV_NODE is the first of two or three mappings for a
8802 pointer, and is either:
8803 - the node before C, when a pair of mappings is used, e.g. for a C/C++
8804 array section.
8805 - not the node before C. This is true when we have a reference-to-pointer
8806 type (with a mapping for the reference and for the pointer), or for
8807 Fortran derived-type mappings with a GOMP_MAP_TO_PSET.
8808 If SCP is non-null, the new node is inserted before *SCP.
8809 if SCP is null, the new node is inserted before PREV_NODE.
8810 The return type is:
8811 - PREV_NODE, if SCP is non-null.
8812 - The newly-created ALLOC or RELEASE node, if SCP is null.
8813 - The second newly-created ALLOC or RELEASE node, if we are mapping a
8814 reference to a pointer. */
8816 static tree
8817 insert_struct_comp_map (enum tree_code code, tree c, tree struct_node,
8818 tree prev_node, tree *scp)
8820 enum gomp_map_kind mkind
8821 = (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA)
8822 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
8824 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8825 tree cl = scp ? prev_node : c2;
8826 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
8827 OMP_CLAUSE_DECL (c2) = unshare_expr (OMP_CLAUSE_DECL (c));
8828 OMP_CLAUSE_CHAIN (c2) = scp ? *scp : prev_node;
8829 if (OMP_CLAUSE_CHAIN (prev_node) != c
8830 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8831 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8832 == GOMP_MAP_TO_PSET))
8833 OMP_CLAUSE_SIZE (c2) = OMP_CLAUSE_SIZE (OMP_CLAUSE_CHAIN (prev_node));
8834 else
8835 OMP_CLAUSE_SIZE (c2) = TYPE_SIZE_UNIT (ptr_type_node);
8836 if (struct_node)
8837 OMP_CLAUSE_CHAIN (struct_node) = c2;
8839 /* We might need to create an additional mapping if we have a reference to a
8840 pointer (in C++). Don't do this if we have something other than a
8841 GOMP_MAP_ALWAYS_POINTER though, i.e. a GOMP_MAP_TO_PSET. */
8842 if (OMP_CLAUSE_CHAIN (prev_node) != c
8843 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8844 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8845 == GOMP_MAP_ALWAYS_POINTER)
8846 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8847 == GOMP_MAP_ATTACH_DETACH)))
8849 tree c4 = OMP_CLAUSE_CHAIN (prev_node);
8850 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8851 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
8852 OMP_CLAUSE_DECL (c3) = unshare_expr (OMP_CLAUSE_DECL (c4));
8853 OMP_CLAUSE_SIZE (c3) = TYPE_SIZE_UNIT (ptr_type_node);
8854 OMP_CLAUSE_CHAIN (c3) = prev_node;
8855 if (!scp)
8856 OMP_CLAUSE_CHAIN (c2) = c3;
8857 else
8858 cl = c3;
8861 if (scp)
8862 *scp = c2;
8864 return cl;
8867 /* Strip ARRAY_REFS or an indirect ref off BASE, find the containing object,
8868 and set *BITPOSP and *POFFSETP to the bit offset of the access.
8869 If BASE_REF is non-NULL and the containing object is a reference, set
8870 *BASE_REF to that reference before dereferencing the object.
8871 If BASE_REF is NULL, check that the containing object is a COMPONENT_REF or
8872 has array type, else return NULL. */
8874 static tree
8875 extract_base_bit_offset (tree base, tree *base_ref, poly_int64 *bitposp,
8876 poly_offset_int *poffsetp, tree *offsetp)
8878 tree offset;
8879 poly_int64 bitsize, bitpos;
8880 machine_mode mode;
8881 int unsignedp, reversep, volatilep = 0;
8882 poly_offset_int poffset;
8884 if (base_ref)
8886 *base_ref = NULL_TREE;
8888 while (TREE_CODE (base) == ARRAY_REF)
8889 base = TREE_OPERAND (base, 0);
8891 if (TREE_CODE (base) == INDIRECT_REF)
8892 base = TREE_OPERAND (base, 0);
8894 else
8896 if (TREE_CODE (base) == ARRAY_REF)
8898 while (TREE_CODE (base) == ARRAY_REF)
8899 base = TREE_OPERAND (base, 0);
8900 if (TREE_CODE (base) != COMPONENT_REF
8901 || TREE_CODE (TREE_TYPE (base)) != ARRAY_TYPE)
8902 return NULL_TREE;
8904 else if (TREE_CODE (base) == INDIRECT_REF
8905 && TREE_CODE (TREE_OPERAND (base, 0)) == COMPONENT_REF
8906 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0)))
8907 == REFERENCE_TYPE))
8908 base = TREE_OPERAND (base, 0);
8911 base = get_inner_reference (base, &bitsize, &bitpos, &offset, &mode,
8912 &unsignedp, &reversep, &volatilep);
8914 tree orig_base = base;
8916 if ((TREE_CODE (base) == INDIRECT_REF
8917 || (TREE_CODE (base) == MEM_REF
8918 && integer_zerop (TREE_OPERAND (base, 1))))
8919 && DECL_P (TREE_OPERAND (base, 0))
8920 && TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0))) == REFERENCE_TYPE)
8921 base = TREE_OPERAND (base, 0);
8923 if (offset && poly_int_tree_p (offset))
8925 poffset = wi::to_poly_offset (offset);
8926 offset = NULL_TREE;
8928 else
8929 poffset = 0;
8931 if (maybe_ne (bitpos, 0))
8932 poffset += bits_to_bytes_round_down (bitpos);
8934 *bitposp = bitpos;
8935 *poffsetp = poffset;
8936 *offsetp = offset;
8938 /* Set *BASE_REF if BASE was a dereferenced reference variable. */
8939 if (base_ref && orig_base != base)
8940 *base_ref = orig_base;
8942 return base;
8945 /* Returns true if EXPR is or contains (as a sub-component) BASE_PTR. */
8947 static bool
8948 is_or_contains_p (tree expr, tree base_ptr)
8950 if ((TREE_CODE (expr) == INDIRECT_REF && TREE_CODE (base_ptr) == MEM_REF)
8951 || (TREE_CODE (expr) == MEM_REF && TREE_CODE (base_ptr) == INDIRECT_REF))
8952 return operand_equal_p (TREE_OPERAND (expr, 0),
8953 TREE_OPERAND (base_ptr, 0));
8954 while (!operand_equal_p (expr, base_ptr))
8956 if (TREE_CODE (base_ptr) == COMPOUND_EXPR)
8957 base_ptr = TREE_OPERAND (base_ptr, 1);
8958 if (TREE_CODE (base_ptr) == COMPONENT_REF
8959 || TREE_CODE (base_ptr) == POINTER_PLUS_EXPR
8960 || TREE_CODE (base_ptr) == SAVE_EXPR)
8961 base_ptr = TREE_OPERAND (base_ptr, 0);
8962 else
8963 break;
8965 return operand_equal_p (expr, base_ptr);
8968 /* Implement OpenMP 5.x map ordering rules for target directives. There are
8969 several rules, and with some level of ambiguity, hopefully we can at least
8970 collect the complexity here in one place. */
8972 static void
8973 omp_target_reorder_clauses (tree *list_p)
8975 /* Collect refs to alloc/release/delete maps. */
8976 auto_vec<tree, 32> ard;
8977 tree *cp = list_p;
8978 while (*cp != NULL_TREE)
8979 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8980 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALLOC
8981 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_RELEASE
8982 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_DELETE))
8984 /* Unlink cp and push to ard. */
8985 tree c = *cp;
8986 tree nc = OMP_CLAUSE_CHAIN (c);
8987 *cp = nc;
8988 ard.safe_push (c);
8990 /* Any associated pointer type maps should also move along. */
8991 while (*cp != NULL_TREE
8992 && OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8993 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
8994 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_POINTER
8995 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ATTACH_DETACH
8996 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_POINTER
8997 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALWAYS_POINTER
8998 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_TO_PSET))
9000 c = *cp;
9001 nc = OMP_CLAUSE_CHAIN (c);
9002 *cp = nc;
9003 ard.safe_push (c);
9006 else
9007 cp = &OMP_CLAUSE_CHAIN (*cp);
9009 /* Link alloc/release/delete maps to the end of list. */
9010 for (unsigned int i = 0; i < ard.length (); i++)
9012 *cp = ard[i];
9013 cp = &OMP_CLAUSE_CHAIN (ard[i]);
9015 *cp = NULL_TREE;
9017 /* OpenMP 5.0 requires that pointer variables are mapped before
9018 its use as a base-pointer. */
9019 auto_vec<tree *, 32> atf;
9020 for (tree *cp = list_p; *cp; cp = &OMP_CLAUSE_CHAIN (*cp))
9021 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP)
9023 /* Collect alloc, to, from, to/from clause tree pointers. */
9024 gomp_map_kind k = OMP_CLAUSE_MAP_KIND (*cp);
9025 if (k == GOMP_MAP_ALLOC
9026 || k == GOMP_MAP_TO
9027 || k == GOMP_MAP_FROM
9028 || k == GOMP_MAP_TOFROM
9029 || k == GOMP_MAP_ALWAYS_TO
9030 || k == GOMP_MAP_ALWAYS_FROM
9031 || k == GOMP_MAP_ALWAYS_TOFROM)
9032 atf.safe_push (cp);
9035 for (unsigned int i = 0; i < atf.length (); i++)
9036 if (atf[i])
9038 tree *cp = atf[i];
9039 tree decl = OMP_CLAUSE_DECL (*cp);
9040 if (TREE_CODE (decl) == INDIRECT_REF || TREE_CODE (decl) == MEM_REF)
9042 tree base_ptr = TREE_OPERAND (decl, 0);
9043 STRIP_TYPE_NOPS (base_ptr);
9044 for (unsigned int j = i + 1; j < atf.length (); j++)
9045 if (atf[j])
9047 tree *cp2 = atf[j];
9048 tree decl2 = OMP_CLAUSE_DECL (*cp2);
9050 decl2 = OMP_CLAUSE_DECL (*cp2);
9051 if (is_or_contains_p (decl2, base_ptr))
9053 /* Move *cp2 to before *cp. */
9054 tree c = *cp2;
9055 *cp2 = OMP_CLAUSE_CHAIN (c);
9056 OMP_CLAUSE_CHAIN (c) = *cp;
9057 *cp = c;
9059 if (*cp2 != NULL_TREE
9060 && OMP_CLAUSE_CODE (*cp2) == OMP_CLAUSE_MAP
9061 && OMP_CLAUSE_MAP_KIND (*cp2) == GOMP_MAP_ALWAYS_POINTER)
9063 tree c2 = *cp2;
9064 *cp2 = OMP_CLAUSE_CHAIN (c2);
9065 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (c);
9066 OMP_CLAUSE_CHAIN (c) = c2;
9069 atf[j] = NULL;
9075 /* For attach_detach map clauses, if there is another map that maps the
9076 attached/detached pointer, make sure that map is ordered before the
9077 attach_detach. */
9078 atf.truncate (0);
9079 for (tree *cp = list_p; *cp; cp = &OMP_CLAUSE_CHAIN (*cp))
9080 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP)
9082 /* Collect alloc, to, from, to/from clauses, and
9083 always_pointer/attach_detach clauses. */
9084 gomp_map_kind k = OMP_CLAUSE_MAP_KIND (*cp);
9085 if (k == GOMP_MAP_ALLOC
9086 || k == GOMP_MAP_TO
9087 || k == GOMP_MAP_FROM
9088 || k == GOMP_MAP_TOFROM
9089 || k == GOMP_MAP_ALWAYS_TO
9090 || k == GOMP_MAP_ALWAYS_FROM
9091 || k == GOMP_MAP_ALWAYS_TOFROM
9092 || k == GOMP_MAP_ATTACH_DETACH
9093 || k == GOMP_MAP_ALWAYS_POINTER)
9094 atf.safe_push (cp);
9097 for (unsigned int i = 0; i < atf.length (); i++)
9098 if (atf[i])
9100 tree *cp = atf[i];
9101 tree ptr = OMP_CLAUSE_DECL (*cp);
9102 STRIP_TYPE_NOPS (ptr);
9103 if (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ATTACH_DETACH)
9104 for (unsigned int j = i + 1; j < atf.length (); j++)
9106 tree *cp2 = atf[j];
9107 tree decl2 = OMP_CLAUSE_DECL (*cp2);
9108 if (OMP_CLAUSE_MAP_KIND (*cp2) != GOMP_MAP_ATTACH_DETACH
9109 && OMP_CLAUSE_MAP_KIND (*cp2) != GOMP_MAP_ALWAYS_POINTER
9110 && is_or_contains_p (decl2, ptr))
9112 /* Move *cp2 to before *cp. */
9113 tree c = *cp2;
9114 *cp2 = OMP_CLAUSE_CHAIN (c);
9115 OMP_CLAUSE_CHAIN (c) = *cp;
9116 *cp = c;
9117 atf[j] = NULL;
9119 /* If decl2 is of the form '*decl2_opnd0', and followed by an
9120 ALWAYS_POINTER or ATTACH_DETACH of 'decl2_opnd0', move the
9121 pointer operation along with *cp2. This can happen for C++
9122 reference sequences. */
9123 if (j + 1 < atf.length ()
9124 && (TREE_CODE (decl2) == INDIRECT_REF
9125 || TREE_CODE (decl2) == MEM_REF))
9127 tree *cp3 = atf[j + 1];
9128 tree decl3 = OMP_CLAUSE_DECL (*cp3);
9129 tree decl2_opnd0 = TREE_OPERAND (decl2, 0);
9130 if ((OMP_CLAUSE_MAP_KIND (*cp3) == GOMP_MAP_ALWAYS_POINTER
9131 || OMP_CLAUSE_MAP_KIND (*cp3) == GOMP_MAP_ATTACH_DETACH)
9132 && operand_equal_p (decl3, decl2_opnd0))
9134 /* Also move *cp3 to before *cp. */
9135 c = *cp3;
9136 *cp2 = OMP_CLAUSE_CHAIN (c);
9137 OMP_CLAUSE_CHAIN (c) = *cp;
9138 *cp = c;
9139 atf[j + 1] = NULL;
9140 j += 1;
9148 /* DECL is supposed to have lastprivate semantics in the outer contexts
9149 of combined/composite constructs, starting with OCTX.
9150 Add needed lastprivate, shared or map clause if no data sharing or
9151 mapping clause are present. IMPLICIT_P is true if it is an implicit
9152 clause (IV on simd), in which case the lastprivate will not be
9153 copied to some constructs. */
9155 static void
9156 omp_lastprivate_for_combined_outer_constructs (struct gimplify_omp_ctx *octx,
9157 tree decl, bool implicit_p)
9159 struct gimplify_omp_ctx *orig_octx = octx;
9160 for (; octx; octx = octx->outer_context)
9162 if ((octx->region_type == ORT_COMBINED_PARALLEL
9163 || (octx->region_type & ORT_COMBINED_TEAMS) == ORT_COMBINED_TEAMS)
9164 && splay_tree_lookup (octx->variables,
9165 (splay_tree_key) decl) == NULL)
9167 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
9168 continue;
9170 if ((octx->region_type & ORT_TASK) != 0
9171 && octx->combined_loop
9172 && splay_tree_lookup (octx->variables,
9173 (splay_tree_key) decl) == NULL)
9175 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
9176 continue;
9178 if (implicit_p
9179 && octx->region_type == ORT_WORKSHARE
9180 && octx->combined_loop
9181 && splay_tree_lookup (octx->variables,
9182 (splay_tree_key) decl) == NULL
9183 && octx->outer_context
9184 && octx->outer_context->region_type == ORT_COMBINED_PARALLEL
9185 && splay_tree_lookup (octx->outer_context->variables,
9186 (splay_tree_key) decl) == NULL)
9188 octx = octx->outer_context;
9189 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
9190 continue;
9192 if ((octx->region_type == ORT_WORKSHARE || octx->region_type == ORT_ACC)
9193 && octx->combined_loop
9194 && splay_tree_lookup (octx->variables,
9195 (splay_tree_key) decl) == NULL
9196 && !omp_check_private (octx, decl, false))
9198 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
9199 continue;
9201 if (octx->region_type == ORT_COMBINED_TARGET)
9203 splay_tree_node n = splay_tree_lookup (octx->variables,
9204 (splay_tree_key) decl);
9205 if (n == NULL)
9207 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
9208 octx = octx->outer_context;
9210 else if (!implicit_p
9211 && (n->value & GOVD_FIRSTPRIVATE_IMPLICIT))
9213 n->value &= ~(GOVD_FIRSTPRIVATE
9214 | GOVD_FIRSTPRIVATE_IMPLICIT
9215 | GOVD_EXPLICIT);
9216 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
9217 octx = octx->outer_context;
9220 break;
9222 if (octx && (implicit_p || octx != orig_octx))
9223 omp_notice_variable (octx, decl, true);
9226 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
9227 and previous omp contexts. */
9229 static void
9230 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
9231 enum omp_region_type region_type,
9232 enum tree_code code)
9234 struct gimplify_omp_ctx *ctx, *outer_ctx;
9235 tree c;
9236 hash_map<tree_operand_hash, tree> *struct_map_to_clause = NULL;
9237 hash_map<tree_operand_hash, tree *> *struct_seen_clause = NULL;
9238 hash_set<tree> *struct_deref_set = NULL;
9239 tree *prev_list_p = NULL, *orig_list_p = list_p;
9240 int handled_depend_iterators = -1;
9241 int nowait = -1;
9243 ctx = new_omp_context (region_type);
9244 ctx->code = code;
9245 outer_ctx = ctx->outer_context;
9246 if (code == OMP_TARGET)
9248 if (!lang_GNU_Fortran ())
9249 ctx->defaultmap[GDMK_POINTER] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
9250 ctx->defaultmap[GDMK_SCALAR] = GOVD_FIRSTPRIVATE;
9251 ctx->defaultmap[GDMK_SCALAR_TARGET] = (lang_GNU_Fortran ()
9252 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
9254 if (!lang_GNU_Fortran ())
9255 switch (code)
9257 case OMP_TARGET:
9258 case OMP_TARGET_DATA:
9259 case OMP_TARGET_ENTER_DATA:
9260 case OMP_TARGET_EXIT_DATA:
9261 case OACC_DECLARE:
9262 case OACC_HOST_DATA:
9263 case OACC_PARALLEL:
9264 case OACC_KERNELS:
9265 ctx->target_firstprivatize_array_bases = true;
9266 default:
9267 break;
9270 if (code == OMP_TARGET
9271 || code == OMP_TARGET_DATA
9272 || code == OMP_TARGET_ENTER_DATA
9273 || code == OMP_TARGET_EXIT_DATA)
9274 omp_target_reorder_clauses (list_p);
9276 while ((c = *list_p) != NULL)
9278 bool remove = false;
9279 bool notice_outer = true;
9280 const char *check_non_private = NULL;
9281 unsigned int flags;
9282 tree decl;
9284 switch (OMP_CLAUSE_CODE (c))
9286 case OMP_CLAUSE_PRIVATE:
9287 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
9288 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
9290 flags |= GOVD_PRIVATE_OUTER_REF;
9291 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
9293 else
9294 notice_outer = false;
9295 goto do_add;
9296 case OMP_CLAUSE_SHARED:
9297 flags = GOVD_SHARED | GOVD_EXPLICIT;
9298 goto do_add;
9299 case OMP_CLAUSE_FIRSTPRIVATE:
9300 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
9301 check_non_private = "firstprivate";
9302 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
9304 gcc_assert (code == OMP_TARGET);
9305 flags |= GOVD_FIRSTPRIVATE_IMPLICIT;
9307 goto do_add;
9308 case OMP_CLAUSE_LASTPRIVATE:
9309 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
9310 switch (code)
9312 case OMP_DISTRIBUTE:
9313 error_at (OMP_CLAUSE_LOCATION (c),
9314 "conditional %<lastprivate%> clause on "
9315 "%qs construct", "distribute");
9316 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
9317 break;
9318 case OMP_TASKLOOP:
9319 error_at (OMP_CLAUSE_LOCATION (c),
9320 "conditional %<lastprivate%> clause on "
9321 "%qs construct", "taskloop");
9322 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
9323 break;
9324 default:
9325 break;
9327 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
9328 if (code != OMP_LOOP)
9329 check_non_private = "lastprivate";
9330 decl = OMP_CLAUSE_DECL (c);
9331 if (error_operand_p (decl))
9332 goto do_add;
9333 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c)
9334 && !lang_hooks.decls.omp_scalar_p (decl, true))
9336 error_at (OMP_CLAUSE_LOCATION (c),
9337 "non-scalar variable %qD in conditional "
9338 "%<lastprivate%> clause", decl);
9339 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
9341 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
9342 flags |= GOVD_LASTPRIVATE_CONDITIONAL;
9343 omp_lastprivate_for_combined_outer_constructs (outer_ctx, decl,
9344 false);
9345 goto do_add;
9346 case OMP_CLAUSE_REDUCTION:
9347 if (OMP_CLAUSE_REDUCTION_TASK (c))
9349 if (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
9351 if (nowait == -1)
9352 nowait = omp_find_clause (*list_p,
9353 OMP_CLAUSE_NOWAIT) != NULL_TREE;
9354 if (nowait
9355 && (outer_ctx == NULL
9356 || outer_ctx->region_type != ORT_COMBINED_PARALLEL))
9358 error_at (OMP_CLAUSE_LOCATION (c),
9359 "%<task%> reduction modifier on a construct "
9360 "with a %<nowait%> clause");
9361 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
9364 else if ((region_type & ORT_PARALLEL) != ORT_PARALLEL)
9366 error_at (OMP_CLAUSE_LOCATION (c),
9367 "invalid %<task%> reduction modifier on construct "
9368 "other than %<parallel%>, %qs, %<sections%> or "
9369 "%<scope%>", lang_GNU_Fortran () ? "do" : "for");
9370 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
9373 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
9374 switch (code)
9376 case OMP_SECTIONS:
9377 error_at (OMP_CLAUSE_LOCATION (c),
9378 "%<inscan%> %<reduction%> clause on "
9379 "%qs construct", "sections");
9380 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9381 break;
9382 case OMP_PARALLEL:
9383 error_at (OMP_CLAUSE_LOCATION (c),
9384 "%<inscan%> %<reduction%> clause on "
9385 "%qs construct", "parallel");
9386 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9387 break;
9388 case OMP_TEAMS:
9389 error_at (OMP_CLAUSE_LOCATION (c),
9390 "%<inscan%> %<reduction%> clause on "
9391 "%qs construct", "teams");
9392 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9393 break;
9394 case OMP_TASKLOOP:
9395 error_at (OMP_CLAUSE_LOCATION (c),
9396 "%<inscan%> %<reduction%> clause on "
9397 "%qs construct", "taskloop");
9398 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9399 break;
9400 case OMP_SCOPE:
9401 error_at (OMP_CLAUSE_LOCATION (c),
9402 "%<inscan%> %<reduction%> clause on "
9403 "%qs construct", "scope");
9404 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
9405 break;
9406 default:
9407 break;
9409 /* FALLTHRU */
9410 case OMP_CLAUSE_IN_REDUCTION:
9411 case OMP_CLAUSE_TASK_REDUCTION:
9412 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
9413 /* OpenACC permits reductions on private variables. */
9414 if (!(region_type & ORT_ACC)
9415 /* taskgroup is actually not a worksharing region. */
9416 && code != OMP_TASKGROUP)
9417 check_non_private = omp_clause_code_name[OMP_CLAUSE_CODE (c)];
9418 decl = OMP_CLAUSE_DECL (c);
9419 if (TREE_CODE (decl) == MEM_REF)
9421 tree type = TREE_TYPE (decl);
9422 bool saved_into_ssa = gimplify_ctxp->into_ssa;
9423 gimplify_ctxp->into_ssa = false;
9424 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
9425 NULL, is_gimple_val, fb_rvalue, false)
9426 == GS_ERROR)
9428 gimplify_ctxp->into_ssa = saved_into_ssa;
9429 remove = true;
9430 break;
9432 gimplify_ctxp->into_ssa = saved_into_ssa;
9433 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
9434 if (DECL_P (v))
9436 omp_firstprivatize_variable (ctx, v);
9437 omp_notice_variable (ctx, v, true);
9439 decl = TREE_OPERAND (decl, 0);
9440 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
9442 gimplify_ctxp->into_ssa = false;
9443 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
9444 NULL, is_gimple_val, fb_rvalue, false)
9445 == GS_ERROR)
9447 gimplify_ctxp->into_ssa = saved_into_ssa;
9448 remove = true;
9449 break;
9451 gimplify_ctxp->into_ssa = saved_into_ssa;
9452 v = TREE_OPERAND (decl, 1);
9453 if (DECL_P (v))
9455 omp_firstprivatize_variable (ctx, v);
9456 omp_notice_variable (ctx, v, true);
9458 decl = TREE_OPERAND (decl, 0);
9460 if (TREE_CODE (decl) == ADDR_EXPR
9461 || TREE_CODE (decl) == INDIRECT_REF)
9462 decl = TREE_OPERAND (decl, 0);
9464 goto do_add_decl;
9465 case OMP_CLAUSE_LINEAR:
9466 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
9467 is_gimple_val, fb_rvalue) == GS_ERROR)
9469 remove = true;
9470 break;
9472 else
9474 if (code == OMP_SIMD
9475 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
9477 struct gimplify_omp_ctx *octx = outer_ctx;
9478 if (octx
9479 && octx->region_type == ORT_WORKSHARE
9480 && octx->combined_loop
9481 && !octx->distribute)
9483 if (octx->outer_context
9484 && (octx->outer_context->region_type
9485 == ORT_COMBINED_PARALLEL))
9486 octx = octx->outer_context->outer_context;
9487 else
9488 octx = octx->outer_context;
9490 if (octx
9491 && octx->region_type == ORT_WORKSHARE
9492 && octx->combined_loop
9493 && octx->distribute)
9495 error_at (OMP_CLAUSE_LOCATION (c),
9496 "%<linear%> clause for variable other than "
9497 "loop iterator specified on construct "
9498 "combined with %<distribute%>");
9499 remove = true;
9500 break;
9503 /* For combined #pragma omp parallel for simd, need to put
9504 lastprivate and perhaps firstprivate too on the
9505 parallel. Similarly for #pragma omp for simd. */
9506 struct gimplify_omp_ctx *octx = outer_ctx;
9507 bool taskloop_seen = false;
9508 decl = NULL_TREE;
9511 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9512 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9513 break;
9514 decl = OMP_CLAUSE_DECL (c);
9515 if (error_operand_p (decl))
9517 decl = NULL_TREE;
9518 break;
9520 flags = GOVD_SEEN;
9521 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
9522 flags |= GOVD_FIRSTPRIVATE;
9523 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9524 flags |= GOVD_LASTPRIVATE;
9525 if (octx
9526 && octx->region_type == ORT_WORKSHARE
9527 && octx->combined_loop)
9529 if (octx->outer_context
9530 && (octx->outer_context->region_type
9531 == ORT_COMBINED_PARALLEL))
9532 octx = octx->outer_context;
9533 else if (omp_check_private (octx, decl, false))
9534 break;
9536 else if (octx
9537 && (octx->region_type & ORT_TASK) != 0
9538 && octx->combined_loop)
9539 taskloop_seen = true;
9540 else if (octx
9541 && octx->region_type == ORT_COMBINED_PARALLEL
9542 && ((ctx->region_type == ORT_WORKSHARE
9543 && octx == outer_ctx)
9544 || taskloop_seen))
9545 flags = GOVD_SEEN | GOVD_SHARED;
9546 else if (octx
9547 && ((octx->region_type & ORT_COMBINED_TEAMS)
9548 == ORT_COMBINED_TEAMS))
9549 flags = GOVD_SEEN | GOVD_SHARED;
9550 else if (octx
9551 && octx->region_type == ORT_COMBINED_TARGET)
9553 if (flags & GOVD_LASTPRIVATE)
9554 flags = GOVD_SEEN | GOVD_MAP;
9556 else
9557 break;
9558 splay_tree_node on
9559 = splay_tree_lookup (octx->variables,
9560 (splay_tree_key) decl);
9561 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
9563 octx = NULL;
9564 break;
9566 omp_add_variable (octx, decl, flags);
9567 if (octx->outer_context == NULL)
9568 break;
9569 octx = octx->outer_context;
9571 while (1);
9572 if (octx
9573 && decl
9574 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9575 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
9576 omp_notice_variable (octx, decl, true);
9578 flags = GOVD_LINEAR | GOVD_EXPLICIT;
9579 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9580 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9582 notice_outer = false;
9583 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9585 goto do_add;
9587 case OMP_CLAUSE_MAP:
9588 decl = OMP_CLAUSE_DECL (c);
9589 if (error_operand_p (decl))
9590 remove = true;
9591 switch (code)
9593 case OMP_TARGET:
9594 break;
9595 case OACC_DATA:
9596 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
9597 break;
9598 /* FALLTHRU */
9599 case OMP_TARGET_DATA:
9600 case OMP_TARGET_ENTER_DATA:
9601 case OMP_TARGET_EXIT_DATA:
9602 case OACC_ENTER_DATA:
9603 case OACC_EXIT_DATA:
9604 case OACC_HOST_DATA:
9605 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9606 || (OMP_CLAUSE_MAP_KIND (c)
9607 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
9608 /* For target {,enter ,exit }data only the array slice is
9609 mapped, but not the pointer to it. */
9610 remove = true;
9611 break;
9612 default:
9613 break;
9615 /* For Fortran, not only the pointer to the data is mapped but also
9616 the address of the pointer, the array descriptor etc.; for
9617 'exit data' - and in particular for 'delete:' - having an 'alloc:'
9618 does not make sense. Likewise, for 'update' only transferring the
9619 data itself is needed as the rest has been handled in previous
9620 directives. However, for 'exit data', the array descriptor needs
9621 to be delete; hence, we turn the MAP_TO_PSET into a MAP_DELETE.
9623 NOTE: Generally, it is not safe to perform "enter data" operations
9624 on arrays where the data *or the descriptor* may go out of scope
9625 before a corresponding "exit data" operation -- and such a
9626 descriptor may be synthesized temporarily, e.g. to pass an
9627 explicit-shape array to a function expecting an assumed-shape
9628 argument. Performing "enter data" inside the called function
9629 would thus be problematic. */
9630 if (code == OMP_TARGET_EXIT_DATA
9631 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
9632 OMP_CLAUSE_SET_MAP_KIND (c, OMP_CLAUSE_MAP_KIND (*prev_list_p)
9633 == GOMP_MAP_DELETE
9634 ? GOMP_MAP_DELETE : GOMP_MAP_RELEASE);
9635 else if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
9636 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
9637 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
9638 remove = true;
9640 if (remove)
9641 break;
9642 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
9644 struct gimplify_omp_ctx *octx;
9645 for (octx = outer_ctx; octx; octx = octx->outer_context)
9647 if (octx->region_type != ORT_ACC_HOST_DATA)
9648 break;
9649 splay_tree_node n2
9650 = splay_tree_lookup (octx->variables,
9651 (splay_tree_key) decl);
9652 if (n2)
9653 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
9654 "declared in enclosing %<host_data%> region",
9655 DECL_NAME (decl));
9658 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9659 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9660 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9661 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9662 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
9664 remove = true;
9665 break;
9667 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9668 || (OMP_CLAUSE_MAP_KIND (c)
9669 == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9670 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9671 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
9673 OMP_CLAUSE_SIZE (c)
9674 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
9675 false);
9676 if ((region_type & ORT_TARGET) != 0)
9677 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
9678 GOVD_FIRSTPRIVATE | GOVD_SEEN);
9681 if (TREE_CODE (decl) == TARGET_EXPR)
9683 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
9684 is_gimple_lvalue, fb_lvalue)
9685 == GS_ERROR)
9686 remove = true;
9688 else if (!DECL_P (decl))
9690 tree d = decl, *pd;
9691 if (TREE_CODE (d) == ARRAY_REF)
9693 while (TREE_CODE (d) == ARRAY_REF)
9694 d = TREE_OPERAND (d, 0);
9695 if (TREE_CODE (d) == COMPONENT_REF
9696 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
9697 decl = d;
9699 pd = &OMP_CLAUSE_DECL (c);
9700 if (d == decl
9701 && TREE_CODE (decl) == INDIRECT_REF
9702 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
9703 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9704 == REFERENCE_TYPE)
9705 && (OMP_CLAUSE_MAP_KIND (c)
9706 != GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION))
9708 pd = &TREE_OPERAND (decl, 0);
9709 decl = TREE_OPERAND (decl, 0);
9711 bool indir_p = false;
9712 bool component_ref_p = false;
9713 tree indir_base = NULL_TREE;
9714 tree orig_decl = decl;
9715 tree decl_ref = NULL_TREE;
9716 if ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA)) != 0
9717 && TREE_CODE (*pd) == COMPONENT_REF
9718 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH
9719 && code != OACC_UPDATE)
9721 while (TREE_CODE (decl) == COMPONENT_REF)
9723 decl = TREE_OPERAND (decl, 0);
9724 component_ref_p = true;
9725 if (((TREE_CODE (decl) == MEM_REF
9726 && integer_zerop (TREE_OPERAND (decl, 1)))
9727 || INDIRECT_REF_P (decl))
9728 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9729 == POINTER_TYPE))
9731 indir_p = true;
9732 indir_base = decl;
9733 decl = TREE_OPERAND (decl, 0);
9734 STRIP_NOPS (decl);
9736 if (TREE_CODE (decl) == INDIRECT_REF
9737 && DECL_P (TREE_OPERAND (decl, 0))
9738 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9739 == REFERENCE_TYPE))
9741 decl_ref = decl;
9742 decl = TREE_OPERAND (decl, 0);
9746 else if (TREE_CODE (decl) == COMPONENT_REF
9747 && (OMP_CLAUSE_MAP_KIND (c)
9748 != GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION))
9750 component_ref_p = true;
9751 while (TREE_CODE (decl) == COMPONENT_REF)
9752 decl = TREE_OPERAND (decl, 0);
9753 if (TREE_CODE (decl) == INDIRECT_REF
9754 && DECL_P (TREE_OPERAND (decl, 0))
9755 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9756 == REFERENCE_TYPE))
9757 decl = TREE_OPERAND (decl, 0);
9759 if (decl != orig_decl && DECL_P (decl) && indir_p
9760 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
9761 || (decl_ref
9762 && TREE_CODE (TREE_TYPE (decl_ref)) == POINTER_TYPE)))
9764 gomp_map_kind k
9765 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9766 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9767 /* We have a dereference of a struct member. Make this an
9768 attach/detach operation, and ensure the base pointer is
9769 mapped as a FIRSTPRIVATE_POINTER. */
9770 OMP_CLAUSE_SET_MAP_KIND (c, k);
9771 flags = GOVD_MAP | GOVD_SEEN | GOVD_EXPLICIT;
9772 tree next_clause = OMP_CLAUSE_CHAIN (c);
9773 if (k == GOMP_MAP_ATTACH
9774 && code != OACC_ENTER_DATA
9775 && code != OMP_TARGET_ENTER_DATA
9776 && (!next_clause
9777 || (OMP_CLAUSE_CODE (next_clause) != OMP_CLAUSE_MAP)
9778 || (OMP_CLAUSE_MAP_KIND (next_clause)
9779 != GOMP_MAP_POINTER)
9780 || OMP_CLAUSE_DECL (next_clause) != decl)
9781 && (!struct_deref_set
9782 || !struct_deref_set->contains (decl))
9783 && (!struct_map_to_clause
9784 || !struct_map_to_clause->get (indir_base)))
9786 if (!struct_deref_set)
9787 struct_deref_set = new hash_set<tree> ();
9788 /* As well as the attach, we also need a
9789 FIRSTPRIVATE_POINTER clause to properly map the
9790 pointer to the struct base. */
9791 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9792 OMP_CLAUSE_MAP);
9793 OMP_CLAUSE_SET_MAP_KIND (c2, GOMP_MAP_ALLOC);
9794 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (c2)
9795 = 1;
9796 tree charptr_zero
9797 = build_int_cst (build_pointer_type (char_type_node),
9799 OMP_CLAUSE_DECL (c2)
9800 = build2 (MEM_REF, char_type_node,
9801 decl_ref ? decl_ref : decl, charptr_zero);
9802 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9803 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9804 OMP_CLAUSE_MAP);
9805 OMP_CLAUSE_SET_MAP_KIND (c3,
9806 GOMP_MAP_FIRSTPRIVATE_POINTER);
9807 OMP_CLAUSE_DECL (c3) = decl;
9808 OMP_CLAUSE_SIZE (c3) = size_zero_node;
9809 tree mapgrp = *prev_list_p;
9810 *prev_list_p = c2;
9811 OMP_CLAUSE_CHAIN (c3) = mapgrp;
9812 OMP_CLAUSE_CHAIN (c2) = c3;
9814 struct_deref_set->add (decl);
9816 goto do_add_decl;
9818 /* An "attach/detach" operation on an update directive should
9819 behave as a GOMP_MAP_ALWAYS_POINTER. Beware that
9820 unlike attach or detach map kinds, GOMP_MAP_ALWAYS_POINTER
9821 depends on the previous mapping. */
9822 if (code == OACC_UPDATE
9823 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9824 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_ALWAYS_POINTER);
9825 if ((DECL_P (decl)
9826 || (component_ref_p
9827 && (INDIRECT_REF_P (decl)
9828 || TREE_CODE (decl) == MEM_REF
9829 || TREE_CODE (decl) == ARRAY_REF)))
9830 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9831 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH
9832 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_DETACH
9833 && code != OACC_UPDATE
9834 && code != OMP_TARGET_UPDATE)
9836 if (error_operand_p (decl))
9838 remove = true;
9839 break;
9842 tree stype = TREE_TYPE (decl);
9843 if (TREE_CODE (stype) == REFERENCE_TYPE)
9844 stype = TREE_TYPE (stype);
9845 if (TYPE_SIZE_UNIT (stype) == NULL
9846 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
9848 error_at (OMP_CLAUSE_LOCATION (c),
9849 "mapping field %qE of variable length "
9850 "structure", OMP_CLAUSE_DECL (c));
9851 remove = true;
9852 break;
9855 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER
9856 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9858 /* Error recovery. */
9859 if (prev_list_p == NULL)
9861 remove = true;
9862 break;
9865 /* The below prev_list_p based error recovery code is
9866 currently no longer valid for OpenMP. */
9867 if (code != OMP_TARGET
9868 && code != OMP_TARGET_DATA
9869 && code != OMP_TARGET_UPDATE
9870 && code != OMP_TARGET_ENTER_DATA
9871 && code != OMP_TARGET_EXIT_DATA
9872 && OMP_CLAUSE_CHAIN (*prev_list_p) != c)
9874 tree ch = OMP_CLAUSE_CHAIN (*prev_list_p);
9875 if (ch == NULL_TREE || OMP_CLAUSE_CHAIN (ch) != c)
9877 remove = true;
9878 break;
9883 poly_offset_int offset1;
9884 poly_int64 bitpos1;
9885 tree tree_offset1;
9886 tree base_ref;
9888 tree base
9889 = extract_base_bit_offset (OMP_CLAUSE_DECL (c), &base_ref,
9890 &bitpos1, &offset1,
9891 &tree_offset1);
9893 bool do_map_struct = (base == decl && !tree_offset1);
9895 splay_tree_node n
9896 = (DECL_P (decl)
9897 ? splay_tree_lookup (ctx->variables,
9898 (splay_tree_key) decl)
9899 : NULL);
9900 bool ptr = (OMP_CLAUSE_MAP_KIND (c)
9901 == GOMP_MAP_ALWAYS_POINTER);
9902 bool attach_detach = (OMP_CLAUSE_MAP_KIND (c)
9903 == GOMP_MAP_ATTACH_DETACH);
9904 bool attach = OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
9905 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DETACH;
9906 bool has_attachments = false;
9907 /* For OpenACC, pointers in structs should trigger an
9908 attach action. */
9909 if (attach_detach
9910 && ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA))
9911 || code == OMP_TARGET_ENTER_DATA
9912 || code == OMP_TARGET_EXIT_DATA))
9915 /* Turn a GOMP_MAP_ATTACH_DETACH clause into a
9916 GOMP_MAP_ATTACH or GOMP_MAP_DETACH clause after we
9917 have detected a case that needs a GOMP_MAP_STRUCT
9918 mapping added. */
9919 gomp_map_kind k
9920 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9921 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9922 OMP_CLAUSE_SET_MAP_KIND (c, k);
9923 has_attachments = true;
9926 /* We currently don't handle non-constant offset accesses wrt to
9927 GOMP_MAP_STRUCT elements. */
9928 if (!do_map_struct)
9929 goto skip_map_struct;
9931 /* Nor for attach_detach for OpenMP. */
9932 if ((code == OMP_TARGET
9933 || code == OMP_TARGET_DATA
9934 || code == OMP_TARGET_UPDATE
9935 || code == OMP_TARGET_ENTER_DATA
9936 || code == OMP_TARGET_EXIT_DATA)
9937 && attach_detach)
9939 if (DECL_P (decl))
9941 if (struct_seen_clause == NULL)
9942 struct_seen_clause
9943 = new hash_map<tree_operand_hash, tree *>;
9944 if (!struct_seen_clause->get (decl))
9945 struct_seen_clause->put (decl, list_p);
9948 goto skip_map_struct;
9951 if ((DECL_P (decl)
9952 && (n == NULL || (n->value & GOVD_MAP) == 0))
9953 || (!DECL_P (decl)
9954 && (!struct_map_to_clause
9955 || struct_map_to_clause->get (decl) == NULL)))
9957 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9958 OMP_CLAUSE_MAP);
9959 gomp_map_kind k = attach ? GOMP_MAP_FORCE_PRESENT
9960 : GOMP_MAP_STRUCT;
9962 OMP_CLAUSE_SET_MAP_KIND (l, k);
9963 if (base_ref)
9964 OMP_CLAUSE_DECL (l) = unshare_expr (base_ref);
9965 else
9967 OMP_CLAUSE_DECL (l) = unshare_expr (decl);
9968 if (!DECL_P (OMP_CLAUSE_DECL (l))
9969 && (gimplify_expr (&OMP_CLAUSE_DECL (l),
9970 pre_p, NULL, is_gimple_lvalue,
9971 fb_lvalue)
9972 == GS_ERROR))
9974 remove = true;
9975 break;
9978 OMP_CLAUSE_SIZE (l)
9979 = (!attach
9980 ? size_int (1)
9981 : DECL_P (OMP_CLAUSE_DECL (l))
9982 ? DECL_SIZE_UNIT (OMP_CLAUSE_DECL (l))
9983 : TYPE_SIZE_UNIT (TREE_TYPE (OMP_CLAUSE_DECL (l))));
9984 if (struct_map_to_clause == NULL)
9985 struct_map_to_clause
9986 = new hash_map<tree_operand_hash, tree>;
9987 struct_map_to_clause->put (decl, l);
9988 if (ptr || attach_detach)
9990 tree **sc = (struct_seen_clause
9991 ? struct_seen_clause->get (decl)
9992 : NULL);
9993 tree *insert_node_pos = sc ? *sc : prev_list_p;
9995 insert_struct_comp_map (code, c, l, *insert_node_pos,
9996 NULL);
9997 *insert_node_pos = l;
9998 prev_list_p = NULL;
10000 else
10002 OMP_CLAUSE_CHAIN (l) = c;
10003 *list_p = l;
10004 list_p = &OMP_CLAUSE_CHAIN (l);
10006 if (base_ref && code == OMP_TARGET)
10008 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10009 OMP_CLAUSE_MAP);
10010 enum gomp_map_kind mkind
10011 = GOMP_MAP_FIRSTPRIVATE_REFERENCE;
10012 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
10013 OMP_CLAUSE_DECL (c2) = decl;
10014 OMP_CLAUSE_SIZE (c2) = size_zero_node;
10015 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
10016 OMP_CLAUSE_CHAIN (l) = c2;
10018 flags = GOVD_MAP | GOVD_EXPLICIT;
10019 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
10020 || ptr
10021 || attach_detach)
10022 flags |= GOVD_SEEN;
10023 if (has_attachments)
10024 flags |= GOVD_MAP_HAS_ATTACHMENTS;
10026 /* If this is a *pointer-to-struct expression, make sure a
10027 firstprivate map of the base-pointer exists. */
10028 if (component_ref_p
10029 && ((TREE_CODE (decl) == MEM_REF
10030 && integer_zerop (TREE_OPERAND (decl, 1)))
10031 || INDIRECT_REF_P (decl))
10032 && DECL_P (TREE_OPERAND (decl, 0))
10033 && !splay_tree_lookup (ctx->variables,
10034 ((splay_tree_key)
10035 TREE_OPERAND (decl, 0))))
10037 decl = TREE_OPERAND (decl, 0);
10038 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10039 OMP_CLAUSE_MAP);
10040 enum gomp_map_kind mkind
10041 = GOMP_MAP_FIRSTPRIVATE_POINTER;
10042 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
10043 OMP_CLAUSE_DECL (c2) = decl;
10044 OMP_CLAUSE_SIZE (c2) = size_zero_node;
10045 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (c);
10046 OMP_CLAUSE_CHAIN (c) = c2;
10049 if (DECL_P (decl))
10050 goto do_add_decl;
10052 else if (struct_map_to_clause)
10054 tree *osc = struct_map_to_clause->get (decl);
10055 tree *sc = NULL, *scp = NULL;
10056 if (n != NULL
10057 && (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
10058 || ptr
10059 || attach_detach))
10060 n->value |= GOVD_SEEN;
10061 sc = &OMP_CLAUSE_CHAIN (*osc);
10062 if (*sc != c
10063 && (OMP_CLAUSE_MAP_KIND (*sc)
10064 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10065 sc = &OMP_CLAUSE_CHAIN (*sc);
10066 /* Here "prev_list_p" is the end of the inserted
10067 alloc/release nodes after the struct node, OSC. */
10068 for (; *sc != c; sc = &OMP_CLAUSE_CHAIN (*sc))
10069 if ((ptr || attach_detach) && sc == prev_list_p)
10070 break;
10071 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc))
10072 != COMPONENT_REF
10073 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
10074 != INDIRECT_REF)
10075 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
10076 != ARRAY_REF))
10077 break;
10078 else
10080 tree sc_decl = OMP_CLAUSE_DECL (*sc);
10081 poly_offset_int offsetn;
10082 poly_int64 bitposn;
10083 tree tree_offsetn;
10084 tree base
10085 = extract_base_bit_offset (sc_decl, NULL,
10086 &bitposn, &offsetn,
10087 &tree_offsetn);
10088 if (base != decl)
10089 break;
10090 if (scp)
10091 continue;
10092 if ((region_type & ORT_ACC) != 0)
10094 /* This duplicate checking code is currently only
10095 enabled for OpenACC. */
10096 tree d1 = OMP_CLAUSE_DECL (*sc);
10097 tree d2 = OMP_CLAUSE_DECL (c);
10098 while (TREE_CODE (d1) == ARRAY_REF)
10099 d1 = TREE_OPERAND (d1, 0);
10100 while (TREE_CODE (d2) == ARRAY_REF)
10101 d2 = TREE_OPERAND (d2, 0);
10102 if (TREE_CODE (d1) == INDIRECT_REF)
10103 d1 = TREE_OPERAND (d1, 0);
10104 if (TREE_CODE (d2) == INDIRECT_REF)
10105 d2 = TREE_OPERAND (d2, 0);
10106 while (TREE_CODE (d1) == COMPONENT_REF)
10107 if (TREE_CODE (d2) == COMPONENT_REF
10108 && TREE_OPERAND (d1, 1)
10109 == TREE_OPERAND (d2, 1))
10111 d1 = TREE_OPERAND (d1, 0);
10112 d2 = TREE_OPERAND (d2, 0);
10114 else
10115 break;
10116 if (d1 == d2)
10118 error_at (OMP_CLAUSE_LOCATION (c),
10119 "%qE appears more than once in map "
10120 "clauses", OMP_CLAUSE_DECL (c));
10121 remove = true;
10122 break;
10125 if (maybe_lt (offset1, offsetn)
10126 || (known_eq (offset1, offsetn)
10127 && maybe_lt (bitpos1, bitposn)))
10129 if (ptr || attach_detach)
10130 scp = sc;
10131 else
10132 break;
10135 if (remove)
10136 break;
10137 if (!attach)
10138 OMP_CLAUSE_SIZE (*osc)
10139 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc),
10140 size_one_node);
10141 if (ptr || attach_detach)
10143 tree cl = insert_struct_comp_map (code, c, NULL,
10144 *prev_list_p, scp);
10145 if (sc == prev_list_p)
10147 *sc = cl;
10148 prev_list_p = NULL;
10150 else
10152 *prev_list_p = OMP_CLAUSE_CHAIN (c);
10153 list_p = prev_list_p;
10154 prev_list_p = NULL;
10155 OMP_CLAUSE_CHAIN (c) = *sc;
10156 *sc = cl;
10157 continue;
10160 else if (*sc != c)
10162 if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue,
10163 fb_lvalue)
10164 == GS_ERROR)
10166 remove = true;
10167 break;
10169 *list_p = OMP_CLAUSE_CHAIN (c);
10170 OMP_CLAUSE_CHAIN (c) = *sc;
10171 *sc = c;
10172 continue;
10175 skip_map_struct:
10178 else if ((code == OACC_ENTER_DATA
10179 || code == OACC_EXIT_DATA
10180 || code == OACC_DATA
10181 || code == OACC_PARALLEL
10182 || code == OACC_KERNELS
10183 || code == OACC_SERIAL
10184 || code == OMP_TARGET_ENTER_DATA
10185 || code == OMP_TARGET_EXIT_DATA)
10186 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
10188 gomp_map_kind k = ((code == OACC_EXIT_DATA
10189 || code == OMP_TARGET_EXIT_DATA)
10190 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
10191 OMP_CLAUSE_SET_MAP_KIND (c, k);
10194 if (code == OMP_TARGET && OMP_CLAUSE_MAP_IN_REDUCTION (c))
10196 /* Don't gimplify *pd fully at this point, as the base
10197 will need to be adjusted during omp lowering. */
10198 auto_vec<tree, 10> expr_stack;
10199 tree *p = pd;
10200 while (handled_component_p (*p)
10201 || TREE_CODE (*p) == INDIRECT_REF
10202 || TREE_CODE (*p) == ADDR_EXPR
10203 || TREE_CODE (*p) == MEM_REF
10204 || TREE_CODE (*p) == NON_LVALUE_EXPR)
10206 expr_stack.safe_push (*p);
10207 p = &TREE_OPERAND (*p, 0);
10209 for (int i = expr_stack.length () - 1; i >= 0; i--)
10211 tree t = expr_stack[i];
10212 if (TREE_CODE (t) == ARRAY_REF
10213 || TREE_CODE (t) == ARRAY_RANGE_REF)
10215 if (TREE_OPERAND (t, 2) == NULL_TREE)
10217 tree low = unshare_expr (array_ref_low_bound (t));
10218 if (!is_gimple_min_invariant (low))
10220 TREE_OPERAND (t, 2) = low;
10221 if (gimplify_expr (&TREE_OPERAND (t, 2),
10222 pre_p, NULL,
10223 is_gimple_reg,
10224 fb_rvalue) == GS_ERROR)
10225 remove = true;
10228 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
10229 NULL, is_gimple_reg,
10230 fb_rvalue) == GS_ERROR)
10231 remove = true;
10232 if (TREE_OPERAND (t, 3) == NULL_TREE)
10234 tree elmt_size = array_ref_element_size (t);
10235 if (!is_gimple_min_invariant (elmt_size))
10237 elmt_size = unshare_expr (elmt_size);
10238 tree elmt_type
10239 = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t,
10240 0)));
10241 tree factor
10242 = size_int (TYPE_ALIGN_UNIT (elmt_type));
10243 elmt_size
10244 = size_binop (EXACT_DIV_EXPR, elmt_size,
10245 factor);
10246 TREE_OPERAND (t, 3) = elmt_size;
10247 if (gimplify_expr (&TREE_OPERAND (t, 3),
10248 pre_p, NULL,
10249 is_gimple_reg,
10250 fb_rvalue) == GS_ERROR)
10251 remove = true;
10254 else if (gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
10255 NULL, is_gimple_reg,
10256 fb_rvalue) == GS_ERROR)
10257 remove = true;
10259 else if (TREE_CODE (t) == COMPONENT_REF)
10261 if (TREE_OPERAND (t, 2) == NULL_TREE)
10263 tree offset = component_ref_field_offset (t);
10264 if (!is_gimple_min_invariant (offset))
10266 offset = unshare_expr (offset);
10267 tree field = TREE_OPERAND (t, 1);
10268 tree factor
10269 = size_int (DECL_OFFSET_ALIGN (field)
10270 / BITS_PER_UNIT);
10271 offset = size_binop (EXACT_DIV_EXPR, offset,
10272 factor);
10273 TREE_OPERAND (t, 2) = offset;
10274 if (gimplify_expr (&TREE_OPERAND (t, 2),
10275 pre_p, NULL,
10276 is_gimple_reg,
10277 fb_rvalue) == GS_ERROR)
10278 remove = true;
10281 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
10282 NULL, is_gimple_reg,
10283 fb_rvalue) == GS_ERROR)
10284 remove = true;
10287 for (; expr_stack.length () > 0; )
10289 tree t = expr_stack.pop ();
10291 if (TREE_CODE (t) == ARRAY_REF
10292 || TREE_CODE (t) == ARRAY_RANGE_REF)
10294 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1))
10295 && gimplify_expr (&TREE_OPERAND (t, 1), pre_p,
10296 NULL, is_gimple_val,
10297 fb_rvalue) == GS_ERROR)
10298 remove = true;
10302 else if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue,
10303 fb_lvalue) == GS_ERROR)
10305 remove = true;
10306 break;
10309 /* If this was of the form map(*pointer_to_struct), then the
10310 'pointer_to_struct' DECL should be considered deref'ed. */
10311 if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALLOC
10312 || GOMP_MAP_COPY_TO_P (OMP_CLAUSE_MAP_KIND (c))
10313 || GOMP_MAP_COPY_FROM_P (OMP_CLAUSE_MAP_KIND (c)))
10314 && INDIRECT_REF_P (orig_decl)
10315 && DECL_P (TREE_OPERAND (orig_decl, 0))
10316 && TREE_CODE (TREE_TYPE (orig_decl)) == RECORD_TYPE)
10318 tree ptr = TREE_OPERAND (orig_decl, 0);
10319 if (!struct_deref_set || !struct_deref_set->contains (ptr))
10321 if (!struct_deref_set)
10322 struct_deref_set = new hash_set<tree> ();
10323 struct_deref_set->add (ptr);
10327 if (!remove
10328 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ALWAYS_POINTER
10329 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH_DETACH
10330 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
10331 && OMP_CLAUSE_CHAIN (c)
10332 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c)) == OMP_CLAUSE_MAP
10333 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
10334 == GOMP_MAP_ALWAYS_POINTER)
10335 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
10336 == GOMP_MAP_ATTACH_DETACH)
10337 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
10338 == GOMP_MAP_TO_PSET)))
10339 prev_list_p = list_p;
10341 break;
10343 else
10345 /* DECL_P (decl) == true */
10346 tree *sc;
10347 if (struct_map_to_clause
10348 && (sc = struct_map_to_clause->get (decl)) != NULL
10349 && OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_STRUCT
10350 && decl == OMP_CLAUSE_DECL (*sc))
10352 /* We have found a map of the whole structure after a
10353 leading GOMP_MAP_STRUCT has been created, so refill the
10354 leading clause into a map of the whole structure
10355 variable, and remove the current one.
10356 TODO: we should be able to remove some maps of the
10357 following structure element maps if they are of
10358 compatible TO/FROM/ALLOC type. */
10359 OMP_CLAUSE_SET_MAP_KIND (*sc, OMP_CLAUSE_MAP_KIND (c));
10360 OMP_CLAUSE_SIZE (*sc) = unshare_expr (OMP_CLAUSE_SIZE (c));
10361 remove = true;
10362 break;
10365 flags = GOVD_MAP | GOVD_EXPLICIT;
10366 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
10367 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM)
10368 flags |= GOVD_MAP_ALWAYS_TO;
10370 if ((code == OMP_TARGET
10371 || code == OMP_TARGET_DATA
10372 || code == OMP_TARGET_ENTER_DATA
10373 || code == OMP_TARGET_EXIT_DATA)
10374 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
10376 for (struct gimplify_omp_ctx *octx = outer_ctx; octx;
10377 octx = octx->outer_context)
10379 splay_tree_node n
10380 = splay_tree_lookup (octx->variables,
10381 (splay_tree_key) OMP_CLAUSE_DECL (c));
10382 /* If this is contained in an outer OpenMP region as a
10383 firstprivate value, remove the attach/detach. */
10384 if (n && (n->value & GOVD_FIRSTPRIVATE))
10386 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FIRSTPRIVATE_POINTER);
10387 goto do_add;
10391 enum gomp_map_kind map_kind = (code == OMP_TARGET_EXIT_DATA
10392 ? GOMP_MAP_DETACH
10393 : GOMP_MAP_ATTACH);
10394 OMP_CLAUSE_SET_MAP_KIND (c, map_kind);
10397 goto do_add;
10399 case OMP_CLAUSE_AFFINITY:
10400 gimplify_omp_affinity (list_p, pre_p);
10401 remove = true;
10402 break;
10403 case OMP_CLAUSE_DOACROSS:
10404 if (OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SINK)
10406 tree deps = OMP_CLAUSE_DECL (c);
10407 while (deps && TREE_CODE (deps) == TREE_LIST)
10409 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
10410 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
10411 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
10412 pre_p, NULL, is_gimple_val, fb_rvalue);
10413 deps = TREE_CHAIN (deps);
10416 else
10417 gcc_assert (OMP_CLAUSE_DOACROSS_KIND (c)
10418 == OMP_CLAUSE_DOACROSS_SOURCE);
10419 break;
10420 case OMP_CLAUSE_DEPEND:
10421 if (handled_depend_iterators == -1)
10422 handled_depend_iterators = gimplify_omp_depend (list_p, pre_p);
10423 if (handled_depend_iterators)
10425 if (handled_depend_iterators == 2)
10426 remove = true;
10427 break;
10429 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
10431 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
10432 NULL, is_gimple_val, fb_rvalue);
10433 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
10435 if (error_operand_p (OMP_CLAUSE_DECL (c)))
10437 remove = true;
10438 break;
10440 if (OMP_CLAUSE_DECL (c) != null_pointer_node)
10442 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
10443 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
10444 is_gimple_val, fb_rvalue) == GS_ERROR)
10446 remove = true;
10447 break;
10450 if (code == OMP_TASK)
10451 ctx->has_depend = true;
10452 break;
10454 case OMP_CLAUSE_TO:
10455 case OMP_CLAUSE_FROM:
10456 case OMP_CLAUSE__CACHE_:
10457 decl = OMP_CLAUSE_DECL (c);
10458 if (error_operand_p (decl))
10460 remove = true;
10461 break;
10463 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
10464 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
10465 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
10466 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
10467 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
10469 remove = true;
10470 break;
10472 if (!DECL_P (decl))
10474 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
10475 NULL, is_gimple_lvalue, fb_lvalue)
10476 == GS_ERROR)
10478 remove = true;
10479 break;
10481 break;
10483 goto do_notice;
10485 case OMP_CLAUSE_USE_DEVICE_PTR:
10486 case OMP_CLAUSE_USE_DEVICE_ADDR:
10487 flags = GOVD_EXPLICIT;
10488 goto do_add;
10490 case OMP_CLAUSE_HAS_DEVICE_ADDR:
10491 decl = OMP_CLAUSE_DECL (c);
10492 while (TREE_CODE (decl) == INDIRECT_REF
10493 || TREE_CODE (decl) == ARRAY_REF)
10494 decl = TREE_OPERAND (decl, 0);
10495 flags = GOVD_EXPLICIT;
10496 goto do_add_decl;
10498 case OMP_CLAUSE_IS_DEVICE_PTR:
10499 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
10500 goto do_add;
10502 do_add:
10503 decl = OMP_CLAUSE_DECL (c);
10504 do_add_decl:
10505 if (error_operand_p (decl))
10507 remove = true;
10508 break;
10510 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
10512 tree t = omp_member_access_dummy_var (decl);
10513 if (t)
10515 tree v = DECL_VALUE_EXPR (decl);
10516 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
10517 if (outer_ctx)
10518 omp_notice_variable (outer_ctx, t, true);
10521 if (code == OACC_DATA
10522 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
10523 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
10524 flags |= GOVD_MAP_0LEN_ARRAY;
10525 omp_add_variable (ctx, decl, flags);
10526 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10527 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_IN_REDUCTION
10528 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_TASK_REDUCTION)
10529 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
10531 struct gimplify_omp_ctx *pctx
10532 = code == OMP_TARGET ? outer_ctx : ctx;
10533 if (pctx)
10534 omp_add_variable (pctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
10535 GOVD_LOCAL | GOVD_SEEN);
10536 if (pctx
10537 && OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
10538 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
10539 find_decl_expr,
10540 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
10541 NULL) == NULL_TREE)
10542 omp_add_variable (pctx,
10543 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
10544 GOVD_LOCAL | GOVD_SEEN);
10545 gimplify_omp_ctxp = pctx;
10546 push_gimplify_context ();
10548 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
10549 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
10551 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
10552 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
10553 pop_gimplify_context
10554 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
10555 push_gimplify_context ();
10556 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
10557 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
10558 pop_gimplify_context
10559 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
10560 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
10561 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
10563 gimplify_omp_ctxp = outer_ctx;
10565 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10566 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
10568 gimplify_omp_ctxp = ctx;
10569 push_gimplify_context ();
10570 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
10572 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
10573 NULL, NULL);
10574 TREE_SIDE_EFFECTS (bind) = 1;
10575 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
10576 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
10578 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
10579 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
10580 pop_gimplify_context
10581 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
10582 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
10584 gimplify_omp_ctxp = outer_ctx;
10586 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
10587 && OMP_CLAUSE_LINEAR_STMT (c))
10589 gimplify_omp_ctxp = ctx;
10590 push_gimplify_context ();
10591 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
10593 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
10594 NULL, NULL);
10595 TREE_SIDE_EFFECTS (bind) = 1;
10596 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
10597 OMP_CLAUSE_LINEAR_STMT (c) = bind;
10599 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
10600 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
10601 pop_gimplify_context
10602 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
10603 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
10605 gimplify_omp_ctxp = outer_ctx;
10607 if (notice_outer)
10608 goto do_notice;
10609 break;
10611 case OMP_CLAUSE_COPYIN:
10612 case OMP_CLAUSE_COPYPRIVATE:
10613 decl = OMP_CLAUSE_DECL (c);
10614 if (error_operand_p (decl))
10616 remove = true;
10617 break;
10619 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
10620 && !remove
10621 && !omp_check_private (ctx, decl, true))
10623 remove = true;
10624 if (is_global_var (decl))
10626 if (DECL_THREAD_LOCAL_P (decl))
10627 remove = false;
10628 else if (DECL_HAS_VALUE_EXPR_P (decl))
10630 tree value = get_base_address (DECL_VALUE_EXPR (decl));
10632 if (value
10633 && DECL_P (value)
10634 && DECL_THREAD_LOCAL_P (value))
10635 remove = false;
10638 if (remove)
10639 error_at (OMP_CLAUSE_LOCATION (c),
10640 "copyprivate variable %qE is not threadprivate"
10641 " or private in outer context", DECL_NAME (decl));
10643 do_notice:
10644 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10645 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE
10646 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
10647 && outer_ctx
10648 && ((region_type & ORT_TASKLOOP) == ORT_TASKLOOP
10649 || (region_type == ORT_WORKSHARE
10650 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10651 && (OMP_CLAUSE_REDUCTION_INSCAN (c)
10652 || code == OMP_LOOP)))
10653 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
10654 || (code == OMP_LOOP
10655 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10656 && ((outer_ctx->region_type & ORT_COMBINED_TEAMS)
10657 == ORT_COMBINED_TEAMS))))
10659 splay_tree_node on
10660 = splay_tree_lookup (outer_ctx->variables,
10661 (splay_tree_key)decl);
10662 if (on == NULL || (on->value & GOVD_DATA_SHARE_CLASS) == 0)
10664 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
10665 && TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
10666 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
10667 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
10668 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
10669 == POINTER_TYPE))))
10670 omp_firstprivatize_variable (outer_ctx, decl);
10671 else
10673 omp_add_variable (outer_ctx, decl,
10674 GOVD_SEEN | GOVD_SHARED);
10675 if (outer_ctx->outer_context)
10676 omp_notice_variable (outer_ctx->outer_context, decl,
10677 true);
10681 if (outer_ctx)
10682 omp_notice_variable (outer_ctx, decl, true);
10683 if (check_non_private
10684 && (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
10685 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
10686 || decl == OMP_CLAUSE_DECL (c)
10687 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
10688 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
10689 == ADDR_EXPR
10690 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
10691 == POINTER_PLUS_EXPR
10692 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
10693 (OMP_CLAUSE_DECL (c), 0), 0))
10694 == ADDR_EXPR)))))
10695 && omp_check_private (ctx, decl, false))
10697 error ("%s variable %qE is private in outer context",
10698 check_non_private, DECL_NAME (decl));
10699 remove = true;
10701 break;
10703 case OMP_CLAUSE_DETACH:
10704 flags = GOVD_FIRSTPRIVATE | GOVD_SEEN;
10705 goto do_add;
10707 case OMP_CLAUSE_IF:
10708 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
10709 && OMP_CLAUSE_IF_MODIFIER (c) != code)
10711 const char *p[2];
10712 for (int i = 0; i < 2; i++)
10713 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
10715 case VOID_CST: p[i] = "cancel"; break;
10716 case OMP_PARALLEL: p[i] = "parallel"; break;
10717 case OMP_SIMD: p[i] = "simd"; break;
10718 case OMP_TASK: p[i] = "task"; break;
10719 case OMP_TASKLOOP: p[i] = "taskloop"; break;
10720 case OMP_TARGET_DATA: p[i] = "target data"; break;
10721 case OMP_TARGET: p[i] = "target"; break;
10722 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
10723 case OMP_TARGET_ENTER_DATA:
10724 p[i] = "target enter data"; break;
10725 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
10726 default: gcc_unreachable ();
10728 error_at (OMP_CLAUSE_LOCATION (c),
10729 "expected %qs %<if%> clause modifier rather than %qs",
10730 p[0], p[1]);
10731 remove = true;
10733 /* Fall through. */
10735 case OMP_CLAUSE_FINAL:
10736 OMP_CLAUSE_OPERAND (c, 0)
10737 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
10738 /* Fall through. */
10740 case OMP_CLAUSE_NUM_TEAMS:
10741 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS
10742 && OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
10743 && !is_gimple_min_invariant (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)))
10745 if (error_operand_p (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)))
10747 remove = true;
10748 break;
10750 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
10751 = get_initialized_tmp_var (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c),
10752 pre_p, NULL, true);
10754 /* Fall through. */
10756 case OMP_CLAUSE_SCHEDULE:
10757 case OMP_CLAUSE_NUM_THREADS:
10758 case OMP_CLAUSE_THREAD_LIMIT:
10759 case OMP_CLAUSE_DIST_SCHEDULE:
10760 case OMP_CLAUSE_DEVICE:
10761 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEVICE
10762 && OMP_CLAUSE_DEVICE_ANCESTOR (c))
10764 if (code != OMP_TARGET)
10766 error_at (OMP_CLAUSE_LOCATION (c),
10767 "%<device%> clause with %<ancestor%> is only "
10768 "allowed on %<target%> construct");
10769 remove = true;
10770 break;
10773 tree clauses = *orig_list_p;
10774 for (; clauses ; clauses = OMP_CLAUSE_CHAIN (clauses))
10775 if (OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEVICE
10776 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_FIRSTPRIVATE
10777 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_PRIVATE
10778 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEFAULTMAP
10779 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_MAP
10782 error_at (OMP_CLAUSE_LOCATION (c),
10783 "with %<ancestor%>, only the %<device%>, "
10784 "%<firstprivate%>, %<private%>, %<defaultmap%>, "
10785 "and %<map%> clauses may appear on the "
10786 "construct");
10787 remove = true;
10788 break;
10791 /* Fall through. */
10793 case OMP_CLAUSE_PRIORITY:
10794 case OMP_CLAUSE_GRAINSIZE:
10795 case OMP_CLAUSE_NUM_TASKS:
10796 case OMP_CLAUSE_FILTER:
10797 case OMP_CLAUSE_HINT:
10798 case OMP_CLAUSE_ASYNC:
10799 case OMP_CLAUSE_WAIT:
10800 case OMP_CLAUSE_NUM_GANGS:
10801 case OMP_CLAUSE_NUM_WORKERS:
10802 case OMP_CLAUSE_VECTOR_LENGTH:
10803 case OMP_CLAUSE_WORKER:
10804 case OMP_CLAUSE_VECTOR:
10805 if (OMP_CLAUSE_OPERAND (c, 0)
10806 && !is_gimple_min_invariant (OMP_CLAUSE_OPERAND (c, 0)))
10808 if (error_operand_p (OMP_CLAUSE_OPERAND (c, 0)))
10810 remove = true;
10811 break;
10813 /* All these clauses care about value, not a particular decl,
10814 so try to force it into a SSA_NAME or fresh temporary. */
10815 OMP_CLAUSE_OPERAND (c, 0)
10816 = get_initialized_tmp_var (OMP_CLAUSE_OPERAND (c, 0),
10817 pre_p, NULL, true);
10819 break;
10821 case OMP_CLAUSE_GANG:
10822 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
10823 is_gimple_val, fb_rvalue) == GS_ERROR)
10824 remove = true;
10825 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
10826 is_gimple_val, fb_rvalue) == GS_ERROR)
10827 remove = true;
10828 break;
10830 case OMP_CLAUSE_NOWAIT:
10831 nowait = 1;
10832 break;
10834 case OMP_CLAUSE_ORDERED:
10835 case OMP_CLAUSE_UNTIED:
10836 case OMP_CLAUSE_COLLAPSE:
10837 case OMP_CLAUSE_TILE:
10838 case OMP_CLAUSE_AUTO:
10839 case OMP_CLAUSE_SEQ:
10840 case OMP_CLAUSE_INDEPENDENT:
10841 case OMP_CLAUSE_MERGEABLE:
10842 case OMP_CLAUSE_PROC_BIND:
10843 case OMP_CLAUSE_SAFELEN:
10844 case OMP_CLAUSE_SIMDLEN:
10845 case OMP_CLAUSE_NOGROUP:
10846 case OMP_CLAUSE_THREADS:
10847 case OMP_CLAUSE_SIMD:
10848 case OMP_CLAUSE_BIND:
10849 case OMP_CLAUSE_IF_PRESENT:
10850 case OMP_CLAUSE_FINALIZE:
10851 break;
10853 case OMP_CLAUSE_ORDER:
10854 ctx->order_concurrent = true;
10855 break;
10857 case OMP_CLAUSE_DEFAULTMAP:
10858 enum gimplify_defaultmap_kind gdmkmin, gdmkmax;
10859 switch (OMP_CLAUSE_DEFAULTMAP_CATEGORY (c))
10861 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED:
10862 gdmkmin = GDMK_SCALAR;
10863 gdmkmax = GDMK_POINTER;
10864 break;
10865 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_SCALAR:
10866 gdmkmin = GDMK_SCALAR;
10867 gdmkmax = GDMK_SCALAR_TARGET;
10868 break;
10869 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_AGGREGATE:
10870 gdmkmin = gdmkmax = GDMK_AGGREGATE;
10871 break;
10872 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALLOCATABLE:
10873 gdmkmin = gdmkmax = GDMK_ALLOCATABLE;
10874 break;
10875 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_POINTER:
10876 gdmkmin = gdmkmax = GDMK_POINTER;
10877 break;
10878 default:
10879 gcc_unreachable ();
10881 for (int gdmk = gdmkmin; gdmk <= gdmkmax; gdmk++)
10882 switch (OMP_CLAUSE_DEFAULTMAP_BEHAVIOR (c))
10884 case OMP_CLAUSE_DEFAULTMAP_ALLOC:
10885 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_ALLOC_ONLY;
10886 break;
10887 case OMP_CLAUSE_DEFAULTMAP_TO:
10888 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_TO_ONLY;
10889 break;
10890 case OMP_CLAUSE_DEFAULTMAP_FROM:
10891 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FROM_ONLY;
10892 break;
10893 case OMP_CLAUSE_DEFAULTMAP_TOFROM:
10894 ctx->defaultmap[gdmk] = GOVD_MAP;
10895 break;
10896 case OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE:
10897 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
10898 break;
10899 case OMP_CLAUSE_DEFAULTMAP_NONE:
10900 ctx->defaultmap[gdmk] = 0;
10901 break;
10902 case OMP_CLAUSE_DEFAULTMAP_DEFAULT:
10903 switch (gdmk)
10905 case GDMK_SCALAR:
10906 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
10907 break;
10908 case GDMK_SCALAR_TARGET:
10909 ctx->defaultmap[gdmk] = (lang_GNU_Fortran ()
10910 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
10911 break;
10912 case GDMK_AGGREGATE:
10913 case GDMK_ALLOCATABLE:
10914 ctx->defaultmap[gdmk] = GOVD_MAP;
10915 break;
10916 case GDMK_POINTER:
10917 ctx->defaultmap[gdmk] = GOVD_MAP;
10918 if (!lang_GNU_Fortran ())
10919 ctx->defaultmap[gdmk] |= GOVD_MAP_0LEN_ARRAY;
10920 break;
10921 default:
10922 gcc_unreachable ();
10924 break;
10925 default:
10926 gcc_unreachable ();
10928 break;
10930 case OMP_CLAUSE_ALIGNED:
10931 decl = OMP_CLAUSE_DECL (c);
10932 if (error_operand_p (decl))
10934 remove = true;
10935 break;
10937 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
10938 is_gimple_val, fb_rvalue) == GS_ERROR)
10940 remove = true;
10941 break;
10943 if (!is_global_var (decl)
10944 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
10945 omp_add_variable (ctx, decl, GOVD_ALIGNED);
10946 break;
10948 case OMP_CLAUSE_NONTEMPORAL:
10949 decl = OMP_CLAUSE_DECL (c);
10950 if (error_operand_p (decl))
10952 remove = true;
10953 break;
10955 omp_add_variable (ctx, decl, GOVD_NONTEMPORAL);
10956 break;
10958 case OMP_CLAUSE_ALLOCATE:
10959 decl = OMP_CLAUSE_DECL (c);
10960 if (error_operand_p (decl))
10962 remove = true;
10963 break;
10965 if (gimplify_expr (&OMP_CLAUSE_ALLOCATE_ALLOCATOR (c), pre_p, NULL,
10966 is_gimple_val, fb_rvalue) == GS_ERROR)
10968 remove = true;
10969 break;
10971 else if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c) == NULL_TREE
10972 || (TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c))
10973 == INTEGER_CST))
10975 else if (code == OMP_TASKLOOP
10976 || !DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
10977 OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
10978 = get_initialized_tmp_var (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
10979 pre_p, NULL, false);
10980 break;
10982 case OMP_CLAUSE_DEFAULT:
10983 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
10984 break;
10986 case OMP_CLAUSE_INCLUSIVE:
10987 case OMP_CLAUSE_EXCLUSIVE:
10988 decl = OMP_CLAUSE_DECL (c);
10990 splay_tree_node n = splay_tree_lookup (outer_ctx->variables,
10991 (splay_tree_key) decl);
10992 if (n == NULL || (n->value & GOVD_REDUCTION) == 0)
10994 error_at (OMP_CLAUSE_LOCATION (c),
10995 "%qD specified in %qs clause but not in %<inscan%> "
10996 "%<reduction%> clause on the containing construct",
10997 decl, omp_clause_code_name[OMP_CLAUSE_CODE (c)]);
10998 remove = true;
11000 else
11002 n->value |= GOVD_REDUCTION_INSCAN;
11003 if (outer_ctx->region_type == ORT_SIMD
11004 && outer_ctx->outer_context
11005 && outer_ctx->outer_context->region_type == ORT_WORKSHARE)
11007 n = splay_tree_lookup (outer_ctx->outer_context->variables,
11008 (splay_tree_key) decl);
11009 if (n && (n->value & GOVD_REDUCTION) != 0)
11010 n->value |= GOVD_REDUCTION_INSCAN;
11014 break;
11016 case OMP_CLAUSE_NOHOST:
11017 default:
11018 gcc_unreachable ();
11021 if (code == OACC_DATA
11022 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
11023 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
11024 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
11025 remove = true;
11026 if (remove)
11027 *list_p = OMP_CLAUSE_CHAIN (c);
11028 else
11029 list_p = &OMP_CLAUSE_CHAIN (c);
11032 ctx->clauses = *orig_list_p;
11033 gimplify_omp_ctxp = ctx;
11034 if (struct_seen_clause)
11035 delete struct_seen_clause;
11036 if (struct_map_to_clause)
11037 delete struct_map_to_clause;
11038 if (struct_deref_set)
11039 delete struct_deref_set;
11042 /* Return true if DECL is a candidate for shared to firstprivate
11043 optimization. We only consider non-addressable scalars, not
11044 too big, and not references. */
11046 static bool
11047 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
11049 if (TREE_ADDRESSABLE (decl))
11050 return false;
11051 tree type = TREE_TYPE (decl);
11052 if (!is_gimple_reg_type (type)
11053 || TREE_CODE (type) == REFERENCE_TYPE
11054 || TREE_ADDRESSABLE (type))
11055 return false;
11056 /* Don't optimize too large decls, as each thread/task will have
11057 its own. */
11058 HOST_WIDE_INT len = int_size_in_bytes (type);
11059 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
11060 return false;
11061 if (omp_privatize_by_reference (decl))
11062 return false;
11063 return true;
11066 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
11067 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
11068 GOVD_WRITTEN in outer contexts. */
11070 static void
11071 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
11073 for (; ctx; ctx = ctx->outer_context)
11075 splay_tree_node n = splay_tree_lookup (ctx->variables,
11076 (splay_tree_key) decl);
11077 if (n == NULL)
11078 continue;
11079 else if (n->value & GOVD_SHARED)
11081 n->value |= GOVD_WRITTEN;
11082 return;
11084 else if (n->value & GOVD_DATA_SHARE_CLASS)
11085 return;
11089 /* Helper callback for walk_gimple_seq to discover possible stores
11090 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
11091 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
11092 for those. */
11094 static tree
11095 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
11097 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
11099 *walk_subtrees = 0;
11100 if (!wi->is_lhs)
11101 return NULL_TREE;
11103 tree op = *tp;
11106 if (handled_component_p (op))
11107 op = TREE_OPERAND (op, 0);
11108 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
11109 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
11110 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
11111 else
11112 break;
11114 while (1);
11115 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
11116 return NULL_TREE;
11118 omp_mark_stores (gimplify_omp_ctxp, op);
11119 return NULL_TREE;
11122 /* Helper callback for walk_gimple_seq to discover possible stores
11123 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
11124 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
11125 for those. */
11127 static tree
11128 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
11129 bool *handled_ops_p,
11130 struct walk_stmt_info *wi)
11132 gimple *stmt = gsi_stmt (*gsi_p);
11133 switch (gimple_code (stmt))
11135 /* Don't recurse on OpenMP constructs for which
11136 gimplify_adjust_omp_clauses already handled the bodies,
11137 except handle gimple_omp_for_pre_body. */
11138 case GIMPLE_OMP_FOR:
11139 *handled_ops_p = true;
11140 if (gimple_omp_for_pre_body (stmt))
11141 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
11142 omp_find_stores_stmt, omp_find_stores_op, wi);
11143 break;
11144 case GIMPLE_OMP_PARALLEL:
11145 case GIMPLE_OMP_TASK:
11146 case GIMPLE_OMP_SECTIONS:
11147 case GIMPLE_OMP_SINGLE:
11148 case GIMPLE_OMP_SCOPE:
11149 case GIMPLE_OMP_TARGET:
11150 case GIMPLE_OMP_TEAMS:
11151 case GIMPLE_OMP_CRITICAL:
11152 *handled_ops_p = true;
11153 break;
11154 default:
11155 break;
11157 return NULL_TREE;
11160 struct gimplify_adjust_omp_clauses_data
11162 tree *list_p;
11163 gimple_seq *pre_p;
11166 /* For all variables that were not actually used within the context,
11167 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
11169 static int
11170 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
11172 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
11173 gimple_seq *pre_p
11174 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
11175 tree decl = (tree) n->key;
11176 unsigned flags = n->value;
11177 enum omp_clause_code code;
11178 tree clause;
11179 bool private_debug;
11181 if (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
11182 && (flags & GOVD_LASTPRIVATE_CONDITIONAL) != 0)
11183 flags = GOVD_SHARED | GOVD_SEEN | GOVD_WRITTEN;
11184 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
11185 return 0;
11186 if ((flags & GOVD_SEEN) == 0)
11187 return 0;
11188 if ((flags & GOVD_MAP_HAS_ATTACHMENTS) != 0)
11189 return 0;
11190 if (flags & GOVD_DEBUG_PRIVATE)
11192 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_SHARED);
11193 private_debug = true;
11195 else if (flags & GOVD_MAP)
11196 private_debug = false;
11197 else
11198 private_debug
11199 = lang_hooks.decls.omp_private_debug_clause (decl,
11200 !!(flags & GOVD_SHARED));
11201 if (private_debug)
11202 code = OMP_CLAUSE_PRIVATE;
11203 else if (flags & GOVD_MAP)
11205 code = OMP_CLAUSE_MAP;
11206 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
11207 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
11209 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
11210 return 0;
11212 if (VAR_P (decl)
11213 && DECL_IN_CONSTANT_POOL (decl)
11214 && !lookup_attribute ("omp declare target",
11215 DECL_ATTRIBUTES (decl)))
11217 tree id = get_identifier ("omp declare target");
11218 DECL_ATTRIBUTES (decl)
11219 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (decl));
11220 varpool_node *node = varpool_node::get (decl);
11221 if (node)
11223 node->offloadable = 1;
11224 if (ENABLE_OFFLOADING)
11225 g->have_offload = true;
11229 else if (flags & GOVD_SHARED)
11231 if (is_global_var (decl))
11233 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
11234 while (ctx != NULL)
11236 splay_tree_node on
11237 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11238 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
11239 | GOVD_PRIVATE | GOVD_REDUCTION
11240 | GOVD_LINEAR | GOVD_MAP)) != 0)
11241 break;
11242 ctx = ctx->outer_context;
11244 if (ctx == NULL)
11245 return 0;
11247 code = OMP_CLAUSE_SHARED;
11248 /* Don't optimize shared into firstprivate for read-only vars
11249 on tasks with depend clause, we shouldn't try to copy them
11250 until the dependencies are satisfied. */
11251 if (gimplify_omp_ctxp->has_depend)
11252 flags |= GOVD_WRITTEN;
11254 else if (flags & GOVD_PRIVATE)
11255 code = OMP_CLAUSE_PRIVATE;
11256 else if (flags & GOVD_FIRSTPRIVATE)
11258 code = OMP_CLAUSE_FIRSTPRIVATE;
11259 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
11260 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
11261 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
11263 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
11264 "%<target%> construct", decl);
11265 return 0;
11268 else if (flags & GOVD_LASTPRIVATE)
11269 code = OMP_CLAUSE_LASTPRIVATE;
11270 else if (flags & (GOVD_ALIGNED | GOVD_NONTEMPORAL))
11271 return 0;
11272 else if (flags & GOVD_CONDTEMP)
11274 code = OMP_CLAUSE__CONDTEMP_;
11275 gimple_add_tmp_var (decl);
11277 else
11278 gcc_unreachable ();
11280 if (((flags & GOVD_LASTPRIVATE)
11281 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
11282 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11283 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11285 tree chain = *list_p;
11286 clause = build_omp_clause (input_location, code);
11287 OMP_CLAUSE_DECL (clause) = decl;
11288 OMP_CLAUSE_CHAIN (clause) = chain;
11289 if (private_debug)
11290 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
11291 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
11292 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
11293 else if (code == OMP_CLAUSE_SHARED
11294 && (flags & GOVD_WRITTEN) == 0
11295 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11296 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
11297 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
11298 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
11299 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
11301 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
11302 OMP_CLAUSE_DECL (nc) = decl;
11303 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
11304 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
11305 OMP_CLAUSE_DECL (clause)
11306 = build_simple_mem_ref_loc (input_location, decl);
11307 OMP_CLAUSE_DECL (clause)
11308 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
11309 build_int_cst (build_pointer_type (char_type_node), 0));
11310 OMP_CLAUSE_SIZE (clause) = size_zero_node;
11311 OMP_CLAUSE_SIZE (nc) = size_zero_node;
11312 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
11313 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
11314 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
11315 OMP_CLAUSE_CHAIN (nc) = chain;
11316 OMP_CLAUSE_CHAIN (clause) = nc;
11317 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
11318 gimplify_omp_ctxp = ctx->outer_context;
11319 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
11320 pre_p, NULL, is_gimple_val, fb_rvalue);
11321 gimplify_omp_ctxp = ctx;
11323 else if (code == OMP_CLAUSE_MAP)
11325 int kind;
11326 /* Not all combinations of these GOVD_MAP flags are actually valid. */
11327 switch (flags & (GOVD_MAP_TO_ONLY
11328 | GOVD_MAP_FORCE
11329 | GOVD_MAP_FORCE_PRESENT
11330 | GOVD_MAP_ALLOC_ONLY
11331 | GOVD_MAP_FROM_ONLY))
11333 case 0:
11334 kind = GOMP_MAP_TOFROM;
11335 break;
11336 case GOVD_MAP_FORCE:
11337 kind = GOMP_MAP_TOFROM | GOMP_MAP_FLAG_FORCE;
11338 break;
11339 case GOVD_MAP_TO_ONLY:
11340 kind = GOMP_MAP_TO;
11341 break;
11342 case GOVD_MAP_FROM_ONLY:
11343 kind = GOMP_MAP_FROM;
11344 break;
11345 case GOVD_MAP_ALLOC_ONLY:
11346 kind = GOMP_MAP_ALLOC;
11347 break;
11348 case GOVD_MAP_TO_ONLY | GOVD_MAP_FORCE:
11349 kind = GOMP_MAP_TO | GOMP_MAP_FLAG_FORCE;
11350 break;
11351 case GOVD_MAP_FORCE_PRESENT:
11352 kind = GOMP_MAP_FORCE_PRESENT;
11353 break;
11354 default:
11355 gcc_unreachable ();
11357 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
11358 /* Setting of the implicit flag for the runtime is currently disabled for
11359 OpenACC. */
11360 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0)
11361 OMP_CLAUSE_MAP_RUNTIME_IMPLICIT_P (clause) = 1;
11362 if (DECL_SIZE (decl)
11363 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
11365 tree decl2 = DECL_VALUE_EXPR (decl);
11366 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
11367 decl2 = TREE_OPERAND (decl2, 0);
11368 gcc_assert (DECL_P (decl2));
11369 tree mem = build_simple_mem_ref (decl2);
11370 OMP_CLAUSE_DECL (clause) = mem;
11371 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
11372 if (gimplify_omp_ctxp->outer_context)
11374 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
11375 omp_notice_variable (ctx, decl2, true);
11376 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
11378 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
11379 OMP_CLAUSE_MAP);
11380 OMP_CLAUSE_DECL (nc) = decl;
11381 OMP_CLAUSE_SIZE (nc) = size_zero_node;
11382 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
11383 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
11384 else
11385 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
11386 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
11387 OMP_CLAUSE_CHAIN (clause) = nc;
11389 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
11390 && omp_privatize_by_reference (decl))
11392 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
11393 OMP_CLAUSE_SIZE (clause)
11394 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
11395 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
11396 gimplify_omp_ctxp = ctx->outer_context;
11397 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
11398 pre_p, NULL, is_gimple_val, fb_rvalue);
11399 gimplify_omp_ctxp = ctx;
11400 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
11401 OMP_CLAUSE_MAP);
11402 OMP_CLAUSE_DECL (nc) = decl;
11403 OMP_CLAUSE_SIZE (nc) = size_zero_node;
11404 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
11405 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
11406 OMP_CLAUSE_CHAIN (clause) = nc;
11408 else
11409 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
11411 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
11413 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
11414 OMP_CLAUSE_DECL (nc) = decl;
11415 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
11416 OMP_CLAUSE_CHAIN (nc) = chain;
11417 OMP_CLAUSE_CHAIN (clause) = nc;
11418 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
11419 gimplify_omp_ctxp = ctx->outer_context;
11420 lang_hooks.decls.omp_finish_clause (nc, pre_p,
11421 (ctx->region_type & ORT_ACC) != 0);
11422 gimplify_omp_ctxp = ctx;
11424 *list_p = clause;
11425 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
11426 gimplify_omp_ctxp = ctx->outer_context;
11427 /* Don't call omp_finish_clause on implicitly added OMP_CLAUSE_PRIVATE
11428 in simd. Those are only added for the local vars inside of simd body
11429 and they don't need to be e.g. default constructible. */
11430 if (code != OMP_CLAUSE_PRIVATE || ctx->region_type != ORT_SIMD)
11431 lang_hooks.decls.omp_finish_clause (clause, pre_p,
11432 (ctx->region_type & ORT_ACC) != 0);
11433 if (gimplify_omp_ctxp)
11434 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
11435 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
11436 && DECL_P (OMP_CLAUSE_SIZE (clause)))
11437 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
11438 true);
11439 gimplify_omp_ctxp = ctx;
11440 return 0;
11443 static void
11444 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
11445 enum tree_code code)
11447 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
11448 tree *orig_list_p = list_p;
11449 tree c, decl;
11450 bool has_inscan_reductions = false;
11452 if (body)
11454 struct gimplify_omp_ctx *octx;
11455 for (octx = ctx; octx; octx = octx->outer_context)
11456 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
11457 break;
11458 if (octx)
11460 struct walk_stmt_info wi;
11461 memset (&wi, 0, sizeof (wi));
11462 walk_gimple_seq (body, omp_find_stores_stmt,
11463 omp_find_stores_op, &wi);
11467 if (ctx->add_safelen1)
11469 /* If there are VLAs in the body of simd loop, prevent
11470 vectorization. */
11471 gcc_assert (ctx->region_type == ORT_SIMD);
11472 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_SAFELEN);
11473 OMP_CLAUSE_SAFELEN_EXPR (c) = integer_one_node;
11474 OMP_CLAUSE_CHAIN (c) = *list_p;
11475 *list_p = c;
11476 list_p = &OMP_CLAUSE_CHAIN (c);
11479 if (ctx->region_type == ORT_WORKSHARE
11480 && ctx->outer_context
11481 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL)
11483 for (c = ctx->outer_context->clauses; c; c = OMP_CLAUSE_CHAIN (c))
11484 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
11485 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
11487 decl = OMP_CLAUSE_DECL (c);
11488 splay_tree_node n
11489 = splay_tree_lookup (ctx->outer_context->variables,
11490 (splay_tree_key) decl);
11491 gcc_checking_assert (!splay_tree_lookup (ctx->variables,
11492 (splay_tree_key) decl));
11493 omp_add_variable (ctx, decl, n->value);
11494 tree c2 = copy_node (c);
11495 OMP_CLAUSE_CHAIN (c2) = *list_p;
11496 *list_p = c2;
11497 if ((n->value & GOVD_FIRSTPRIVATE) == 0)
11498 continue;
11499 c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
11500 OMP_CLAUSE_FIRSTPRIVATE);
11501 OMP_CLAUSE_DECL (c2) = decl;
11502 OMP_CLAUSE_CHAIN (c2) = *list_p;
11503 *list_p = c2;
11506 while ((c = *list_p) != NULL)
11508 splay_tree_node n;
11509 bool remove = false;
11511 switch (OMP_CLAUSE_CODE (c))
11513 case OMP_CLAUSE_FIRSTPRIVATE:
11514 if ((ctx->region_type & ORT_TARGET)
11515 && (ctx->region_type & ORT_ACC) == 0
11516 && TYPE_ATOMIC (strip_array_types
11517 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
11519 error_at (OMP_CLAUSE_LOCATION (c),
11520 "%<_Atomic%> %qD in %<firstprivate%> clause on "
11521 "%<target%> construct", OMP_CLAUSE_DECL (c));
11522 remove = true;
11523 break;
11525 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
11527 decl = OMP_CLAUSE_DECL (c);
11528 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11529 if ((n->value & GOVD_MAP) != 0)
11531 remove = true;
11532 break;
11534 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT_TARGET (c) = 0;
11535 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c) = 0;
11537 /* FALLTHRU */
11538 case OMP_CLAUSE_PRIVATE:
11539 case OMP_CLAUSE_SHARED:
11540 case OMP_CLAUSE_LINEAR:
11541 decl = OMP_CLAUSE_DECL (c);
11542 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11543 remove = !(n->value & GOVD_SEEN);
11544 if ((n->value & GOVD_LASTPRIVATE_CONDITIONAL) != 0
11545 && code == OMP_PARALLEL
11546 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE)
11547 remove = true;
11548 if (! remove)
11550 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
11551 if ((n->value & GOVD_DEBUG_PRIVATE)
11552 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
11554 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
11555 || ((n->value & GOVD_DATA_SHARE_CLASS)
11556 == GOVD_SHARED));
11557 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
11558 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
11560 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11561 && ctx->has_depend
11562 && DECL_P (decl))
11563 n->value |= GOVD_WRITTEN;
11564 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11565 && (n->value & GOVD_WRITTEN) == 0
11566 && DECL_P (decl)
11567 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11568 OMP_CLAUSE_SHARED_READONLY (c) = 1;
11569 else if (DECL_P (decl)
11570 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
11571 && (n->value & GOVD_WRITTEN) != 0)
11572 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11573 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
11574 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11575 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11577 else
11578 n->value &= ~GOVD_EXPLICIT;
11579 break;
11581 case OMP_CLAUSE_LASTPRIVATE:
11582 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
11583 accurately reflect the presence of a FIRSTPRIVATE clause. */
11584 decl = OMP_CLAUSE_DECL (c);
11585 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11586 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
11587 = (n->value & GOVD_FIRSTPRIVATE) != 0;
11588 if (code == OMP_DISTRIBUTE
11589 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
11591 remove = true;
11592 error_at (OMP_CLAUSE_LOCATION (c),
11593 "same variable used in %<firstprivate%> and "
11594 "%<lastprivate%> clauses on %<distribute%> "
11595 "construct");
11597 if (!remove
11598 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
11599 && DECL_P (decl)
11600 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11601 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11602 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) && code == OMP_PARALLEL)
11603 remove = true;
11604 break;
11606 case OMP_CLAUSE_ALIGNED:
11607 decl = OMP_CLAUSE_DECL (c);
11608 if (!is_global_var (decl))
11610 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11611 remove = n == NULL || !(n->value & GOVD_SEEN);
11612 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
11614 struct gimplify_omp_ctx *octx;
11615 if (n != NULL
11616 && (n->value & (GOVD_DATA_SHARE_CLASS
11617 & ~GOVD_FIRSTPRIVATE)))
11618 remove = true;
11619 else
11620 for (octx = ctx->outer_context; octx;
11621 octx = octx->outer_context)
11623 n = splay_tree_lookup (octx->variables,
11624 (splay_tree_key) decl);
11625 if (n == NULL)
11626 continue;
11627 if (n->value & GOVD_LOCAL)
11628 break;
11629 /* We have to avoid assigning a shared variable
11630 to itself when trying to add
11631 __builtin_assume_aligned. */
11632 if (n->value & GOVD_SHARED)
11634 remove = true;
11635 break;
11640 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
11642 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11643 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
11644 remove = true;
11646 break;
11648 case OMP_CLAUSE_HAS_DEVICE_ADDR:
11649 decl = OMP_CLAUSE_DECL (c);
11650 while (TREE_CODE (decl) == INDIRECT_REF
11651 || TREE_CODE (decl) == ARRAY_REF)
11652 decl = TREE_OPERAND (decl, 0);
11653 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11654 remove = n == NULL || !(n->value & GOVD_SEEN);
11655 break;
11657 case OMP_CLAUSE_IS_DEVICE_PTR:
11658 case OMP_CLAUSE_NONTEMPORAL:
11659 decl = OMP_CLAUSE_DECL (c);
11660 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11661 remove = n == NULL || !(n->value & GOVD_SEEN);
11662 break;
11664 case OMP_CLAUSE_MAP:
11665 if (code == OMP_TARGET_EXIT_DATA
11666 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
11668 remove = true;
11669 break;
11671 decl = OMP_CLAUSE_DECL (c);
11672 /* Data clauses associated with reductions must be
11673 compatible with present_or_copy. Warn and adjust the clause
11674 if that is not the case. */
11675 if (ctx->region_type == ORT_ACC_PARALLEL
11676 || ctx->region_type == ORT_ACC_SERIAL)
11678 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
11679 n = NULL;
11681 if (DECL_P (t))
11682 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
11684 if (n && (n->value & GOVD_REDUCTION))
11686 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
11688 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
11689 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
11690 && kind != GOMP_MAP_FORCE_PRESENT
11691 && kind != GOMP_MAP_POINTER)
11693 warning_at (OMP_CLAUSE_LOCATION (c), 0,
11694 "incompatible data clause with reduction "
11695 "on %qE; promoting to %<present_or_copy%>",
11696 DECL_NAME (t));
11697 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
11701 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
11702 && (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA))
11704 remove = true;
11705 break;
11707 if (!DECL_P (decl))
11709 if ((ctx->region_type & ORT_TARGET) != 0
11710 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
11712 if (TREE_CODE (decl) == INDIRECT_REF
11713 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
11714 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
11715 == REFERENCE_TYPE))
11716 decl = TREE_OPERAND (decl, 0);
11717 if (TREE_CODE (decl) == COMPONENT_REF)
11719 while (TREE_CODE (decl) == COMPONENT_REF)
11720 decl = TREE_OPERAND (decl, 0);
11721 if (DECL_P (decl))
11723 n = splay_tree_lookup (ctx->variables,
11724 (splay_tree_key) decl);
11725 if (!(n->value & GOVD_SEEN))
11726 remove = true;
11730 break;
11732 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11733 if ((ctx->region_type & ORT_TARGET) != 0
11734 && !(n->value & GOVD_SEEN)
11735 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
11736 && (!is_global_var (decl)
11737 || !lookup_attribute ("omp declare target link",
11738 DECL_ATTRIBUTES (decl))))
11740 remove = true;
11741 /* For struct element mapping, if struct is never referenced
11742 in target block and none of the mapping has always modifier,
11743 remove all the struct element mappings, which immediately
11744 follow the GOMP_MAP_STRUCT map clause. */
11745 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
11747 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
11748 while (cnt--)
11749 OMP_CLAUSE_CHAIN (c)
11750 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
11753 else if (DECL_SIZE (decl)
11754 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
11755 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
11756 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
11757 && (OMP_CLAUSE_MAP_KIND (c)
11758 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
11760 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
11761 for these, TREE_CODE (DECL_SIZE (decl)) will always be
11762 INTEGER_CST. */
11763 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
11765 tree decl2 = DECL_VALUE_EXPR (decl);
11766 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
11767 decl2 = TREE_OPERAND (decl2, 0);
11768 gcc_assert (DECL_P (decl2));
11769 tree mem = build_simple_mem_ref (decl2);
11770 OMP_CLAUSE_DECL (c) = mem;
11771 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
11772 if (ctx->outer_context)
11774 omp_notice_variable (ctx->outer_context, decl2, true);
11775 omp_notice_variable (ctx->outer_context,
11776 OMP_CLAUSE_SIZE (c), true);
11778 if (((ctx->region_type & ORT_TARGET) != 0
11779 || !ctx->target_firstprivatize_array_bases)
11780 && ((n->value & GOVD_SEEN) == 0
11781 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
11783 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
11784 OMP_CLAUSE_MAP);
11785 OMP_CLAUSE_DECL (nc) = decl;
11786 OMP_CLAUSE_SIZE (nc) = size_zero_node;
11787 if (ctx->target_firstprivatize_array_bases)
11788 OMP_CLAUSE_SET_MAP_KIND (nc,
11789 GOMP_MAP_FIRSTPRIVATE_POINTER);
11790 else
11791 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
11792 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
11793 OMP_CLAUSE_CHAIN (c) = nc;
11794 c = nc;
11797 else
11799 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
11800 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
11801 gcc_assert ((n->value & GOVD_SEEN) == 0
11802 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
11803 == 0));
11805 break;
11807 case OMP_CLAUSE_TO:
11808 case OMP_CLAUSE_FROM:
11809 case OMP_CLAUSE__CACHE_:
11810 decl = OMP_CLAUSE_DECL (c);
11811 if (!DECL_P (decl))
11812 break;
11813 if (DECL_SIZE (decl)
11814 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
11816 tree decl2 = DECL_VALUE_EXPR (decl);
11817 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
11818 decl2 = TREE_OPERAND (decl2, 0);
11819 gcc_assert (DECL_P (decl2));
11820 tree mem = build_simple_mem_ref (decl2);
11821 OMP_CLAUSE_DECL (c) = mem;
11822 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
11823 if (ctx->outer_context)
11825 omp_notice_variable (ctx->outer_context, decl2, true);
11826 omp_notice_variable (ctx->outer_context,
11827 OMP_CLAUSE_SIZE (c), true);
11830 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
11831 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
11832 break;
11834 case OMP_CLAUSE_REDUCTION:
11835 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
11837 decl = OMP_CLAUSE_DECL (c);
11838 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11839 if ((n->value & GOVD_REDUCTION_INSCAN) == 0)
11841 remove = true;
11842 error_at (OMP_CLAUSE_LOCATION (c),
11843 "%qD specified in %<inscan%> %<reduction%> clause "
11844 "but not in %<scan%> directive clause", decl);
11845 break;
11847 has_inscan_reductions = true;
11849 /* FALLTHRU */
11850 case OMP_CLAUSE_IN_REDUCTION:
11851 case OMP_CLAUSE_TASK_REDUCTION:
11852 decl = OMP_CLAUSE_DECL (c);
11853 /* OpenACC reductions need a present_or_copy data clause.
11854 Add one if necessary. Emit error when the reduction is private. */
11855 if (ctx->region_type == ORT_ACC_PARALLEL
11856 || ctx->region_type == ORT_ACC_SERIAL)
11858 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11859 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
11861 remove = true;
11862 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
11863 "reduction on %qE", DECL_NAME (decl));
11865 else if ((n->value & GOVD_MAP) == 0)
11867 tree next = OMP_CLAUSE_CHAIN (c);
11868 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
11869 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
11870 OMP_CLAUSE_DECL (nc) = decl;
11871 OMP_CLAUSE_CHAIN (c) = nc;
11872 lang_hooks.decls.omp_finish_clause (nc, pre_p,
11873 (ctx->region_type
11874 & ORT_ACC) != 0);
11875 while (1)
11877 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
11878 if (OMP_CLAUSE_CHAIN (nc) == NULL)
11879 break;
11880 nc = OMP_CLAUSE_CHAIN (nc);
11882 OMP_CLAUSE_CHAIN (nc) = next;
11883 n->value |= GOVD_MAP;
11886 if (DECL_P (decl)
11887 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11888 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11889 break;
11891 case OMP_CLAUSE_ALLOCATE:
11892 decl = OMP_CLAUSE_DECL (c);
11893 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11894 if (n != NULL && !(n->value & GOVD_SEEN))
11896 if ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE | GOVD_LINEAR))
11897 != 0
11898 && (n->value & (GOVD_REDUCTION | GOVD_LASTPRIVATE)) == 0)
11899 remove = true;
11901 if (!remove
11902 && OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
11903 && TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)) != INTEGER_CST
11904 && ((ctx->region_type & (ORT_PARALLEL | ORT_TARGET)) != 0
11905 || (ctx->region_type & ORT_TASKLOOP) == ORT_TASK
11906 || (ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS))
11908 tree allocator = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
11909 n = splay_tree_lookup (ctx->variables, (splay_tree_key) allocator);
11910 if (n == NULL)
11912 enum omp_clause_default_kind default_kind
11913 = ctx->default_kind;
11914 ctx->default_kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
11915 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
11916 true);
11917 ctx->default_kind = default_kind;
11919 else
11920 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
11921 true);
11923 break;
11925 case OMP_CLAUSE_COPYIN:
11926 case OMP_CLAUSE_COPYPRIVATE:
11927 case OMP_CLAUSE_IF:
11928 case OMP_CLAUSE_NUM_THREADS:
11929 case OMP_CLAUSE_NUM_TEAMS:
11930 case OMP_CLAUSE_THREAD_LIMIT:
11931 case OMP_CLAUSE_DIST_SCHEDULE:
11932 case OMP_CLAUSE_DEVICE:
11933 case OMP_CLAUSE_SCHEDULE:
11934 case OMP_CLAUSE_NOWAIT:
11935 case OMP_CLAUSE_ORDERED:
11936 case OMP_CLAUSE_DEFAULT:
11937 case OMP_CLAUSE_UNTIED:
11938 case OMP_CLAUSE_COLLAPSE:
11939 case OMP_CLAUSE_FINAL:
11940 case OMP_CLAUSE_MERGEABLE:
11941 case OMP_CLAUSE_PROC_BIND:
11942 case OMP_CLAUSE_SAFELEN:
11943 case OMP_CLAUSE_SIMDLEN:
11944 case OMP_CLAUSE_DEPEND:
11945 case OMP_CLAUSE_DOACROSS:
11946 case OMP_CLAUSE_PRIORITY:
11947 case OMP_CLAUSE_GRAINSIZE:
11948 case OMP_CLAUSE_NUM_TASKS:
11949 case OMP_CLAUSE_NOGROUP:
11950 case OMP_CLAUSE_THREADS:
11951 case OMP_CLAUSE_SIMD:
11952 case OMP_CLAUSE_FILTER:
11953 case OMP_CLAUSE_HINT:
11954 case OMP_CLAUSE_DEFAULTMAP:
11955 case OMP_CLAUSE_ORDER:
11956 case OMP_CLAUSE_BIND:
11957 case OMP_CLAUSE_DETACH:
11958 case OMP_CLAUSE_USE_DEVICE_PTR:
11959 case OMP_CLAUSE_USE_DEVICE_ADDR:
11960 case OMP_CLAUSE_ASYNC:
11961 case OMP_CLAUSE_WAIT:
11962 case OMP_CLAUSE_INDEPENDENT:
11963 case OMP_CLAUSE_NUM_GANGS:
11964 case OMP_CLAUSE_NUM_WORKERS:
11965 case OMP_CLAUSE_VECTOR_LENGTH:
11966 case OMP_CLAUSE_GANG:
11967 case OMP_CLAUSE_WORKER:
11968 case OMP_CLAUSE_VECTOR:
11969 case OMP_CLAUSE_AUTO:
11970 case OMP_CLAUSE_SEQ:
11971 case OMP_CLAUSE_TILE:
11972 case OMP_CLAUSE_IF_PRESENT:
11973 case OMP_CLAUSE_FINALIZE:
11974 case OMP_CLAUSE_INCLUSIVE:
11975 case OMP_CLAUSE_EXCLUSIVE:
11976 break;
11978 case OMP_CLAUSE_NOHOST:
11979 default:
11980 gcc_unreachable ();
11983 if (remove)
11984 *list_p = OMP_CLAUSE_CHAIN (c);
11985 else
11986 list_p = &OMP_CLAUSE_CHAIN (c);
11989 /* Add in any implicit data sharing. */
11990 struct gimplify_adjust_omp_clauses_data data;
11991 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0)
11993 /* OpenMP. Implicit clauses are added at the start of the clause list,
11994 but after any non-map clauses. */
11995 tree *implicit_add_list_p = orig_list_p;
11996 while (*implicit_add_list_p
11997 && OMP_CLAUSE_CODE (*implicit_add_list_p) != OMP_CLAUSE_MAP)
11998 implicit_add_list_p = &OMP_CLAUSE_CHAIN (*implicit_add_list_p);
11999 data.list_p = implicit_add_list_p;
12001 else
12002 /* OpenACC. */
12003 data.list_p = list_p;
12004 data.pre_p = pre_p;
12005 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
12007 if (has_inscan_reductions)
12008 for (c = *orig_list_p; c; c = OMP_CLAUSE_CHAIN (c))
12009 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12010 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
12012 error_at (OMP_CLAUSE_LOCATION (c),
12013 "%<inscan%> %<reduction%> clause used together with "
12014 "%<linear%> clause for a variable other than loop "
12015 "iterator");
12016 break;
12019 gimplify_omp_ctxp = ctx->outer_context;
12020 delete_omp_context (ctx);
12023 /* Return 0 if CONSTRUCTS selectors don't match the OpenMP context,
12024 -1 if unknown yet (simd is involved, won't be known until vectorization)
12025 and 1 if they do. If SCORES is non-NULL, it should point to an array
12026 of at least 2*NCONSTRUCTS+2 ints, and will be filled with the positions
12027 of the CONSTRUCTS (position -1 if it will never match) followed by
12028 number of constructs in the OpenMP context construct trait. If the
12029 score depends on whether it will be in a declare simd clone or not,
12030 the function returns 2 and there will be two sets of the scores, the first
12031 one for the case that it is not in a declare simd clone, the other
12032 that it is in a declare simd clone. */
12035 omp_construct_selector_matches (enum tree_code *constructs, int nconstructs,
12036 int *scores)
12038 int matched = 0, cnt = 0;
12039 bool simd_seen = false;
12040 bool target_seen = false;
12041 int declare_simd_cnt = -1;
12042 auto_vec<enum tree_code, 16> codes;
12043 for (struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp; ctx;)
12045 if (((ctx->region_type & ORT_PARALLEL) && ctx->code == OMP_PARALLEL)
12046 || ((ctx->region_type & (ORT_TARGET | ORT_IMPLICIT_TARGET | ORT_ACC))
12047 == ORT_TARGET && ctx->code == OMP_TARGET)
12048 || ((ctx->region_type & ORT_TEAMS) && ctx->code == OMP_TEAMS)
12049 || (ctx->region_type == ORT_WORKSHARE && ctx->code == OMP_FOR)
12050 || (ctx->region_type == ORT_SIMD
12051 && ctx->code == OMP_SIMD
12052 && !omp_find_clause (ctx->clauses, OMP_CLAUSE_BIND)))
12054 ++cnt;
12055 if (scores)
12056 codes.safe_push (ctx->code);
12057 else if (matched < nconstructs && ctx->code == constructs[matched])
12059 if (ctx->code == OMP_SIMD)
12061 if (matched)
12062 return 0;
12063 simd_seen = true;
12065 ++matched;
12067 if (ctx->code == OMP_TARGET)
12069 if (scores == NULL)
12070 return matched < nconstructs ? 0 : simd_seen ? -1 : 1;
12071 target_seen = true;
12072 break;
12075 else if (ctx->region_type == ORT_WORKSHARE
12076 && ctx->code == OMP_LOOP
12077 && ctx->outer_context
12078 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL
12079 && ctx->outer_context->outer_context
12080 && ctx->outer_context->outer_context->code == OMP_LOOP
12081 && ctx->outer_context->outer_context->distribute)
12082 ctx = ctx->outer_context->outer_context;
12083 ctx = ctx->outer_context;
12085 if (!target_seen
12086 && lookup_attribute ("omp declare simd",
12087 DECL_ATTRIBUTES (current_function_decl)))
12089 /* Declare simd is a maybe case, it is supposed to be added only to the
12090 omp-simd-clone.cc added clones and not to the base function. */
12091 declare_simd_cnt = cnt++;
12092 if (scores)
12093 codes.safe_push (OMP_SIMD);
12094 else if (cnt == 0
12095 && constructs[0] == OMP_SIMD)
12097 gcc_assert (matched == 0);
12098 simd_seen = true;
12099 if (++matched == nconstructs)
12100 return -1;
12103 if (tree attr = lookup_attribute ("omp declare variant variant",
12104 DECL_ATTRIBUTES (current_function_decl)))
12106 enum tree_code variant_constructs[5];
12107 int variant_nconstructs = 0;
12108 if (!target_seen)
12109 variant_nconstructs
12110 = omp_constructor_traits_to_codes (TREE_VALUE (attr),
12111 variant_constructs);
12112 for (int i = 0; i < variant_nconstructs; i++)
12114 ++cnt;
12115 if (scores)
12116 codes.safe_push (variant_constructs[i]);
12117 else if (matched < nconstructs
12118 && variant_constructs[i] == constructs[matched])
12120 if (variant_constructs[i] == OMP_SIMD)
12122 if (matched)
12123 return 0;
12124 simd_seen = true;
12126 ++matched;
12130 if (!target_seen
12131 && lookup_attribute ("omp declare target block",
12132 DECL_ATTRIBUTES (current_function_decl)))
12134 if (scores)
12135 codes.safe_push (OMP_TARGET);
12136 else if (matched < nconstructs && constructs[matched] == OMP_TARGET)
12137 ++matched;
12139 if (scores)
12141 for (int pass = 0; pass < (declare_simd_cnt == -1 ? 1 : 2); pass++)
12143 int j = codes.length () - 1;
12144 for (int i = nconstructs - 1; i >= 0; i--)
12146 while (j >= 0
12147 && (pass != 0 || declare_simd_cnt != j)
12148 && constructs[i] != codes[j])
12149 --j;
12150 if (pass == 0 && declare_simd_cnt != -1 && j > declare_simd_cnt)
12151 *scores++ = j - 1;
12152 else
12153 *scores++ = j;
12155 *scores++ = ((pass == 0 && declare_simd_cnt != -1)
12156 ? codes.length () - 1 : codes.length ());
12158 return declare_simd_cnt == -1 ? 1 : 2;
12160 if (matched == nconstructs)
12161 return simd_seen ? -1 : 1;
12162 return 0;
12165 /* Gimplify OACC_CACHE. */
12167 static void
12168 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
12170 tree expr = *expr_p;
12172 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
12173 OACC_CACHE);
12174 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
12175 OACC_CACHE);
12177 /* TODO: Do something sensible with this information. */
12179 *expr_p = NULL_TREE;
12182 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
12183 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
12184 kind. The entry kind will replace the one in CLAUSE, while the exit
12185 kind will be used in a new omp_clause and returned to the caller. */
12187 static tree
12188 gimplify_oacc_declare_1 (tree clause)
12190 HOST_WIDE_INT kind, new_op;
12191 bool ret = false;
12192 tree c = NULL;
12194 kind = OMP_CLAUSE_MAP_KIND (clause);
12196 switch (kind)
12198 case GOMP_MAP_ALLOC:
12199 new_op = GOMP_MAP_RELEASE;
12200 ret = true;
12201 break;
12203 case GOMP_MAP_FROM:
12204 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
12205 new_op = GOMP_MAP_FROM;
12206 ret = true;
12207 break;
12209 case GOMP_MAP_TOFROM:
12210 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
12211 new_op = GOMP_MAP_FROM;
12212 ret = true;
12213 break;
12215 case GOMP_MAP_DEVICE_RESIDENT:
12216 case GOMP_MAP_FORCE_DEVICEPTR:
12217 case GOMP_MAP_FORCE_PRESENT:
12218 case GOMP_MAP_LINK:
12219 case GOMP_MAP_POINTER:
12220 case GOMP_MAP_TO:
12221 break;
12223 default:
12224 gcc_unreachable ();
12225 break;
12228 if (ret)
12230 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
12231 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
12232 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
12235 return c;
12238 /* Gimplify OACC_DECLARE. */
12240 static void
12241 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
12243 tree expr = *expr_p;
12244 gomp_target *stmt;
12245 tree clauses, t, decl;
12247 clauses = OACC_DECLARE_CLAUSES (expr);
12249 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
12250 gimplify_adjust_omp_clauses (pre_p, NULL, &clauses, OACC_DECLARE);
12252 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
12254 decl = OMP_CLAUSE_DECL (t);
12256 if (TREE_CODE (decl) == MEM_REF)
12257 decl = TREE_OPERAND (decl, 0);
12259 if (VAR_P (decl) && !is_oacc_declared (decl))
12261 tree attr = get_identifier ("oacc declare target");
12262 DECL_ATTRIBUTES (decl) = tree_cons (attr, NULL_TREE,
12263 DECL_ATTRIBUTES (decl));
12266 if (VAR_P (decl)
12267 && !is_global_var (decl)
12268 && DECL_CONTEXT (decl) == current_function_decl)
12270 tree c = gimplify_oacc_declare_1 (t);
12271 if (c)
12273 if (oacc_declare_returns == NULL)
12274 oacc_declare_returns = new hash_map<tree, tree>;
12276 oacc_declare_returns->put (decl, c);
12280 if (gimplify_omp_ctxp)
12281 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
12284 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
12285 clauses);
12287 gimplify_seq_add_stmt (pre_p, stmt);
12289 *expr_p = NULL_TREE;
12292 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
12293 gimplification of the body, as well as scanning the body for used
12294 variables. We need to do this scan now, because variable-sized
12295 decls will be decomposed during gimplification. */
12297 static void
12298 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
12300 tree expr = *expr_p;
12301 gimple *g;
12302 gimple_seq body = NULL;
12304 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
12305 OMP_PARALLEL_COMBINED (expr)
12306 ? ORT_COMBINED_PARALLEL
12307 : ORT_PARALLEL, OMP_PARALLEL);
12309 push_gimplify_context ();
12311 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
12312 if (gimple_code (g) == GIMPLE_BIND)
12313 pop_gimplify_context (g);
12314 else
12315 pop_gimplify_context (NULL);
12317 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
12318 OMP_PARALLEL);
12320 g = gimple_build_omp_parallel (body,
12321 OMP_PARALLEL_CLAUSES (expr),
12322 NULL_TREE, NULL_TREE);
12323 if (OMP_PARALLEL_COMBINED (expr))
12324 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
12325 gimplify_seq_add_stmt (pre_p, g);
12326 *expr_p = NULL_TREE;
12329 /* Gimplify the contents of an OMP_TASK statement. This involves
12330 gimplification of the body, as well as scanning the body for used
12331 variables. We need to do this scan now, because variable-sized
12332 decls will be decomposed during gimplification. */
12334 static void
12335 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
12337 tree expr = *expr_p;
12338 gimple *g;
12339 gimple_seq body = NULL;
12340 bool nowait = false;
12341 bool has_depend = false;
12343 if (OMP_TASK_BODY (expr) == NULL_TREE)
12345 for (tree c = OMP_TASK_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
12346 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
12348 has_depend = true;
12349 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_MUTEXINOUTSET)
12351 error_at (OMP_CLAUSE_LOCATION (c),
12352 "%<mutexinoutset%> kind in %<depend%> clause on a "
12353 "%<taskwait%> construct");
12354 break;
12357 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NOWAIT)
12358 nowait = true;
12359 if (nowait && !has_depend)
12361 error_at (EXPR_LOCATION (expr),
12362 "%<taskwait%> construct with %<nowait%> clause but no "
12363 "%<depend%> clauses");
12364 *expr_p = NULL_TREE;
12365 return;
12369 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
12370 omp_find_clause (OMP_TASK_CLAUSES (expr),
12371 OMP_CLAUSE_UNTIED)
12372 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
12374 if (OMP_TASK_BODY (expr))
12376 push_gimplify_context ();
12378 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
12379 if (gimple_code (g) == GIMPLE_BIND)
12380 pop_gimplify_context (g);
12381 else
12382 pop_gimplify_context (NULL);
12385 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
12386 OMP_TASK);
12388 g = gimple_build_omp_task (body,
12389 OMP_TASK_CLAUSES (expr),
12390 NULL_TREE, NULL_TREE,
12391 NULL_TREE, NULL_TREE, NULL_TREE);
12392 if (OMP_TASK_BODY (expr) == NULL_TREE)
12393 gimple_omp_task_set_taskwait_p (g, true);
12394 gimplify_seq_add_stmt (pre_p, g);
12395 *expr_p = NULL_TREE;
12398 /* Helper function for gimplify_omp_for. If *TP is not a gimple constant,
12399 force it into a temporary initialized in PRE_P and add firstprivate clause
12400 to ORIG_FOR_STMT. */
12402 static void
12403 gimplify_omp_taskloop_expr (tree type, tree *tp, gimple_seq *pre_p,
12404 tree orig_for_stmt)
12406 if (*tp == NULL || is_gimple_constant (*tp))
12407 return;
12409 *tp = get_initialized_tmp_var (*tp, pre_p, NULL, false);
12410 /* Reference to pointer conversion is considered useless,
12411 but is significant for firstprivate clause. Force it
12412 here. */
12413 if (type
12414 && TREE_CODE (type) == POINTER_TYPE
12415 && TREE_CODE (TREE_TYPE (*tp)) == REFERENCE_TYPE)
12417 tree v = create_tmp_var (TYPE_MAIN_VARIANT (type));
12418 tree m = build2 (INIT_EXPR, TREE_TYPE (v), v, *tp);
12419 gimplify_and_add (m, pre_p);
12420 *tp = v;
12423 tree c = build_omp_clause (input_location, OMP_CLAUSE_FIRSTPRIVATE);
12424 OMP_CLAUSE_DECL (c) = *tp;
12425 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
12426 OMP_FOR_CLAUSES (orig_for_stmt) = c;
12429 /* Helper function of gimplify_omp_for, find OMP_ORDERED with
12430 null OMP_ORDERED_BODY inside of OMP_FOR's body. */
12432 static tree
12433 find_standalone_omp_ordered (tree *tp, int *walk_subtrees, void *)
12435 switch (TREE_CODE (*tp))
12437 case OMP_ORDERED:
12438 if (OMP_ORDERED_BODY (*tp) == NULL_TREE)
12439 return *tp;
12440 break;
12441 case OMP_SIMD:
12442 case OMP_PARALLEL:
12443 case OMP_TARGET:
12444 *walk_subtrees = 0;
12445 break;
12446 default:
12447 break;
12449 return NULL_TREE;
12452 /* Gimplify the gross structure of an OMP_FOR statement. */
12454 static enum gimplify_status
12455 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
12457 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
12458 enum gimplify_status ret = GS_ALL_DONE;
12459 enum gimplify_status tret;
12460 gomp_for *gfor;
12461 gimple_seq for_body, for_pre_body;
12462 int i;
12463 bitmap has_decl_expr = NULL;
12464 enum omp_region_type ort = ORT_WORKSHARE;
12465 bool openacc = TREE_CODE (*expr_p) == OACC_LOOP;
12467 orig_for_stmt = for_stmt = *expr_p;
12469 bool loop_p = (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_BIND)
12470 != NULL_TREE);
12471 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
12473 tree *data[4] = { NULL, NULL, NULL, NULL };
12474 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
12475 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
12476 find_combined_omp_for, data, NULL);
12477 if (inner_for_stmt == NULL_TREE)
12479 gcc_assert (seen_error ());
12480 *expr_p = NULL_TREE;
12481 return GS_ERROR;
12483 if (data[2] && OMP_FOR_PRE_BODY (*data[2]))
12485 append_to_statement_list_force (OMP_FOR_PRE_BODY (*data[2]),
12486 &OMP_FOR_PRE_BODY (for_stmt));
12487 OMP_FOR_PRE_BODY (*data[2]) = NULL_TREE;
12489 if (OMP_FOR_PRE_BODY (inner_for_stmt))
12491 append_to_statement_list_force (OMP_FOR_PRE_BODY (inner_for_stmt),
12492 &OMP_FOR_PRE_BODY (for_stmt));
12493 OMP_FOR_PRE_BODY (inner_for_stmt) = NULL_TREE;
12496 if (data[0])
12498 /* We have some statements or variable declarations in between
12499 the composite construct directives. Move them around the
12500 inner_for_stmt. */
12501 data[0] = expr_p;
12502 for (i = 0; i < 3; i++)
12503 if (data[i])
12505 tree t = *data[i];
12506 if (i < 2 && data[i + 1] == &OMP_BODY (t))
12507 data[i + 1] = data[i];
12508 *data[i] = OMP_BODY (t);
12509 tree body = build3 (BIND_EXPR, void_type_node, NULL_TREE,
12510 NULL_TREE, make_node (BLOCK));
12511 OMP_BODY (t) = body;
12512 append_to_statement_list_force (inner_for_stmt,
12513 &BIND_EXPR_BODY (body));
12514 *data[3] = t;
12515 data[3] = tsi_stmt_ptr (tsi_start (BIND_EXPR_BODY (body)));
12516 gcc_assert (*data[3] == inner_for_stmt);
12518 return GS_OK;
12521 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
12522 if (!loop_p
12523 && OMP_FOR_ORIG_DECLS (inner_for_stmt)
12524 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
12525 i)) == TREE_LIST
12526 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
12527 i)))
12529 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
12530 /* Class iterators aren't allowed on OMP_SIMD, so the only
12531 case we need to solve is distribute parallel for. They are
12532 allowed on the loop construct, but that is already handled
12533 in gimplify_omp_loop. */
12534 gcc_assert (TREE_CODE (inner_for_stmt) == OMP_FOR
12535 && TREE_CODE (for_stmt) == OMP_DISTRIBUTE
12536 && data[1]);
12537 tree orig_decl = TREE_PURPOSE (orig);
12538 tree last = TREE_VALUE (orig);
12539 tree *pc;
12540 for (pc = &OMP_FOR_CLAUSES (inner_for_stmt);
12541 *pc; pc = &OMP_CLAUSE_CHAIN (*pc))
12542 if ((OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE
12543 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LASTPRIVATE)
12544 && OMP_CLAUSE_DECL (*pc) == orig_decl)
12545 break;
12546 if (*pc == NULL_TREE)
12548 tree *spc;
12549 for (spc = &OMP_PARALLEL_CLAUSES (*data[1]);
12550 *spc; spc = &OMP_CLAUSE_CHAIN (*spc))
12551 if (OMP_CLAUSE_CODE (*spc) == OMP_CLAUSE_PRIVATE
12552 && OMP_CLAUSE_DECL (*spc) == orig_decl)
12553 break;
12554 if (*spc)
12556 tree c = *spc;
12557 *spc = OMP_CLAUSE_CHAIN (c);
12558 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
12559 *pc = c;
12562 if (*pc == NULL_TREE)
12564 else if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE)
12566 /* private clause will appear only on inner_for_stmt.
12567 Change it into firstprivate, and add private clause
12568 on for_stmt. */
12569 tree c = copy_node (*pc);
12570 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12571 OMP_FOR_CLAUSES (for_stmt) = c;
12572 OMP_CLAUSE_CODE (*pc) = OMP_CLAUSE_FIRSTPRIVATE;
12573 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
12575 else
12577 /* lastprivate clause will appear on both inner_for_stmt
12578 and for_stmt. Add firstprivate clause to
12579 inner_for_stmt. */
12580 tree c = build_omp_clause (OMP_CLAUSE_LOCATION (*pc),
12581 OMP_CLAUSE_FIRSTPRIVATE);
12582 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (*pc);
12583 OMP_CLAUSE_CHAIN (c) = *pc;
12584 *pc = c;
12585 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
12587 tree c = build_omp_clause (UNKNOWN_LOCATION,
12588 OMP_CLAUSE_FIRSTPRIVATE);
12589 OMP_CLAUSE_DECL (c) = last;
12590 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12591 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12592 c = build_omp_clause (UNKNOWN_LOCATION,
12593 *pc ? OMP_CLAUSE_SHARED
12594 : OMP_CLAUSE_FIRSTPRIVATE);
12595 OMP_CLAUSE_DECL (c) = orig_decl;
12596 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12597 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12599 /* Similarly, take care of C++ range for temporaries, those should
12600 be firstprivate on OMP_PARALLEL if any. */
12601 if (data[1])
12602 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
12603 if (OMP_FOR_ORIG_DECLS (inner_for_stmt)
12604 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
12605 i)) == TREE_LIST
12606 && TREE_CHAIN (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
12607 i)))
12609 tree orig
12610 = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
12611 tree v = TREE_CHAIN (orig);
12612 tree c = build_omp_clause (UNKNOWN_LOCATION,
12613 OMP_CLAUSE_FIRSTPRIVATE);
12614 /* First add firstprivate clause for the __for_end artificial
12615 decl. */
12616 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 1);
12617 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
12618 == REFERENCE_TYPE)
12619 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
12620 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12621 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12622 if (TREE_VEC_ELT (v, 0))
12624 /* And now the same for __for_range artificial decl if it
12625 exists. */
12626 c = build_omp_clause (UNKNOWN_LOCATION,
12627 OMP_CLAUSE_FIRSTPRIVATE);
12628 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 0);
12629 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
12630 == REFERENCE_TYPE)
12631 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
12632 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
12633 OMP_PARALLEL_CLAUSES (*data[1]) = c;
12638 switch (TREE_CODE (for_stmt))
12640 case OMP_FOR:
12641 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
12643 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12644 OMP_CLAUSE_SCHEDULE))
12645 error_at (EXPR_LOCATION (for_stmt),
12646 "%qs clause may not appear on non-rectangular %qs",
12647 "schedule", lang_GNU_Fortran () ? "do" : "for");
12648 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED))
12649 error_at (EXPR_LOCATION (for_stmt),
12650 "%qs clause may not appear on non-rectangular %qs",
12651 "ordered", lang_GNU_Fortran () ? "do" : "for");
12653 break;
12654 case OMP_DISTRIBUTE:
12655 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt)
12656 && omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12657 OMP_CLAUSE_DIST_SCHEDULE))
12658 error_at (EXPR_LOCATION (for_stmt),
12659 "%qs clause may not appear on non-rectangular %qs",
12660 "dist_schedule", "distribute");
12661 break;
12662 case OACC_LOOP:
12663 ort = ORT_ACC;
12664 break;
12665 case OMP_TASKLOOP:
12666 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
12668 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12669 OMP_CLAUSE_GRAINSIZE))
12670 error_at (EXPR_LOCATION (for_stmt),
12671 "%qs clause may not appear on non-rectangular %qs",
12672 "grainsize", "taskloop");
12673 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12674 OMP_CLAUSE_NUM_TASKS))
12675 error_at (EXPR_LOCATION (for_stmt),
12676 "%qs clause may not appear on non-rectangular %qs",
12677 "num_tasks", "taskloop");
12679 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
12680 ort = ORT_UNTIED_TASKLOOP;
12681 else
12682 ort = ORT_TASKLOOP;
12683 break;
12684 case OMP_SIMD:
12685 ort = ORT_SIMD;
12686 break;
12687 default:
12688 gcc_unreachable ();
12691 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
12692 clause for the IV. */
12693 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
12695 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
12696 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12697 decl = TREE_OPERAND (t, 0);
12698 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
12699 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12700 && OMP_CLAUSE_DECL (c) == decl)
12702 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
12703 break;
12707 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
12708 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
12709 loop_p && TREE_CODE (for_stmt) != OMP_SIMD
12710 ? OMP_LOOP : TREE_CODE (for_stmt));
12712 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
12713 gimplify_omp_ctxp->distribute = true;
12715 /* Handle OMP_FOR_INIT. */
12716 for_pre_body = NULL;
12717 if ((ort == ORT_SIMD
12718 || (inner_for_stmt && TREE_CODE (inner_for_stmt) == OMP_SIMD))
12719 && OMP_FOR_PRE_BODY (for_stmt))
12721 has_decl_expr = BITMAP_ALLOC (NULL);
12722 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
12723 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
12724 == VAR_DECL)
12726 t = OMP_FOR_PRE_BODY (for_stmt);
12727 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
12729 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
12731 tree_stmt_iterator si;
12732 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
12733 tsi_next (&si))
12735 t = tsi_stmt (si);
12736 if (TREE_CODE (t) == DECL_EXPR
12737 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
12738 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
12742 if (OMP_FOR_PRE_BODY (for_stmt))
12744 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
12745 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
12746 else
12748 struct gimplify_omp_ctx ctx;
12749 memset (&ctx, 0, sizeof (ctx));
12750 ctx.region_type = ORT_NONE;
12751 gimplify_omp_ctxp = &ctx;
12752 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
12753 gimplify_omp_ctxp = NULL;
12756 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
12758 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
12759 for_stmt = inner_for_stmt;
12761 /* For taskloop, need to gimplify the start, end and step before the
12762 taskloop, outside of the taskloop omp context. */
12763 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12765 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12767 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12768 gimple_seq *for_pre_p = (gimple_seq_empty_p (for_pre_body)
12769 ? pre_p : &for_pre_body);
12770 tree type = TREE_TYPE (TREE_OPERAND (t, 0));
12771 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12773 tree v = TREE_OPERAND (t, 1);
12774 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
12775 for_pre_p, orig_for_stmt);
12776 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
12777 for_pre_p, orig_for_stmt);
12779 else
12780 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
12781 orig_for_stmt);
12783 /* Handle OMP_FOR_COND. */
12784 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12785 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12787 tree v = TREE_OPERAND (t, 1);
12788 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
12789 for_pre_p, orig_for_stmt);
12790 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
12791 for_pre_p, orig_for_stmt);
12793 else
12794 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
12795 orig_for_stmt);
12797 /* Handle OMP_FOR_INCR. */
12798 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12799 if (TREE_CODE (t) == MODIFY_EXPR)
12801 decl = TREE_OPERAND (t, 0);
12802 t = TREE_OPERAND (t, 1);
12803 tree *tp = &TREE_OPERAND (t, 1);
12804 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
12805 tp = &TREE_OPERAND (t, 0);
12807 gimplify_omp_taskloop_expr (NULL_TREE, tp, for_pre_p,
12808 orig_for_stmt);
12812 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
12813 OMP_TASKLOOP);
12816 if (orig_for_stmt != for_stmt)
12817 gimplify_omp_ctxp->combined_loop = true;
12819 for_body = NULL;
12820 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12821 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
12822 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12823 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
12825 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
12826 bool is_doacross = false;
12827 if (c && walk_tree_without_duplicates (&OMP_FOR_BODY (for_stmt),
12828 find_standalone_omp_ordered, NULL))
12830 OMP_CLAUSE_ORDERED_DOACROSS (c) = 1;
12831 is_doacross = true;
12832 int len = TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt));
12833 gimplify_omp_ctxp->loop_iter_var.create (len * 2);
12834 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
12835 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LINEAR)
12837 error_at (OMP_CLAUSE_LOCATION (*pc),
12838 "%<linear%> clause may not be specified together "
12839 "with %<ordered%> clause if stand-alone %<ordered%> "
12840 "construct is nested in it");
12841 *pc = OMP_CLAUSE_CHAIN (*pc);
12843 else
12844 pc = &OMP_CLAUSE_CHAIN (*pc);
12846 int collapse = 1, tile = 0;
12847 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
12848 if (c)
12849 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
12850 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_TILE);
12851 if (c)
12852 tile = list_length (OMP_CLAUSE_TILE_LIST (c));
12853 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ALLOCATE);
12854 hash_set<tree> *allocate_uids = NULL;
12855 if (c)
12857 allocate_uids = new hash_set<tree>;
12858 for (; c; c = OMP_CLAUSE_CHAIN (c))
12859 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_ALLOCATE)
12860 allocate_uids->add (OMP_CLAUSE_DECL (c));
12862 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12864 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12865 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12866 decl = TREE_OPERAND (t, 0);
12867 gcc_assert (DECL_P (decl));
12868 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
12869 || POINTER_TYPE_P (TREE_TYPE (decl)));
12870 if (is_doacross)
12872 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
12874 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12875 if (TREE_CODE (orig_decl) == TREE_LIST)
12877 orig_decl = TREE_PURPOSE (orig_decl);
12878 if (!orig_decl)
12879 orig_decl = decl;
12881 gimplify_omp_ctxp->loop_iter_var.quick_push (orig_decl);
12883 else
12884 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
12885 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
12888 if (for_stmt == orig_for_stmt)
12890 tree orig_decl = decl;
12891 if (OMP_FOR_ORIG_DECLS (for_stmt))
12893 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12894 if (TREE_CODE (orig_decl) == TREE_LIST)
12896 orig_decl = TREE_PURPOSE (orig_decl);
12897 if (!orig_decl)
12898 orig_decl = decl;
12901 if (is_global_var (orig_decl) && DECL_THREAD_LOCAL_P (orig_decl))
12902 error_at (EXPR_LOCATION (for_stmt),
12903 "threadprivate iteration variable %qD", orig_decl);
12906 /* Make sure the iteration variable is private. */
12907 tree c = NULL_TREE;
12908 tree c2 = NULL_TREE;
12909 if (orig_for_stmt != for_stmt)
12911 /* Preserve this information until we gimplify the inner simd. */
12912 if (has_decl_expr
12913 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
12914 TREE_PRIVATE (t) = 1;
12916 else if (ort == ORT_SIMD)
12918 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
12919 (splay_tree_key) decl);
12920 omp_is_private (gimplify_omp_ctxp, decl,
12921 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
12922 != 1));
12923 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
12925 omp_notice_variable (gimplify_omp_ctxp, decl, true);
12926 if (n->value & GOVD_LASTPRIVATE_CONDITIONAL)
12927 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12928 OMP_CLAUSE_LASTPRIVATE);
12929 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
12930 OMP_CLAUSE_LASTPRIVATE))
12931 if (OMP_CLAUSE_DECL (c3) == decl)
12933 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
12934 "conditional %<lastprivate%> on loop "
12935 "iterator %qD ignored", decl);
12936 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
12937 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
12940 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1 && !loop_p)
12942 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
12943 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
12944 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
12945 if ((has_decl_expr
12946 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
12947 || TREE_PRIVATE (t))
12949 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12950 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12952 struct gimplify_omp_ctx *outer
12953 = gimplify_omp_ctxp->outer_context;
12954 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12956 if (outer->region_type == ORT_WORKSHARE
12957 && outer->combined_loop)
12959 n = splay_tree_lookup (outer->variables,
12960 (splay_tree_key)decl);
12961 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
12963 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12964 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12966 else
12968 struct gimplify_omp_ctx *octx = outer->outer_context;
12969 if (octx
12970 && octx->region_type == ORT_COMBINED_PARALLEL
12971 && octx->outer_context
12972 && (octx->outer_context->region_type
12973 == ORT_WORKSHARE)
12974 && octx->outer_context->combined_loop)
12976 octx = octx->outer_context;
12977 n = splay_tree_lookup (octx->variables,
12978 (splay_tree_key)decl);
12979 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
12981 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12982 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12989 OMP_CLAUSE_DECL (c) = decl;
12990 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12991 OMP_FOR_CLAUSES (for_stmt) = c;
12992 omp_add_variable (gimplify_omp_ctxp, decl, flags);
12993 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12994 omp_lastprivate_for_combined_outer_constructs (outer, decl,
12995 true);
12997 else
12999 bool lastprivate
13000 = (!has_decl_expr
13001 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
13002 if (TREE_PRIVATE (t))
13003 lastprivate = false;
13004 if (loop_p && OMP_FOR_ORIG_DECLS (for_stmt))
13006 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
13007 if (TREE_CODE (elt) == TREE_LIST && TREE_PURPOSE (elt))
13008 lastprivate = false;
13011 struct gimplify_omp_ctx *outer
13012 = gimplify_omp_ctxp->outer_context;
13013 if (outer && lastprivate)
13014 omp_lastprivate_for_combined_outer_constructs (outer, decl,
13015 true);
13017 c = build_omp_clause (input_location,
13018 lastprivate ? OMP_CLAUSE_LASTPRIVATE
13019 : OMP_CLAUSE_PRIVATE);
13020 OMP_CLAUSE_DECL (c) = decl;
13021 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
13022 OMP_FOR_CLAUSES (for_stmt) = c;
13023 omp_add_variable (gimplify_omp_ctxp, decl,
13024 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
13025 | GOVD_EXPLICIT | GOVD_SEEN);
13026 c = NULL_TREE;
13029 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
13031 omp_notice_variable (gimplify_omp_ctxp, decl, true);
13032 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
13033 (splay_tree_key) decl);
13034 if (n && (n->value & GOVD_LASTPRIVATE_CONDITIONAL))
13035 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
13036 OMP_CLAUSE_LASTPRIVATE);
13037 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
13038 OMP_CLAUSE_LASTPRIVATE))
13039 if (OMP_CLAUSE_DECL (c3) == decl)
13041 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
13042 "conditional %<lastprivate%> on loop "
13043 "iterator %qD ignored", decl);
13044 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
13045 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
13048 else
13049 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
13051 /* If DECL is not a gimple register, create a temporary variable to act
13052 as an iteration counter. This is valid, since DECL cannot be
13053 modified in the body of the loop. Similarly for any iteration vars
13054 in simd with collapse > 1 where the iterator vars must be
13055 lastprivate. And similarly for vars mentioned in allocate clauses. */
13056 if (orig_for_stmt != for_stmt)
13057 var = decl;
13058 else if (!is_gimple_reg (decl)
13059 || (ort == ORT_SIMD
13060 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
13061 || (allocate_uids && allocate_uids->contains (decl)))
13063 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13064 /* Make sure omp_add_variable is not called on it prematurely.
13065 We call it ourselves a few lines later. */
13066 gimplify_omp_ctxp = NULL;
13067 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
13068 gimplify_omp_ctxp = ctx;
13069 TREE_OPERAND (t, 0) = var;
13071 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
13073 if (ort == ORT_SIMD
13074 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
13076 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
13077 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
13078 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
13079 OMP_CLAUSE_DECL (c2) = var;
13080 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
13081 OMP_FOR_CLAUSES (for_stmt) = c2;
13082 omp_add_variable (gimplify_omp_ctxp, var,
13083 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
13084 if (c == NULL_TREE)
13086 c = c2;
13087 c2 = NULL_TREE;
13090 else
13091 omp_add_variable (gimplify_omp_ctxp, var,
13092 GOVD_PRIVATE | GOVD_SEEN);
13094 else
13095 var = decl;
13097 gimplify_omp_ctxp->in_for_exprs = true;
13098 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
13100 tree lb = TREE_OPERAND (t, 1);
13101 tret = gimplify_expr (&TREE_VEC_ELT (lb, 1), &for_pre_body, NULL,
13102 is_gimple_val, fb_rvalue, false);
13103 ret = MIN (ret, tret);
13104 tret = gimplify_expr (&TREE_VEC_ELT (lb, 2), &for_pre_body, NULL,
13105 is_gimple_val, fb_rvalue, false);
13107 else
13108 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
13109 is_gimple_val, fb_rvalue, false);
13110 gimplify_omp_ctxp->in_for_exprs = false;
13111 ret = MIN (ret, tret);
13112 if (ret == GS_ERROR)
13113 return ret;
13115 /* Handle OMP_FOR_COND. */
13116 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
13117 gcc_assert (COMPARISON_CLASS_P (t));
13118 gcc_assert (TREE_OPERAND (t, 0) == decl);
13120 gimplify_omp_ctxp->in_for_exprs = true;
13121 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
13123 tree ub = TREE_OPERAND (t, 1);
13124 tret = gimplify_expr (&TREE_VEC_ELT (ub, 1), &for_pre_body, NULL,
13125 is_gimple_val, fb_rvalue, false);
13126 ret = MIN (ret, tret);
13127 tret = gimplify_expr (&TREE_VEC_ELT (ub, 2), &for_pre_body, NULL,
13128 is_gimple_val, fb_rvalue, false);
13130 else
13131 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
13132 is_gimple_val, fb_rvalue, false);
13133 gimplify_omp_ctxp->in_for_exprs = false;
13134 ret = MIN (ret, tret);
13136 /* Handle OMP_FOR_INCR. */
13137 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
13138 switch (TREE_CODE (t))
13140 case PREINCREMENT_EXPR:
13141 case POSTINCREMENT_EXPR:
13143 tree decl = TREE_OPERAND (t, 0);
13144 /* c_omp_for_incr_canonicalize_ptr() should have been
13145 called to massage things appropriately. */
13146 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
13148 if (orig_for_stmt != for_stmt)
13149 break;
13150 t = build_int_cst (TREE_TYPE (decl), 1);
13151 if (c)
13152 OMP_CLAUSE_LINEAR_STEP (c) = t;
13153 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
13154 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
13155 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
13156 break;
13159 case PREDECREMENT_EXPR:
13160 case POSTDECREMENT_EXPR:
13161 /* c_omp_for_incr_canonicalize_ptr() should have been
13162 called to massage things appropriately. */
13163 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
13164 if (orig_for_stmt != for_stmt)
13165 break;
13166 t = build_int_cst (TREE_TYPE (decl), -1);
13167 if (c)
13168 OMP_CLAUSE_LINEAR_STEP (c) = t;
13169 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
13170 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
13171 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
13172 break;
13174 case MODIFY_EXPR:
13175 gcc_assert (TREE_OPERAND (t, 0) == decl);
13176 TREE_OPERAND (t, 0) = var;
13178 t = TREE_OPERAND (t, 1);
13179 switch (TREE_CODE (t))
13181 case PLUS_EXPR:
13182 if (TREE_OPERAND (t, 1) == decl)
13184 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
13185 TREE_OPERAND (t, 0) = var;
13186 break;
13189 /* Fallthru. */
13190 case MINUS_EXPR:
13191 case POINTER_PLUS_EXPR:
13192 gcc_assert (TREE_OPERAND (t, 0) == decl);
13193 TREE_OPERAND (t, 0) = var;
13194 break;
13195 default:
13196 gcc_unreachable ();
13199 gimplify_omp_ctxp->in_for_exprs = true;
13200 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
13201 is_gimple_val, fb_rvalue, false);
13202 ret = MIN (ret, tret);
13203 if (c)
13205 tree step = TREE_OPERAND (t, 1);
13206 tree stept = TREE_TYPE (decl);
13207 if (POINTER_TYPE_P (stept))
13208 stept = sizetype;
13209 step = fold_convert (stept, step);
13210 if (TREE_CODE (t) == MINUS_EXPR)
13211 step = fold_build1 (NEGATE_EXPR, stept, step);
13212 OMP_CLAUSE_LINEAR_STEP (c) = step;
13213 if (step != TREE_OPERAND (t, 1))
13215 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
13216 &for_pre_body, NULL,
13217 is_gimple_val, fb_rvalue, false);
13218 ret = MIN (ret, tret);
13221 gimplify_omp_ctxp->in_for_exprs = false;
13222 break;
13224 default:
13225 gcc_unreachable ();
13228 if (c2)
13230 gcc_assert (c);
13231 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
13234 if ((var != decl || collapse > 1 || tile) && orig_for_stmt == for_stmt)
13236 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
13237 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13238 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
13239 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
13240 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
13241 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
13242 && OMP_CLAUSE_DECL (c) == decl)
13244 if (is_doacross && (collapse == 1 || i >= collapse))
13245 t = var;
13246 else
13248 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
13249 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
13250 gcc_assert (TREE_OPERAND (t, 0) == var);
13251 t = TREE_OPERAND (t, 1);
13252 gcc_assert (TREE_CODE (t) == PLUS_EXPR
13253 || TREE_CODE (t) == MINUS_EXPR
13254 || TREE_CODE (t) == POINTER_PLUS_EXPR);
13255 gcc_assert (TREE_OPERAND (t, 0) == var);
13256 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
13257 is_doacross ? var : decl,
13258 TREE_OPERAND (t, 1));
13260 gimple_seq *seq;
13261 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
13262 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
13263 else
13264 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
13265 push_gimplify_context ();
13266 gimplify_assign (decl, t, seq);
13267 gimple *bind = NULL;
13268 if (gimplify_ctxp->temps)
13270 bind = gimple_build_bind (NULL_TREE, *seq, NULL_TREE);
13271 *seq = NULL;
13272 gimplify_seq_add_stmt (seq, bind);
13274 pop_gimplify_context (bind);
13277 if (OMP_FOR_NON_RECTANGULAR (for_stmt) && var != decl)
13278 for (int j = i + 1; j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
13280 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
13281 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
13282 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
13283 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
13284 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
13285 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
13286 gcc_assert (COMPARISON_CLASS_P (t));
13287 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
13288 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
13289 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
13293 BITMAP_FREE (has_decl_expr);
13294 delete allocate_uids;
13296 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
13297 || (loop_p && orig_for_stmt == for_stmt))
13299 push_gimplify_context ();
13300 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
13302 OMP_FOR_BODY (orig_for_stmt)
13303 = build3 (BIND_EXPR, void_type_node, NULL,
13304 OMP_FOR_BODY (orig_for_stmt), NULL);
13305 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
13309 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
13310 &for_body);
13312 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
13313 || (loop_p && orig_for_stmt == for_stmt))
13315 if (gimple_code (g) == GIMPLE_BIND)
13316 pop_gimplify_context (g);
13317 else
13318 pop_gimplify_context (NULL);
13321 if (orig_for_stmt != for_stmt)
13322 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
13324 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
13325 decl = TREE_OPERAND (t, 0);
13326 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13327 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
13328 gimplify_omp_ctxp = ctx->outer_context;
13329 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
13330 gimplify_omp_ctxp = ctx;
13331 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
13332 TREE_OPERAND (t, 0) = var;
13333 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
13334 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
13335 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
13336 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
13337 for (int j = i + 1;
13338 j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
13340 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
13341 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
13342 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
13343 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
13345 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
13346 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
13348 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
13349 gcc_assert (COMPARISON_CLASS_P (t));
13350 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
13351 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
13353 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
13354 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
13359 gimplify_adjust_omp_clauses (pre_p, for_body,
13360 &OMP_FOR_CLAUSES (orig_for_stmt),
13361 TREE_CODE (orig_for_stmt));
13363 int kind;
13364 switch (TREE_CODE (orig_for_stmt))
13366 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
13367 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
13368 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
13369 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
13370 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
13371 default:
13372 gcc_unreachable ();
13374 if (loop_p && kind == GF_OMP_FOR_KIND_SIMD)
13376 gimplify_seq_add_seq (pre_p, for_pre_body);
13377 for_pre_body = NULL;
13379 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
13380 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
13381 for_pre_body);
13382 if (orig_for_stmt != for_stmt)
13383 gimple_omp_for_set_combined_p (gfor, true);
13384 if (gimplify_omp_ctxp
13385 && (gimplify_omp_ctxp->combined_loop
13386 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
13387 && gimplify_omp_ctxp->outer_context
13388 && gimplify_omp_ctxp->outer_context->combined_loop)))
13390 gimple_omp_for_set_combined_into_p (gfor, true);
13391 if (gimplify_omp_ctxp->combined_loop)
13392 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
13393 else
13394 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
13397 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
13399 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
13400 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
13401 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
13402 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
13403 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
13404 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
13405 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
13406 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
13409 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
13410 constructs with GIMPLE_OMP_TASK sandwiched in between them.
13411 The outer taskloop stands for computing the number of iterations,
13412 counts for collapsed loops and holding taskloop specific clauses.
13413 The task construct stands for the effect of data sharing on the
13414 explicit task it creates and the inner taskloop stands for expansion
13415 of the static loop inside of the explicit task construct. */
13416 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
13418 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
13419 tree task_clauses = NULL_TREE;
13420 tree c = *gfor_clauses_ptr;
13421 tree *gtask_clauses_ptr = &task_clauses;
13422 tree outer_for_clauses = NULL_TREE;
13423 tree *gforo_clauses_ptr = &outer_for_clauses;
13424 bitmap lastprivate_uids = NULL;
13425 if (omp_find_clause (c, OMP_CLAUSE_ALLOCATE))
13427 c = omp_find_clause (c, OMP_CLAUSE_LASTPRIVATE);
13428 if (c)
13430 lastprivate_uids = BITMAP_ALLOC (NULL);
13431 for (; c; c = omp_find_clause (OMP_CLAUSE_CHAIN (c),
13432 OMP_CLAUSE_LASTPRIVATE))
13433 bitmap_set_bit (lastprivate_uids,
13434 DECL_UID (OMP_CLAUSE_DECL (c)));
13436 c = *gfor_clauses_ptr;
13438 for (; c; c = OMP_CLAUSE_CHAIN (c))
13439 switch (OMP_CLAUSE_CODE (c))
13441 /* These clauses are allowed on task, move them there. */
13442 case OMP_CLAUSE_SHARED:
13443 case OMP_CLAUSE_FIRSTPRIVATE:
13444 case OMP_CLAUSE_DEFAULT:
13445 case OMP_CLAUSE_IF:
13446 case OMP_CLAUSE_UNTIED:
13447 case OMP_CLAUSE_FINAL:
13448 case OMP_CLAUSE_MERGEABLE:
13449 case OMP_CLAUSE_PRIORITY:
13450 case OMP_CLAUSE_REDUCTION:
13451 case OMP_CLAUSE_IN_REDUCTION:
13452 *gtask_clauses_ptr = c;
13453 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
13454 break;
13455 case OMP_CLAUSE_PRIVATE:
13456 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
13458 /* We want private on outer for and firstprivate
13459 on task. */
13460 *gtask_clauses_ptr
13461 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13462 OMP_CLAUSE_FIRSTPRIVATE);
13463 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
13464 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
13465 openacc);
13466 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
13467 *gforo_clauses_ptr = c;
13468 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
13470 else
13472 *gtask_clauses_ptr = c;
13473 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
13475 break;
13476 /* These clauses go into outer taskloop clauses. */
13477 case OMP_CLAUSE_GRAINSIZE:
13478 case OMP_CLAUSE_NUM_TASKS:
13479 case OMP_CLAUSE_NOGROUP:
13480 *gforo_clauses_ptr = c;
13481 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
13482 break;
13483 /* Collapse clause we duplicate on both taskloops. */
13484 case OMP_CLAUSE_COLLAPSE:
13485 *gfor_clauses_ptr = c;
13486 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
13487 *gforo_clauses_ptr = copy_node (c);
13488 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
13489 break;
13490 /* For lastprivate, keep the clause on inner taskloop, and add
13491 a shared clause on task. If the same decl is also firstprivate,
13492 add also firstprivate clause on the inner taskloop. */
13493 case OMP_CLAUSE_LASTPRIVATE:
13494 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
13496 /* For taskloop C++ lastprivate IVs, we want:
13497 1) private on outer taskloop
13498 2) firstprivate and shared on task
13499 3) lastprivate on inner taskloop */
13500 *gtask_clauses_ptr
13501 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13502 OMP_CLAUSE_FIRSTPRIVATE);
13503 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
13504 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
13505 openacc);
13506 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
13507 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
13508 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13509 OMP_CLAUSE_PRIVATE);
13510 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
13511 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
13512 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
13513 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
13515 *gfor_clauses_ptr = c;
13516 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
13517 *gtask_clauses_ptr
13518 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
13519 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
13520 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
13521 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
13522 gtask_clauses_ptr
13523 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
13524 break;
13525 /* Allocate clause we duplicate on task and inner taskloop
13526 if the decl is lastprivate, otherwise just put on task. */
13527 case OMP_CLAUSE_ALLOCATE:
13528 if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
13529 && DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
13531 /* Additionally, put firstprivate clause on task
13532 for the allocator if it is not constant. */
13533 *gtask_clauses_ptr
13534 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13535 OMP_CLAUSE_FIRSTPRIVATE);
13536 OMP_CLAUSE_DECL (*gtask_clauses_ptr)
13537 = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
13538 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
13540 if (lastprivate_uids
13541 && bitmap_bit_p (lastprivate_uids,
13542 DECL_UID (OMP_CLAUSE_DECL (c))))
13544 *gfor_clauses_ptr = c;
13545 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
13546 *gtask_clauses_ptr = copy_node (c);
13547 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
13549 else
13551 *gtask_clauses_ptr = c;
13552 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
13554 break;
13555 default:
13556 gcc_unreachable ();
13558 *gfor_clauses_ptr = NULL_TREE;
13559 *gtask_clauses_ptr = NULL_TREE;
13560 *gforo_clauses_ptr = NULL_TREE;
13561 BITMAP_FREE (lastprivate_uids);
13562 gimple_set_location (gfor, input_location);
13563 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
13564 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
13565 NULL_TREE, NULL_TREE, NULL_TREE);
13566 gimple_set_location (g, input_location);
13567 gimple_omp_task_set_taskloop_p (g, true);
13568 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
13569 gomp_for *gforo
13570 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
13571 gimple_omp_for_collapse (gfor),
13572 gimple_omp_for_pre_body (gfor));
13573 gimple_omp_for_set_pre_body (gfor, NULL);
13574 gimple_omp_for_set_combined_p (gforo, true);
13575 gimple_omp_for_set_combined_into_p (gfor, true);
13576 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
13578 tree type = TREE_TYPE (gimple_omp_for_index (gfor, i));
13579 tree v = create_tmp_var (type);
13580 gimple_omp_for_set_index (gforo, i, v);
13581 t = unshare_expr (gimple_omp_for_initial (gfor, i));
13582 gimple_omp_for_set_initial (gforo, i, t);
13583 gimple_omp_for_set_cond (gforo, i,
13584 gimple_omp_for_cond (gfor, i));
13585 t = unshare_expr (gimple_omp_for_final (gfor, i));
13586 gimple_omp_for_set_final (gforo, i, t);
13587 t = unshare_expr (gimple_omp_for_incr (gfor, i));
13588 gcc_assert (TREE_OPERAND (t, 0) == gimple_omp_for_index (gfor, i));
13589 TREE_OPERAND (t, 0) = v;
13590 gimple_omp_for_set_incr (gforo, i, t);
13591 t = build_omp_clause (input_location, OMP_CLAUSE_PRIVATE);
13592 OMP_CLAUSE_DECL (t) = v;
13593 OMP_CLAUSE_CHAIN (t) = gimple_omp_for_clauses (gforo);
13594 gimple_omp_for_set_clauses (gforo, t);
13595 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
13597 tree *p1 = NULL, *p2 = NULL;
13598 t = gimple_omp_for_initial (gforo, i);
13599 if (TREE_CODE (t) == TREE_VEC)
13600 p1 = &TREE_VEC_ELT (t, 0);
13601 t = gimple_omp_for_final (gforo, i);
13602 if (TREE_CODE (t) == TREE_VEC)
13604 if (p1)
13605 p2 = &TREE_VEC_ELT (t, 0);
13606 else
13607 p1 = &TREE_VEC_ELT (t, 0);
13609 if (p1)
13611 int j;
13612 for (j = 0; j < i; j++)
13613 if (*p1 == gimple_omp_for_index (gfor, j))
13615 *p1 = gimple_omp_for_index (gforo, j);
13616 if (p2)
13617 *p2 = *p1;
13618 break;
13620 gcc_assert (j < i);
13624 gimplify_seq_add_stmt (pre_p, gforo);
13626 else
13627 gimplify_seq_add_stmt (pre_p, gfor);
13629 if (TREE_CODE (orig_for_stmt) == OMP_FOR)
13631 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13632 unsigned lastprivate_conditional = 0;
13633 while (ctx
13634 && (ctx->region_type == ORT_TARGET_DATA
13635 || ctx->region_type == ORT_TASKGROUP))
13636 ctx = ctx->outer_context;
13637 if (ctx && (ctx->region_type & ORT_PARALLEL) != 0)
13638 for (tree c = gimple_omp_for_clauses (gfor);
13639 c; c = OMP_CLAUSE_CHAIN (c))
13640 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13641 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
13642 ++lastprivate_conditional;
13643 if (lastprivate_conditional)
13645 struct omp_for_data fd;
13646 omp_extract_for_data (gfor, &fd, NULL);
13647 tree type = build_array_type_nelts (unsigned_type_for (fd.iter_type),
13648 lastprivate_conditional);
13649 tree var = create_tmp_var_raw (type);
13650 tree c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE__CONDTEMP_);
13651 OMP_CLAUSE_DECL (c) = var;
13652 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
13653 gimple_omp_for_set_clauses (gfor, c);
13654 omp_add_variable (ctx, var, GOVD_CONDTEMP | GOVD_SEEN);
13657 else if (TREE_CODE (orig_for_stmt) == OMP_SIMD)
13659 unsigned lastprivate_conditional = 0;
13660 for (tree c = gimple_omp_for_clauses (gfor); c; c = OMP_CLAUSE_CHAIN (c))
13661 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13662 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
13663 ++lastprivate_conditional;
13664 if (lastprivate_conditional)
13666 struct omp_for_data fd;
13667 omp_extract_for_data (gfor, &fd, NULL);
13668 tree type = unsigned_type_for (fd.iter_type);
13669 while (lastprivate_conditional--)
13671 tree c = build_omp_clause (UNKNOWN_LOCATION,
13672 OMP_CLAUSE__CONDTEMP_);
13673 OMP_CLAUSE_DECL (c) = create_tmp_var (type);
13674 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
13675 gimple_omp_for_set_clauses (gfor, c);
13680 if (ret != GS_ALL_DONE)
13681 return GS_ERROR;
13682 *expr_p = NULL_TREE;
13683 return GS_ALL_DONE;
13686 /* Helper for gimplify_omp_loop, called through walk_tree. */
13688 static tree
13689 note_no_context_vars (tree *tp, int *, void *data)
13691 if (VAR_P (*tp)
13692 && DECL_CONTEXT (*tp) == NULL_TREE
13693 && !is_global_var (*tp))
13695 vec<tree> *d = (vec<tree> *) data;
13696 d->safe_push (*tp);
13697 DECL_CONTEXT (*tp) = current_function_decl;
13699 return NULL_TREE;
13702 /* Gimplify the gross structure of an OMP_LOOP statement. */
13704 static enum gimplify_status
13705 gimplify_omp_loop (tree *expr_p, gimple_seq *pre_p)
13707 tree for_stmt = *expr_p;
13708 tree clauses = OMP_FOR_CLAUSES (for_stmt);
13709 struct gimplify_omp_ctx *octx = gimplify_omp_ctxp;
13710 enum omp_clause_bind_kind kind = OMP_CLAUSE_BIND_THREAD;
13711 int i;
13713 /* If order is not present, the behavior is as if order(concurrent)
13714 appeared. */
13715 tree order = omp_find_clause (clauses, OMP_CLAUSE_ORDER);
13716 if (order == NULL_TREE)
13718 order = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_ORDER);
13719 OMP_CLAUSE_CHAIN (order) = clauses;
13720 OMP_FOR_CLAUSES (for_stmt) = clauses = order;
13723 tree bind = omp_find_clause (clauses, OMP_CLAUSE_BIND);
13724 if (bind == NULL_TREE)
13726 if (!flag_openmp) /* flag_openmp_simd */
13728 else if (octx && (octx->region_type & ORT_TEAMS) != 0)
13729 kind = OMP_CLAUSE_BIND_TEAMS;
13730 else if (octx && (octx->region_type & ORT_PARALLEL) != 0)
13731 kind = OMP_CLAUSE_BIND_PARALLEL;
13732 else
13734 for (; octx; octx = octx->outer_context)
13736 if ((octx->region_type & ORT_ACC) != 0
13737 || octx->region_type == ORT_NONE
13738 || octx->region_type == ORT_IMPLICIT_TARGET)
13739 continue;
13740 break;
13742 if (octx == NULL && !in_omp_construct)
13743 error_at (EXPR_LOCATION (for_stmt),
13744 "%<bind%> clause not specified on a %<loop%> "
13745 "construct not nested inside another OpenMP construct");
13747 bind = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_BIND);
13748 OMP_CLAUSE_CHAIN (bind) = clauses;
13749 OMP_CLAUSE_BIND_KIND (bind) = kind;
13750 OMP_FOR_CLAUSES (for_stmt) = bind;
13752 else
13753 switch (OMP_CLAUSE_BIND_KIND (bind))
13755 case OMP_CLAUSE_BIND_THREAD:
13756 break;
13757 case OMP_CLAUSE_BIND_PARALLEL:
13758 if (!flag_openmp) /* flag_openmp_simd */
13760 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13761 break;
13763 for (; octx; octx = octx->outer_context)
13764 if (octx->region_type == ORT_SIMD
13765 && omp_find_clause (octx->clauses, OMP_CLAUSE_BIND) == NULL_TREE)
13767 error_at (EXPR_LOCATION (for_stmt),
13768 "%<bind(parallel)%> on a %<loop%> construct nested "
13769 "inside %<simd%> construct");
13770 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13771 break;
13773 kind = OMP_CLAUSE_BIND_PARALLEL;
13774 break;
13775 case OMP_CLAUSE_BIND_TEAMS:
13776 if (!flag_openmp) /* flag_openmp_simd */
13778 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13779 break;
13781 if ((octx
13782 && octx->region_type != ORT_IMPLICIT_TARGET
13783 && octx->region_type != ORT_NONE
13784 && (octx->region_type & ORT_TEAMS) == 0)
13785 || in_omp_construct)
13787 error_at (EXPR_LOCATION (for_stmt),
13788 "%<bind(teams)%> on a %<loop%> region not strictly "
13789 "nested inside of a %<teams%> region");
13790 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
13791 break;
13793 kind = OMP_CLAUSE_BIND_TEAMS;
13794 break;
13795 default:
13796 gcc_unreachable ();
13799 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
13800 switch (OMP_CLAUSE_CODE (*pc))
13802 case OMP_CLAUSE_REDUCTION:
13803 if (OMP_CLAUSE_REDUCTION_INSCAN (*pc))
13805 error_at (OMP_CLAUSE_LOCATION (*pc),
13806 "%<inscan%> %<reduction%> clause on "
13807 "%qs construct", "loop");
13808 OMP_CLAUSE_REDUCTION_INSCAN (*pc) = 0;
13810 if (OMP_CLAUSE_REDUCTION_TASK (*pc))
13812 error_at (OMP_CLAUSE_LOCATION (*pc),
13813 "invalid %<task%> reduction modifier on construct "
13814 "other than %<parallel%>, %qs or %<sections%>",
13815 lang_GNU_Fortran () ? "do" : "for");
13816 OMP_CLAUSE_REDUCTION_TASK (*pc) = 0;
13818 pc = &OMP_CLAUSE_CHAIN (*pc);
13819 break;
13820 case OMP_CLAUSE_LASTPRIVATE:
13821 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
13823 tree t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
13824 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
13825 if (OMP_CLAUSE_DECL (*pc) == TREE_OPERAND (t, 0))
13826 break;
13827 if (OMP_FOR_ORIG_DECLS (for_stmt)
13828 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
13829 i)) == TREE_LIST
13830 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
13831 i)))
13833 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
13834 if (OMP_CLAUSE_DECL (*pc) == TREE_PURPOSE (orig))
13835 break;
13838 if (i == TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)))
13840 error_at (OMP_CLAUSE_LOCATION (*pc),
13841 "%<lastprivate%> clause on a %<loop%> construct refers "
13842 "to a variable %qD which is not the loop iterator",
13843 OMP_CLAUSE_DECL (*pc));
13844 *pc = OMP_CLAUSE_CHAIN (*pc);
13845 break;
13847 pc = &OMP_CLAUSE_CHAIN (*pc);
13848 break;
13849 default:
13850 pc = &OMP_CLAUSE_CHAIN (*pc);
13851 break;
13854 TREE_SET_CODE (for_stmt, OMP_SIMD);
13856 int last;
13857 switch (kind)
13859 case OMP_CLAUSE_BIND_THREAD: last = 0; break;
13860 case OMP_CLAUSE_BIND_PARALLEL: last = 1; break;
13861 case OMP_CLAUSE_BIND_TEAMS: last = 2; break;
13863 for (int pass = 1; pass <= last; pass++)
13865 if (pass == 2)
13867 tree bind = build3 (BIND_EXPR, void_type_node, NULL, NULL,
13868 make_node (BLOCK));
13869 append_to_statement_list (*expr_p, &BIND_EXPR_BODY (bind));
13870 *expr_p = make_node (OMP_PARALLEL);
13871 TREE_TYPE (*expr_p) = void_type_node;
13872 OMP_PARALLEL_BODY (*expr_p) = bind;
13873 OMP_PARALLEL_COMBINED (*expr_p) = 1;
13874 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (for_stmt));
13875 tree *pc = &OMP_PARALLEL_CLAUSES (*expr_p);
13876 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
13877 if (OMP_FOR_ORIG_DECLS (for_stmt)
13878 && (TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i))
13879 == TREE_LIST))
13881 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
13882 if (TREE_PURPOSE (elt) && TREE_VALUE (elt))
13884 *pc = build_omp_clause (UNKNOWN_LOCATION,
13885 OMP_CLAUSE_FIRSTPRIVATE);
13886 OMP_CLAUSE_DECL (*pc) = TREE_VALUE (elt);
13887 pc = &OMP_CLAUSE_CHAIN (*pc);
13891 tree t = make_node (pass == 2 ? OMP_DISTRIBUTE : OMP_FOR);
13892 tree *pc = &OMP_FOR_CLAUSES (t);
13893 TREE_TYPE (t) = void_type_node;
13894 OMP_FOR_BODY (t) = *expr_p;
13895 SET_EXPR_LOCATION (t, EXPR_LOCATION (for_stmt));
13896 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
13897 switch (OMP_CLAUSE_CODE (c))
13899 case OMP_CLAUSE_BIND:
13900 case OMP_CLAUSE_ORDER:
13901 case OMP_CLAUSE_COLLAPSE:
13902 *pc = copy_node (c);
13903 pc = &OMP_CLAUSE_CHAIN (*pc);
13904 break;
13905 case OMP_CLAUSE_PRIVATE:
13906 case OMP_CLAUSE_FIRSTPRIVATE:
13907 /* Only needed on innermost. */
13908 break;
13909 case OMP_CLAUSE_LASTPRIVATE:
13910 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c) && pass != last)
13912 *pc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13913 OMP_CLAUSE_FIRSTPRIVATE);
13914 OMP_CLAUSE_DECL (*pc) = OMP_CLAUSE_DECL (c);
13915 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
13916 pc = &OMP_CLAUSE_CHAIN (*pc);
13918 *pc = copy_node (c);
13919 OMP_CLAUSE_LASTPRIVATE_STMT (*pc) = NULL_TREE;
13920 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
13921 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
13923 if (pass != last)
13924 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (*pc) = 1;
13925 else
13926 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
13927 OMP_CLAUSE_LASTPRIVATE_LOOP_IV (*pc) = 0;
13929 pc = &OMP_CLAUSE_CHAIN (*pc);
13930 break;
13931 case OMP_CLAUSE_REDUCTION:
13932 *pc = copy_node (c);
13933 OMP_CLAUSE_DECL (*pc) = unshare_expr (OMP_CLAUSE_DECL (c));
13934 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
13935 if (OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc))
13937 auto_vec<tree> no_context_vars;
13938 int walk_subtrees = 0;
13939 note_no_context_vars (&OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
13940 &walk_subtrees, &no_context_vars);
13941 if (tree p = OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c))
13942 note_no_context_vars (&p, &walk_subtrees, &no_context_vars);
13943 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_INIT (c),
13944 note_no_context_vars,
13945 &no_context_vars);
13946 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_MERGE (c),
13947 note_no_context_vars,
13948 &no_context_vars);
13950 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc)
13951 = copy_node (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c));
13952 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
13953 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc)
13954 = copy_node (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c));
13956 hash_map<tree, tree> decl_map;
13957 decl_map.put (OMP_CLAUSE_DECL (c), OMP_CLAUSE_DECL (c));
13958 decl_map.put (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
13959 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc));
13960 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
13961 decl_map.put (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
13962 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc));
13964 copy_body_data id;
13965 memset (&id, 0, sizeof (id));
13966 id.src_fn = current_function_decl;
13967 id.dst_fn = current_function_decl;
13968 id.src_cfun = cfun;
13969 id.decl_map = &decl_map;
13970 id.copy_decl = copy_decl_no_change;
13971 id.transform_call_graph_edges = CB_CGE_DUPLICATE;
13972 id.transform_new_cfg = true;
13973 id.transform_return_to_modify = false;
13974 id.eh_lp_nr = 0;
13975 walk_tree (&OMP_CLAUSE_REDUCTION_INIT (*pc), copy_tree_body_r,
13976 &id, NULL);
13977 walk_tree (&OMP_CLAUSE_REDUCTION_MERGE (*pc), copy_tree_body_r,
13978 &id, NULL);
13980 for (tree d : no_context_vars)
13982 DECL_CONTEXT (d) = NULL_TREE;
13983 DECL_CONTEXT (*decl_map.get (d)) = NULL_TREE;
13986 else
13988 OMP_CLAUSE_REDUCTION_INIT (*pc)
13989 = unshare_expr (OMP_CLAUSE_REDUCTION_INIT (c));
13990 OMP_CLAUSE_REDUCTION_MERGE (*pc)
13991 = unshare_expr (OMP_CLAUSE_REDUCTION_MERGE (c));
13993 pc = &OMP_CLAUSE_CHAIN (*pc);
13994 break;
13995 default:
13996 gcc_unreachable ();
13998 *pc = NULL_TREE;
13999 *expr_p = t;
14001 return gimplify_expr (expr_p, pre_p, NULL, is_gimple_stmt, fb_none);
14005 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
14006 of OMP_TARGET's body. */
14008 static tree
14009 find_omp_teams (tree *tp, int *walk_subtrees, void *)
14011 *walk_subtrees = 0;
14012 switch (TREE_CODE (*tp))
14014 case OMP_TEAMS:
14015 return *tp;
14016 case BIND_EXPR:
14017 case STATEMENT_LIST:
14018 *walk_subtrees = 1;
14019 break;
14020 default:
14021 break;
14023 return NULL_TREE;
14026 /* Helper function of optimize_target_teams, determine if the expression
14027 can be computed safely before the target construct on the host. */
14029 static tree
14030 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
14032 splay_tree_node n;
14034 if (TYPE_P (*tp))
14036 *walk_subtrees = 0;
14037 return NULL_TREE;
14039 switch (TREE_CODE (*tp))
14041 case VAR_DECL:
14042 case PARM_DECL:
14043 case RESULT_DECL:
14044 *walk_subtrees = 0;
14045 if (error_operand_p (*tp)
14046 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
14047 || DECL_HAS_VALUE_EXPR_P (*tp)
14048 || DECL_THREAD_LOCAL_P (*tp)
14049 || TREE_SIDE_EFFECTS (*tp)
14050 || TREE_THIS_VOLATILE (*tp))
14051 return *tp;
14052 if (is_global_var (*tp)
14053 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
14054 || lookup_attribute ("omp declare target link",
14055 DECL_ATTRIBUTES (*tp))))
14056 return *tp;
14057 if (VAR_P (*tp)
14058 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
14059 && !is_global_var (*tp)
14060 && decl_function_context (*tp) == current_function_decl)
14061 return *tp;
14062 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
14063 (splay_tree_key) *tp);
14064 if (n == NULL)
14066 if (gimplify_omp_ctxp->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
14067 return NULL_TREE;
14068 return *tp;
14070 else if (n->value & GOVD_LOCAL)
14071 return *tp;
14072 else if (n->value & GOVD_FIRSTPRIVATE)
14073 return NULL_TREE;
14074 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
14075 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
14076 return NULL_TREE;
14077 return *tp;
14078 case INTEGER_CST:
14079 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
14080 return *tp;
14081 return NULL_TREE;
14082 case TARGET_EXPR:
14083 if (TARGET_EXPR_INITIAL (*tp)
14084 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
14085 return *tp;
14086 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
14087 walk_subtrees, NULL);
14088 /* Allow some reasonable subset of integral arithmetics. */
14089 case PLUS_EXPR:
14090 case MINUS_EXPR:
14091 case MULT_EXPR:
14092 case TRUNC_DIV_EXPR:
14093 case CEIL_DIV_EXPR:
14094 case FLOOR_DIV_EXPR:
14095 case ROUND_DIV_EXPR:
14096 case TRUNC_MOD_EXPR:
14097 case CEIL_MOD_EXPR:
14098 case FLOOR_MOD_EXPR:
14099 case ROUND_MOD_EXPR:
14100 case RDIV_EXPR:
14101 case EXACT_DIV_EXPR:
14102 case MIN_EXPR:
14103 case MAX_EXPR:
14104 case LSHIFT_EXPR:
14105 case RSHIFT_EXPR:
14106 case BIT_IOR_EXPR:
14107 case BIT_XOR_EXPR:
14108 case BIT_AND_EXPR:
14109 case NEGATE_EXPR:
14110 case ABS_EXPR:
14111 case BIT_NOT_EXPR:
14112 case NON_LVALUE_EXPR:
14113 CASE_CONVERT:
14114 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
14115 return *tp;
14116 return NULL_TREE;
14117 /* And disallow anything else, except for comparisons. */
14118 default:
14119 if (COMPARISON_CLASS_P (*tp))
14120 return NULL_TREE;
14121 return *tp;
14125 /* Try to determine if the num_teams and/or thread_limit expressions
14126 can have their values determined already before entering the
14127 target construct.
14128 INTEGER_CSTs trivially are,
14129 integral decls that are firstprivate (explicitly or implicitly)
14130 or explicitly map(always, to:) or map(always, tofrom:) on the target
14131 region too, and expressions involving simple arithmetics on those
14132 too, function calls are not ok, dereferencing something neither etc.
14133 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
14134 EXPR based on what we find:
14135 0 stands for clause not specified at all, use implementation default
14136 -1 stands for value that can't be determined easily before entering
14137 the target construct.
14138 If teams construct is not present at all, use 1 for num_teams
14139 and 0 for thread_limit (only one team is involved, and the thread
14140 limit is implementation defined. */
14142 static void
14143 optimize_target_teams (tree target, gimple_seq *pre_p)
14145 tree body = OMP_BODY (target);
14146 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
14147 tree num_teams_lower = NULL_TREE;
14148 tree num_teams_upper = integer_zero_node;
14149 tree thread_limit = integer_zero_node;
14150 location_t num_teams_loc = EXPR_LOCATION (target);
14151 location_t thread_limit_loc = EXPR_LOCATION (target);
14152 tree c, *p, expr;
14153 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
14155 if (teams == NULL_TREE)
14156 num_teams_upper = integer_one_node;
14157 else
14158 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
14160 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
14162 p = &num_teams_upper;
14163 num_teams_loc = OMP_CLAUSE_LOCATION (c);
14164 if (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c))
14166 expr = OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c);
14167 if (TREE_CODE (expr) == INTEGER_CST)
14168 num_teams_lower = expr;
14169 else if (walk_tree (&expr, computable_teams_clause,
14170 NULL, NULL))
14171 num_teams_lower = integer_minus_one_node;
14172 else
14174 num_teams_lower = expr;
14175 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
14176 if (gimplify_expr (&num_teams_lower, pre_p, NULL,
14177 is_gimple_val, fb_rvalue, false)
14178 == GS_ERROR)
14180 gimplify_omp_ctxp = target_ctx;
14181 num_teams_lower = integer_minus_one_node;
14183 else
14185 gimplify_omp_ctxp = target_ctx;
14186 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
14187 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
14188 = num_teams_lower;
14193 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
14195 p = &thread_limit;
14196 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
14198 else
14199 continue;
14200 expr = OMP_CLAUSE_OPERAND (c, 0);
14201 if (TREE_CODE (expr) == INTEGER_CST)
14203 *p = expr;
14204 continue;
14206 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
14208 *p = integer_minus_one_node;
14209 continue;
14211 *p = expr;
14212 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
14213 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
14214 == GS_ERROR)
14216 gimplify_omp_ctxp = target_ctx;
14217 *p = integer_minus_one_node;
14218 continue;
14220 gimplify_omp_ctxp = target_ctx;
14221 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
14222 OMP_CLAUSE_OPERAND (c, 0) = *p;
14224 if (!omp_find_clause (OMP_TARGET_CLAUSES (target), OMP_CLAUSE_THREAD_LIMIT))
14226 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
14227 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
14228 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
14229 OMP_TARGET_CLAUSES (target) = c;
14231 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
14232 OMP_CLAUSE_NUM_TEAMS_UPPER_EXPR (c) = num_teams_upper;
14233 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c) = num_teams_lower;
14234 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
14235 OMP_TARGET_CLAUSES (target) = c;
14238 /* Gimplify the gross structure of several OMP constructs. */
14240 static void
14241 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
14243 tree expr = *expr_p;
14244 gimple *stmt;
14245 gimple_seq body = NULL;
14246 enum omp_region_type ort;
14248 switch (TREE_CODE (expr))
14250 case OMP_SECTIONS:
14251 case OMP_SINGLE:
14252 ort = ORT_WORKSHARE;
14253 break;
14254 case OMP_SCOPE:
14255 ort = ORT_TASKGROUP;
14256 break;
14257 case OMP_TARGET:
14258 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
14259 break;
14260 case OACC_KERNELS:
14261 ort = ORT_ACC_KERNELS;
14262 break;
14263 case OACC_PARALLEL:
14264 ort = ORT_ACC_PARALLEL;
14265 break;
14266 case OACC_SERIAL:
14267 ort = ORT_ACC_SERIAL;
14268 break;
14269 case OACC_DATA:
14270 ort = ORT_ACC_DATA;
14271 break;
14272 case OMP_TARGET_DATA:
14273 ort = ORT_TARGET_DATA;
14274 break;
14275 case OMP_TEAMS:
14276 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
14277 if (gimplify_omp_ctxp == NULL
14278 || gimplify_omp_ctxp->region_type == ORT_IMPLICIT_TARGET)
14279 ort = (enum omp_region_type) (ort | ORT_HOST_TEAMS);
14280 break;
14281 case OACC_HOST_DATA:
14282 ort = ORT_ACC_HOST_DATA;
14283 break;
14284 default:
14285 gcc_unreachable ();
14288 bool save_in_omp_construct = in_omp_construct;
14289 if ((ort & ORT_ACC) == 0)
14290 in_omp_construct = false;
14291 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
14292 TREE_CODE (expr));
14293 if (TREE_CODE (expr) == OMP_TARGET)
14294 optimize_target_teams (expr, pre_p);
14295 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0
14296 || (ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
14298 push_gimplify_context ();
14299 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
14300 if (gimple_code (g) == GIMPLE_BIND)
14301 pop_gimplify_context (g);
14302 else
14303 pop_gimplify_context (NULL);
14304 if ((ort & ORT_TARGET_DATA) != 0)
14306 enum built_in_function end_ix;
14307 switch (TREE_CODE (expr))
14309 case OACC_DATA:
14310 case OACC_HOST_DATA:
14311 end_ix = BUILT_IN_GOACC_DATA_END;
14312 break;
14313 case OMP_TARGET_DATA:
14314 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
14315 break;
14316 default:
14317 gcc_unreachable ();
14319 tree fn = builtin_decl_explicit (end_ix);
14320 g = gimple_build_call (fn, 0);
14321 gimple_seq cleanup = NULL;
14322 gimple_seq_add_stmt (&cleanup, g);
14323 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
14324 body = NULL;
14325 gimple_seq_add_stmt (&body, g);
14328 else
14329 gimplify_and_add (OMP_BODY (expr), &body);
14330 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
14331 TREE_CODE (expr));
14332 in_omp_construct = save_in_omp_construct;
14334 switch (TREE_CODE (expr))
14336 case OACC_DATA:
14337 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
14338 OMP_CLAUSES (expr));
14339 break;
14340 case OACC_HOST_DATA:
14341 if (omp_find_clause (OMP_CLAUSES (expr), OMP_CLAUSE_IF_PRESENT))
14343 for (tree c = OMP_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
14344 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_USE_DEVICE_PTR)
14345 OMP_CLAUSE_USE_DEVICE_PTR_IF_PRESENT (c) = 1;
14348 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
14349 OMP_CLAUSES (expr));
14350 break;
14351 case OACC_KERNELS:
14352 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
14353 OMP_CLAUSES (expr));
14354 break;
14355 case OACC_PARALLEL:
14356 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
14357 OMP_CLAUSES (expr));
14358 break;
14359 case OACC_SERIAL:
14360 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_SERIAL,
14361 OMP_CLAUSES (expr));
14362 break;
14363 case OMP_SECTIONS:
14364 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
14365 break;
14366 case OMP_SINGLE:
14367 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
14368 break;
14369 case OMP_SCOPE:
14370 stmt = gimple_build_omp_scope (body, OMP_CLAUSES (expr));
14371 break;
14372 case OMP_TARGET:
14373 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
14374 OMP_CLAUSES (expr));
14375 break;
14376 case OMP_TARGET_DATA:
14377 /* Put use_device_{ptr,addr} clauses last, as map clauses are supposed
14378 to be evaluated before the use_device_{ptr,addr} clauses if they
14379 refer to the same variables. */
14381 tree use_device_clauses;
14382 tree *pc, *uc = &use_device_clauses;
14383 for (pc = &OMP_CLAUSES (expr); *pc; )
14384 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_PTR
14385 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_ADDR)
14387 *uc = *pc;
14388 *pc = OMP_CLAUSE_CHAIN (*pc);
14389 uc = &OMP_CLAUSE_CHAIN (*uc);
14391 else
14392 pc = &OMP_CLAUSE_CHAIN (*pc);
14393 *uc = NULL_TREE;
14394 *pc = use_device_clauses;
14395 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
14396 OMP_CLAUSES (expr));
14398 break;
14399 case OMP_TEAMS:
14400 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
14401 if ((ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
14402 gimple_omp_teams_set_host (as_a <gomp_teams *> (stmt), true);
14403 break;
14404 default:
14405 gcc_unreachable ();
14408 gimplify_seq_add_stmt (pre_p, stmt);
14409 *expr_p = NULL_TREE;
14412 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
14413 target update constructs. */
14415 static void
14416 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
14418 tree expr = *expr_p;
14419 int kind;
14420 gomp_target *stmt;
14421 enum omp_region_type ort = ORT_WORKSHARE;
14423 switch (TREE_CODE (expr))
14425 case OACC_ENTER_DATA:
14426 kind = GF_OMP_TARGET_KIND_OACC_ENTER_DATA;
14427 ort = ORT_ACC;
14428 break;
14429 case OACC_EXIT_DATA:
14430 kind = GF_OMP_TARGET_KIND_OACC_EXIT_DATA;
14431 ort = ORT_ACC;
14432 break;
14433 case OACC_UPDATE:
14434 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
14435 ort = ORT_ACC;
14436 break;
14437 case OMP_TARGET_UPDATE:
14438 kind = GF_OMP_TARGET_KIND_UPDATE;
14439 break;
14440 case OMP_TARGET_ENTER_DATA:
14441 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
14442 break;
14443 case OMP_TARGET_EXIT_DATA:
14444 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
14445 break;
14446 default:
14447 gcc_unreachable ();
14449 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
14450 ort, TREE_CODE (expr));
14451 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
14452 TREE_CODE (expr));
14453 if (TREE_CODE (expr) == OACC_UPDATE
14454 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
14455 OMP_CLAUSE_IF_PRESENT))
14457 /* The runtime uses GOMP_MAP_{TO,FROM} to denote the if_present
14458 clause. */
14459 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
14460 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
14461 switch (OMP_CLAUSE_MAP_KIND (c))
14463 case GOMP_MAP_FORCE_TO:
14464 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TO);
14465 break;
14466 case GOMP_MAP_FORCE_FROM:
14467 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FROM);
14468 break;
14469 default:
14470 break;
14473 else if (TREE_CODE (expr) == OACC_EXIT_DATA
14474 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
14475 OMP_CLAUSE_FINALIZE))
14477 /* Use GOMP_MAP_DELETE/GOMP_MAP_FORCE_FROM to denote "finalize"
14478 semantics. */
14479 bool have_clause = false;
14480 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
14481 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
14482 switch (OMP_CLAUSE_MAP_KIND (c))
14484 case GOMP_MAP_FROM:
14485 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_FROM);
14486 have_clause = true;
14487 break;
14488 case GOMP_MAP_RELEASE:
14489 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
14490 have_clause = true;
14491 break;
14492 case GOMP_MAP_TO_PSET:
14493 /* Fortran arrays with descriptors must map that descriptor when
14494 doing standalone "attach" operations (in OpenACC). In that
14495 case GOMP_MAP_TO_PSET appears by itself with no preceding
14496 clause (see trans-openmp.cc:gfc_trans_omp_clauses). */
14497 break;
14498 case GOMP_MAP_POINTER:
14499 /* TODO PR92929: we may see these here, but they'll always follow
14500 one of the clauses above, and will be handled by libgomp as
14501 one group, so no handling required here. */
14502 gcc_assert (have_clause);
14503 break;
14504 case GOMP_MAP_DETACH:
14505 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_DETACH);
14506 have_clause = false;
14507 break;
14508 case GOMP_MAP_STRUCT:
14509 have_clause = false;
14510 break;
14511 default:
14512 gcc_unreachable ();
14515 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
14517 gimplify_seq_add_stmt (pre_p, stmt);
14518 *expr_p = NULL_TREE;
14521 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
14522 stabilized the lhs of the atomic operation as *ADDR. Return true if
14523 EXPR is this stabilized form. */
14525 static bool
14526 goa_lhs_expr_p (tree expr, tree addr)
14528 /* Also include casts to other type variants. The C front end is fond
14529 of adding these for e.g. volatile variables. This is like
14530 STRIP_TYPE_NOPS but includes the main variant lookup. */
14531 STRIP_USELESS_TYPE_CONVERSION (expr);
14533 if (TREE_CODE (expr) == INDIRECT_REF)
14535 expr = TREE_OPERAND (expr, 0);
14536 while (expr != addr
14537 && (CONVERT_EXPR_P (expr)
14538 || TREE_CODE (expr) == NON_LVALUE_EXPR)
14539 && TREE_CODE (expr) == TREE_CODE (addr)
14540 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
14542 expr = TREE_OPERAND (expr, 0);
14543 addr = TREE_OPERAND (addr, 0);
14545 if (expr == addr)
14546 return true;
14547 return (TREE_CODE (addr) == ADDR_EXPR
14548 && TREE_CODE (expr) == ADDR_EXPR
14549 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
14551 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
14552 return true;
14553 return false;
14556 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
14557 expression does not involve the lhs, evaluate it into a temporary.
14558 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
14559 or -1 if an error was encountered. */
14561 static int
14562 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
14563 tree lhs_var, tree &target_expr, bool rhs, int depth)
14565 tree expr = *expr_p;
14566 int saw_lhs = 0;
14568 if (goa_lhs_expr_p (expr, lhs_addr))
14570 if (pre_p)
14571 *expr_p = lhs_var;
14572 return 1;
14574 if (is_gimple_val (expr))
14575 return 0;
14577 /* Maximum depth of lhs in expression is for the
14578 __builtin_clear_padding (...), __builtin_clear_padding (...),
14579 __builtin_memcmp (&TARGET_EXPR <lhs, >, ...) == 0 ? ... : lhs; */
14580 if (++depth > 7)
14581 goto finish;
14583 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
14585 case tcc_binary:
14586 case tcc_comparison:
14587 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
14588 lhs_var, target_expr, true, depth);
14589 /* FALLTHRU */
14590 case tcc_unary:
14591 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
14592 lhs_var, target_expr, true, depth);
14593 break;
14594 case tcc_expression:
14595 switch (TREE_CODE (expr))
14597 case TRUTH_ANDIF_EXPR:
14598 case TRUTH_ORIF_EXPR:
14599 case TRUTH_AND_EXPR:
14600 case TRUTH_OR_EXPR:
14601 case TRUTH_XOR_EXPR:
14602 case BIT_INSERT_EXPR:
14603 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
14604 lhs_addr, lhs_var, target_expr, true,
14605 depth);
14606 /* FALLTHRU */
14607 case TRUTH_NOT_EXPR:
14608 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
14609 lhs_addr, lhs_var, target_expr, true,
14610 depth);
14611 break;
14612 case MODIFY_EXPR:
14613 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
14614 target_expr, true, depth))
14615 break;
14616 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
14617 lhs_addr, lhs_var, target_expr, true,
14618 depth);
14619 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
14620 lhs_addr, lhs_var, target_expr, false,
14621 depth);
14622 break;
14623 /* FALLTHRU */
14624 case ADDR_EXPR:
14625 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
14626 target_expr, true, depth))
14627 break;
14628 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
14629 lhs_addr, lhs_var, target_expr, false,
14630 depth);
14631 break;
14632 case COMPOUND_EXPR:
14633 /* Break out any preevaluations from cp_build_modify_expr. */
14634 for (; TREE_CODE (expr) == COMPOUND_EXPR;
14635 expr = TREE_OPERAND (expr, 1))
14637 /* Special-case __builtin_clear_padding call before
14638 __builtin_memcmp. */
14639 if (TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR)
14641 tree fndecl = get_callee_fndecl (TREE_OPERAND (expr, 0));
14642 if (fndecl
14643 && fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING)
14644 && VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (expr, 0)))
14645 && (!pre_p
14646 || goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL,
14647 lhs_addr, lhs_var,
14648 target_expr, true, depth)))
14650 if (pre_p)
14651 *expr_p = expr;
14652 saw_lhs = goa_stabilize_expr (&TREE_OPERAND (expr, 0),
14653 pre_p, lhs_addr, lhs_var,
14654 target_expr, true, depth);
14655 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1),
14656 pre_p, lhs_addr, lhs_var,
14657 target_expr, rhs, depth);
14658 return saw_lhs;
14662 if (pre_p)
14663 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
14665 if (!pre_p)
14666 return goa_stabilize_expr (&expr, pre_p, lhs_addr, lhs_var,
14667 target_expr, rhs, depth);
14668 *expr_p = expr;
14669 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var,
14670 target_expr, rhs, depth);
14671 case COND_EXPR:
14672 if (!goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL, lhs_addr,
14673 lhs_var, target_expr, true, depth))
14674 break;
14675 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
14676 lhs_addr, lhs_var, target_expr, true,
14677 depth);
14678 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
14679 lhs_addr, lhs_var, target_expr, true,
14680 depth);
14681 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 2), pre_p,
14682 lhs_addr, lhs_var, target_expr, true,
14683 depth);
14684 break;
14685 case TARGET_EXPR:
14686 if (TARGET_EXPR_INITIAL (expr))
14688 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr,
14689 lhs_var, target_expr, true,
14690 depth))
14691 break;
14692 if (expr == target_expr)
14693 saw_lhs = 1;
14694 else
14696 saw_lhs = goa_stabilize_expr (&TARGET_EXPR_INITIAL (expr),
14697 pre_p, lhs_addr, lhs_var,
14698 target_expr, true, depth);
14699 if (saw_lhs && target_expr == NULL_TREE && pre_p)
14700 target_expr = expr;
14703 break;
14704 default:
14705 break;
14707 break;
14708 case tcc_reference:
14709 if (TREE_CODE (expr) == BIT_FIELD_REF
14710 || TREE_CODE (expr) == VIEW_CONVERT_EXPR)
14711 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
14712 lhs_addr, lhs_var, target_expr, true,
14713 depth);
14714 break;
14715 case tcc_vl_exp:
14716 if (TREE_CODE (expr) == CALL_EXPR)
14718 if (tree fndecl = get_callee_fndecl (expr))
14719 if (fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING)
14720 || fndecl_built_in_p (fndecl, BUILT_IN_MEMCMP))
14722 int nargs = call_expr_nargs (expr);
14723 for (int i = 0; i < nargs; i++)
14724 saw_lhs |= goa_stabilize_expr (&CALL_EXPR_ARG (expr, i),
14725 pre_p, lhs_addr, lhs_var,
14726 target_expr, true, depth);
14729 break;
14730 default:
14731 break;
14734 finish:
14735 if (saw_lhs == 0 && pre_p)
14737 enum gimplify_status gs;
14738 if (TREE_CODE (expr) == CALL_EXPR && VOID_TYPE_P (TREE_TYPE (expr)))
14740 gimplify_stmt (&expr, pre_p);
14741 return saw_lhs;
14743 else if (rhs)
14744 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
14745 else
14746 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_lvalue, fb_lvalue);
14747 if (gs != GS_ALL_DONE)
14748 saw_lhs = -1;
14751 return saw_lhs;
14754 /* Gimplify an OMP_ATOMIC statement. */
14756 static enum gimplify_status
14757 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
14759 tree addr = TREE_OPERAND (*expr_p, 0);
14760 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
14761 ? NULL : TREE_OPERAND (*expr_p, 1);
14762 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
14763 tree tmp_load;
14764 gomp_atomic_load *loadstmt;
14765 gomp_atomic_store *storestmt;
14766 tree target_expr = NULL_TREE;
14768 tmp_load = create_tmp_reg (type);
14769 if (rhs
14770 && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load, target_expr,
14771 true, 0) < 0)
14772 return GS_ERROR;
14774 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
14775 != GS_ALL_DONE)
14776 return GS_ERROR;
14778 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr,
14779 OMP_ATOMIC_MEMORY_ORDER (*expr_p));
14780 gimplify_seq_add_stmt (pre_p, loadstmt);
14781 if (rhs)
14783 /* BIT_INSERT_EXPR is not valid for non-integral bitfield
14784 representatives. Use BIT_FIELD_REF on the lhs instead. */
14785 tree rhsarg = rhs;
14786 if (TREE_CODE (rhs) == COND_EXPR)
14787 rhsarg = TREE_OPERAND (rhs, 1);
14788 if (TREE_CODE (rhsarg) == BIT_INSERT_EXPR
14789 && !INTEGRAL_TYPE_P (TREE_TYPE (tmp_load)))
14791 tree bitpos = TREE_OPERAND (rhsarg, 2);
14792 tree op1 = TREE_OPERAND (rhsarg, 1);
14793 tree bitsize;
14794 tree tmp_store = tmp_load;
14795 if (TREE_CODE (*expr_p) == OMP_ATOMIC_CAPTURE_OLD)
14796 tmp_store = get_initialized_tmp_var (tmp_load, pre_p);
14797 if (INTEGRAL_TYPE_P (TREE_TYPE (op1)))
14798 bitsize = bitsize_int (TYPE_PRECISION (TREE_TYPE (op1)));
14799 else
14800 bitsize = TYPE_SIZE (TREE_TYPE (op1));
14801 gcc_assert (TREE_OPERAND (rhsarg, 0) == tmp_load);
14802 tree t = build2_loc (EXPR_LOCATION (rhsarg),
14803 MODIFY_EXPR, void_type_node,
14804 build3_loc (EXPR_LOCATION (rhsarg),
14805 BIT_FIELD_REF, TREE_TYPE (op1),
14806 tmp_store, bitsize, bitpos), op1);
14807 if (TREE_CODE (rhs) == COND_EXPR)
14808 t = build3_loc (EXPR_LOCATION (rhs), COND_EXPR, void_type_node,
14809 TREE_OPERAND (rhs, 0), t, void_node);
14810 gimplify_and_add (t, pre_p);
14811 rhs = tmp_store;
14813 bool save_allow_rhs_cond_expr = gimplify_ctxp->allow_rhs_cond_expr;
14814 if (TREE_CODE (rhs) == COND_EXPR)
14815 gimplify_ctxp->allow_rhs_cond_expr = true;
14816 enum gimplify_status gs = gimplify_expr (&rhs, pre_p, NULL,
14817 is_gimple_val, fb_rvalue);
14818 gimplify_ctxp->allow_rhs_cond_expr = save_allow_rhs_cond_expr;
14819 if (gs != GS_ALL_DONE)
14820 return GS_ERROR;
14823 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
14824 rhs = tmp_load;
14825 storestmt
14826 = gimple_build_omp_atomic_store (rhs, OMP_ATOMIC_MEMORY_ORDER (*expr_p));
14827 if (TREE_CODE (*expr_p) != OMP_ATOMIC_READ && OMP_ATOMIC_WEAK (*expr_p))
14829 gimple_omp_atomic_set_weak (loadstmt);
14830 gimple_omp_atomic_set_weak (storestmt);
14832 gimplify_seq_add_stmt (pre_p, storestmt);
14833 switch (TREE_CODE (*expr_p))
14835 case OMP_ATOMIC_READ:
14836 case OMP_ATOMIC_CAPTURE_OLD:
14837 *expr_p = tmp_load;
14838 gimple_omp_atomic_set_need_value (loadstmt);
14839 break;
14840 case OMP_ATOMIC_CAPTURE_NEW:
14841 *expr_p = rhs;
14842 gimple_omp_atomic_set_need_value (storestmt);
14843 break;
14844 default:
14845 *expr_p = NULL;
14846 break;
14849 return GS_ALL_DONE;
14852 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
14853 body, and adding some EH bits. */
14855 static enum gimplify_status
14856 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
14858 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
14859 gimple *body_stmt;
14860 gtransaction *trans_stmt;
14861 gimple_seq body = NULL;
14862 int subcode = 0;
14864 /* Wrap the transaction body in a BIND_EXPR so we have a context
14865 where to put decls for OMP. */
14866 if (TREE_CODE (tbody) != BIND_EXPR)
14868 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
14869 TREE_SIDE_EFFECTS (bind) = 1;
14870 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
14871 TRANSACTION_EXPR_BODY (expr) = bind;
14874 push_gimplify_context ();
14875 temp = voidify_wrapper_expr (*expr_p, NULL);
14877 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
14878 pop_gimplify_context (body_stmt);
14880 trans_stmt = gimple_build_transaction (body);
14881 if (TRANSACTION_EXPR_OUTER (expr))
14882 subcode = GTMA_IS_OUTER;
14883 else if (TRANSACTION_EXPR_RELAXED (expr))
14884 subcode = GTMA_IS_RELAXED;
14885 gimple_transaction_set_subcode (trans_stmt, subcode);
14887 gimplify_seq_add_stmt (pre_p, trans_stmt);
14889 if (temp)
14891 *expr_p = temp;
14892 return GS_OK;
14895 *expr_p = NULL_TREE;
14896 return GS_ALL_DONE;
14899 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
14900 is the OMP_BODY of the original EXPR (which has already been
14901 gimplified so it's not present in the EXPR).
14903 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
14905 static gimple *
14906 gimplify_omp_ordered (tree expr, gimple_seq body)
14908 tree c, decls;
14909 int failures = 0;
14910 unsigned int i;
14911 tree source_c = NULL_TREE;
14912 tree sink_c = NULL_TREE;
14914 if (gimplify_omp_ctxp)
14916 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
14917 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
14918 && gimplify_omp_ctxp->loop_iter_var.is_empty ())
14920 error_at (OMP_CLAUSE_LOCATION (c),
14921 "%<ordered%> construct with %qs clause must be "
14922 "closely nested inside a loop with %<ordered%> clause",
14923 OMP_CLAUSE_DOACROSS_DEPEND (c) ? "depend" : "doacross");
14924 failures++;
14926 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
14927 && OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SINK)
14929 bool fail = false;
14930 sink_c = c;
14931 if (OMP_CLAUSE_DECL (c) == NULL_TREE)
14932 continue; /* omp_cur_iteration - 1 */
14933 for (decls = OMP_CLAUSE_DECL (c), i = 0;
14934 decls && TREE_CODE (decls) == TREE_LIST;
14935 decls = TREE_CHAIN (decls), ++i)
14936 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
14937 continue;
14938 else if (TREE_VALUE (decls)
14939 != gimplify_omp_ctxp->loop_iter_var[2 * i])
14941 error_at (OMP_CLAUSE_LOCATION (c),
14942 "variable %qE is not an iteration "
14943 "of outermost loop %d, expected %qE",
14944 TREE_VALUE (decls), i + 1,
14945 gimplify_omp_ctxp->loop_iter_var[2 * i]);
14946 fail = true;
14947 failures++;
14949 else
14950 TREE_VALUE (decls)
14951 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
14952 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
14954 error_at (OMP_CLAUSE_LOCATION (c),
14955 "number of variables in %qs clause with "
14956 "%<sink%> modifier does not match number of "
14957 "iteration variables",
14958 OMP_CLAUSE_DOACROSS_DEPEND (c)
14959 ? "depend" : "doacross");
14960 failures++;
14963 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
14964 && OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SOURCE)
14966 if (source_c)
14968 error_at (OMP_CLAUSE_LOCATION (c),
14969 "more than one %qs clause with %<source%> "
14970 "modifier on an %<ordered%> construct",
14971 OMP_CLAUSE_DOACROSS_DEPEND (source_c)
14972 ? "depend" : "doacross");
14973 failures++;
14975 else
14976 source_c = c;
14979 if (source_c && sink_c)
14981 error_at (OMP_CLAUSE_LOCATION (source_c),
14982 "%qs clause with %<source%> modifier specified "
14983 "together with %qs clauses with %<sink%> modifier "
14984 "on the same construct",
14985 OMP_CLAUSE_DOACROSS_DEPEND (source_c) ? "depend" : "doacross",
14986 OMP_CLAUSE_DOACROSS_DEPEND (sink_c) ? "depend" : "doacross");
14987 failures++;
14990 if (failures)
14991 return gimple_build_nop ();
14992 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
14995 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
14996 expression produces a value to be used as an operand inside a GIMPLE
14997 statement, the value will be stored back in *EXPR_P. This value will
14998 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
14999 an SSA_NAME. The corresponding sequence of GIMPLE statements is
15000 emitted in PRE_P and POST_P.
15002 Additionally, this process may overwrite parts of the input
15003 expression during gimplification. Ideally, it should be
15004 possible to do non-destructive gimplification.
15006 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
15007 the expression needs to evaluate to a value to be used as
15008 an operand in a GIMPLE statement, this value will be stored in
15009 *EXPR_P on exit. This happens when the caller specifies one
15010 of fb_lvalue or fb_rvalue fallback flags.
15012 PRE_P will contain the sequence of GIMPLE statements corresponding
15013 to the evaluation of EXPR and all the side-effects that must
15014 be executed before the main expression. On exit, the last
15015 statement of PRE_P is the core statement being gimplified. For
15016 instance, when gimplifying 'if (++a)' the last statement in
15017 PRE_P will be 'if (t.1)' where t.1 is the result of
15018 pre-incrementing 'a'.
15020 POST_P will contain the sequence of GIMPLE statements corresponding
15021 to the evaluation of all the side-effects that must be executed
15022 after the main expression. If this is NULL, the post
15023 side-effects are stored at the end of PRE_P.
15025 The reason why the output is split in two is to handle post
15026 side-effects explicitly. In some cases, an expression may have
15027 inner and outer post side-effects which need to be emitted in
15028 an order different from the one given by the recursive
15029 traversal. For instance, for the expression (*p--)++ the post
15030 side-effects of '--' must actually occur *after* the post
15031 side-effects of '++'. However, gimplification will first visit
15032 the inner expression, so if a separate POST sequence was not
15033 used, the resulting sequence would be:
15035 1 t.1 = *p
15036 2 p = p - 1
15037 3 t.2 = t.1 + 1
15038 4 *p = t.2
15040 However, the post-decrement operation in line #2 must not be
15041 evaluated until after the store to *p at line #4, so the
15042 correct sequence should be:
15044 1 t.1 = *p
15045 2 t.2 = t.1 + 1
15046 3 *p = t.2
15047 4 p = p - 1
15049 So, by specifying a separate post queue, it is possible
15050 to emit the post side-effects in the correct order.
15051 If POST_P is NULL, an internal queue will be used. Before
15052 returning to the caller, the sequence POST_P is appended to
15053 the main output sequence PRE_P.
15055 GIMPLE_TEST_F points to a function that takes a tree T and
15056 returns nonzero if T is in the GIMPLE form requested by the
15057 caller. The GIMPLE predicates are in gimple.cc.
15059 FALLBACK tells the function what sort of a temporary we want if
15060 gimplification cannot produce an expression that complies with
15061 GIMPLE_TEST_F.
15063 fb_none means that no temporary should be generated
15064 fb_rvalue means that an rvalue is OK to generate
15065 fb_lvalue means that an lvalue is OK to generate
15066 fb_either means that either is OK, but an lvalue is preferable.
15067 fb_mayfail means that gimplification may fail (in which case
15068 GS_ERROR will be returned)
15070 The return value is either GS_ERROR or GS_ALL_DONE, since this
15071 function iterates until EXPR is completely gimplified or an error
15072 occurs. */
15074 enum gimplify_status
15075 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
15076 bool (*gimple_test_f) (tree), fallback_t fallback)
15078 tree tmp;
15079 gimple_seq internal_pre = NULL;
15080 gimple_seq internal_post = NULL;
15081 tree save_expr;
15082 bool is_statement;
15083 location_t saved_location;
15084 enum gimplify_status ret;
15085 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
15086 tree label;
15088 save_expr = *expr_p;
15089 if (save_expr == NULL_TREE)
15090 return GS_ALL_DONE;
15092 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
15093 is_statement = gimple_test_f == is_gimple_stmt;
15094 if (is_statement)
15095 gcc_assert (pre_p);
15097 /* Consistency checks. */
15098 if (gimple_test_f == is_gimple_reg)
15099 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
15100 else if (gimple_test_f == is_gimple_val
15101 || gimple_test_f == is_gimple_call_addr
15102 || gimple_test_f == is_gimple_condexpr_for_cond
15103 || gimple_test_f == is_gimple_mem_rhs
15104 || gimple_test_f == is_gimple_mem_rhs_or_call
15105 || gimple_test_f == is_gimple_reg_rhs
15106 || gimple_test_f == is_gimple_reg_rhs_or_call
15107 || gimple_test_f == is_gimple_asm_val
15108 || gimple_test_f == is_gimple_mem_ref_addr)
15109 gcc_assert (fallback & fb_rvalue);
15110 else if (gimple_test_f == is_gimple_min_lval
15111 || gimple_test_f == is_gimple_lvalue)
15112 gcc_assert (fallback & fb_lvalue);
15113 else if (gimple_test_f == is_gimple_addressable)
15114 gcc_assert (fallback & fb_either);
15115 else if (gimple_test_f == is_gimple_stmt)
15116 gcc_assert (fallback == fb_none);
15117 else
15119 /* We should have recognized the GIMPLE_TEST_F predicate to
15120 know what kind of fallback to use in case a temporary is
15121 needed to hold the value or address of *EXPR_P. */
15122 gcc_unreachable ();
15125 /* We used to check the predicate here and return immediately if it
15126 succeeds. This is wrong; the design is for gimplification to be
15127 idempotent, and for the predicates to only test for valid forms, not
15128 whether they are fully simplified. */
15129 if (pre_p == NULL)
15130 pre_p = &internal_pre;
15132 if (post_p == NULL)
15133 post_p = &internal_post;
15135 /* Remember the last statements added to PRE_P and POST_P. Every
15136 new statement added by the gimplification helpers needs to be
15137 annotated with location information. To centralize the
15138 responsibility, we remember the last statement that had been
15139 added to both queues before gimplifying *EXPR_P. If
15140 gimplification produces new statements in PRE_P and POST_P, those
15141 statements will be annotated with the same location information
15142 as *EXPR_P. */
15143 pre_last_gsi = gsi_last (*pre_p);
15144 post_last_gsi = gsi_last (*post_p);
15146 saved_location = input_location;
15147 if (save_expr != error_mark_node
15148 && EXPR_HAS_LOCATION (*expr_p))
15149 input_location = EXPR_LOCATION (*expr_p);
15151 /* Loop over the specific gimplifiers until the toplevel node
15152 remains the same. */
15155 /* Strip away as many useless type conversions as possible
15156 at the toplevel. */
15157 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
15159 /* Remember the expr. */
15160 save_expr = *expr_p;
15162 /* Die, die, die, my darling. */
15163 if (error_operand_p (save_expr))
15165 ret = GS_ERROR;
15166 break;
15169 /* Do any language-specific gimplification. */
15170 ret = ((enum gimplify_status)
15171 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
15172 if (ret == GS_OK)
15174 if (*expr_p == NULL_TREE)
15175 break;
15176 if (*expr_p != save_expr)
15177 continue;
15179 else if (ret != GS_UNHANDLED)
15180 break;
15182 /* Make sure that all the cases set 'ret' appropriately. */
15183 ret = GS_UNHANDLED;
15184 switch (TREE_CODE (*expr_p))
15186 /* First deal with the special cases. */
15188 case POSTINCREMENT_EXPR:
15189 case POSTDECREMENT_EXPR:
15190 case PREINCREMENT_EXPR:
15191 case PREDECREMENT_EXPR:
15192 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
15193 fallback != fb_none,
15194 TREE_TYPE (*expr_p));
15195 break;
15197 case VIEW_CONVERT_EXPR:
15198 if ((fallback & fb_rvalue)
15199 && is_gimple_reg_type (TREE_TYPE (*expr_p))
15200 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
15202 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15203 post_p, is_gimple_val, fb_rvalue);
15204 recalculate_side_effects (*expr_p);
15205 break;
15207 /* Fallthru. */
15209 case ARRAY_REF:
15210 case ARRAY_RANGE_REF:
15211 case REALPART_EXPR:
15212 case IMAGPART_EXPR:
15213 case COMPONENT_REF:
15214 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
15215 fallback ? fallback : fb_rvalue);
15216 break;
15218 case COND_EXPR:
15219 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
15221 /* C99 code may assign to an array in a structure value of a
15222 conditional expression, and this has undefined behavior
15223 only on execution, so create a temporary if an lvalue is
15224 required. */
15225 if (fallback == fb_lvalue)
15227 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
15228 mark_addressable (*expr_p);
15229 ret = GS_OK;
15231 break;
15233 case CALL_EXPR:
15234 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
15236 /* C99 code may assign to an array in a structure returned
15237 from a function, and this has undefined behavior only on
15238 execution, so create a temporary if an lvalue is
15239 required. */
15240 if (fallback == fb_lvalue)
15242 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
15243 mark_addressable (*expr_p);
15244 ret = GS_OK;
15246 break;
15248 case TREE_LIST:
15249 gcc_unreachable ();
15251 case COMPOUND_EXPR:
15252 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
15253 break;
15255 case COMPOUND_LITERAL_EXPR:
15256 ret = gimplify_compound_literal_expr (expr_p, pre_p,
15257 gimple_test_f, fallback);
15258 break;
15260 case MODIFY_EXPR:
15261 case INIT_EXPR:
15262 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
15263 fallback != fb_none);
15264 break;
15266 case TRUTH_ANDIF_EXPR:
15267 case TRUTH_ORIF_EXPR:
15269 /* Preserve the original type of the expression and the
15270 source location of the outer expression. */
15271 tree org_type = TREE_TYPE (*expr_p);
15272 *expr_p = gimple_boolify (*expr_p);
15273 *expr_p = build3_loc (input_location, COND_EXPR,
15274 org_type, *expr_p,
15275 fold_convert_loc
15276 (input_location,
15277 org_type, boolean_true_node),
15278 fold_convert_loc
15279 (input_location,
15280 org_type, boolean_false_node));
15281 ret = GS_OK;
15282 break;
15285 case TRUTH_NOT_EXPR:
15287 tree type = TREE_TYPE (*expr_p);
15288 /* The parsers are careful to generate TRUTH_NOT_EXPR
15289 only with operands that are always zero or one.
15290 We do not fold here but handle the only interesting case
15291 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
15292 *expr_p = gimple_boolify (*expr_p);
15293 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
15294 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
15295 TREE_TYPE (*expr_p),
15296 TREE_OPERAND (*expr_p, 0));
15297 else
15298 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
15299 TREE_TYPE (*expr_p),
15300 TREE_OPERAND (*expr_p, 0),
15301 build_int_cst (TREE_TYPE (*expr_p), 1));
15302 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
15303 *expr_p = fold_convert_loc (input_location, type, *expr_p);
15304 ret = GS_OK;
15305 break;
15308 case ADDR_EXPR:
15309 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
15310 break;
15312 case ANNOTATE_EXPR:
15314 tree cond = TREE_OPERAND (*expr_p, 0);
15315 tree kind = TREE_OPERAND (*expr_p, 1);
15316 tree data = TREE_OPERAND (*expr_p, 2);
15317 tree type = TREE_TYPE (cond);
15318 if (!INTEGRAL_TYPE_P (type))
15320 *expr_p = cond;
15321 ret = GS_OK;
15322 break;
15324 tree tmp = create_tmp_var (type);
15325 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
15326 gcall *call
15327 = gimple_build_call_internal (IFN_ANNOTATE, 3, cond, kind, data);
15328 gimple_call_set_lhs (call, tmp);
15329 gimplify_seq_add_stmt (pre_p, call);
15330 *expr_p = tmp;
15331 ret = GS_ALL_DONE;
15332 break;
15335 case VA_ARG_EXPR:
15336 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
15337 break;
15339 CASE_CONVERT:
15340 if (IS_EMPTY_STMT (*expr_p))
15342 ret = GS_ALL_DONE;
15343 break;
15346 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
15347 || fallback == fb_none)
15349 /* Just strip a conversion to void (or in void context) and
15350 try again. */
15351 *expr_p = TREE_OPERAND (*expr_p, 0);
15352 ret = GS_OK;
15353 break;
15356 ret = gimplify_conversion (expr_p);
15357 if (ret == GS_ERROR)
15358 break;
15359 if (*expr_p != save_expr)
15360 break;
15361 /* FALLTHRU */
15363 case FIX_TRUNC_EXPR:
15364 /* unary_expr: ... | '(' cast ')' val | ... */
15365 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
15366 is_gimple_val, fb_rvalue);
15367 recalculate_side_effects (*expr_p);
15368 break;
15370 case INDIRECT_REF:
15372 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
15373 bool notrap = TREE_THIS_NOTRAP (*expr_p);
15374 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
15376 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
15377 if (*expr_p != save_expr)
15379 ret = GS_OK;
15380 break;
15383 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
15384 is_gimple_reg, fb_rvalue);
15385 if (ret == GS_ERROR)
15386 break;
15388 recalculate_side_effects (*expr_p);
15389 *expr_p = fold_build2_loc (input_location, MEM_REF,
15390 TREE_TYPE (*expr_p),
15391 TREE_OPERAND (*expr_p, 0),
15392 build_int_cst (saved_ptr_type, 0));
15393 TREE_THIS_VOLATILE (*expr_p) = volatilep;
15394 TREE_THIS_NOTRAP (*expr_p) = notrap;
15395 ret = GS_OK;
15396 break;
15399 /* We arrive here through the various re-gimplifcation paths. */
15400 case MEM_REF:
15401 /* First try re-folding the whole thing. */
15402 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
15403 TREE_OPERAND (*expr_p, 0),
15404 TREE_OPERAND (*expr_p, 1));
15405 if (tmp)
15407 REF_REVERSE_STORAGE_ORDER (tmp)
15408 = REF_REVERSE_STORAGE_ORDER (*expr_p);
15409 *expr_p = tmp;
15410 recalculate_side_effects (*expr_p);
15411 ret = GS_OK;
15412 break;
15414 /* Avoid re-gimplifying the address operand if it is already
15415 in suitable form. Re-gimplifying would mark the address
15416 operand addressable. Always gimplify when not in SSA form
15417 as we still may have to gimplify decls with value-exprs. */
15418 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
15419 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
15421 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
15422 is_gimple_mem_ref_addr, fb_rvalue);
15423 if (ret == GS_ERROR)
15424 break;
15426 recalculate_side_effects (*expr_p);
15427 ret = GS_ALL_DONE;
15428 break;
15430 /* Constants need not be gimplified. */
15431 case INTEGER_CST:
15432 case REAL_CST:
15433 case FIXED_CST:
15434 case STRING_CST:
15435 case COMPLEX_CST:
15436 case VECTOR_CST:
15437 /* Drop the overflow flag on constants, we do not want
15438 that in the GIMPLE IL. */
15439 if (TREE_OVERFLOW_P (*expr_p))
15440 *expr_p = drop_tree_overflow (*expr_p);
15441 ret = GS_ALL_DONE;
15442 break;
15444 case CONST_DECL:
15445 /* If we require an lvalue, such as for ADDR_EXPR, retain the
15446 CONST_DECL node. Otherwise the decl is replaceable by its
15447 value. */
15448 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
15449 if (fallback & fb_lvalue)
15450 ret = GS_ALL_DONE;
15451 else
15453 *expr_p = DECL_INITIAL (*expr_p);
15454 ret = GS_OK;
15456 break;
15458 case DECL_EXPR:
15459 ret = gimplify_decl_expr (expr_p, pre_p);
15460 break;
15462 case BIND_EXPR:
15463 ret = gimplify_bind_expr (expr_p, pre_p);
15464 break;
15466 case LOOP_EXPR:
15467 ret = gimplify_loop_expr (expr_p, pre_p);
15468 break;
15470 case SWITCH_EXPR:
15471 ret = gimplify_switch_expr (expr_p, pre_p);
15472 break;
15474 case EXIT_EXPR:
15475 ret = gimplify_exit_expr (expr_p);
15476 break;
15478 case GOTO_EXPR:
15479 /* If the target is not LABEL, then it is a computed jump
15480 and the target needs to be gimplified. */
15481 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
15483 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
15484 NULL, is_gimple_val, fb_rvalue);
15485 if (ret == GS_ERROR)
15486 break;
15488 gimplify_seq_add_stmt (pre_p,
15489 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
15490 ret = GS_ALL_DONE;
15491 break;
15493 case PREDICT_EXPR:
15494 gimplify_seq_add_stmt (pre_p,
15495 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
15496 PREDICT_EXPR_OUTCOME (*expr_p)));
15497 ret = GS_ALL_DONE;
15498 break;
15500 case LABEL_EXPR:
15501 ret = gimplify_label_expr (expr_p, pre_p);
15502 label = LABEL_EXPR_LABEL (*expr_p);
15503 gcc_assert (decl_function_context (label) == current_function_decl);
15505 /* If the label is used in a goto statement, or address of the label
15506 is taken, we need to unpoison all variables that were seen so far.
15507 Doing so would prevent us from reporting a false positives. */
15508 if (asan_poisoned_variables
15509 && asan_used_labels != NULL
15510 && asan_used_labels->contains (label)
15511 && !gimplify_omp_ctxp)
15512 asan_poison_variables (asan_poisoned_variables, false, pre_p);
15513 break;
15515 case CASE_LABEL_EXPR:
15516 ret = gimplify_case_label_expr (expr_p, pre_p);
15518 if (gimplify_ctxp->live_switch_vars)
15519 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
15520 pre_p);
15521 break;
15523 case RETURN_EXPR:
15524 ret = gimplify_return_expr (*expr_p, pre_p);
15525 break;
15527 case CONSTRUCTOR:
15528 /* Don't reduce this in place; let gimplify_init_constructor work its
15529 magic. Buf if we're just elaborating this for side effects, just
15530 gimplify any element that has side-effects. */
15531 if (fallback == fb_none)
15533 unsigned HOST_WIDE_INT ix;
15534 tree val;
15535 tree temp = NULL_TREE;
15536 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
15537 if (TREE_SIDE_EFFECTS (val))
15538 append_to_statement_list (val, &temp);
15540 *expr_p = temp;
15541 ret = temp ? GS_OK : GS_ALL_DONE;
15543 /* C99 code may assign to an array in a constructed
15544 structure or union, and this has undefined behavior only
15545 on execution, so create a temporary if an lvalue is
15546 required. */
15547 else if (fallback == fb_lvalue)
15549 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
15550 mark_addressable (*expr_p);
15551 ret = GS_OK;
15553 else
15554 ret = GS_ALL_DONE;
15555 break;
15557 /* The following are special cases that are not handled by the
15558 original GIMPLE grammar. */
15560 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
15561 eliminated. */
15562 case SAVE_EXPR:
15563 ret = gimplify_save_expr (expr_p, pre_p, post_p);
15564 break;
15566 case BIT_FIELD_REF:
15567 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15568 post_p, is_gimple_lvalue, fb_either);
15569 recalculate_side_effects (*expr_p);
15570 break;
15572 case TARGET_MEM_REF:
15574 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
15576 if (TMR_BASE (*expr_p))
15577 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
15578 post_p, is_gimple_mem_ref_addr, fb_either);
15579 if (TMR_INDEX (*expr_p))
15580 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
15581 post_p, is_gimple_val, fb_rvalue);
15582 if (TMR_INDEX2 (*expr_p))
15583 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
15584 post_p, is_gimple_val, fb_rvalue);
15585 /* TMR_STEP and TMR_OFFSET are always integer constants. */
15586 ret = MIN (r0, r1);
15588 break;
15590 case NON_LVALUE_EXPR:
15591 /* This should have been stripped above. */
15592 gcc_unreachable ();
15594 case ASM_EXPR:
15595 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
15596 break;
15598 case TRY_FINALLY_EXPR:
15599 case TRY_CATCH_EXPR:
15601 gimple_seq eval, cleanup;
15602 gtry *try_;
15604 /* Calls to destructors are generated automatically in FINALLY/CATCH
15605 block. They should have location as UNKNOWN_LOCATION. However,
15606 gimplify_call_expr will reset these call stmts to input_location
15607 if it finds stmt's location is unknown. To prevent resetting for
15608 destructors, we set the input_location to unknown.
15609 Note that this only affects the destructor calls in FINALLY/CATCH
15610 block, and will automatically reset to its original value by the
15611 end of gimplify_expr. */
15612 input_location = UNKNOWN_LOCATION;
15613 eval = cleanup = NULL;
15614 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
15615 if (TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
15616 && TREE_CODE (TREE_OPERAND (*expr_p, 1)) == EH_ELSE_EXPR)
15618 gimple_seq n = NULL, e = NULL;
15619 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
15620 0), &n);
15621 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
15622 1), &e);
15623 if (!gimple_seq_empty_p (n) && !gimple_seq_empty_p (e))
15625 geh_else *stmt = gimple_build_eh_else (n, e);
15626 gimple_seq_add_stmt (&cleanup, stmt);
15629 else
15630 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
15631 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
15632 if (gimple_seq_empty_p (cleanup))
15634 gimple_seq_add_seq (pre_p, eval);
15635 ret = GS_ALL_DONE;
15636 break;
15638 try_ = gimple_build_try (eval, cleanup,
15639 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
15640 ? GIMPLE_TRY_FINALLY
15641 : GIMPLE_TRY_CATCH);
15642 if (EXPR_HAS_LOCATION (save_expr))
15643 gimple_set_location (try_, EXPR_LOCATION (save_expr));
15644 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
15645 gimple_set_location (try_, saved_location);
15646 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
15647 gimple_try_set_catch_is_cleanup (try_,
15648 TRY_CATCH_IS_CLEANUP (*expr_p));
15649 gimplify_seq_add_stmt (pre_p, try_);
15650 ret = GS_ALL_DONE;
15651 break;
15654 case CLEANUP_POINT_EXPR:
15655 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
15656 break;
15658 case TARGET_EXPR:
15659 ret = gimplify_target_expr (expr_p, pre_p, post_p);
15660 break;
15662 case CATCH_EXPR:
15664 gimple *c;
15665 gimple_seq handler = NULL;
15666 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
15667 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
15668 gimplify_seq_add_stmt (pre_p, c);
15669 ret = GS_ALL_DONE;
15670 break;
15673 case EH_FILTER_EXPR:
15675 gimple *ehf;
15676 gimple_seq failure = NULL;
15678 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
15679 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
15680 copy_warning (ehf, *expr_p);
15681 gimplify_seq_add_stmt (pre_p, ehf);
15682 ret = GS_ALL_DONE;
15683 break;
15686 case OBJ_TYPE_REF:
15688 enum gimplify_status r0, r1;
15689 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
15690 post_p, is_gimple_val, fb_rvalue);
15691 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
15692 post_p, is_gimple_val, fb_rvalue);
15693 TREE_SIDE_EFFECTS (*expr_p) = 0;
15694 ret = MIN (r0, r1);
15696 break;
15698 case LABEL_DECL:
15699 /* We get here when taking the address of a label. We mark
15700 the label as "forced"; meaning it can never be removed and
15701 it is a potential target for any computed goto. */
15702 FORCED_LABEL (*expr_p) = 1;
15703 ret = GS_ALL_DONE;
15704 break;
15706 case STATEMENT_LIST:
15707 ret = gimplify_statement_list (expr_p, pre_p);
15708 break;
15710 case WITH_SIZE_EXPR:
15712 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15713 post_p == &internal_post ? NULL : post_p,
15714 gimple_test_f, fallback);
15715 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
15716 is_gimple_val, fb_rvalue);
15717 ret = GS_ALL_DONE;
15719 break;
15721 case VAR_DECL:
15722 case PARM_DECL:
15723 ret = gimplify_var_or_parm_decl (expr_p);
15724 break;
15726 case RESULT_DECL:
15727 /* When within an OMP context, notice uses of variables. */
15728 if (gimplify_omp_ctxp)
15729 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
15730 ret = GS_ALL_DONE;
15731 break;
15733 case DEBUG_EXPR_DECL:
15734 gcc_unreachable ();
15736 case DEBUG_BEGIN_STMT:
15737 gimplify_seq_add_stmt (pre_p,
15738 gimple_build_debug_begin_stmt
15739 (TREE_BLOCK (*expr_p),
15740 EXPR_LOCATION (*expr_p)));
15741 ret = GS_ALL_DONE;
15742 *expr_p = NULL;
15743 break;
15745 case SSA_NAME:
15746 /* Allow callbacks into the gimplifier during optimization. */
15747 ret = GS_ALL_DONE;
15748 break;
15750 case OMP_PARALLEL:
15751 gimplify_omp_parallel (expr_p, pre_p);
15752 ret = GS_ALL_DONE;
15753 break;
15755 case OMP_TASK:
15756 gimplify_omp_task (expr_p, pre_p);
15757 ret = GS_ALL_DONE;
15758 break;
15760 case OMP_SIMD:
15762 /* Temporarily disable into_ssa, as scan_omp_simd
15763 which calls copy_gimple_seq_and_replace_locals can't deal
15764 with SSA_NAMEs defined outside of the body properly. */
15765 bool saved_into_ssa = gimplify_ctxp->into_ssa;
15766 gimplify_ctxp->into_ssa = false;
15767 ret = gimplify_omp_for (expr_p, pre_p);
15768 gimplify_ctxp->into_ssa = saved_into_ssa;
15769 break;
15772 case OMP_FOR:
15773 case OMP_DISTRIBUTE:
15774 case OMP_TASKLOOP:
15775 case OACC_LOOP:
15776 ret = gimplify_omp_for (expr_p, pre_p);
15777 break;
15779 case OMP_LOOP:
15780 ret = gimplify_omp_loop (expr_p, pre_p);
15781 break;
15783 case OACC_CACHE:
15784 gimplify_oacc_cache (expr_p, pre_p);
15785 ret = GS_ALL_DONE;
15786 break;
15788 case OACC_DECLARE:
15789 gimplify_oacc_declare (expr_p, pre_p);
15790 ret = GS_ALL_DONE;
15791 break;
15793 case OACC_HOST_DATA:
15794 case OACC_DATA:
15795 case OACC_KERNELS:
15796 case OACC_PARALLEL:
15797 case OACC_SERIAL:
15798 case OMP_SCOPE:
15799 case OMP_SECTIONS:
15800 case OMP_SINGLE:
15801 case OMP_TARGET:
15802 case OMP_TARGET_DATA:
15803 case OMP_TEAMS:
15804 gimplify_omp_workshare (expr_p, pre_p);
15805 ret = GS_ALL_DONE;
15806 break;
15808 case OACC_ENTER_DATA:
15809 case OACC_EXIT_DATA:
15810 case OACC_UPDATE:
15811 case OMP_TARGET_UPDATE:
15812 case OMP_TARGET_ENTER_DATA:
15813 case OMP_TARGET_EXIT_DATA:
15814 gimplify_omp_target_update (expr_p, pre_p);
15815 ret = GS_ALL_DONE;
15816 break;
15818 case OMP_SECTION:
15819 case OMP_MASTER:
15820 case OMP_MASKED:
15821 case OMP_ORDERED:
15822 case OMP_CRITICAL:
15823 case OMP_SCAN:
15825 gimple_seq body = NULL;
15826 gimple *g;
15827 bool saved_in_omp_construct = in_omp_construct;
15829 in_omp_construct = true;
15830 gimplify_and_add (OMP_BODY (*expr_p), &body);
15831 in_omp_construct = saved_in_omp_construct;
15832 switch (TREE_CODE (*expr_p))
15834 case OMP_SECTION:
15835 g = gimple_build_omp_section (body);
15836 break;
15837 case OMP_MASTER:
15838 g = gimple_build_omp_master (body);
15839 break;
15840 case OMP_ORDERED:
15841 g = gimplify_omp_ordered (*expr_p, body);
15842 if (OMP_BODY (*expr_p) == NULL_TREE
15843 && gimple_code (g) == GIMPLE_OMP_ORDERED)
15844 gimple_omp_ordered_standalone (g);
15845 break;
15846 case OMP_MASKED:
15847 gimplify_scan_omp_clauses (&OMP_MASKED_CLAUSES (*expr_p),
15848 pre_p, ORT_WORKSHARE, OMP_MASKED);
15849 gimplify_adjust_omp_clauses (pre_p, body,
15850 &OMP_MASKED_CLAUSES (*expr_p),
15851 OMP_MASKED);
15852 g = gimple_build_omp_masked (body,
15853 OMP_MASKED_CLAUSES (*expr_p));
15854 break;
15855 case OMP_CRITICAL:
15856 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
15857 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
15858 gimplify_adjust_omp_clauses (pre_p, body,
15859 &OMP_CRITICAL_CLAUSES (*expr_p),
15860 OMP_CRITICAL);
15861 g = gimple_build_omp_critical (body,
15862 OMP_CRITICAL_NAME (*expr_p),
15863 OMP_CRITICAL_CLAUSES (*expr_p));
15864 break;
15865 case OMP_SCAN:
15866 gimplify_scan_omp_clauses (&OMP_SCAN_CLAUSES (*expr_p),
15867 pre_p, ORT_WORKSHARE, OMP_SCAN);
15868 gimplify_adjust_omp_clauses (pre_p, body,
15869 &OMP_SCAN_CLAUSES (*expr_p),
15870 OMP_SCAN);
15871 g = gimple_build_omp_scan (body, OMP_SCAN_CLAUSES (*expr_p));
15872 break;
15873 default:
15874 gcc_unreachable ();
15876 gimplify_seq_add_stmt (pre_p, g);
15877 ret = GS_ALL_DONE;
15878 break;
15881 case OMP_TASKGROUP:
15883 gimple_seq body = NULL;
15885 tree *pclauses = &OMP_TASKGROUP_CLAUSES (*expr_p);
15886 bool saved_in_omp_construct = in_omp_construct;
15887 gimplify_scan_omp_clauses (pclauses, pre_p, ORT_TASKGROUP,
15888 OMP_TASKGROUP);
15889 gimplify_adjust_omp_clauses (pre_p, NULL, pclauses, OMP_TASKGROUP);
15891 in_omp_construct = true;
15892 gimplify_and_add (OMP_BODY (*expr_p), &body);
15893 in_omp_construct = saved_in_omp_construct;
15894 gimple_seq cleanup = NULL;
15895 tree fn = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
15896 gimple *g = gimple_build_call (fn, 0);
15897 gimple_seq_add_stmt (&cleanup, g);
15898 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
15899 body = NULL;
15900 gimple_seq_add_stmt (&body, g);
15901 g = gimple_build_omp_taskgroup (body, *pclauses);
15902 gimplify_seq_add_stmt (pre_p, g);
15903 ret = GS_ALL_DONE;
15904 break;
15907 case OMP_ATOMIC:
15908 case OMP_ATOMIC_READ:
15909 case OMP_ATOMIC_CAPTURE_OLD:
15910 case OMP_ATOMIC_CAPTURE_NEW:
15911 ret = gimplify_omp_atomic (expr_p, pre_p);
15912 break;
15914 case TRANSACTION_EXPR:
15915 ret = gimplify_transaction (expr_p, pre_p);
15916 break;
15918 case TRUTH_AND_EXPR:
15919 case TRUTH_OR_EXPR:
15920 case TRUTH_XOR_EXPR:
15922 tree orig_type = TREE_TYPE (*expr_p);
15923 tree new_type, xop0, xop1;
15924 *expr_p = gimple_boolify (*expr_p);
15925 new_type = TREE_TYPE (*expr_p);
15926 if (!useless_type_conversion_p (orig_type, new_type))
15928 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
15929 ret = GS_OK;
15930 break;
15933 /* Boolified binary truth expressions are semantically equivalent
15934 to bitwise binary expressions. Canonicalize them to the
15935 bitwise variant. */
15936 switch (TREE_CODE (*expr_p))
15938 case TRUTH_AND_EXPR:
15939 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
15940 break;
15941 case TRUTH_OR_EXPR:
15942 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
15943 break;
15944 case TRUTH_XOR_EXPR:
15945 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
15946 break;
15947 default:
15948 break;
15950 /* Now make sure that operands have compatible type to
15951 expression's new_type. */
15952 xop0 = TREE_OPERAND (*expr_p, 0);
15953 xop1 = TREE_OPERAND (*expr_p, 1);
15954 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
15955 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
15956 new_type,
15957 xop0);
15958 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
15959 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
15960 new_type,
15961 xop1);
15962 /* Continue classified as tcc_binary. */
15963 goto expr_2;
15966 case VEC_COND_EXPR:
15967 goto expr_3;
15969 case VEC_PERM_EXPR:
15970 /* Classified as tcc_expression. */
15971 goto expr_3;
15973 case BIT_INSERT_EXPR:
15974 /* Argument 3 is a constant. */
15975 goto expr_2;
15977 case POINTER_PLUS_EXPR:
15979 enum gimplify_status r0, r1;
15980 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
15981 post_p, is_gimple_val, fb_rvalue);
15982 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
15983 post_p, is_gimple_val, fb_rvalue);
15984 recalculate_side_effects (*expr_p);
15985 ret = MIN (r0, r1);
15986 break;
15989 default:
15990 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
15992 case tcc_comparison:
15993 /* Handle comparison of objects of non scalar mode aggregates
15994 with a call to memcmp. It would be nice to only have to do
15995 this for variable-sized objects, but then we'd have to allow
15996 the same nest of reference nodes we allow for MODIFY_EXPR and
15997 that's too complex.
15999 Compare scalar mode aggregates as scalar mode values. Using
16000 memcmp for them would be very inefficient at best, and is
16001 plain wrong if bitfields are involved. */
16003 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
16005 /* Vector comparisons need no boolification. */
16006 if (TREE_CODE (type) == VECTOR_TYPE)
16007 goto expr_2;
16008 else if (!AGGREGATE_TYPE_P (type))
16010 tree org_type = TREE_TYPE (*expr_p);
16011 *expr_p = gimple_boolify (*expr_p);
16012 if (!useless_type_conversion_p (org_type,
16013 TREE_TYPE (*expr_p)))
16015 *expr_p = fold_convert_loc (input_location,
16016 org_type, *expr_p);
16017 ret = GS_OK;
16019 else
16020 goto expr_2;
16022 else if (TYPE_MODE (type) != BLKmode)
16023 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
16024 else
16025 ret = gimplify_variable_sized_compare (expr_p);
16027 break;
16030 /* If *EXPR_P does not need to be special-cased, handle it
16031 according to its class. */
16032 case tcc_unary:
16033 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
16034 post_p, is_gimple_val, fb_rvalue);
16035 break;
16037 case tcc_binary:
16038 expr_2:
16040 enum gimplify_status r0, r1;
16042 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
16043 post_p, is_gimple_val, fb_rvalue);
16044 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
16045 post_p, is_gimple_val, fb_rvalue);
16047 ret = MIN (r0, r1);
16048 break;
16051 expr_3:
16053 enum gimplify_status r0, r1, r2;
16055 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
16056 post_p, is_gimple_val, fb_rvalue);
16057 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
16058 post_p, is_gimple_val, fb_rvalue);
16059 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
16060 post_p, is_gimple_val, fb_rvalue);
16062 ret = MIN (MIN (r0, r1), r2);
16063 break;
16066 case tcc_declaration:
16067 case tcc_constant:
16068 ret = GS_ALL_DONE;
16069 goto dont_recalculate;
16071 default:
16072 gcc_unreachable ();
16075 recalculate_side_effects (*expr_p);
16077 dont_recalculate:
16078 break;
16081 gcc_assert (*expr_p || ret != GS_OK);
16083 while (ret == GS_OK);
16085 /* If we encountered an error_mark somewhere nested inside, either
16086 stub out the statement or propagate the error back out. */
16087 if (ret == GS_ERROR)
16089 if (is_statement)
16090 *expr_p = NULL;
16091 goto out;
16094 /* This was only valid as a return value from the langhook, which
16095 we handled. Make sure it doesn't escape from any other context. */
16096 gcc_assert (ret != GS_UNHANDLED);
16098 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
16100 /* We aren't looking for a value, and we don't have a valid
16101 statement. If it doesn't have side-effects, throw it away.
16102 We can also get here with code such as "*&&L;", where L is
16103 a LABEL_DECL that is marked as FORCED_LABEL. */
16104 if (TREE_CODE (*expr_p) == LABEL_DECL
16105 || !TREE_SIDE_EFFECTS (*expr_p))
16106 *expr_p = NULL;
16107 else if (!TREE_THIS_VOLATILE (*expr_p))
16109 /* This is probably a _REF that contains something nested that
16110 has side effects. Recurse through the operands to find it. */
16111 enum tree_code code = TREE_CODE (*expr_p);
16113 switch (code)
16115 case COMPONENT_REF:
16116 case REALPART_EXPR:
16117 case IMAGPART_EXPR:
16118 case VIEW_CONVERT_EXPR:
16119 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
16120 gimple_test_f, fallback);
16121 break;
16123 case ARRAY_REF:
16124 case ARRAY_RANGE_REF:
16125 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
16126 gimple_test_f, fallback);
16127 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
16128 gimple_test_f, fallback);
16129 break;
16131 default:
16132 /* Anything else with side-effects must be converted to
16133 a valid statement before we get here. */
16134 gcc_unreachable ();
16137 *expr_p = NULL;
16139 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
16140 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode
16141 && !is_empty_type (TREE_TYPE (*expr_p)))
16143 /* Historically, the compiler has treated a bare reference
16144 to a non-BLKmode volatile lvalue as forcing a load. */
16145 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
16147 /* Normally, we do not want to create a temporary for a
16148 TREE_ADDRESSABLE type because such a type should not be
16149 copied by bitwise-assignment. However, we make an
16150 exception here, as all we are doing here is ensuring that
16151 we read the bytes that make up the type. We use
16152 create_tmp_var_raw because create_tmp_var will abort when
16153 given a TREE_ADDRESSABLE type. */
16154 tree tmp = create_tmp_var_raw (type, "vol");
16155 gimple_add_tmp_var (tmp);
16156 gimplify_assign (tmp, *expr_p, pre_p);
16157 *expr_p = NULL;
16159 else
16160 /* We can't do anything useful with a volatile reference to
16161 an incomplete type, so just throw it away. Likewise for
16162 a BLKmode type, since any implicit inner load should
16163 already have been turned into an explicit one by the
16164 gimplification process. */
16165 *expr_p = NULL;
16168 /* If we are gimplifying at the statement level, we're done. Tack
16169 everything together and return. */
16170 if (fallback == fb_none || is_statement)
16172 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
16173 it out for GC to reclaim it. */
16174 *expr_p = NULL_TREE;
16176 if (!gimple_seq_empty_p (internal_pre)
16177 || !gimple_seq_empty_p (internal_post))
16179 gimplify_seq_add_seq (&internal_pre, internal_post);
16180 gimplify_seq_add_seq (pre_p, internal_pre);
16183 /* The result of gimplifying *EXPR_P is going to be the last few
16184 statements in *PRE_P and *POST_P. Add location information
16185 to all the statements that were added by the gimplification
16186 helpers. */
16187 if (!gimple_seq_empty_p (*pre_p))
16188 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
16190 if (!gimple_seq_empty_p (*post_p))
16191 annotate_all_with_location_after (*post_p, post_last_gsi,
16192 input_location);
16194 goto out;
16197 #ifdef ENABLE_GIMPLE_CHECKING
16198 if (*expr_p)
16200 enum tree_code code = TREE_CODE (*expr_p);
16201 /* These expressions should already be in gimple IR form. */
16202 gcc_assert (code != MODIFY_EXPR
16203 && code != ASM_EXPR
16204 && code != BIND_EXPR
16205 && code != CATCH_EXPR
16206 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
16207 && code != EH_FILTER_EXPR
16208 && code != GOTO_EXPR
16209 && code != LABEL_EXPR
16210 && code != LOOP_EXPR
16211 && code != SWITCH_EXPR
16212 && code != TRY_FINALLY_EXPR
16213 && code != EH_ELSE_EXPR
16214 && code != OACC_PARALLEL
16215 && code != OACC_KERNELS
16216 && code != OACC_SERIAL
16217 && code != OACC_DATA
16218 && code != OACC_HOST_DATA
16219 && code != OACC_DECLARE
16220 && code != OACC_UPDATE
16221 && code != OACC_ENTER_DATA
16222 && code != OACC_EXIT_DATA
16223 && code != OACC_CACHE
16224 && code != OMP_CRITICAL
16225 && code != OMP_FOR
16226 && code != OACC_LOOP
16227 && code != OMP_MASTER
16228 && code != OMP_MASKED
16229 && code != OMP_TASKGROUP
16230 && code != OMP_ORDERED
16231 && code != OMP_PARALLEL
16232 && code != OMP_SCAN
16233 && code != OMP_SECTIONS
16234 && code != OMP_SECTION
16235 && code != OMP_SINGLE
16236 && code != OMP_SCOPE);
16238 #endif
16240 /* Otherwise we're gimplifying a subexpression, so the resulting
16241 value is interesting. If it's a valid operand that matches
16242 GIMPLE_TEST_F, we're done. Unless we are handling some
16243 post-effects internally; if that's the case, we need to copy into
16244 a temporary before adding the post-effects to POST_P. */
16245 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
16246 goto out;
16248 /* Otherwise, we need to create a new temporary for the gimplified
16249 expression. */
16251 /* We can't return an lvalue if we have an internal postqueue. The
16252 object the lvalue refers to would (probably) be modified by the
16253 postqueue; we need to copy the value out first, which means an
16254 rvalue. */
16255 if ((fallback & fb_lvalue)
16256 && gimple_seq_empty_p (internal_post)
16257 && is_gimple_addressable (*expr_p))
16259 /* An lvalue will do. Take the address of the expression, store it
16260 in a temporary, and replace the expression with an INDIRECT_REF of
16261 that temporary. */
16262 tree ref_alias_type = reference_alias_ptr_type (*expr_p);
16263 unsigned int ref_align = get_object_alignment (*expr_p);
16264 tree ref_type = TREE_TYPE (*expr_p);
16265 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
16266 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
16267 if (TYPE_ALIGN (ref_type) != ref_align)
16268 ref_type = build_aligned_type (ref_type, ref_align);
16269 *expr_p = build2 (MEM_REF, ref_type,
16270 tmp, build_zero_cst (ref_alias_type));
16272 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
16274 /* An rvalue will do. Assign the gimplified expression into a
16275 new temporary TMP and replace the original expression with
16276 TMP. First, make sure that the expression has a type so that
16277 it can be assigned into a temporary. */
16278 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
16279 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
16281 else
16283 #ifdef ENABLE_GIMPLE_CHECKING
16284 if (!(fallback & fb_mayfail))
16286 fprintf (stderr, "gimplification failed:\n");
16287 print_generic_expr (stderr, *expr_p);
16288 debug_tree (*expr_p);
16289 internal_error ("gimplification failed");
16291 #endif
16292 gcc_assert (fallback & fb_mayfail);
16294 /* If this is an asm statement, and the user asked for the
16295 impossible, don't die. Fail and let gimplify_asm_expr
16296 issue an error. */
16297 ret = GS_ERROR;
16298 goto out;
16301 /* Make sure the temporary matches our predicate. */
16302 gcc_assert ((*gimple_test_f) (*expr_p));
16304 if (!gimple_seq_empty_p (internal_post))
16306 annotate_all_with_location (internal_post, input_location);
16307 gimplify_seq_add_seq (pre_p, internal_post);
16310 out:
16311 input_location = saved_location;
16312 return ret;
16315 /* Like gimplify_expr but make sure the gimplified result is not itself
16316 a SSA name (but a decl if it were). Temporaries required by
16317 evaluating *EXPR_P may be still SSA names. */
16319 static enum gimplify_status
16320 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
16321 bool (*gimple_test_f) (tree), fallback_t fallback,
16322 bool allow_ssa)
16324 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
16325 gimple_test_f, fallback);
16326 if (! allow_ssa
16327 && TREE_CODE (*expr_p) == SSA_NAME)
16328 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
16329 return ret;
16332 /* Look through TYPE for variable-sized objects and gimplify each such
16333 size that we find. Add to LIST_P any statements generated. */
16335 void
16336 gimplify_type_sizes (tree type, gimple_seq *list_p)
16338 if (type == NULL || type == error_mark_node)
16339 return;
16341 const bool ignored_p
16342 = TYPE_NAME (type)
16343 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
16344 && DECL_IGNORED_P (TYPE_NAME (type));
16345 tree t;
16347 /* We first do the main variant, then copy into any other variants. */
16348 type = TYPE_MAIN_VARIANT (type);
16350 /* Avoid infinite recursion. */
16351 if (TYPE_SIZES_GIMPLIFIED (type))
16352 return;
16354 TYPE_SIZES_GIMPLIFIED (type) = 1;
16356 switch (TREE_CODE (type))
16358 case INTEGER_TYPE:
16359 case ENUMERAL_TYPE:
16360 case BOOLEAN_TYPE:
16361 case REAL_TYPE:
16362 case FIXED_POINT_TYPE:
16363 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
16364 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
16366 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
16368 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
16369 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
16371 break;
16373 case ARRAY_TYPE:
16374 /* These types may not have declarations, so handle them here. */
16375 gimplify_type_sizes (TREE_TYPE (type), list_p);
16376 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
16377 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
16378 with assigned stack slots, for -O1+ -g they should be tracked
16379 by VTA. */
16380 if (!ignored_p
16381 && TYPE_DOMAIN (type)
16382 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
16384 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
16385 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
16386 DECL_IGNORED_P (t) = 0;
16387 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
16388 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
16389 DECL_IGNORED_P (t) = 0;
16391 break;
16393 case RECORD_TYPE:
16394 case UNION_TYPE:
16395 case QUAL_UNION_TYPE:
16396 for (tree field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
16397 if (TREE_CODE (field) == FIELD_DECL)
16399 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
16400 /* Likewise, ensure variable offsets aren't removed. */
16401 if (!ignored_p
16402 && (t = DECL_FIELD_OFFSET (field))
16403 && VAR_P (t)
16404 && DECL_ARTIFICIAL (t))
16405 DECL_IGNORED_P (t) = 0;
16406 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
16407 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
16408 gimplify_type_sizes (TREE_TYPE (field), list_p);
16410 break;
16412 case POINTER_TYPE:
16413 case REFERENCE_TYPE:
16414 /* We used to recurse on the pointed-to type here, which turned out to
16415 be incorrect because its definition might refer to variables not
16416 yet initialized at this point if a forward declaration is involved.
16418 It was actually useful for anonymous pointed-to types to ensure
16419 that the sizes evaluation dominates every possible later use of the
16420 values. Restricting to such types here would be safe since there
16421 is no possible forward declaration around, but would introduce an
16422 undesirable middle-end semantic to anonymity. We then defer to
16423 front-ends the responsibility of ensuring that the sizes are
16424 evaluated both early and late enough, e.g. by attaching artificial
16425 type declarations to the tree. */
16426 break;
16428 default:
16429 break;
16432 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
16433 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
16435 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
16437 TYPE_SIZE (t) = TYPE_SIZE (type);
16438 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
16439 TYPE_SIZES_GIMPLIFIED (t) = 1;
16443 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
16444 a size or position, has had all of its SAVE_EXPRs evaluated.
16445 We add any required statements to *STMT_P. */
16447 void
16448 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
16450 tree expr = *expr_p;
16452 /* We don't do anything if the value isn't there, is constant, or contains
16453 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
16454 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
16455 will want to replace it with a new variable, but that will cause problems
16456 if this type is from outside the function. It's OK to have that here. */
16457 if (expr == NULL_TREE
16458 || is_gimple_constant (expr)
16459 || TREE_CODE (expr) == VAR_DECL
16460 || CONTAINS_PLACEHOLDER_P (expr))
16461 return;
16463 *expr_p = unshare_expr (expr);
16465 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
16466 if the def vanishes. */
16467 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
16469 /* If expr wasn't already is_gimple_sizepos or is_gimple_constant from the
16470 FE, ensure that it is a VAR_DECL, otherwise we might handle some decls
16471 as gimplify_vla_decl even when they would have all sizes INTEGER_CSTs. */
16472 if (is_gimple_constant (*expr_p))
16473 *expr_p = get_initialized_tmp_var (*expr_p, stmt_p, NULL, false);
16476 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
16477 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
16478 is true, also gimplify the parameters. */
16480 gbind *
16481 gimplify_body (tree fndecl, bool do_parms)
16483 location_t saved_location = input_location;
16484 gimple_seq parm_stmts, parm_cleanup = NULL, seq;
16485 gimple *outer_stmt;
16486 gbind *outer_bind;
16488 timevar_push (TV_TREE_GIMPLIFY);
16490 init_tree_ssa (cfun);
16492 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
16493 gimplification. */
16494 default_rtl_profile ();
16496 gcc_assert (gimplify_ctxp == NULL);
16497 push_gimplify_context (true);
16499 if (flag_openacc || flag_openmp)
16501 gcc_assert (gimplify_omp_ctxp == NULL);
16502 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
16503 gimplify_omp_ctxp = new_omp_context (ORT_IMPLICIT_TARGET);
16506 /* Unshare most shared trees in the body and in that of any nested functions.
16507 It would seem we don't have to do this for nested functions because
16508 they are supposed to be output and then the outer function gimplified
16509 first, but the g++ front end doesn't always do it that way. */
16510 unshare_body (fndecl);
16511 unvisit_body (fndecl);
16513 /* Make sure input_location isn't set to something weird. */
16514 input_location = DECL_SOURCE_LOCATION (fndecl);
16516 /* Resolve callee-copies. This has to be done before processing
16517 the body so that DECL_VALUE_EXPR gets processed correctly. */
16518 parm_stmts = do_parms ? gimplify_parameters (&parm_cleanup) : NULL;
16520 /* Gimplify the function's body. */
16521 seq = NULL;
16522 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
16523 outer_stmt = gimple_seq_first_nondebug_stmt (seq);
16524 if (!outer_stmt)
16526 outer_stmt = gimple_build_nop ();
16527 gimplify_seq_add_stmt (&seq, outer_stmt);
16530 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
16531 not the case, wrap everything in a GIMPLE_BIND to make it so. */
16532 if (gimple_code (outer_stmt) == GIMPLE_BIND
16533 && (gimple_seq_first_nondebug_stmt (seq)
16534 == gimple_seq_last_nondebug_stmt (seq)))
16536 outer_bind = as_a <gbind *> (outer_stmt);
16537 if (gimple_seq_first_stmt (seq) != outer_stmt
16538 || gimple_seq_last_stmt (seq) != outer_stmt)
16540 /* If there are debug stmts before or after outer_stmt, move them
16541 inside of outer_bind body. */
16542 gimple_stmt_iterator gsi = gsi_for_stmt (outer_stmt, &seq);
16543 gimple_seq second_seq = NULL;
16544 if (gimple_seq_first_stmt (seq) != outer_stmt
16545 && gimple_seq_last_stmt (seq) != outer_stmt)
16547 second_seq = gsi_split_seq_after (gsi);
16548 gsi_remove (&gsi, false);
16550 else if (gimple_seq_first_stmt (seq) != outer_stmt)
16551 gsi_remove (&gsi, false);
16552 else
16554 gsi_remove (&gsi, false);
16555 second_seq = seq;
16556 seq = NULL;
16558 gimple_seq_add_seq_without_update (&seq,
16559 gimple_bind_body (outer_bind));
16560 gimple_seq_add_seq_without_update (&seq, second_seq);
16561 gimple_bind_set_body (outer_bind, seq);
16564 else
16565 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
16567 DECL_SAVED_TREE (fndecl) = NULL_TREE;
16569 /* If we had callee-copies statements, insert them at the beginning
16570 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
16571 if (!gimple_seq_empty_p (parm_stmts))
16573 tree parm;
16575 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
16576 if (parm_cleanup)
16578 gtry *g = gimple_build_try (parm_stmts, parm_cleanup,
16579 GIMPLE_TRY_FINALLY);
16580 parm_stmts = NULL;
16581 gimple_seq_add_stmt (&parm_stmts, g);
16583 gimple_bind_set_body (outer_bind, parm_stmts);
16585 for (parm = DECL_ARGUMENTS (current_function_decl);
16586 parm; parm = DECL_CHAIN (parm))
16587 if (DECL_HAS_VALUE_EXPR_P (parm))
16589 DECL_HAS_VALUE_EXPR_P (parm) = 0;
16590 DECL_IGNORED_P (parm) = 0;
16594 if ((flag_openacc || flag_openmp || flag_openmp_simd)
16595 && gimplify_omp_ctxp)
16597 delete_omp_context (gimplify_omp_ctxp);
16598 gimplify_omp_ctxp = NULL;
16601 pop_gimplify_context (outer_bind);
16602 gcc_assert (gimplify_ctxp == NULL);
16604 if (flag_checking && !seen_error ())
16605 verify_gimple_in_seq (gimple_bind_body (outer_bind));
16607 timevar_pop (TV_TREE_GIMPLIFY);
16608 input_location = saved_location;
16610 return outer_bind;
16613 typedef char *char_p; /* For DEF_VEC_P. */
16615 /* Return whether we should exclude FNDECL from instrumentation. */
16617 static bool
16618 flag_instrument_functions_exclude_p (tree fndecl)
16620 vec<char_p> *v;
16622 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
16623 if (v && v->length () > 0)
16625 const char *name;
16626 int i;
16627 char *s;
16629 name = lang_hooks.decl_printable_name (fndecl, 1);
16630 FOR_EACH_VEC_ELT (*v, i, s)
16631 if (strstr (name, s) != NULL)
16632 return true;
16635 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
16636 if (v && v->length () > 0)
16638 const char *name;
16639 int i;
16640 char *s;
16642 name = DECL_SOURCE_FILE (fndecl);
16643 FOR_EACH_VEC_ELT (*v, i, s)
16644 if (strstr (name, s) != NULL)
16645 return true;
16648 return false;
16651 /* Build a call to the instrumentation function FNCODE and add it to SEQ.
16652 If COND_VAR is not NULL, it is a boolean variable guarding the call to
16653 the instrumentation function. IF STMT is not NULL, it is a statement
16654 to be executed just before the call to the instrumentation function. */
16656 static void
16657 build_instrumentation_call (gimple_seq *seq, enum built_in_function fncode,
16658 tree cond_var, gimple *stmt)
16660 /* The instrumentation hooks aren't going to call the instrumented
16661 function and the address they receive is expected to be matchable
16662 against symbol addresses. Make sure we don't create a trampoline,
16663 in case the current function is nested. */
16664 tree this_fn_addr = build_fold_addr_expr (current_function_decl);
16665 TREE_NO_TRAMPOLINE (this_fn_addr) = 1;
16667 tree label_true, label_false;
16668 if (cond_var)
16670 label_true = create_artificial_label (UNKNOWN_LOCATION);
16671 label_false = create_artificial_label (UNKNOWN_LOCATION);
16672 gcond *cond = gimple_build_cond (EQ_EXPR, cond_var, boolean_false_node,
16673 label_true, label_false);
16674 gimplify_seq_add_stmt (seq, cond);
16675 gimplify_seq_add_stmt (seq, gimple_build_label (label_true));
16676 gimplify_seq_add_stmt (seq, gimple_build_predict (PRED_COLD_LABEL,
16677 NOT_TAKEN));
16680 if (stmt)
16681 gimplify_seq_add_stmt (seq, stmt);
16683 tree x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
16684 gcall *call = gimple_build_call (x, 1, integer_zero_node);
16685 tree tmp_var = create_tmp_var (ptr_type_node, "return_addr");
16686 gimple_call_set_lhs (call, tmp_var);
16687 gimplify_seq_add_stmt (seq, call);
16688 x = builtin_decl_implicit (fncode);
16689 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
16690 gimplify_seq_add_stmt (seq, call);
16692 if (cond_var)
16693 gimplify_seq_add_stmt (seq, gimple_build_label (label_false));
16696 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
16697 node for the function we want to gimplify.
16699 Return the sequence of GIMPLE statements corresponding to the body
16700 of FNDECL. */
16702 void
16703 gimplify_function_tree (tree fndecl)
16705 gimple_seq seq;
16706 gbind *bind;
16708 gcc_assert (!gimple_body (fndecl));
16710 if (DECL_STRUCT_FUNCTION (fndecl))
16711 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
16712 else
16713 push_struct_function (fndecl);
16715 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
16716 if necessary. */
16717 cfun->curr_properties |= PROP_gimple_lva;
16719 if (asan_sanitize_use_after_scope ())
16720 asan_poisoned_variables = new hash_set<tree> ();
16721 bind = gimplify_body (fndecl, true);
16722 if (asan_poisoned_variables)
16724 delete asan_poisoned_variables;
16725 asan_poisoned_variables = NULL;
16728 /* The tree body of the function is no longer needed, replace it
16729 with the new GIMPLE body. */
16730 seq = NULL;
16731 gimple_seq_add_stmt (&seq, bind);
16732 gimple_set_body (fndecl, seq);
16734 /* If we're instrumenting function entry/exit, then prepend the call to
16735 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
16736 catch the exit hook. */
16737 /* ??? Add some way to ignore exceptions for this TFE. */
16738 if (flag_instrument_function_entry_exit
16739 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
16740 /* Do not instrument extern inline functions. */
16741 && !(DECL_DECLARED_INLINE_P (fndecl)
16742 && DECL_EXTERNAL (fndecl)
16743 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
16744 && !flag_instrument_functions_exclude_p (fndecl))
16746 gimple_seq body = NULL, cleanup = NULL;
16747 gassign *assign;
16748 tree cond_var;
16750 /* If -finstrument-functions-once is specified, generate:
16752 static volatile bool C.0 = false;
16753 bool tmp_called;
16755 tmp_called = C.0;
16756 if (!tmp_called)
16758 C.0 = true;
16759 [call profiling enter function]
16762 without specific protection for data races. */
16763 if (flag_instrument_function_entry_exit > 1)
16765 tree first_var
16766 = build_decl (DECL_SOURCE_LOCATION (current_function_decl),
16767 VAR_DECL,
16768 create_tmp_var_name ("C"),
16769 boolean_type_node);
16770 DECL_ARTIFICIAL (first_var) = 1;
16771 DECL_IGNORED_P (first_var) = 1;
16772 TREE_STATIC (first_var) = 1;
16773 TREE_THIS_VOLATILE (first_var) = 1;
16774 TREE_USED (first_var) = 1;
16775 DECL_INITIAL (first_var) = boolean_false_node;
16776 varpool_node::add (first_var);
16778 cond_var = create_tmp_var (boolean_type_node, "tmp_called");
16779 assign = gimple_build_assign (cond_var, first_var);
16780 gimplify_seq_add_stmt (&body, assign);
16782 assign = gimple_build_assign (first_var, boolean_true_node);
16785 else
16787 cond_var = NULL_TREE;
16788 assign = NULL;
16791 build_instrumentation_call (&body, BUILT_IN_PROFILE_FUNC_ENTER,
16792 cond_var, assign);
16794 /* If -finstrument-functions-once is specified, generate:
16796 if (!tmp_called)
16797 [call profiling exit function]
16799 without specific protection for data races. */
16800 build_instrumentation_call (&cleanup, BUILT_IN_PROFILE_FUNC_EXIT,
16801 cond_var, NULL);
16803 gimple *tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
16804 gimplify_seq_add_stmt (&body, tf);
16805 gbind *new_bind = gimple_build_bind (NULL, body, NULL);
16807 /* Replace the current function body with the body
16808 wrapped in the try/finally TF. */
16809 seq = NULL;
16810 gimple_seq_add_stmt (&seq, new_bind);
16811 gimple_set_body (fndecl, seq);
16812 bind = new_bind;
16815 if (sanitize_flags_p (SANITIZE_THREAD)
16816 && param_tsan_instrument_func_entry_exit)
16818 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
16819 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
16820 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
16821 /* Replace the current function body with the body
16822 wrapped in the try/finally TF. */
16823 seq = NULL;
16824 gimple_seq_add_stmt (&seq, new_bind);
16825 gimple_set_body (fndecl, seq);
16828 DECL_SAVED_TREE (fndecl) = NULL_TREE;
16829 cfun->curr_properties |= PROP_gimple_any;
16831 pop_cfun ();
16833 dump_function (TDI_gimple, fndecl);
16836 /* Return a dummy expression of type TYPE in order to keep going after an
16837 error. */
16839 static tree
16840 dummy_object (tree type)
16842 tree t = build_int_cst (build_pointer_type (type), 0);
16843 return build2 (MEM_REF, type, t, t);
16846 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
16847 builtin function, but a very special sort of operator. */
16849 enum gimplify_status
16850 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
16851 gimple_seq *post_p ATTRIBUTE_UNUSED)
16853 tree promoted_type, have_va_type;
16854 tree valist = TREE_OPERAND (*expr_p, 0);
16855 tree type = TREE_TYPE (*expr_p);
16856 tree t, tag, aptag;
16857 location_t loc = EXPR_LOCATION (*expr_p);
16859 /* Verify that valist is of the proper type. */
16860 have_va_type = TREE_TYPE (valist);
16861 if (have_va_type == error_mark_node)
16862 return GS_ERROR;
16863 have_va_type = targetm.canonical_va_list_type (have_va_type);
16864 if (have_va_type == NULL_TREE
16865 && POINTER_TYPE_P (TREE_TYPE (valist)))
16866 /* Handle 'Case 1: Not an array type' from c-common.cc/build_va_arg. */
16867 have_va_type
16868 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
16869 gcc_assert (have_va_type != NULL_TREE);
16871 /* Generate a diagnostic for requesting data of a type that cannot
16872 be passed through `...' due to type promotion at the call site. */
16873 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
16874 != type)
16876 static bool gave_help;
16877 bool warned;
16878 /* Use the expansion point to handle cases such as passing bool (defined
16879 in a system header) through `...'. */
16880 location_t xloc
16881 = expansion_point_location_if_in_system_header (loc);
16883 /* Unfortunately, this is merely undefined, rather than a constraint
16884 violation, so we cannot make this an error. If this call is never
16885 executed, the program is still strictly conforming. */
16886 auto_diagnostic_group d;
16887 warned = warning_at (xloc, 0,
16888 "%qT is promoted to %qT when passed through %<...%>",
16889 type, promoted_type);
16890 if (!gave_help && warned)
16892 gave_help = true;
16893 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
16894 promoted_type, type);
16897 /* We can, however, treat "undefined" any way we please.
16898 Call abort to encourage the user to fix the program. */
16899 if (warned)
16900 inform (xloc, "if this code is reached, the program will abort");
16901 /* Before the abort, allow the evaluation of the va_list
16902 expression to exit or longjmp. */
16903 gimplify_and_add (valist, pre_p);
16904 t = build_call_expr_loc (loc,
16905 builtin_decl_implicit (BUILT_IN_TRAP), 0);
16906 gimplify_and_add (t, pre_p);
16908 /* This is dead code, but go ahead and finish so that the
16909 mode of the result comes out right. */
16910 *expr_p = dummy_object (type);
16911 return GS_ALL_DONE;
16914 tag = build_int_cst (build_pointer_type (type), 0);
16915 aptag = build_int_cst (TREE_TYPE (valist), 0);
16917 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
16918 valist, tag, aptag);
16920 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
16921 needs to be expanded. */
16922 cfun->curr_properties &= ~PROP_gimple_lva;
16924 return GS_OK;
16927 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
16929 DST/SRC are the destination and source respectively. You can pass
16930 ungimplified trees in DST or SRC, in which case they will be
16931 converted to a gimple operand if necessary.
16933 This function returns the newly created GIMPLE_ASSIGN tuple. */
16935 gimple *
16936 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
16938 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
16939 gimplify_and_add (t, seq_p);
16940 ggc_free (t);
16941 return gimple_seq_last_stmt (*seq_p);
16944 inline hashval_t
16945 gimplify_hasher::hash (const elt_t *p)
16947 tree t = p->val;
16948 return iterative_hash_expr (t, 0);
16951 inline bool
16952 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
16954 tree t1 = p1->val;
16955 tree t2 = p2->val;
16956 enum tree_code code = TREE_CODE (t1);
16958 if (TREE_CODE (t2) != code
16959 || TREE_TYPE (t1) != TREE_TYPE (t2))
16960 return false;
16962 if (!operand_equal_p (t1, t2, 0))
16963 return false;
16965 /* Only allow them to compare equal if they also hash equal; otherwise
16966 results are nondeterminate, and we fail bootstrap comparison. */
16967 gcc_checking_assert (hash (p1) == hash (p2));
16969 return true;