2017-02-20 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / gimplify.c
blob1b9c8d23f1ac38fe8473e0e2240e1a342083ba08
1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2017 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 "gimple.h"
31 #include "gimple-predict.h"
32 #include "tree-pass.h" /* FIXME: only for PROP_gimple_any */
33 #include "ssa.h"
34 #include "cgraph.h"
35 #include "tree-pretty-print.h"
36 #include "diagnostic-core.h"
37 #include "alias.h"
38 #include "fold-const.h"
39 #include "calls.h"
40 #include "varasm.h"
41 #include "stmt.h"
42 #include "expr.h"
43 #include "gimple-fold.h"
44 #include "tree-eh.h"
45 #include "gimplify.h"
46 #include "gimple-iterator.h"
47 #include "stor-layout.h"
48 #include "print-tree.h"
49 #include "tree-iterator.h"
50 #include "tree-inline.h"
51 #include "langhooks.h"
52 #include "tree-cfg.h"
53 #include "tree-ssa.h"
54 #include "omp-general.h"
55 #include "omp-low.h"
56 #include "gimple-low.h"
57 #include "cilk.h"
58 #include "gomp-constants.h"
59 #include "tree-dump.h"
60 #include "gimple-walk.h"
61 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
62 #include "builtins.h"
63 #include "asan.h"
64 #include "dbgcnt.h"
66 /* Hash set of poisoned variables in a bind expr. */
67 static hash_set<tree> *asan_poisoned_variables = NULL;
69 enum gimplify_omp_var_data
71 GOVD_SEEN = 1,
72 GOVD_EXPLICIT = 2,
73 GOVD_SHARED = 4,
74 GOVD_PRIVATE = 8,
75 GOVD_FIRSTPRIVATE = 16,
76 GOVD_LASTPRIVATE = 32,
77 GOVD_REDUCTION = 64,
78 GOVD_LOCAL = 128,
79 GOVD_MAP = 256,
80 GOVD_DEBUG_PRIVATE = 512,
81 GOVD_PRIVATE_OUTER_REF = 1024,
82 GOVD_LINEAR = 2048,
83 GOVD_ALIGNED = 4096,
85 /* Flag for GOVD_MAP: don't copy back. */
86 GOVD_MAP_TO_ONLY = 8192,
88 /* Flag for GOVD_LINEAR or GOVD_LASTPRIVATE: no outer reference. */
89 GOVD_LINEAR_LASTPRIVATE_NO_OUTER = 16384,
91 GOVD_MAP_0LEN_ARRAY = 32768,
93 /* Flag for GOVD_MAP, if it is always, to or always, tofrom mapping. */
94 GOVD_MAP_ALWAYS_TO = 65536,
96 /* Flag for shared vars that are or might be stored to in the region. */
97 GOVD_WRITTEN = 131072,
99 /* Flag for GOVD_MAP, if it is a forced mapping. */
100 GOVD_MAP_FORCE = 262144,
102 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
103 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
104 | GOVD_LOCAL)
108 enum omp_region_type
110 ORT_WORKSHARE = 0x00,
111 ORT_SIMD = 0x01,
113 ORT_PARALLEL = 0x02,
114 ORT_COMBINED_PARALLEL = 0x03,
116 ORT_TASK = 0x04,
117 ORT_UNTIED_TASK = 0x05,
119 ORT_TEAMS = 0x08,
120 ORT_COMBINED_TEAMS = 0x09,
122 /* Data region. */
123 ORT_TARGET_DATA = 0x10,
125 /* Data region with offloading. */
126 ORT_TARGET = 0x20,
127 ORT_COMBINED_TARGET = 0x21,
129 /* OpenACC variants. */
130 ORT_ACC = 0x40, /* A generic OpenACC region. */
131 ORT_ACC_DATA = ORT_ACC | ORT_TARGET_DATA, /* Data construct. */
132 ORT_ACC_PARALLEL = ORT_ACC | ORT_TARGET, /* Parallel construct */
133 ORT_ACC_KERNELS = ORT_ACC | ORT_TARGET | 0x80, /* Kernels construct. */
134 ORT_ACC_HOST_DATA = ORT_ACC | ORT_TARGET_DATA | 0x80, /* Host data. */
136 /* Dummy OpenMP region, used to disable expansion of
137 DECL_VALUE_EXPRs in taskloop pre body. */
138 ORT_NONE = 0x100
141 /* Gimplify hashtable helper. */
143 struct gimplify_hasher : free_ptr_hash <elt_t>
145 static inline hashval_t hash (const elt_t *);
146 static inline bool equal (const elt_t *, const elt_t *);
149 struct gimplify_ctx
151 struct gimplify_ctx *prev_context;
153 vec<gbind *> bind_expr_stack;
154 tree temps;
155 gimple_seq conditional_cleanups;
156 tree exit_label;
157 tree return_temp;
159 vec<tree> case_labels;
160 hash_set<tree> *live_switch_vars;
161 /* The formal temporary table. Should this be persistent? */
162 hash_table<gimplify_hasher> *temp_htab;
164 int conditions;
165 unsigned into_ssa : 1;
166 unsigned allow_rhs_cond_expr : 1;
167 unsigned in_cleanup_point_expr : 1;
168 unsigned keep_stack : 1;
169 unsigned save_stack : 1;
170 unsigned in_switch_expr : 1;
173 struct gimplify_omp_ctx
175 struct gimplify_omp_ctx *outer_context;
176 splay_tree variables;
177 hash_set<tree> *privatized_types;
178 /* Iteration variables in an OMP_FOR. */
179 vec<tree> loop_iter_var;
180 location_t location;
181 enum omp_clause_default_kind default_kind;
182 enum omp_region_type region_type;
183 bool combined_loop;
184 bool distribute;
185 bool target_map_scalars_firstprivate;
186 bool target_map_pointers_as_0len_arrays;
187 bool target_firstprivatize_array_bases;
190 static struct gimplify_ctx *gimplify_ctxp;
191 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
193 /* Forward declaration. */
194 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
195 static hash_map<tree, tree> *oacc_declare_returns;
196 static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
197 bool (*) (tree), fallback_t, bool);
199 /* Shorter alias name for the above function for use in gimplify.c
200 only. */
202 static inline void
203 gimplify_seq_add_stmt (gimple_seq *seq_p, gimple *gs)
205 gimple_seq_add_stmt_without_update (seq_p, gs);
208 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
209 NULL, a new sequence is allocated. This function is
210 similar to gimple_seq_add_seq, but does not scan the operands.
211 During gimplification, we need to manipulate statement sequences
212 before the def/use vectors have been constructed. */
214 static void
215 gimplify_seq_add_seq (gimple_seq *dst_p, gimple_seq src)
217 gimple_stmt_iterator si;
219 if (src == NULL)
220 return;
222 si = gsi_last (*dst_p);
223 gsi_insert_seq_after_without_update (&si, src, GSI_NEW_STMT);
227 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
228 and popping gimplify contexts. */
230 static struct gimplify_ctx *ctx_pool = NULL;
232 /* Return a gimplify context struct from the pool. */
234 static inline struct gimplify_ctx *
235 ctx_alloc (void)
237 struct gimplify_ctx * c = ctx_pool;
239 if (c)
240 ctx_pool = c->prev_context;
241 else
242 c = XNEW (struct gimplify_ctx);
244 memset (c, '\0', sizeof (*c));
245 return c;
248 /* Put gimplify context C back into the pool. */
250 static inline void
251 ctx_free (struct gimplify_ctx *c)
253 c->prev_context = ctx_pool;
254 ctx_pool = c;
257 /* Free allocated ctx stack memory. */
259 void
260 free_gimplify_stack (void)
262 struct gimplify_ctx *c;
264 while ((c = ctx_pool))
266 ctx_pool = c->prev_context;
267 free (c);
272 /* Set up a context for the gimplifier. */
274 void
275 push_gimplify_context (bool in_ssa, bool rhs_cond_ok)
277 struct gimplify_ctx *c = ctx_alloc ();
279 c->prev_context = gimplify_ctxp;
280 gimplify_ctxp = c;
281 gimplify_ctxp->into_ssa = in_ssa;
282 gimplify_ctxp->allow_rhs_cond_expr = rhs_cond_ok;
285 /* Tear down a context for the gimplifier. If BODY is non-null, then
286 put the temporaries into the outer BIND_EXPR. Otherwise, put them
287 in the local_decls.
289 BODY is not a sequence, but the first tuple in a sequence. */
291 void
292 pop_gimplify_context (gimple *body)
294 struct gimplify_ctx *c = gimplify_ctxp;
296 gcc_assert (c
297 && (!c->bind_expr_stack.exists ()
298 || c->bind_expr_stack.is_empty ()));
299 c->bind_expr_stack.release ();
300 gimplify_ctxp = c->prev_context;
302 if (body)
303 declare_vars (c->temps, body, false);
304 else
305 record_vars (c->temps);
307 delete c->temp_htab;
308 c->temp_htab = NULL;
309 ctx_free (c);
312 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
314 static void
315 gimple_push_bind_expr (gbind *bind_stmt)
317 gimplify_ctxp->bind_expr_stack.reserve (8);
318 gimplify_ctxp->bind_expr_stack.safe_push (bind_stmt);
321 /* Pop the first element off the stack of bindings. */
323 static void
324 gimple_pop_bind_expr (void)
326 gimplify_ctxp->bind_expr_stack.pop ();
329 /* Return the first element of the stack of bindings. */
331 gbind *
332 gimple_current_bind_expr (void)
334 return gimplify_ctxp->bind_expr_stack.last ();
337 /* Return the stack of bindings created during gimplification. */
339 vec<gbind *>
340 gimple_bind_expr_stack (void)
342 return gimplify_ctxp->bind_expr_stack;
345 /* Return true iff there is a COND_EXPR between us and the innermost
346 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
348 static bool
349 gimple_conditional_context (void)
351 return gimplify_ctxp->conditions > 0;
354 /* Note that we've entered a COND_EXPR. */
356 static void
357 gimple_push_condition (void)
359 #ifdef ENABLE_GIMPLE_CHECKING
360 if (gimplify_ctxp->conditions == 0)
361 gcc_assert (gimple_seq_empty_p (gimplify_ctxp->conditional_cleanups));
362 #endif
363 ++(gimplify_ctxp->conditions);
366 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
367 now, add any conditional cleanups we've seen to the prequeue. */
369 static void
370 gimple_pop_condition (gimple_seq *pre_p)
372 int conds = --(gimplify_ctxp->conditions);
374 gcc_assert (conds >= 0);
375 if (conds == 0)
377 gimplify_seq_add_seq (pre_p, gimplify_ctxp->conditional_cleanups);
378 gimplify_ctxp->conditional_cleanups = NULL;
382 /* A stable comparison routine for use with splay trees and DECLs. */
384 static int
385 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
387 tree a = (tree) xa;
388 tree b = (tree) xb;
390 return DECL_UID (a) - DECL_UID (b);
393 /* Create a new omp construct that deals with variable remapping. */
395 static struct gimplify_omp_ctx *
396 new_omp_context (enum omp_region_type region_type)
398 struct gimplify_omp_ctx *c;
400 c = XCNEW (struct gimplify_omp_ctx);
401 c->outer_context = gimplify_omp_ctxp;
402 c->variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
403 c->privatized_types = new hash_set<tree>;
404 c->location = input_location;
405 c->region_type = region_type;
406 if ((region_type & ORT_TASK) == 0)
407 c->default_kind = OMP_CLAUSE_DEFAULT_SHARED;
408 else
409 c->default_kind = OMP_CLAUSE_DEFAULT_UNSPECIFIED;
411 return c;
414 /* Destroy an omp construct that deals with variable remapping. */
416 static void
417 delete_omp_context (struct gimplify_omp_ctx *c)
419 splay_tree_delete (c->variables);
420 delete c->privatized_types;
421 c->loop_iter_var.release ();
422 XDELETE (c);
425 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
426 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
428 /* Both gimplify the statement T and append it to *SEQ_P. This function
429 behaves exactly as gimplify_stmt, but you don't have to pass T as a
430 reference. */
432 void
433 gimplify_and_add (tree t, gimple_seq *seq_p)
435 gimplify_stmt (&t, seq_p);
438 /* Gimplify statement T into sequence *SEQ_P, and return the first
439 tuple in the sequence of generated tuples for this statement.
440 Return NULL if gimplifying T produced no tuples. */
442 static gimple *
443 gimplify_and_return_first (tree t, gimple_seq *seq_p)
445 gimple_stmt_iterator last = gsi_last (*seq_p);
447 gimplify_and_add (t, seq_p);
449 if (!gsi_end_p (last))
451 gsi_next (&last);
452 return gsi_stmt (last);
454 else
455 return gimple_seq_first_stmt (*seq_p);
458 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
459 LHS, or for a call argument. */
461 static bool
462 is_gimple_mem_rhs (tree t)
464 /* If we're dealing with a renamable type, either source or dest must be
465 a renamed variable. */
466 if (is_gimple_reg_type (TREE_TYPE (t)))
467 return is_gimple_val (t);
468 else
469 return is_gimple_val (t) || is_gimple_lvalue (t);
472 /* Return true if T is a CALL_EXPR or an expression that can be
473 assigned to a temporary. Note that this predicate should only be
474 used during gimplification. See the rationale for this in
475 gimplify_modify_expr. */
477 static bool
478 is_gimple_reg_rhs_or_call (tree t)
480 return (get_gimple_rhs_class (TREE_CODE (t)) != GIMPLE_INVALID_RHS
481 || TREE_CODE (t) == CALL_EXPR);
484 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
485 this predicate should only be used during gimplification. See the
486 rationale for this in gimplify_modify_expr. */
488 static bool
489 is_gimple_mem_rhs_or_call (tree t)
491 /* If we're dealing with a renamable type, either source or dest must be
492 a renamed variable. */
493 if (is_gimple_reg_type (TREE_TYPE (t)))
494 return is_gimple_val (t);
495 else
496 return (is_gimple_val (t) || is_gimple_lvalue (t)
497 || TREE_CODE (t) == CALL_EXPR);
500 /* Create a temporary with a name derived from VAL. Subroutine of
501 lookup_tmp_var; nobody else should call this function. */
503 static inline tree
504 create_tmp_from_val (tree val)
506 /* Drop all qualifiers and address-space information from the value type. */
507 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (val));
508 tree var = create_tmp_var (type, get_name (val));
509 if (TREE_CODE (TREE_TYPE (var)) == COMPLEX_TYPE
510 || TREE_CODE (TREE_TYPE (var)) == VECTOR_TYPE)
511 DECL_GIMPLE_REG_P (var) = 1;
512 return var;
515 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
516 an existing expression temporary. */
518 static tree
519 lookup_tmp_var (tree val, bool is_formal)
521 tree ret;
523 /* If not optimizing, never really reuse a temporary. local-alloc
524 won't allocate any variable that is used in more than one basic
525 block, which means it will go into memory, causing much extra
526 work in reload and final and poorer code generation, outweighing
527 the extra memory allocation here. */
528 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
529 ret = create_tmp_from_val (val);
530 else
532 elt_t elt, *elt_p;
533 elt_t **slot;
535 elt.val = val;
536 if (!gimplify_ctxp->temp_htab)
537 gimplify_ctxp->temp_htab = new hash_table<gimplify_hasher> (1000);
538 slot = gimplify_ctxp->temp_htab->find_slot (&elt, INSERT);
539 if (*slot == NULL)
541 elt_p = XNEW (elt_t);
542 elt_p->val = val;
543 elt_p->temp = ret = create_tmp_from_val (val);
544 *slot = elt_p;
546 else
548 elt_p = *slot;
549 ret = elt_p->temp;
553 return ret;
556 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
558 static tree
559 internal_get_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
560 bool is_formal, bool allow_ssa)
562 tree t, mod;
564 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
565 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
566 gimplify_expr (&val, pre_p, post_p, is_gimple_reg_rhs_or_call,
567 fb_rvalue);
569 if (allow_ssa
570 && gimplify_ctxp->into_ssa
571 && is_gimple_reg_type (TREE_TYPE (val)))
573 t = make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val)));
574 if (! gimple_in_ssa_p (cfun))
576 const char *name = get_name (val);
577 if (name)
578 SET_SSA_NAME_VAR_OR_IDENTIFIER (t, create_tmp_var_name (name));
581 else
582 t = lookup_tmp_var (val, is_formal);
584 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
586 SET_EXPR_LOCATION (mod, EXPR_LOC_OR_LOC (val, input_location));
588 /* gimplify_modify_expr might want to reduce this further. */
589 gimplify_and_add (mod, pre_p);
590 ggc_free (mod);
592 return t;
595 /* Return a formal temporary variable initialized with VAL. PRE_P is as
596 in gimplify_expr. Only use this function if:
598 1) The value of the unfactored expression represented by VAL will not
599 change between the initialization and use of the temporary, and
600 2) The temporary will not be otherwise modified.
602 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
603 and #2 means it is inappropriate for && temps.
605 For other cases, use get_initialized_tmp_var instead. */
607 tree
608 get_formal_tmp_var (tree val, gimple_seq *pre_p)
610 return internal_get_tmp_var (val, pre_p, NULL, true, true);
613 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
614 are as in gimplify_expr. */
616 tree
617 get_initialized_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
618 bool allow_ssa)
620 return internal_get_tmp_var (val, pre_p, post_p, false, allow_ssa);
623 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
624 generate debug info for them; otherwise don't. */
626 void
627 declare_vars (tree vars, gimple *gs, bool debug_info)
629 tree last = vars;
630 if (last)
632 tree temps, block;
634 gbind *scope = as_a <gbind *> (gs);
636 temps = nreverse (last);
638 block = gimple_bind_block (scope);
639 gcc_assert (!block || TREE_CODE (block) == BLOCK);
640 if (!block || !debug_info)
642 DECL_CHAIN (last) = gimple_bind_vars (scope);
643 gimple_bind_set_vars (scope, temps);
645 else
647 /* We need to attach the nodes both to the BIND_EXPR and to its
648 associated BLOCK for debugging purposes. The key point here
649 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
650 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
651 if (BLOCK_VARS (block))
652 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
653 else
655 gimple_bind_set_vars (scope,
656 chainon (gimple_bind_vars (scope), temps));
657 BLOCK_VARS (block) = temps;
663 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
664 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
665 no such upper bound can be obtained. */
667 static void
668 force_constant_size (tree var)
670 /* The only attempt we make is by querying the maximum size of objects
671 of the variable's type. */
673 HOST_WIDE_INT max_size;
675 gcc_assert (VAR_P (var));
677 max_size = max_int_size_in_bytes (TREE_TYPE (var));
679 gcc_assert (max_size >= 0);
681 DECL_SIZE_UNIT (var)
682 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
683 DECL_SIZE (var)
684 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
687 /* Push the temporary variable TMP into the current binding. */
689 void
690 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
692 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
694 /* Later processing assumes that the object size is constant, which might
695 not be true at this point. Force the use of a constant upper bound in
696 this case. */
697 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp)))
698 force_constant_size (tmp);
700 DECL_CONTEXT (tmp) = fn->decl;
701 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
703 record_vars_into (tmp, fn->decl);
706 /* Push the temporary variable TMP into the current binding. */
708 void
709 gimple_add_tmp_var (tree tmp)
711 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
713 /* Later processing assumes that the object size is constant, which might
714 not be true at this point. Force the use of a constant upper bound in
715 this case. */
716 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp)))
717 force_constant_size (tmp);
719 DECL_CONTEXT (tmp) = current_function_decl;
720 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
722 if (gimplify_ctxp)
724 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
725 gimplify_ctxp->temps = tmp;
727 /* Mark temporaries local within the nearest enclosing parallel. */
728 if (gimplify_omp_ctxp)
730 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
731 while (ctx
732 && (ctx->region_type == ORT_WORKSHARE
733 || ctx->region_type == ORT_SIMD
734 || ctx->region_type == ORT_ACC))
735 ctx = ctx->outer_context;
736 if (ctx)
737 omp_add_variable (ctx, tmp, GOVD_LOCAL | GOVD_SEEN);
740 else if (cfun)
741 record_vars (tmp);
742 else
744 gimple_seq body_seq;
746 /* This case is for nested functions. We need to expose the locals
747 they create. */
748 body_seq = gimple_body (current_function_decl);
749 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
755 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
756 nodes that are referenced more than once in GENERIC functions. This is
757 necessary because gimplification (translation into GIMPLE) is performed
758 by modifying tree nodes in-place, so gimplication of a shared node in a
759 first context could generate an invalid GIMPLE form in a second context.
761 This is achieved with a simple mark/copy/unmark algorithm that walks the
762 GENERIC representation top-down, marks nodes with TREE_VISITED the first
763 time it encounters them, duplicates them if they already have TREE_VISITED
764 set, and finally removes the TREE_VISITED marks it has set.
766 The algorithm works only at the function level, i.e. it generates a GENERIC
767 representation of a function with no nodes shared within the function when
768 passed a GENERIC function (except for nodes that are allowed to be shared).
770 At the global level, it is also necessary to unshare tree nodes that are
771 referenced in more than one function, for the same aforementioned reason.
772 This requires some cooperation from the front-end. There are 2 strategies:
774 1. Manual unsharing. The front-end needs to call unshare_expr on every
775 expression that might end up being shared across functions.
777 2. Deep unsharing. This is an extension of regular unsharing. Instead
778 of calling unshare_expr on expressions that might be shared across
779 functions, the front-end pre-marks them with TREE_VISITED. This will
780 ensure that they are unshared on the first reference within functions
781 when the regular unsharing algorithm runs. The counterpart is that
782 this algorithm must look deeper than for manual unsharing, which is
783 specified by LANG_HOOKS_DEEP_UNSHARING.
785 If there are only few specific cases of node sharing across functions, it is
786 probably easier for a front-end to unshare the expressions manually. On the
787 contrary, if the expressions generated at the global level are as widespread
788 as expressions generated within functions, deep unsharing is very likely the
789 way to go. */
791 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
792 These nodes model computations that must be done once. If we were to
793 unshare something like SAVE_EXPR(i++), the gimplification process would
794 create wrong code. However, if DATA is non-null, it must hold a pointer
795 set that is used to unshare the subtrees of these nodes. */
797 static tree
798 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
800 tree t = *tp;
801 enum tree_code code = TREE_CODE (t);
803 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
804 copy their subtrees if we can make sure to do it only once. */
805 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
807 if (data && !((hash_set<tree> *)data)->add (t))
809 else
810 *walk_subtrees = 0;
813 /* Stop at types, decls, constants like copy_tree_r. */
814 else if (TREE_CODE_CLASS (code) == tcc_type
815 || TREE_CODE_CLASS (code) == tcc_declaration
816 || TREE_CODE_CLASS (code) == tcc_constant
817 /* We can't do anything sensible with a BLOCK used as an
818 expression, but we also can't just die when we see it
819 because of non-expression uses. So we avert our eyes
820 and cross our fingers. Silly Java. */
821 || code == BLOCK)
822 *walk_subtrees = 0;
824 /* Cope with the statement expression extension. */
825 else if (code == STATEMENT_LIST)
828 /* Leave the bulk of the work to copy_tree_r itself. */
829 else
830 copy_tree_r (tp, walk_subtrees, NULL);
832 return NULL_TREE;
835 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
836 If *TP has been visited already, then *TP is deeply copied by calling
837 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
839 static tree
840 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
842 tree t = *tp;
843 enum tree_code code = TREE_CODE (t);
845 /* Skip types, decls, and constants. But we do want to look at their
846 types and the bounds of types. Mark them as visited so we properly
847 unmark their subtrees on the unmark pass. If we've already seen them,
848 don't look down further. */
849 if (TREE_CODE_CLASS (code) == tcc_type
850 || TREE_CODE_CLASS (code) == tcc_declaration
851 || TREE_CODE_CLASS (code) == tcc_constant)
853 if (TREE_VISITED (t))
854 *walk_subtrees = 0;
855 else
856 TREE_VISITED (t) = 1;
859 /* If this node has been visited already, unshare it and don't look
860 any deeper. */
861 else if (TREE_VISITED (t))
863 walk_tree (tp, mostly_copy_tree_r, data, NULL);
864 *walk_subtrees = 0;
867 /* Otherwise, mark the node as visited and keep looking. */
868 else
869 TREE_VISITED (t) = 1;
871 return NULL_TREE;
874 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
875 copy_if_shared_r callback unmodified. */
877 static inline void
878 copy_if_shared (tree *tp, void *data)
880 walk_tree (tp, copy_if_shared_r, data, NULL);
883 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
884 any nested functions. */
886 static void
887 unshare_body (tree fndecl)
889 struct cgraph_node *cgn = cgraph_node::get (fndecl);
890 /* If the language requires deep unsharing, we need a pointer set to make
891 sure we don't repeatedly unshare subtrees of unshareable nodes. */
892 hash_set<tree> *visited
893 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
895 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
896 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
897 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
899 delete visited;
901 if (cgn)
902 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
903 unshare_body (cgn->decl);
906 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
907 Subtrees are walked until the first unvisited node is encountered. */
909 static tree
910 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
912 tree t = *tp;
914 /* If this node has been visited, unmark it and keep looking. */
915 if (TREE_VISITED (t))
916 TREE_VISITED (t) = 0;
918 /* Otherwise, don't look any deeper. */
919 else
920 *walk_subtrees = 0;
922 return NULL_TREE;
925 /* Unmark the visited trees rooted at *TP. */
927 static inline void
928 unmark_visited (tree *tp)
930 walk_tree (tp, unmark_visited_r, NULL, NULL);
933 /* Likewise, but mark all trees as not visited. */
935 static void
936 unvisit_body (tree fndecl)
938 struct cgraph_node *cgn = cgraph_node::get (fndecl);
940 unmark_visited (&DECL_SAVED_TREE (fndecl));
941 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
942 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
944 if (cgn)
945 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
946 unvisit_body (cgn->decl);
949 /* Unconditionally make an unshared copy of EXPR. This is used when using
950 stored expressions which span multiple functions, such as BINFO_VTABLE,
951 as the normal unsharing process can't tell that they're shared. */
953 tree
954 unshare_expr (tree expr)
956 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
957 return expr;
960 /* Worker for unshare_expr_without_location. */
962 static tree
963 prune_expr_location (tree *tp, int *walk_subtrees, void *)
965 if (EXPR_P (*tp))
966 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
967 else
968 *walk_subtrees = 0;
969 return NULL_TREE;
972 /* Similar to unshare_expr but also prune all expression locations
973 from EXPR. */
975 tree
976 unshare_expr_without_location (tree expr)
978 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
979 if (EXPR_P (expr))
980 walk_tree (&expr, prune_expr_location, NULL, NULL);
981 return expr;
984 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
985 contain statements and have a value. Assign its value to a temporary
986 and give it void_type_node. Return the temporary, or NULL_TREE if
987 WRAPPER was already void. */
989 tree
990 voidify_wrapper_expr (tree wrapper, tree temp)
992 tree type = TREE_TYPE (wrapper);
993 if (type && !VOID_TYPE_P (type))
995 tree *p;
997 /* Set p to point to the body of the wrapper. Loop until we find
998 something that isn't a wrapper. */
999 for (p = &wrapper; p && *p; )
1001 switch (TREE_CODE (*p))
1003 case BIND_EXPR:
1004 TREE_SIDE_EFFECTS (*p) = 1;
1005 TREE_TYPE (*p) = void_type_node;
1006 /* For a BIND_EXPR, the body is operand 1. */
1007 p = &BIND_EXPR_BODY (*p);
1008 break;
1010 case CLEANUP_POINT_EXPR:
1011 case TRY_FINALLY_EXPR:
1012 case TRY_CATCH_EXPR:
1013 TREE_SIDE_EFFECTS (*p) = 1;
1014 TREE_TYPE (*p) = void_type_node;
1015 p = &TREE_OPERAND (*p, 0);
1016 break;
1018 case STATEMENT_LIST:
1020 tree_stmt_iterator i = tsi_last (*p);
1021 TREE_SIDE_EFFECTS (*p) = 1;
1022 TREE_TYPE (*p) = void_type_node;
1023 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
1025 break;
1027 case COMPOUND_EXPR:
1028 /* Advance to the last statement. Set all container types to
1029 void. */
1030 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
1032 TREE_SIDE_EFFECTS (*p) = 1;
1033 TREE_TYPE (*p) = void_type_node;
1035 break;
1037 case TRANSACTION_EXPR:
1038 TREE_SIDE_EFFECTS (*p) = 1;
1039 TREE_TYPE (*p) = void_type_node;
1040 p = &TRANSACTION_EXPR_BODY (*p);
1041 break;
1043 default:
1044 /* Assume that any tree upon which voidify_wrapper_expr is
1045 directly called is a wrapper, and that its body is op0. */
1046 if (p == &wrapper)
1048 TREE_SIDE_EFFECTS (*p) = 1;
1049 TREE_TYPE (*p) = void_type_node;
1050 p = &TREE_OPERAND (*p, 0);
1051 break;
1053 goto out;
1057 out:
1058 if (p == NULL || IS_EMPTY_STMT (*p))
1059 temp = NULL_TREE;
1060 else if (temp)
1062 /* The wrapper is on the RHS of an assignment that we're pushing
1063 down. */
1064 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1065 || TREE_CODE (temp) == MODIFY_EXPR);
1066 TREE_OPERAND (temp, 1) = *p;
1067 *p = temp;
1069 else
1071 temp = create_tmp_var (type, "retval");
1072 *p = build2 (INIT_EXPR, type, temp, *p);
1075 return temp;
1078 return NULL_TREE;
1081 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1082 a temporary through which they communicate. */
1084 static void
1085 build_stack_save_restore (gcall **save, gcall **restore)
1087 tree tmp_var;
1089 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1090 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1091 gimple_call_set_lhs (*save, tmp_var);
1093 *restore
1094 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1095 1, tmp_var);
1098 /* Generate IFN_ASAN_MARK call that poisons shadow of a for DECL variable. */
1100 static tree
1101 build_asan_poison_call_expr (tree decl)
1103 /* Do not poison variables that have size equal to zero. */
1104 tree unit_size = DECL_SIZE_UNIT (decl);
1105 if (zerop (unit_size))
1106 return NULL_TREE;
1108 tree base = build_fold_addr_expr (decl);
1110 return build_call_expr_internal_loc (UNKNOWN_LOCATION, IFN_ASAN_MARK,
1111 void_type_node, 3,
1112 build_int_cst (integer_type_node,
1113 ASAN_MARK_POISON),
1114 base, unit_size);
1117 /* Generate IFN_ASAN_MARK call that would poison or unpoison, depending
1118 on POISON flag, shadow memory of a DECL variable. The call will be
1119 put on location identified by IT iterator, where BEFORE flag drives
1120 position where the stmt will be put. */
1122 static void
1123 asan_poison_variable (tree decl, bool poison, gimple_stmt_iterator *it,
1124 bool before)
1126 /* When within an OMP context, do not emit ASAN_MARK internal fns. */
1127 if (gimplify_omp_ctxp)
1128 return;
1130 tree unit_size = DECL_SIZE_UNIT (decl);
1131 tree base = build_fold_addr_expr (decl);
1133 /* Do not poison variables that have size equal to zero. */
1134 if (zerop (unit_size))
1135 return;
1137 /* It's necessary to have all stack variables aligned to ASAN granularity
1138 bytes. */
1139 if (DECL_ALIGN_UNIT (decl) <= ASAN_SHADOW_GRANULARITY)
1140 SET_DECL_ALIGN (decl, BITS_PER_UNIT * ASAN_SHADOW_GRANULARITY);
1142 HOST_WIDE_INT flags = poison ? ASAN_MARK_POISON : ASAN_MARK_UNPOISON;
1144 gimple *g
1145 = gimple_build_call_internal (IFN_ASAN_MARK, 3,
1146 build_int_cst (integer_type_node, flags),
1147 base, unit_size);
1149 if (before)
1150 gsi_insert_before (it, g, GSI_NEW_STMT);
1151 else
1152 gsi_insert_after (it, g, GSI_NEW_STMT);
1155 /* Generate IFN_ASAN_MARK internal call that depending on POISON flag
1156 either poisons or unpoisons a DECL. Created statement is appended
1157 to SEQ_P gimple sequence. */
1159 static void
1160 asan_poison_variable (tree decl, bool poison, gimple_seq *seq_p)
1162 gimple_stmt_iterator it = gsi_last (*seq_p);
1163 bool before = false;
1165 if (gsi_end_p (it))
1166 before = true;
1168 asan_poison_variable (decl, poison, &it, before);
1171 /* Sort pair of VAR_DECLs A and B by DECL_UID. */
1173 static int
1174 sort_by_decl_uid (const void *a, const void *b)
1176 const tree *t1 = (const tree *)a;
1177 const tree *t2 = (const tree *)b;
1179 int uid1 = DECL_UID (*t1);
1180 int uid2 = DECL_UID (*t2);
1182 if (uid1 < uid2)
1183 return -1;
1184 else if (uid1 > uid2)
1185 return 1;
1186 else
1187 return 0;
1190 /* Generate IFN_ASAN_MARK internal call for all VARIABLES
1191 depending on POISON flag. Created statement is appended
1192 to SEQ_P gimple sequence. */
1194 static void
1195 asan_poison_variables (hash_set<tree> *variables, bool poison, gimple_seq *seq_p)
1197 unsigned c = variables->elements ();
1198 if (c == 0)
1199 return;
1201 auto_vec<tree> sorted_variables (c);
1203 for (hash_set<tree>::iterator it = variables->begin ();
1204 it != variables->end (); ++it)
1205 sorted_variables.safe_push (*it);
1207 sorted_variables.qsort (sort_by_decl_uid);
1209 unsigned i;
1210 tree var;
1211 FOR_EACH_VEC_ELT (sorted_variables, i, var)
1213 asan_poison_variable (var, poison, seq_p);
1215 /* Add use_after_scope_memory attribute for the variable in order
1216 to prevent re-written into SSA. */
1217 if (!lookup_attribute (ASAN_USE_AFTER_SCOPE_ATTRIBUTE,
1218 DECL_ATTRIBUTES (var)))
1219 DECL_ATTRIBUTES (var)
1220 = tree_cons (get_identifier (ASAN_USE_AFTER_SCOPE_ATTRIBUTE),
1221 integer_one_node,
1222 DECL_ATTRIBUTES (var));
1226 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1228 static enum gimplify_status
1229 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1231 tree bind_expr = *expr_p;
1232 bool old_keep_stack = gimplify_ctxp->keep_stack;
1233 bool old_save_stack = gimplify_ctxp->save_stack;
1234 tree t;
1235 gbind *bind_stmt;
1236 gimple_seq body, cleanup;
1237 gcall *stack_save;
1238 location_t start_locus = 0, end_locus = 0;
1239 tree ret_clauses = NULL;
1241 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1243 /* Mark variables seen in this bind expr. */
1244 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1246 if (VAR_P (t))
1248 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1250 /* Mark variable as local. */
1251 if (ctx && ctx->region_type != ORT_NONE && !DECL_EXTERNAL (t)
1252 && (! DECL_SEEN_IN_BIND_EXPR_P (t)
1253 || splay_tree_lookup (ctx->variables,
1254 (splay_tree_key) t) == NULL))
1256 if (ctx->region_type == ORT_SIMD
1257 && TREE_ADDRESSABLE (t)
1258 && !TREE_STATIC (t))
1259 omp_add_variable (ctx, t, GOVD_PRIVATE | GOVD_SEEN);
1260 else
1261 omp_add_variable (ctx, t, GOVD_LOCAL | GOVD_SEEN);
1264 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1266 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1267 cfun->has_local_explicit_reg_vars = true;
1270 /* Preliminarily mark non-addressed complex variables as eligible
1271 for promotion to gimple registers. We'll transform their uses
1272 as we find them. */
1273 if ((TREE_CODE (TREE_TYPE (t)) == COMPLEX_TYPE
1274 || TREE_CODE (TREE_TYPE (t)) == VECTOR_TYPE)
1275 && !TREE_THIS_VOLATILE (t)
1276 && (VAR_P (t) && !DECL_HARD_REGISTER (t))
1277 && !needs_to_live_in_memory (t))
1278 DECL_GIMPLE_REG_P (t) = 1;
1281 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1282 BIND_EXPR_BLOCK (bind_expr));
1283 gimple_push_bind_expr (bind_stmt);
1285 gimplify_ctxp->keep_stack = false;
1286 gimplify_ctxp->save_stack = false;
1288 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1289 body = NULL;
1290 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1291 gimple_bind_set_body (bind_stmt, body);
1293 /* Source location wise, the cleanup code (stack_restore and clobbers)
1294 belongs to the end of the block, so propagate what we have. The
1295 stack_save operation belongs to the beginning of block, which we can
1296 infer from the bind_expr directly if the block has no explicit
1297 assignment. */
1298 if (BIND_EXPR_BLOCK (bind_expr))
1300 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1301 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1303 if (start_locus == 0)
1304 start_locus = EXPR_LOCATION (bind_expr);
1306 cleanup = NULL;
1307 stack_save = NULL;
1309 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1310 the stack space allocated to the VLAs. */
1311 if (gimplify_ctxp->save_stack && !gimplify_ctxp->keep_stack)
1313 gcall *stack_restore;
1315 /* Save stack on entry and restore it on exit. Add a try_finally
1316 block to achieve this. */
1317 build_stack_save_restore (&stack_save, &stack_restore);
1319 gimple_set_location (stack_save, start_locus);
1320 gimple_set_location (stack_restore, end_locus);
1322 gimplify_seq_add_stmt (&cleanup, stack_restore);
1325 /* Add clobbers for all variables that go out of scope. */
1326 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1328 if (VAR_P (t)
1329 && !is_global_var (t)
1330 && DECL_CONTEXT (t) == current_function_decl)
1332 if (!DECL_HARD_REGISTER (t)
1333 && !TREE_THIS_VOLATILE (t)
1334 && !DECL_HAS_VALUE_EXPR_P (t)
1335 /* Only care for variables that have to be in memory. Others
1336 will be rewritten into SSA names, hence moved to the
1337 top-level. */
1338 && !is_gimple_reg (t)
1339 && flag_stack_reuse != SR_NONE)
1341 tree clobber = build_constructor (TREE_TYPE (t), NULL);
1342 gimple *clobber_stmt;
1343 TREE_THIS_VOLATILE (clobber) = 1;
1344 clobber_stmt = gimple_build_assign (t, clobber);
1345 gimple_set_location (clobber_stmt, end_locus);
1346 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1349 if (flag_openacc && oacc_declare_returns != NULL)
1351 tree *c = oacc_declare_returns->get (t);
1352 if (c != NULL)
1354 if (ret_clauses)
1355 OMP_CLAUSE_CHAIN (*c) = ret_clauses;
1357 ret_clauses = *c;
1359 oacc_declare_returns->remove (t);
1361 if (oacc_declare_returns->elements () == 0)
1363 delete oacc_declare_returns;
1364 oacc_declare_returns = NULL;
1370 if (asan_poisoned_variables != NULL
1371 && asan_poisoned_variables->contains (t))
1373 asan_poisoned_variables->remove (t);
1374 asan_poison_variable (t, true, &cleanup);
1377 if (gimplify_ctxp->live_switch_vars != NULL
1378 && gimplify_ctxp->live_switch_vars->contains (t))
1379 gimplify_ctxp->live_switch_vars->remove (t);
1382 if (ret_clauses)
1384 gomp_target *stmt;
1385 gimple_stmt_iterator si = gsi_start (cleanup);
1387 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
1388 ret_clauses);
1389 gsi_insert_seq_before_without_update (&si, stmt, GSI_NEW_STMT);
1392 if (cleanup)
1394 gtry *gs;
1395 gimple_seq new_body;
1397 new_body = NULL;
1398 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1399 GIMPLE_TRY_FINALLY);
1401 if (stack_save)
1402 gimplify_seq_add_stmt (&new_body, stack_save);
1403 gimplify_seq_add_stmt (&new_body, gs);
1404 gimple_bind_set_body (bind_stmt, new_body);
1407 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1408 if (!gimplify_ctxp->keep_stack)
1409 gimplify_ctxp->keep_stack = old_keep_stack;
1410 gimplify_ctxp->save_stack = old_save_stack;
1412 gimple_pop_bind_expr ();
1414 gimplify_seq_add_stmt (pre_p, bind_stmt);
1416 if (temp)
1418 *expr_p = temp;
1419 return GS_OK;
1422 *expr_p = NULL_TREE;
1423 return GS_ALL_DONE;
1426 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1427 GIMPLE value, it is assigned to a new temporary and the statement is
1428 re-written to return the temporary.
1430 PRE_P points to the sequence where side effects that must happen before
1431 STMT should be stored. */
1433 static enum gimplify_status
1434 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1436 greturn *ret;
1437 tree ret_expr = TREE_OPERAND (stmt, 0);
1438 tree result_decl, result;
1440 if (ret_expr == error_mark_node)
1441 return GS_ERROR;
1443 /* Implicit _Cilk_sync must be inserted right before any return statement
1444 if there is a _Cilk_spawn in the function. If the user has provided a
1445 _Cilk_sync, the optimizer should remove this duplicate one. */
1446 if (fn_contains_cilk_spawn_p (cfun))
1448 tree impl_sync = build0 (CILK_SYNC_STMT, void_type_node);
1449 gimplify_and_add (impl_sync, pre_p);
1452 if (!ret_expr
1453 || TREE_CODE (ret_expr) == RESULT_DECL
1454 || ret_expr == error_mark_node)
1456 greturn *ret = gimple_build_return (ret_expr);
1457 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1458 gimplify_seq_add_stmt (pre_p, ret);
1459 return GS_ALL_DONE;
1462 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1463 result_decl = NULL_TREE;
1464 else
1466 result_decl = TREE_OPERAND (ret_expr, 0);
1468 /* See through a return by reference. */
1469 if (TREE_CODE (result_decl) == INDIRECT_REF)
1470 result_decl = TREE_OPERAND (result_decl, 0);
1472 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1473 || TREE_CODE (ret_expr) == INIT_EXPR)
1474 && TREE_CODE (result_decl) == RESULT_DECL);
1477 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1478 Recall that aggregate_value_p is FALSE for any aggregate type that is
1479 returned in registers. If we're returning values in registers, then
1480 we don't want to extend the lifetime of the RESULT_DECL, particularly
1481 across another call. In addition, for those aggregates for which
1482 hard_function_value generates a PARALLEL, we'll die during normal
1483 expansion of structure assignments; there's special code in expand_return
1484 to handle this case that does not exist in expand_expr. */
1485 if (!result_decl)
1486 result = NULL_TREE;
1487 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1489 if (TREE_CODE (DECL_SIZE (result_decl)) != INTEGER_CST)
1491 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1492 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1493 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1494 should be effectively allocated by the caller, i.e. all calls to
1495 this function must be subject to the Return Slot Optimization. */
1496 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1497 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1499 result = result_decl;
1501 else if (gimplify_ctxp->return_temp)
1502 result = gimplify_ctxp->return_temp;
1503 else
1505 result = create_tmp_reg (TREE_TYPE (result_decl));
1507 /* ??? With complex control flow (usually involving abnormal edges),
1508 we can wind up warning about an uninitialized value for this. Due
1509 to how this variable is constructed and initialized, this is never
1510 true. Give up and never warn. */
1511 TREE_NO_WARNING (result) = 1;
1513 gimplify_ctxp->return_temp = result;
1516 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1517 Then gimplify the whole thing. */
1518 if (result != result_decl)
1519 TREE_OPERAND (ret_expr, 0) = result;
1521 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1523 ret = gimple_build_return (result);
1524 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1525 gimplify_seq_add_stmt (pre_p, ret);
1527 return GS_ALL_DONE;
1530 /* Gimplify a variable-length array DECL. */
1532 static void
1533 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1535 /* This is a variable-sized decl. Simplify its size and mark it
1536 for deferred expansion. */
1537 tree t, addr, ptr_type;
1539 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1540 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1542 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1543 if (DECL_HAS_VALUE_EXPR_P (decl))
1544 return;
1546 /* All occurrences of this decl in final gimplified code will be
1547 replaced by indirection. Setting DECL_VALUE_EXPR does two
1548 things: First, it lets the rest of the gimplifier know what
1549 replacement to use. Second, it lets the debug info know
1550 where to find the value. */
1551 ptr_type = build_pointer_type (TREE_TYPE (decl));
1552 addr = create_tmp_var (ptr_type, get_name (decl));
1553 DECL_IGNORED_P (addr) = 0;
1554 t = build_fold_indirect_ref (addr);
1555 TREE_THIS_NOTRAP (t) = 1;
1556 SET_DECL_VALUE_EXPR (decl, t);
1557 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1559 t = builtin_decl_explicit (BUILT_IN_ALLOCA_WITH_ALIGN);
1560 t = build_call_expr (t, 2, DECL_SIZE_UNIT (decl),
1561 size_int (DECL_ALIGN (decl)));
1562 /* The call has been built for a variable-sized object. */
1563 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1564 t = fold_convert (ptr_type, t);
1565 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1567 gimplify_and_add (t, seq_p);
1570 /* A helper function to be called via walk_tree. Mark all labels under *TP
1571 as being forced. To be called for DECL_INITIAL of static variables. */
1573 static tree
1574 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1576 if (TYPE_P (*tp))
1577 *walk_subtrees = 0;
1578 if (TREE_CODE (*tp) == LABEL_DECL)
1580 FORCED_LABEL (*tp) = 1;
1581 cfun->has_forced_label_in_static = 1;
1584 return NULL_TREE;
1587 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1588 and initialization explicit. */
1590 static enum gimplify_status
1591 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1593 tree stmt = *stmt_p;
1594 tree decl = DECL_EXPR_DECL (stmt);
1596 *stmt_p = NULL_TREE;
1598 if (TREE_TYPE (decl) == error_mark_node)
1599 return GS_ERROR;
1601 if ((TREE_CODE (decl) == TYPE_DECL
1602 || VAR_P (decl))
1603 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1605 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1606 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
1607 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
1610 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1611 in case its size expressions contain problematic nodes like CALL_EXPR. */
1612 if (TREE_CODE (decl) == TYPE_DECL
1613 && DECL_ORIGINAL_TYPE (decl)
1614 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1616 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1617 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
1618 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
1621 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
1623 tree init = DECL_INITIAL (decl);
1624 bool is_vla = false;
1626 if (TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
1627 || (!TREE_STATIC (decl)
1628 && flag_stack_check == GENERIC_STACK_CHECK
1629 && compare_tree_int (DECL_SIZE_UNIT (decl),
1630 STACK_CHECK_MAX_VAR_SIZE) > 0))
1632 gimplify_vla_decl (decl, seq_p);
1633 is_vla = true;
1636 if (asan_poisoned_variables
1637 && !is_vla
1638 && TREE_ADDRESSABLE (decl)
1639 && !TREE_STATIC (decl)
1640 && !DECL_HAS_VALUE_EXPR_P (decl)
1641 && dbg_cnt (asan_use_after_scope))
1643 asan_poisoned_variables->add (decl);
1644 asan_poison_variable (decl, false, seq_p);
1645 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
1646 gimplify_ctxp->live_switch_vars->add (decl);
1649 /* Some front ends do not explicitly declare all anonymous
1650 artificial variables. We compensate here by declaring the
1651 variables, though it would be better if the front ends would
1652 explicitly declare them. */
1653 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1654 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1655 gimple_add_tmp_var (decl);
1657 if (init && init != error_mark_node)
1659 if (!TREE_STATIC (decl))
1661 DECL_INITIAL (decl) = NULL_TREE;
1662 init = build2 (INIT_EXPR, void_type_node, decl, init);
1663 gimplify_and_add (init, seq_p);
1664 ggc_free (init);
1666 else
1667 /* We must still examine initializers for static variables
1668 as they may contain a label address. */
1669 walk_tree (&init, force_labels_r, NULL, NULL);
1673 return GS_ALL_DONE;
1676 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1677 and replacing the LOOP_EXPR with goto, but if the loop contains an
1678 EXIT_EXPR, we need to append a label for it to jump to. */
1680 static enum gimplify_status
1681 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1683 tree saved_label = gimplify_ctxp->exit_label;
1684 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1686 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1688 gimplify_ctxp->exit_label = NULL_TREE;
1690 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1692 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
1694 if (gimplify_ctxp->exit_label)
1695 gimplify_seq_add_stmt (pre_p,
1696 gimple_build_label (gimplify_ctxp->exit_label));
1698 gimplify_ctxp->exit_label = saved_label;
1700 *expr_p = NULL;
1701 return GS_ALL_DONE;
1704 /* Gimplify a statement list onto a sequence. These may be created either
1705 by an enlightened front-end, or by shortcut_cond_expr. */
1707 static enum gimplify_status
1708 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
1710 tree temp = voidify_wrapper_expr (*expr_p, NULL);
1712 tree_stmt_iterator i = tsi_start (*expr_p);
1714 while (!tsi_end_p (i))
1716 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
1717 tsi_delink (&i);
1720 if (temp)
1722 *expr_p = temp;
1723 return GS_OK;
1726 return GS_ALL_DONE;
1729 /* Callback for walk_gimple_seq. */
1731 static tree
1732 warn_switch_unreachable_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
1733 struct walk_stmt_info *wi)
1735 gimple *stmt = gsi_stmt (*gsi_p);
1737 *handled_ops_p = true;
1738 switch (gimple_code (stmt))
1740 case GIMPLE_TRY:
1741 /* A compiler-generated cleanup or a user-written try block.
1742 If it's empty, don't dive into it--that would result in
1743 worse location info. */
1744 if (gimple_try_eval (stmt) == NULL)
1746 wi->info = stmt;
1747 return integer_zero_node;
1749 /* Fall through. */
1750 case GIMPLE_BIND:
1751 case GIMPLE_CATCH:
1752 case GIMPLE_EH_FILTER:
1753 case GIMPLE_TRANSACTION:
1754 /* Walk the sub-statements. */
1755 *handled_ops_p = false;
1756 break;
1757 case GIMPLE_CALL:
1758 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
1760 *handled_ops_p = false;
1761 break;
1763 /* Fall through. */
1764 default:
1765 /* Save the first "real" statement (not a decl/lexical scope/...). */
1766 wi->info = stmt;
1767 return integer_zero_node;
1769 return NULL_TREE;
1772 /* Possibly warn about unreachable statements between switch's controlling
1773 expression and the first case. SEQ is the body of a switch expression. */
1775 static void
1776 maybe_warn_switch_unreachable (gimple_seq seq)
1778 if (!warn_switch_unreachable
1779 /* This warning doesn't play well with Fortran when optimizations
1780 are on. */
1781 || lang_GNU_Fortran ()
1782 || seq == NULL)
1783 return;
1785 struct walk_stmt_info wi;
1786 memset (&wi, 0, sizeof (wi));
1787 walk_gimple_seq (seq, warn_switch_unreachable_r, NULL, &wi);
1788 gimple *stmt = (gimple *) wi.info;
1790 if (stmt && gimple_code (stmt) != GIMPLE_LABEL)
1792 if (gimple_code (stmt) == GIMPLE_GOTO
1793 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
1794 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
1795 /* Don't warn for compiler-generated gotos. These occur
1796 in Duff's devices, for example. */;
1797 else
1798 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
1799 "statement will never be executed");
1804 /* A label entry that pairs label and a location. */
1805 struct label_entry
1807 tree label;
1808 location_t loc;
1811 /* Find LABEL in vector of label entries VEC. */
1813 static struct label_entry *
1814 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
1816 unsigned int i;
1817 struct label_entry *l;
1819 FOR_EACH_VEC_ELT (*vec, i, l)
1820 if (l->label == label)
1821 return l;
1822 return NULL;
1825 /* Return true if LABEL, a LABEL_DECL, represents a case label
1826 in a vector of labels CASES. */
1828 static bool
1829 case_label_p (const vec<tree> *cases, tree label)
1831 unsigned int i;
1832 tree l;
1834 FOR_EACH_VEC_ELT (*cases, i, l)
1835 if (CASE_LABEL (l) == label)
1836 return true;
1837 return false;
1840 /* Find the last statement in a scope STMT. */
1842 static gimple *
1843 last_stmt_in_scope (gimple *stmt)
1845 if (!stmt)
1846 return NULL;
1848 switch (gimple_code (stmt))
1850 case GIMPLE_BIND:
1852 gbind *bind = as_a <gbind *> (stmt);
1853 stmt = gimple_seq_last_stmt (gimple_bind_body (bind));
1854 return last_stmt_in_scope (stmt);
1857 case GIMPLE_TRY:
1859 gtry *try_stmt = as_a <gtry *> (stmt);
1860 stmt = gimple_seq_last_stmt (gimple_try_eval (try_stmt));
1861 gimple *last_eval = last_stmt_in_scope (stmt);
1862 if (gimple_stmt_may_fallthru (last_eval)
1863 && (last_eval == NULL
1864 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
1865 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
1867 stmt = gimple_seq_last_stmt (gimple_try_cleanup (try_stmt));
1868 return last_stmt_in_scope (stmt);
1870 else
1871 return last_eval;
1874 default:
1875 return stmt;
1879 /* Collect interesting labels in LABELS and return the statement preceding
1880 another case label, or a user-defined label. */
1882 static gimple *
1883 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
1884 auto_vec <struct label_entry> *labels)
1886 gimple *prev = NULL;
1890 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
1891 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
1893 /* Nested scope. Only look at the last statement of
1894 the innermost scope. */
1895 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
1896 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
1897 if (last)
1899 prev = last;
1900 /* It might be a label without a location. Use the
1901 location of the scope then. */
1902 if (!gimple_has_location (prev))
1903 gimple_set_location (prev, bind_loc);
1905 gsi_next (gsi_p);
1906 continue;
1909 /* Ifs are tricky. */
1910 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
1912 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
1913 tree false_lab = gimple_cond_false_label (cond_stmt);
1914 location_t if_loc = gimple_location (cond_stmt);
1916 /* If we have e.g.
1917 if (i > 1) goto <D.2259>; else goto D;
1918 we can't do much with the else-branch. */
1919 if (!DECL_ARTIFICIAL (false_lab))
1920 break;
1922 /* Go on until the false label, then one step back. */
1923 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
1925 gimple *stmt = gsi_stmt (*gsi_p);
1926 if (gimple_code (stmt) == GIMPLE_LABEL
1927 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
1928 break;
1931 /* Not found? Oops. */
1932 if (gsi_end_p (*gsi_p))
1933 break;
1935 struct label_entry l = { false_lab, if_loc };
1936 labels->safe_push (l);
1938 /* Go to the last statement of the then branch. */
1939 gsi_prev (gsi_p);
1941 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
1942 <D.1759>:
1943 <stmt>;
1944 goto <D.1761>;
1945 <D.1760>:
1947 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
1948 && !gimple_has_location (gsi_stmt (*gsi_p)))
1950 /* Look at the statement before, it might be
1951 attribute fallthrough, in which case don't warn. */
1952 gsi_prev (gsi_p);
1953 bool fallthru_before_dest
1954 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
1955 gsi_next (gsi_p);
1956 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
1957 if (!fallthru_before_dest)
1959 struct label_entry l = { goto_dest, if_loc };
1960 labels->safe_push (l);
1963 /* And move back. */
1964 gsi_next (gsi_p);
1967 /* Remember the last statement. Skip labels that are of no interest
1968 to us. */
1969 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
1971 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
1972 if (find_label_entry (labels, label))
1973 prev = gsi_stmt (*gsi_p);
1975 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
1977 else
1978 prev = gsi_stmt (*gsi_p);
1979 gsi_next (gsi_p);
1981 while (!gsi_end_p (*gsi_p)
1982 /* Stop if we find a case or a user-defined label. */
1983 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
1984 || !gimple_has_location (gsi_stmt (*gsi_p))));
1986 return prev;
1989 /* Return true if the switch fallthough warning should occur. LABEL is
1990 the label statement that we're falling through to. */
1992 static bool
1993 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
1995 gimple_stmt_iterator gsi = *gsi_p;
1997 /* Don't warn if the label is marked with a "falls through" comment. */
1998 if (FALLTHROUGH_LABEL_P (label))
1999 return false;
2001 /* Don't warn for non-case labels followed by a statement:
2002 case 0:
2003 foo ();
2004 label:
2005 bar ();
2006 as these are likely intentional. */
2007 if (!case_label_p (&gimplify_ctxp->case_labels, label))
2009 tree l;
2010 while (!gsi_end_p (gsi)
2011 && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2012 && (l = gimple_label_label (as_a <glabel *> (gsi_stmt (gsi))))
2013 && !case_label_p (&gimplify_ctxp->case_labels, l))
2014 gsi_next (&gsi);
2015 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
2016 return false;
2019 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2020 immediately breaks. */
2021 gsi = *gsi_p;
2023 /* Skip all immediately following labels. */
2024 while (!gsi_end_p (gsi) && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL)
2025 gsi_next (&gsi);
2027 /* { ... something; default:; } */
2028 if (gsi_end_p (gsi)
2029 /* { ... something; default: break; } or
2030 { ... something; default: goto L; } */
2031 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2032 /* { ... something; default: return; } */
2033 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2034 return false;
2036 return true;
2039 /* Callback for walk_gimple_seq. */
2041 static tree
2042 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2043 struct walk_stmt_info *)
2045 gimple *stmt = gsi_stmt (*gsi_p);
2047 *handled_ops_p = true;
2048 switch (gimple_code (stmt))
2050 case GIMPLE_TRY:
2051 case GIMPLE_BIND:
2052 case GIMPLE_CATCH:
2053 case GIMPLE_EH_FILTER:
2054 case GIMPLE_TRANSACTION:
2055 /* Walk the sub-statements. */
2056 *handled_ops_p = false;
2057 break;
2059 /* Find a sequence of form:
2061 GIMPLE_LABEL
2062 [...]
2063 <may fallthru stmt>
2064 GIMPLE_LABEL
2066 and possibly warn. */
2067 case GIMPLE_LABEL:
2069 /* Found a label. Skip all immediately following labels. */
2070 while (!gsi_end_p (*gsi_p)
2071 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2072 gsi_next (gsi_p);
2074 /* There might be no more statements. */
2075 if (gsi_end_p (*gsi_p))
2076 return integer_zero_node;
2078 /* Vector of labels that fall through. */
2079 auto_vec <struct label_entry> labels;
2080 gimple *prev = collect_fallthrough_labels (gsi_p, &labels);
2082 /* There might be no more statements. */
2083 if (gsi_end_p (*gsi_p))
2084 return integer_zero_node;
2086 gimple *next = gsi_stmt (*gsi_p);
2087 tree label;
2088 /* If what follows is a label, then we may have a fallthrough. */
2089 if (gimple_code (next) == GIMPLE_LABEL
2090 && gimple_has_location (next)
2091 && (label = gimple_label_label (as_a <glabel *> (next)))
2092 && prev != NULL)
2094 struct label_entry *l;
2095 bool warned_p = false;
2096 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2097 /* Quiet. */;
2098 else if (gimple_code (prev) == GIMPLE_LABEL
2099 && (label = gimple_label_label (as_a <glabel *> (prev)))
2100 && (l = find_label_entry (&labels, label)))
2101 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2102 "this statement may fall through");
2103 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2104 /* Try to be clever and don't warn when the statement
2105 can't actually fall through. */
2106 && gimple_stmt_may_fallthru (prev)
2107 && gimple_has_location (prev))
2108 warned_p = warning_at (gimple_location (prev),
2109 OPT_Wimplicit_fallthrough_,
2110 "this statement may fall through");
2111 if (warned_p)
2112 inform (gimple_location (next), "here");
2114 /* Mark this label as processed so as to prevent multiple
2115 warnings in nested switches. */
2116 FALLTHROUGH_LABEL_P (label) = true;
2118 /* So that next warn_implicit_fallthrough_r will start looking for
2119 a new sequence starting with this label. */
2120 gsi_prev (gsi_p);
2123 break;
2124 default:
2125 break;
2127 return NULL_TREE;
2130 /* Warn when a switch case falls through. */
2132 static void
2133 maybe_warn_implicit_fallthrough (gimple_seq seq)
2135 if (!warn_implicit_fallthrough)
2136 return;
2138 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2139 if (!(lang_GNU_C ()
2140 || lang_GNU_CXX ()
2141 || lang_GNU_OBJC ()))
2142 return;
2144 struct walk_stmt_info wi;
2145 memset (&wi, 0, sizeof (wi));
2146 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2149 /* Callback for walk_gimple_seq. */
2151 static tree
2152 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2153 struct walk_stmt_info *)
2155 gimple *stmt = gsi_stmt (*gsi_p);
2157 *handled_ops_p = true;
2158 switch (gimple_code (stmt))
2160 case GIMPLE_TRY:
2161 case GIMPLE_BIND:
2162 case GIMPLE_CATCH:
2163 case GIMPLE_EH_FILTER:
2164 case GIMPLE_TRANSACTION:
2165 /* Walk the sub-statements. */
2166 *handled_ops_p = false;
2167 break;
2168 case GIMPLE_CALL:
2169 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2171 gsi_remove (gsi_p, true);
2172 if (gsi_end_p (*gsi_p))
2173 return integer_zero_node;
2175 bool found = false;
2176 location_t loc = gimple_location (stmt);
2178 gimple_stmt_iterator gsi2 = *gsi_p;
2179 stmt = gsi_stmt (gsi2);
2180 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2182 /* Go on until the artificial label. */
2183 tree goto_dest = gimple_goto_dest (stmt);
2184 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2186 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2187 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2188 == goto_dest)
2189 break;
2192 /* Not found? Stop. */
2193 if (gsi_end_p (gsi2))
2194 break;
2196 /* Look one past it. */
2197 gsi_next (&gsi2);
2200 /* We're looking for a case label or default label here. */
2201 while (!gsi_end_p (gsi2))
2203 stmt = gsi_stmt (gsi2);
2204 if (gimple_code (stmt) == GIMPLE_LABEL)
2206 tree label = gimple_label_label (as_a <glabel *> (stmt));
2207 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2209 found = true;
2210 break;
2213 else
2214 /* Something other than a label. That's not expected. */
2215 break;
2216 gsi_next (&gsi2);
2218 if (!found)
2219 warning_at (loc, 0, "attribute %<fallthrough%> not preceding "
2220 "a case label or default label");
2222 break;
2223 default:
2224 break;
2226 return NULL_TREE;
2229 /* Expand all FALLTHROUGH () calls in SEQ. */
2231 static void
2232 expand_FALLTHROUGH (gimple_seq *seq_p)
2234 struct walk_stmt_info wi;
2235 memset (&wi, 0, sizeof (wi));
2236 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2240 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2241 branch to. */
2243 static enum gimplify_status
2244 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2246 tree switch_expr = *expr_p;
2247 gimple_seq switch_body_seq = NULL;
2248 enum gimplify_status ret;
2249 tree index_type = TREE_TYPE (switch_expr);
2250 if (index_type == NULL_TREE)
2251 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2253 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2254 fb_rvalue);
2255 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2256 return ret;
2258 if (SWITCH_BODY (switch_expr))
2260 vec<tree> labels;
2261 vec<tree> saved_labels;
2262 hash_set<tree> *saved_live_switch_vars = NULL;
2263 tree default_case = NULL_TREE;
2264 gswitch *switch_stmt;
2266 /* If someone can be bothered to fill in the labels, they can
2267 be bothered to null out the body too. */
2268 gcc_assert (!SWITCH_LABELS (switch_expr));
2270 /* Save old labels, get new ones from body, then restore the old
2271 labels. Save all the things from the switch body to append after. */
2272 saved_labels = gimplify_ctxp->case_labels;
2273 gimplify_ctxp->case_labels.create (8);
2275 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2276 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2277 if (TREE_CODE (SWITCH_BODY (switch_expr)) == BIND_EXPR)
2278 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2279 else
2280 gimplify_ctxp->live_switch_vars = NULL;
2282 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2283 gimplify_ctxp->in_switch_expr = true;
2285 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2287 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2288 maybe_warn_switch_unreachable (switch_body_seq);
2289 maybe_warn_implicit_fallthrough (switch_body_seq);
2290 /* Only do this for the outermost GIMPLE_SWITCH. */
2291 if (!gimplify_ctxp->in_switch_expr)
2292 expand_FALLTHROUGH (&switch_body_seq);
2294 labels = gimplify_ctxp->case_labels;
2295 gimplify_ctxp->case_labels = saved_labels;
2297 if (gimplify_ctxp->live_switch_vars)
2299 gcc_assert (gimplify_ctxp->live_switch_vars->elements () == 0);
2300 delete gimplify_ctxp->live_switch_vars;
2302 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2304 preprocess_case_label_vec_for_gimple (labels, index_type,
2305 &default_case);
2307 if (!default_case)
2309 glabel *new_default;
2311 default_case
2312 = build_case_label (NULL_TREE, NULL_TREE,
2313 create_artificial_label (UNKNOWN_LOCATION));
2314 new_default = gimple_build_label (CASE_LABEL (default_case));
2315 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2318 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2319 default_case, labels);
2320 gimplify_seq_add_stmt (pre_p, switch_stmt);
2321 gimplify_seq_add_seq (pre_p, switch_body_seq);
2322 labels.release ();
2324 else
2325 gcc_assert (SWITCH_LABELS (switch_expr));
2327 return GS_ALL_DONE;
2330 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
2332 static enum gimplify_status
2333 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
2335 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
2336 == current_function_decl);
2338 glabel *label_stmt = gimple_build_label (LABEL_EXPR_LABEL (*expr_p));
2339 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2340 gimplify_seq_add_stmt (pre_p, label_stmt);
2342 return GS_ALL_DONE;
2345 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
2347 static enum gimplify_status
2348 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
2350 struct gimplify_ctx *ctxp;
2351 glabel *label_stmt;
2353 /* Invalid programs can play Duff's Device type games with, for example,
2354 #pragma omp parallel. At least in the C front end, we don't
2355 detect such invalid branches until after gimplification, in the
2356 diagnose_omp_blocks pass. */
2357 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
2358 if (ctxp->case_labels.exists ())
2359 break;
2361 label_stmt = gimple_build_label (CASE_LABEL (*expr_p));
2362 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2363 ctxp->case_labels.safe_push (*expr_p);
2364 gimplify_seq_add_stmt (pre_p, label_stmt);
2366 return GS_ALL_DONE;
2369 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
2370 if necessary. */
2372 tree
2373 build_and_jump (tree *label_p)
2375 if (label_p == NULL)
2376 /* If there's nowhere to jump, just fall through. */
2377 return NULL_TREE;
2379 if (*label_p == NULL_TREE)
2381 tree label = create_artificial_label (UNKNOWN_LOCATION);
2382 *label_p = label;
2385 return build1 (GOTO_EXPR, void_type_node, *label_p);
2388 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
2389 This also involves building a label to jump to and communicating it to
2390 gimplify_loop_expr through gimplify_ctxp->exit_label. */
2392 static enum gimplify_status
2393 gimplify_exit_expr (tree *expr_p)
2395 tree cond = TREE_OPERAND (*expr_p, 0);
2396 tree expr;
2398 expr = build_and_jump (&gimplify_ctxp->exit_label);
2399 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
2400 *expr_p = expr;
2402 return GS_OK;
2405 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
2406 different from its canonical type, wrap the whole thing inside a
2407 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
2408 type.
2410 The canonical type of a COMPONENT_REF is the type of the field being
2411 referenced--unless the field is a bit-field which can be read directly
2412 in a smaller mode, in which case the canonical type is the
2413 sign-appropriate type corresponding to that mode. */
2415 static void
2416 canonicalize_component_ref (tree *expr_p)
2418 tree expr = *expr_p;
2419 tree type;
2421 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
2423 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
2424 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
2425 else
2426 type = TREE_TYPE (TREE_OPERAND (expr, 1));
2428 /* One could argue that all the stuff below is not necessary for
2429 the non-bitfield case and declare it a FE error if type
2430 adjustment would be needed. */
2431 if (TREE_TYPE (expr) != type)
2433 #ifdef ENABLE_TYPES_CHECKING
2434 tree old_type = TREE_TYPE (expr);
2435 #endif
2436 int type_quals;
2438 /* We need to preserve qualifiers and propagate them from
2439 operand 0. */
2440 type_quals = TYPE_QUALS (type)
2441 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
2442 if (TYPE_QUALS (type) != type_quals)
2443 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
2445 /* Set the type of the COMPONENT_REF to the underlying type. */
2446 TREE_TYPE (expr) = type;
2448 #ifdef ENABLE_TYPES_CHECKING
2449 /* It is now a FE error, if the conversion from the canonical
2450 type to the original expression type is not useless. */
2451 gcc_assert (useless_type_conversion_p (old_type, type));
2452 #endif
2456 /* If a NOP conversion is changing a pointer to array of foo to a pointer
2457 to foo, embed that change in the ADDR_EXPR by converting
2458 T array[U];
2459 (T *)&array
2461 &array[L]
2462 where L is the lower bound. For simplicity, only do this for constant
2463 lower bound.
2464 The constraint is that the type of &array[L] is trivially convertible
2465 to T *. */
2467 static void
2468 canonicalize_addr_expr (tree *expr_p)
2470 tree expr = *expr_p;
2471 tree addr_expr = TREE_OPERAND (expr, 0);
2472 tree datype, ddatype, pddatype;
2474 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
2475 if (!POINTER_TYPE_P (TREE_TYPE (expr))
2476 || TREE_CODE (addr_expr) != ADDR_EXPR)
2477 return;
2479 /* The addr_expr type should be a pointer to an array. */
2480 datype = TREE_TYPE (TREE_TYPE (addr_expr));
2481 if (TREE_CODE (datype) != ARRAY_TYPE)
2482 return;
2484 /* The pointer to element type shall be trivially convertible to
2485 the expression pointer type. */
2486 ddatype = TREE_TYPE (datype);
2487 pddatype = build_pointer_type (ddatype);
2488 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
2489 pddatype))
2490 return;
2492 /* The lower bound and element sizes must be constant. */
2493 if (!TYPE_SIZE_UNIT (ddatype)
2494 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
2495 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
2496 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
2497 return;
2499 /* All checks succeeded. Build a new node to merge the cast. */
2500 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
2501 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
2502 NULL_TREE, NULL_TREE);
2503 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
2505 /* We can have stripped a required restrict qualifier above. */
2506 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
2507 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
2510 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
2511 underneath as appropriate. */
2513 static enum gimplify_status
2514 gimplify_conversion (tree *expr_p)
2516 location_t loc = EXPR_LOCATION (*expr_p);
2517 gcc_assert (CONVERT_EXPR_P (*expr_p));
2519 /* Then strip away all but the outermost conversion. */
2520 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
2522 /* And remove the outermost conversion if it's useless. */
2523 if (tree_ssa_useless_type_conversion (*expr_p))
2524 *expr_p = TREE_OPERAND (*expr_p, 0);
2526 /* If we still have a conversion at the toplevel,
2527 then canonicalize some constructs. */
2528 if (CONVERT_EXPR_P (*expr_p))
2530 tree sub = TREE_OPERAND (*expr_p, 0);
2532 /* If a NOP conversion is changing the type of a COMPONENT_REF
2533 expression, then canonicalize its type now in order to expose more
2534 redundant conversions. */
2535 if (TREE_CODE (sub) == COMPONENT_REF)
2536 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
2538 /* If a NOP conversion is changing a pointer to array of foo
2539 to a pointer to foo, embed that change in the ADDR_EXPR. */
2540 else if (TREE_CODE (sub) == ADDR_EXPR)
2541 canonicalize_addr_expr (expr_p);
2544 /* If we have a conversion to a non-register type force the
2545 use of a VIEW_CONVERT_EXPR instead. */
2546 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
2547 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
2548 TREE_OPERAND (*expr_p, 0));
2550 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
2551 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
2552 TREE_SET_CODE (*expr_p, NOP_EXPR);
2554 return GS_OK;
2557 /* Nonlocal VLAs seen in the current function. */
2558 static hash_set<tree> *nonlocal_vlas;
2560 /* The VAR_DECLs created for nonlocal VLAs for debug info purposes. */
2561 static tree nonlocal_vla_vars;
2563 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
2564 DECL_VALUE_EXPR, and it's worth re-examining things. */
2566 static enum gimplify_status
2567 gimplify_var_or_parm_decl (tree *expr_p)
2569 tree decl = *expr_p;
2571 /* ??? If this is a local variable, and it has not been seen in any
2572 outer BIND_EXPR, then it's probably the result of a duplicate
2573 declaration, for which we've already issued an error. It would
2574 be really nice if the front end wouldn't leak these at all.
2575 Currently the only known culprit is C++ destructors, as seen
2576 in g++.old-deja/g++.jason/binding.C. */
2577 if (VAR_P (decl)
2578 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
2579 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
2580 && decl_function_context (decl) == current_function_decl)
2582 gcc_assert (seen_error ());
2583 return GS_ERROR;
2586 /* When within an OMP context, notice uses of variables. */
2587 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
2588 return GS_ALL_DONE;
2590 /* If the decl is an alias for another expression, substitute it now. */
2591 if (DECL_HAS_VALUE_EXPR_P (decl))
2593 tree value_expr = DECL_VALUE_EXPR (decl);
2595 /* For referenced nonlocal VLAs add a decl for debugging purposes
2596 to the current function. */
2597 if (VAR_P (decl)
2598 && TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
2599 && nonlocal_vlas != NULL
2600 && TREE_CODE (value_expr) == INDIRECT_REF
2601 && TREE_CODE (TREE_OPERAND (value_expr, 0)) == VAR_DECL
2602 && decl_function_context (decl) != current_function_decl)
2604 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
2605 while (ctx
2606 && (ctx->region_type == ORT_WORKSHARE
2607 || ctx->region_type == ORT_SIMD
2608 || ctx->region_type == ORT_ACC))
2609 ctx = ctx->outer_context;
2610 if (!ctx && !nonlocal_vlas->add (decl))
2612 tree copy = copy_node (decl);
2614 lang_hooks.dup_lang_specific_decl (copy);
2615 SET_DECL_RTL (copy, 0);
2616 TREE_USED (copy) = 1;
2617 DECL_CHAIN (copy) = nonlocal_vla_vars;
2618 nonlocal_vla_vars = copy;
2619 SET_DECL_VALUE_EXPR (copy, unshare_expr (value_expr));
2620 DECL_HAS_VALUE_EXPR_P (copy) = 1;
2624 *expr_p = unshare_expr (value_expr);
2625 return GS_OK;
2628 return GS_ALL_DONE;
2631 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
2633 static void
2634 recalculate_side_effects (tree t)
2636 enum tree_code code = TREE_CODE (t);
2637 int len = TREE_OPERAND_LENGTH (t);
2638 int i;
2640 switch (TREE_CODE_CLASS (code))
2642 case tcc_expression:
2643 switch (code)
2645 case INIT_EXPR:
2646 case MODIFY_EXPR:
2647 case VA_ARG_EXPR:
2648 case PREDECREMENT_EXPR:
2649 case PREINCREMENT_EXPR:
2650 case POSTDECREMENT_EXPR:
2651 case POSTINCREMENT_EXPR:
2652 /* All of these have side-effects, no matter what their
2653 operands are. */
2654 return;
2656 default:
2657 break;
2659 /* Fall through. */
2661 case tcc_comparison: /* a comparison expression */
2662 case tcc_unary: /* a unary arithmetic expression */
2663 case tcc_binary: /* a binary arithmetic expression */
2664 case tcc_reference: /* a reference */
2665 case tcc_vl_exp: /* a function call */
2666 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
2667 for (i = 0; i < len; ++i)
2669 tree op = TREE_OPERAND (t, i);
2670 if (op && TREE_SIDE_EFFECTS (op))
2671 TREE_SIDE_EFFECTS (t) = 1;
2673 break;
2675 case tcc_constant:
2676 /* No side-effects. */
2677 return;
2679 default:
2680 gcc_unreachable ();
2684 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
2685 node *EXPR_P.
2687 compound_lval
2688 : min_lval '[' val ']'
2689 | min_lval '.' ID
2690 | compound_lval '[' val ']'
2691 | compound_lval '.' ID
2693 This is not part of the original SIMPLE definition, which separates
2694 array and member references, but it seems reasonable to handle them
2695 together. Also, this way we don't run into problems with union
2696 aliasing; gcc requires that for accesses through a union to alias, the
2697 union reference must be explicit, which was not always the case when we
2698 were splitting up array and member refs.
2700 PRE_P points to the sequence where side effects that must happen before
2701 *EXPR_P should be stored.
2703 POST_P points to the sequence where side effects that must happen after
2704 *EXPR_P should be stored. */
2706 static enum gimplify_status
2707 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
2708 fallback_t fallback)
2710 tree *p;
2711 enum gimplify_status ret = GS_ALL_DONE, tret;
2712 int i;
2713 location_t loc = EXPR_LOCATION (*expr_p);
2714 tree expr = *expr_p;
2716 /* Create a stack of the subexpressions so later we can walk them in
2717 order from inner to outer. */
2718 auto_vec<tree, 10> expr_stack;
2720 /* We can handle anything that get_inner_reference can deal with. */
2721 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
2723 restart:
2724 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
2725 if (TREE_CODE (*p) == INDIRECT_REF)
2726 *p = fold_indirect_ref_loc (loc, *p);
2728 if (handled_component_p (*p))
2730 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
2731 additional COMPONENT_REFs. */
2732 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
2733 && gimplify_var_or_parm_decl (p) == GS_OK)
2734 goto restart;
2735 else
2736 break;
2738 expr_stack.safe_push (*p);
2741 gcc_assert (expr_stack.length ());
2743 /* Now EXPR_STACK is a stack of pointers to all the refs we've
2744 walked through and P points to the innermost expression.
2746 Java requires that we elaborated nodes in source order. That
2747 means we must gimplify the inner expression followed by each of
2748 the indices, in order. But we can't gimplify the inner
2749 expression until we deal with any variable bounds, sizes, or
2750 positions in order to deal with PLACEHOLDER_EXPRs.
2752 So we do this in three steps. First we deal with the annotations
2753 for any variables in the components, then we gimplify the base,
2754 then we gimplify any indices, from left to right. */
2755 for (i = expr_stack.length () - 1; i >= 0; i--)
2757 tree t = expr_stack[i];
2759 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
2761 /* Gimplify the low bound and element type size and put them into
2762 the ARRAY_REF. If these values are set, they have already been
2763 gimplified. */
2764 if (TREE_OPERAND (t, 2) == NULL_TREE)
2766 tree low = unshare_expr (array_ref_low_bound (t));
2767 if (!is_gimple_min_invariant (low))
2769 TREE_OPERAND (t, 2) = low;
2770 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
2771 post_p, is_gimple_reg,
2772 fb_rvalue);
2773 ret = MIN (ret, tret);
2776 else
2778 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
2779 is_gimple_reg, fb_rvalue);
2780 ret = MIN (ret, tret);
2783 if (TREE_OPERAND (t, 3) == NULL_TREE)
2785 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
2786 tree elmt_size = unshare_expr (array_ref_element_size (t));
2787 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
2789 /* Divide the element size by the alignment of the element
2790 type (above). */
2791 elmt_size
2792 = size_binop_loc (loc, EXACT_DIV_EXPR, elmt_size, factor);
2794 if (!is_gimple_min_invariant (elmt_size))
2796 TREE_OPERAND (t, 3) = elmt_size;
2797 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
2798 post_p, is_gimple_reg,
2799 fb_rvalue);
2800 ret = MIN (ret, tret);
2803 else
2805 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
2806 is_gimple_reg, fb_rvalue);
2807 ret = MIN (ret, tret);
2810 else if (TREE_CODE (t) == COMPONENT_REF)
2812 /* Set the field offset into T and gimplify it. */
2813 if (TREE_OPERAND (t, 2) == NULL_TREE)
2815 tree offset = unshare_expr (component_ref_field_offset (t));
2816 tree field = TREE_OPERAND (t, 1);
2817 tree factor
2818 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
2820 /* Divide the offset by its alignment. */
2821 offset = size_binop_loc (loc, EXACT_DIV_EXPR, offset, factor);
2823 if (!is_gimple_min_invariant (offset))
2825 TREE_OPERAND (t, 2) = offset;
2826 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
2827 post_p, is_gimple_reg,
2828 fb_rvalue);
2829 ret = MIN (ret, tret);
2832 else
2834 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
2835 is_gimple_reg, fb_rvalue);
2836 ret = MIN (ret, tret);
2841 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
2842 so as to match the min_lval predicate. Failure to do so may result
2843 in the creation of large aggregate temporaries. */
2844 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
2845 fallback | fb_lvalue);
2846 ret = MIN (ret, tret);
2848 /* And finally, the indices and operands of ARRAY_REF. During this
2849 loop we also remove any useless conversions. */
2850 for (; expr_stack.length () > 0; )
2852 tree t = expr_stack.pop ();
2854 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
2856 /* Gimplify the dimension. */
2857 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
2859 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
2860 is_gimple_val, fb_rvalue);
2861 ret = MIN (ret, tret);
2865 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
2867 /* The innermost expression P may have originally had
2868 TREE_SIDE_EFFECTS set which would have caused all the outer
2869 expressions in *EXPR_P leading to P to also have had
2870 TREE_SIDE_EFFECTS set. */
2871 recalculate_side_effects (t);
2874 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
2875 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
2877 canonicalize_component_ref (expr_p);
2880 expr_stack.release ();
2882 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
2884 return ret;
2887 /* Gimplify the self modifying expression pointed to by EXPR_P
2888 (++, --, +=, -=).
2890 PRE_P points to the list where side effects that must happen before
2891 *EXPR_P should be stored.
2893 POST_P points to the list where side effects that must happen after
2894 *EXPR_P should be stored.
2896 WANT_VALUE is nonzero iff we want to use the value of this expression
2897 in another expression.
2899 ARITH_TYPE is the type the computation should be performed in. */
2901 enum gimplify_status
2902 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
2903 bool want_value, tree arith_type)
2905 enum tree_code code;
2906 tree lhs, lvalue, rhs, t1;
2907 gimple_seq post = NULL, *orig_post_p = post_p;
2908 bool postfix;
2909 enum tree_code arith_code;
2910 enum gimplify_status ret;
2911 location_t loc = EXPR_LOCATION (*expr_p);
2913 code = TREE_CODE (*expr_p);
2915 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
2916 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
2918 /* Prefix or postfix? */
2919 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
2920 /* Faster to treat as prefix if result is not used. */
2921 postfix = want_value;
2922 else
2923 postfix = false;
2925 /* For postfix, make sure the inner expression's post side effects
2926 are executed after side effects from this expression. */
2927 if (postfix)
2928 post_p = &post;
2930 /* Add or subtract? */
2931 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
2932 arith_code = PLUS_EXPR;
2933 else
2934 arith_code = MINUS_EXPR;
2936 /* Gimplify the LHS into a GIMPLE lvalue. */
2937 lvalue = TREE_OPERAND (*expr_p, 0);
2938 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
2939 if (ret == GS_ERROR)
2940 return ret;
2942 /* Extract the operands to the arithmetic operation. */
2943 lhs = lvalue;
2944 rhs = TREE_OPERAND (*expr_p, 1);
2946 /* For postfix operator, we evaluate the LHS to an rvalue and then use
2947 that as the result value and in the postqueue operation. */
2948 if (postfix)
2950 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
2951 if (ret == GS_ERROR)
2952 return ret;
2954 lhs = get_initialized_tmp_var (lhs, pre_p, NULL);
2957 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
2958 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
2960 rhs = convert_to_ptrofftype_loc (loc, rhs);
2961 if (arith_code == MINUS_EXPR)
2962 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
2963 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
2965 else
2966 t1 = fold_convert (TREE_TYPE (*expr_p),
2967 fold_build2 (arith_code, arith_type,
2968 fold_convert (arith_type, lhs),
2969 fold_convert (arith_type, rhs)));
2971 if (postfix)
2973 gimplify_assign (lvalue, t1, pre_p);
2974 gimplify_seq_add_seq (orig_post_p, post);
2975 *expr_p = lhs;
2976 return GS_ALL_DONE;
2978 else
2980 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
2981 return GS_OK;
2985 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
2987 static void
2988 maybe_with_size_expr (tree *expr_p)
2990 tree expr = *expr_p;
2991 tree type = TREE_TYPE (expr);
2992 tree size;
2994 /* If we've already wrapped this or the type is error_mark_node, we can't do
2995 anything. */
2996 if (TREE_CODE (expr) == WITH_SIZE_EXPR
2997 || type == error_mark_node)
2998 return;
3000 /* If the size isn't known or is a constant, we have nothing to do. */
3001 size = TYPE_SIZE_UNIT (type);
3002 if (!size || TREE_CODE (size) == INTEGER_CST)
3003 return;
3005 /* Otherwise, make a WITH_SIZE_EXPR. */
3006 size = unshare_expr (size);
3007 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
3008 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
3011 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
3012 Store any side-effects in PRE_P. CALL_LOCATION is the location of
3013 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
3014 gimplified to an SSA name. */
3016 enum gimplify_status
3017 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3018 bool allow_ssa)
3020 bool (*test) (tree);
3021 fallback_t fb;
3023 /* In general, we allow lvalues for function arguments to avoid
3024 extra overhead of copying large aggregates out of even larger
3025 aggregates into temporaries only to copy the temporaries to
3026 the argument list. Make optimizers happy by pulling out to
3027 temporaries those types that fit in registers. */
3028 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3029 test = is_gimple_val, fb = fb_rvalue;
3030 else
3032 test = is_gimple_lvalue, fb = fb_either;
3033 /* Also strip a TARGET_EXPR that would force an extra copy. */
3034 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3036 tree init = TARGET_EXPR_INITIAL (*arg_p);
3037 if (init
3038 && !VOID_TYPE_P (TREE_TYPE (init)))
3039 *arg_p = init;
3043 /* If this is a variable sized type, we must remember the size. */
3044 maybe_with_size_expr (arg_p);
3046 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3047 /* Make sure arguments have the same location as the function call
3048 itself. */
3049 protected_set_expr_location (*arg_p, call_location);
3051 /* There is a sequence point before a function call. Side effects in
3052 the argument list must occur before the actual call. So, when
3053 gimplifying arguments, force gimplify_expr to use an internal
3054 post queue which is then appended to the end of PRE_P. */
3055 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3058 /* Don't fold inside offloading or taskreg regions: it can break code by
3059 adding decl references that weren't in the source. We'll do it during
3060 omplower pass instead. */
3062 static bool
3063 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3065 struct gimplify_omp_ctx *ctx;
3066 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3067 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3068 return false;
3069 return fold_stmt (gsi);
3072 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3073 WANT_VALUE is true if the result of the call is desired. */
3075 static enum gimplify_status
3076 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3078 tree fndecl, parms, p, fnptrtype;
3079 enum gimplify_status ret;
3080 int i, nargs;
3081 gcall *call;
3082 bool builtin_va_start_p = false;
3083 location_t loc = EXPR_LOCATION (*expr_p);
3085 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3087 /* For reliable diagnostics during inlining, it is necessary that
3088 every call_expr be annotated with file and line. */
3089 if (! EXPR_HAS_LOCATION (*expr_p))
3090 SET_EXPR_LOCATION (*expr_p, input_location);
3092 /* Gimplify internal functions created in the FEs. */
3093 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3095 if (want_value)
3096 return GS_ALL_DONE;
3098 nargs = call_expr_nargs (*expr_p);
3099 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3100 auto_vec<tree> vargs (nargs);
3102 for (i = 0; i < nargs; i++)
3104 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3105 EXPR_LOCATION (*expr_p));
3106 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3108 gimple *call = gimple_build_call_internal_vec (ifn, vargs);
3109 gimplify_seq_add_stmt (pre_p, call);
3110 return GS_ALL_DONE;
3113 /* This may be a call to a builtin function.
3115 Builtin function calls may be transformed into different
3116 (and more efficient) builtin function calls under certain
3117 circumstances. Unfortunately, gimplification can muck things
3118 up enough that the builtin expanders are not aware that certain
3119 transformations are still valid.
3121 So we attempt transformation/gimplification of the call before
3122 we gimplify the CALL_EXPR. At this time we do not manage to
3123 transform all calls in the same manner as the expanders do, but
3124 we do transform most of them. */
3125 fndecl = get_callee_fndecl (*expr_p);
3126 if (fndecl
3127 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL)
3128 switch (DECL_FUNCTION_CODE (fndecl))
3130 case BUILT_IN_ALLOCA:
3131 case BUILT_IN_ALLOCA_WITH_ALIGN:
3132 /* If the call has been built for a variable-sized object, then we
3133 want to restore the stack level when the enclosing BIND_EXPR is
3134 exited to reclaim the allocated space; otherwise, we precisely
3135 need to do the opposite and preserve the latest stack level. */
3136 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3137 gimplify_ctxp->save_stack = true;
3138 else
3139 gimplify_ctxp->keep_stack = true;
3140 break;
3142 case BUILT_IN_VA_START:
3144 builtin_va_start_p = TRUE;
3145 if (call_expr_nargs (*expr_p) < 2)
3147 error ("too few arguments to function %<va_start%>");
3148 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3149 return GS_OK;
3152 if (fold_builtin_next_arg (*expr_p, true))
3154 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3155 return GS_OK;
3157 break;
3160 default:
3163 if (fndecl && DECL_BUILT_IN (fndecl))
3165 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3166 if (new_tree && new_tree != *expr_p)
3168 /* There was a transformation of this call which computes the
3169 same value, but in a more efficient way. Return and try
3170 again. */
3171 *expr_p = new_tree;
3172 return GS_OK;
3176 /* Remember the original function pointer type. */
3177 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3179 /* There is a sequence point before the call, so any side effects in
3180 the calling expression must occur before the actual call. Force
3181 gimplify_expr to use an internal post queue. */
3182 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3183 is_gimple_call_addr, fb_rvalue);
3185 nargs = call_expr_nargs (*expr_p);
3187 /* Get argument types for verification. */
3188 fndecl = get_callee_fndecl (*expr_p);
3189 parms = NULL_TREE;
3190 if (fndecl)
3191 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3192 else
3193 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3195 if (fndecl && DECL_ARGUMENTS (fndecl))
3196 p = DECL_ARGUMENTS (fndecl);
3197 else if (parms)
3198 p = parms;
3199 else
3200 p = NULL_TREE;
3201 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3204 /* If the last argument is __builtin_va_arg_pack () and it is not
3205 passed as a named argument, decrease the number of CALL_EXPR
3206 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3207 if (!p
3208 && i < nargs
3209 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3211 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3212 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3214 if (last_arg_fndecl
3215 && TREE_CODE (last_arg_fndecl) == FUNCTION_DECL
3216 && DECL_BUILT_IN_CLASS (last_arg_fndecl) == BUILT_IN_NORMAL
3217 && DECL_FUNCTION_CODE (last_arg_fndecl) == BUILT_IN_VA_ARG_PACK)
3219 tree call = *expr_p;
3221 --nargs;
3222 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
3223 CALL_EXPR_FN (call),
3224 nargs, CALL_EXPR_ARGP (call));
3226 /* Copy all CALL_EXPR flags, location and block, except
3227 CALL_EXPR_VA_ARG_PACK flag. */
3228 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
3229 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
3230 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
3231 = CALL_EXPR_RETURN_SLOT_OPT (call);
3232 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
3233 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
3235 /* Set CALL_EXPR_VA_ARG_PACK. */
3236 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
3240 /* If the call returns twice then after building the CFG the call
3241 argument computations will no longer dominate the call because
3242 we add an abnormal incoming edge to the call. So do not use SSA
3243 vars there. */
3244 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
3246 /* Gimplify the function arguments. */
3247 if (nargs > 0)
3249 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
3250 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
3251 PUSH_ARGS_REVERSED ? i-- : i++)
3253 enum gimplify_status t;
3255 /* Avoid gimplifying the second argument to va_start, which needs to
3256 be the plain PARM_DECL. */
3257 if ((i != 1) || !builtin_va_start_p)
3259 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3260 EXPR_LOCATION (*expr_p), ! returns_twice);
3262 if (t == GS_ERROR)
3263 ret = GS_ERROR;
3268 /* Gimplify the static chain. */
3269 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
3271 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
3272 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
3273 else
3275 enum gimplify_status t;
3276 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
3277 EXPR_LOCATION (*expr_p), ! returns_twice);
3278 if (t == GS_ERROR)
3279 ret = GS_ERROR;
3283 /* Verify the function result. */
3284 if (want_value && fndecl
3285 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
3287 error_at (loc, "using result of function returning %<void%>");
3288 ret = GS_ERROR;
3291 /* Try this again in case gimplification exposed something. */
3292 if (ret != GS_ERROR)
3294 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3296 if (new_tree && new_tree != *expr_p)
3298 /* There was a transformation of this call which computes the
3299 same value, but in a more efficient way. Return and try
3300 again. */
3301 *expr_p = new_tree;
3302 return GS_OK;
3305 else
3307 *expr_p = error_mark_node;
3308 return GS_ERROR;
3311 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
3312 decl. This allows us to eliminate redundant or useless
3313 calls to "const" functions. */
3314 if (TREE_CODE (*expr_p) == CALL_EXPR)
3316 int flags = call_expr_flags (*expr_p);
3317 if (flags & (ECF_CONST | ECF_PURE)
3318 /* An infinite loop is considered a side effect. */
3319 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
3320 TREE_SIDE_EFFECTS (*expr_p) = 0;
3323 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
3324 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
3325 form and delegate the creation of a GIMPLE_CALL to
3326 gimplify_modify_expr. This is always possible because when
3327 WANT_VALUE is true, the caller wants the result of this call into
3328 a temporary, which means that we will emit an INIT_EXPR in
3329 internal_get_tmp_var which will then be handled by
3330 gimplify_modify_expr. */
3331 if (!want_value)
3333 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
3334 have to do is replicate it as a GIMPLE_CALL tuple. */
3335 gimple_stmt_iterator gsi;
3336 call = gimple_build_call_from_tree (*expr_p);
3337 gimple_call_set_fntype (call, TREE_TYPE (fnptrtype));
3338 notice_special_calls (call);
3339 gimplify_seq_add_stmt (pre_p, call);
3340 gsi = gsi_last (*pre_p);
3341 maybe_fold_stmt (&gsi);
3342 *expr_p = NULL_TREE;
3344 else
3345 /* Remember the original function type. */
3346 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
3347 CALL_EXPR_FN (*expr_p));
3349 return ret;
3352 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
3353 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
3355 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
3356 condition is true or false, respectively. If null, we should generate
3357 our own to skip over the evaluation of this specific expression.
3359 LOCUS is the source location of the COND_EXPR.
3361 This function is the tree equivalent of do_jump.
3363 shortcut_cond_r should only be called by shortcut_cond_expr. */
3365 static tree
3366 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
3367 location_t locus)
3369 tree local_label = NULL_TREE;
3370 tree t, expr = NULL;
3372 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
3373 retain the shortcut semantics. Just insert the gotos here;
3374 shortcut_cond_expr will append the real blocks later. */
3375 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3377 location_t new_locus;
3379 /* Turn if (a && b) into
3381 if (a); else goto no;
3382 if (b) goto yes; else goto no;
3383 (no:) */
3385 if (false_label_p == NULL)
3386 false_label_p = &local_label;
3388 /* Keep the original source location on the first 'if'. */
3389 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
3390 append_to_statement_list (t, &expr);
3392 /* Set the source location of the && on the second 'if'. */
3393 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
3394 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3395 new_locus);
3396 append_to_statement_list (t, &expr);
3398 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3400 location_t new_locus;
3402 /* Turn if (a || b) into
3404 if (a) goto yes;
3405 if (b) goto yes; else goto no;
3406 (yes:) */
3408 if (true_label_p == NULL)
3409 true_label_p = &local_label;
3411 /* Keep the original source location on the first 'if'. */
3412 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
3413 append_to_statement_list (t, &expr);
3415 /* Set the source location of the || on the second 'if'. */
3416 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
3417 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3418 new_locus);
3419 append_to_statement_list (t, &expr);
3421 else if (TREE_CODE (pred) == COND_EXPR
3422 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
3423 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
3425 location_t new_locus;
3427 /* As long as we're messing with gotos, turn if (a ? b : c) into
3428 if (a)
3429 if (b) goto yes; else goto no;
3430 else
3431 if (c) goto yes; else goto no;
3433 Don't do this if one of the arms has void type, which can happen
3434 in C++ when the arm is throw. */
3436 /* Keep the original source location on the first 'if'. Set the source
3437 location of the ? on the second 'if'. */
3438 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
3439 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
3440 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
3441 false_label_p, locus),
3442 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
3443 false_label_p, new_locus));
3445 else
3447 expr = build3 (COND_EXPR, void_type_node, pred,
3448 build_and_jump (true_label_p),
3449 build_and_jump (false_label_p));
3450 SET_EXPR_LOCATION (expr, locus);
3453 if (local_label)
3455 t = build1 (LABEL_EXPR, void_type_node, local_label);
3456 append_to_statement_list (t, &expr);
3459 return expr;
3462 /* Given a conditional expression EXPR with short-circuit boolean
3463 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
3464 predicate apart into the equivalent sequence of conditionals. */
3466 static tree
3467 shortcut_cond_expr (tree expr)
3469 tree pred = TREE_OPERAND (expr, 0);
3470 tree then_ = TREE_OPERAND (expr, 1);
3471 tree else_ = TREE_OPERAND (expr, 2);
3472 tree true_label, false_label, end_label, t;
3473 tree *true_label_p;
3474 tree *false_label_p;
3475 bool emit_end, emit_false, jump_over_else;
3476 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
3477 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
3479 /* First do simple transformations. */
3480 if (!else_se)
3482 /* If there is no 'else', turn
3483 if (a && b) then c
3484 into
3485 if (a) if (b) then c. */
3486 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3488 /* Keep the original source location on the first 'if'. */
3489 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3490 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3491 /* Set the source location of the && on the second 'if'. */
3492 if (EXPR_HAS_LOCATION (pred))
3493 SET_EXPR_LOCATION (expr, EXPR_LOCATION (pred));
3494 then_ = shortcut_cond_expr (expr);
3495 then_se = then_ && TREE_SIDE_EFFECTS (then_);
3496 pred = TREE_OPERAND (pred, 0);
3497 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
3498 SET_EXPR_LOCATION (expr, locus);
3502 if (!then_se)
3504 /* If there is no 'then', turn
3505 if (a || b); else d
3506 into
3507 if (a); else if (b); else d. */
3508 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3510 /* Keep the original source location on the first 'if'. */
3511 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3512 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3513 /* Set the source location of the || on the second 'if'. */
3514 if (EXPR_HAS_LOCATION (pred))
3515 SET_EXPR_LOCATION (expr, EXPR_LOCATION (pred));
3516 else_ = shortcut_cond_expr (expr);
3517 else_se = else_ && TREE_SIDE_EFFECTS (else_);
3518 pred = TREE_OPERAND (pred, 0);
3519 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
3520 SET_EXPR_LOCATION (expr, locus);
3524 /* If we're done, great. */
3525 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
3526 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
3527 return expr;
3529 /* Otherwise we need to mess with gotos. Change
3530 if (a) c; else d;
3532 if (a); else goto no;
3533 c; goto end;
3534 no: d; end:
3535 and recursively gimplify the condition. */
3537 true_label = false_label = end_label = NULL_TREE;
3539 /* If our arms just jump somewhere, hijack those labels so we don't
3540 generate jumps to jumps. */
3542 if (then_
3543 && TREE_CODE (then_) == GOTO_EXPR
3544 && TREE_CODE (GOTO_DESTINATION (then_)) == LABEL_DECL)
3546 true_label = GOTO_DESTINATION (then_);
3547 then_ = NULL;
3548 then_se = false;
3551 if (else_
3552 && TREE_CODE (else_) == GOTO_EXPR
3553 && TREE_CODE (GOTO_DESTINATION (else_)) == LABEL_DECL)
3555 false_label = GOTO_DESTINATION (else_);
3556 else_ = NULL;
3557 else_se = false;
3560 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
3561 if (true_label)
3562 true_label_p = &true_label;
3563 else
3564 true_label_p = NULL;
3566 /* The 'else' branch also needs a label if it contains interesting code. */
3567 if (false_label || else_se)
3568 false_label_p = &false_label;
3569 else
3570 false_label_p = NULL;
3572 /* If there was nothing else in our arms, just forward the label(s). */
3573 if (!then_se && !else_se)
3574 return shortcut_cond_r (pred, true_label_p, false_label_p,
3575 EXPR_LOC_OR_LOC (expr, input_location));
3577 /* If our last subexpression already has a terminal label, reuse it. */
3578 if (else_se)
3579 t = expr_last (else_);
3580 else if (then_se)
3581 t = expr_last (then_);
3582 else
3583 t = NULL;
3584 if (t && TREE_CODE (t) == LABEL_EXPR)
3585 end_label = LABEL_EXPR_LABEL (t);
3587 /* If we don't care about jumping to the 'else' branch, jump to the end
3588 if the condition is false. */
3589 if (!false_label_p)
3590 false_label_p = &end_label;
3592 /* We only want to emit these labels if we aren't hijacking them. */
3593 emit_end = (end_label == NULL_TREE);
3594 emit_false = (false_label == NULL_TREE);
3596 /* We only emit the jump over the else clause if we have to--if the
3597 then clause may fall through. Otherwise we can wind up with a
3598 useless jump and a useless label at the end of gimplified code,
3599 which will cause us to think that this conditional as a whole
3600 falls through even if it doesn't. If we then inline a function
3601 which ends with such a condition, that can cause us to issue an
3602 inappropriate warning about control reaching the end of a
3603 non-void function. */
3604 jump_over_else = block_may_fallthru (then_);
3606 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
3607 EXPR_LOC_OR_LOC (expr, input_location));
3609 expr = NULL;
3610 append_to_statement_list (pred, &expr);
3612 append_to_statement_list (then_, &expr);
3613 if (else_se)
3615 if (jump_over_else)
3617 tree last = expr_last (expr);
3618 t = build_and_jump (&end_label);
3619 if (EXPR_HAS_LOCATION (last))
3620 SET_EXPR_LOCATION (t, EXPR_LOCATION (last));
3621 append_to_statement_list (t, &expr);
3623 if (emit_false)
3625 t = build1 (LABEL_EXPR, void_type_node, false_label);
3626 append_to_statement_list (t, &expr);
3628 append_to_statement_list (else_, &expr);
3630 if (emit_end && end_label)
3632 t = build1 (LABEL_EXPR, void_type_node, end_label);
3633 append_to_statement_list (t, &expr);
3636 return expr;
3639 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
3641 tree
3642 gimple_boolify (tree expr)
3644 tree type = TREE_TYPE (expr);
3645 location_t loc = EXPR_LOCATION (expr);
3647 if (TREE_CODE (expr) == NE_EXPR
3648 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
3649 && integer_zerop (TREE_OPERAND (expr, 1)))
3651 tree call = TREE_OPERAND (expr, 0);
3652 tree fn = get_callee_fndecl (call);
3654 /* For __builtin_expect ((long) (x), y) recurse into x as well
3655 if x is truth_value_p. */
3656 if (fn
3657 && DECL_BUILT_IN_CLASS (fn) == BUILT_IN_NORMAL
3658 && DECL_FUNCTION_CODE (fn) == BUILT_IN_EXPECT
3659 && call_expr_nargs (call) == 2)
3661 tree arg = CALL_EXPR_ARG (call, 0);
3662 if (arg)
3664 if (TREE_CODE (arg) == NOP_EXPR
3665 && TREE_TYPE (arg) == TREE_TYPE (call))
3666 arg = TREE_OPERAND (arg, 0);
3667 if (truth_value_p (TREE_CODE (arg)))
3669 arg = gimple_boolify (arg);
3670 CALL_EXPR_ARG (call, 0)
3671 = fold_convert_loc (loc, TREE_TYPE (call), arg);
3677 switch (TREE_CODE (expr))
3679 case TRUTH_AND_EXPR:
3680 case TRUTH_OR_EXPR:
3681 case TRUTH_XOR_EXPR:
3682 case TRUTH_ANDIF_EXPR:
3683 case TRUTH_ORIF_EXPR:
3684 /* Also boolify the arguments of truth exprs. */
3685 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
3686 /* FALLTHRU */
3688 case TRUTH_NOT_EXPR:
3689 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3691 /* These expressions always produce boolean results. */
3692 if (TREE_CODE (type) != BOOLEAN_TYPE)
3693 TREE_TYPE (expr) = boolean_type_node;
3694 return expr;
3696 case ANNOTATE_EXPR:
3697 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
3699 case annot_expr_ivdep_kind:
3700 case annot_expr_no_vector_kind:
3701 case annot_expr_vector_kind:
3702 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3703 if (TREE_CODE (type) != BOOLEAN_TYPE)
3704 TREE_TYPE (expr) = boolean_type_node;
3705 return expr;
3706 default:
3707 gcc_unreachable ();
3710 default:
3711 if (COMPARISON_CLASS_P (expr))
3713 /* There expressions always prduce boolean results. */
3714 if (TREE_CODE (type) != BOOLEAN_TYPE)
3715 TREE_TYPE (expr) = boolean_type_node;
3716 return expr;
3718 /* Other expressions that get here must have boolean values, but
3719 might need to be converted to the appropriate mode. */
3720 if (TREE_CODE (type) == BOOLEAN_TYPE)
3721 return expr;
3722 return fold_convert_loc (loc, boolean_type_node, expr);
3726 /* Given a conditional expression *EXPR_P without side effects, gimplify
3727 its operands. New statements are inserted to PRE_P. */
3729 static enum gimplify_status
3730 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
3732 tree expr = *expr_p, cond;
3733 enum gimplify_status ret, tret;
3734 enum tree_code code;
3736 cond = gimple_boolify (COND_EXPR_COND (expr));
3738 /* We need to handle && and || specially, as their gimplification
3739 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
3740 code = TREE_CODE (cond);
3741 if (code == TRUTH_ANDIF_EXPR)
3742 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
3743 else if (code == TRUTH_ORIF_EXPR)
3744 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
3745 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_condexpr, fb_rvalue);
3746 COND_EXPR_COND (*expr_p) = cond;
3748 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
3749 is_gimple_val, fb_rvalue);
3750 ret = MIN (ret, tret);
3751 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
3752 is_gimple_val, fb_rvalue);
3754 return MIN (ret, tret);
3757 /* Return true if evaluating EXPR could trap.
3758 EXPR is GENERIC, while tree_could_trap_p can be called
3759 only on GIMPLE. */
3761 static bool
3762 generic_expr_could_trap_p (tree expr)
3764 unsigned i, n;
3766 if (!expr || is_gimple_val (expr))
3767 return false;
3769 if (!EXPR_P (expr) || tree_could_trap_p (expr))
3770 return true;
3772 n = TREE_OPERAND_LENGTH (expr);
3773 for (i = 0; i < n; i++)
3774 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
3775 return true;
3777 return false;
3780 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
3781 into
3783 if (p) if (p)
3784 t1 = a; a;
3785 else or else
3786 t1 = b; b;
3789 The second form is used when *EXPR_P is of type void.
3791 PRE_P points to the list where side effects that must happen before
3792 *EXPR_P should be stored. */
3794 static enum gimplify_status
3795 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
3797 tree expr = *expr_p;
3798 tree type = TREE_TYPE (expr);
3799 location_t loc = EXPR_LOCATION (expr);
3800 tree tmp, arm1, arm2;
3801 enum gimplify_status ret;
3802 tree label_true, label_false, label_cont;
3803 bool have_then_clause_p, have_else_clause_p;
3804 gcond *cond_stmt;
3805 enum tree_code pred_code;
3806 gimple_seq seq = NULL;
3808 /* If this COND_EXPR has a value, copy the values into a temporary within
3809 the arms. */
3810 if (!VOID_TYPE_P (type))
3812 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
3813 tree result;
3815 /* If either an rvalue is ok or we do not require an lvalue, create the
3816 temporary. But we cannot do that if the type is addressable. */
3817 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
3818 && !TREE_ADDRESSABLE (type))
3820 if (gimplify_ctxp->allow_rhs_cond_expr
3821 /* If either branch has side effects or could trap, it can't be
3822 evaluated unconditionally. */
3823 && !TREE_SIDE_EFFECTS (then_)
3824 && !generic_expr_could_trap_p (then_)
3825 && !TREE_SIDE_EFFECTS (else_)
3826 && !generic_expr_could_trap_p (else_))
3827 return gimplify_pure_cond_expr (expr_p, pre_p);
3829 tmp = create_tmp_var (type, "iftmp");
3830 result = tmp;
3833 /* Otherwise, only create and copy references to the values. */
3834 else
3836 type = build_pointer_type (type);
3838 if (!VOID_TYPE_P (TREE_TYPE (then_)))
3839 then_ = build_fold_addr_expr_loc (loc, then_);
3841 if (!VOID_TYPE_P (TREE_TYPE (else_)))
3842 else_ = build_fold_addr_expr_loc (loc, else_);
3844 expr
3845 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
3847 tmp = create_tmp_var (type, "iftmp");
3848 result = build_simple_mem_ref_loc (loc, tmp);
3851 /* Build the new then clause, `tmp = then_;'. But don't build the
3852 assignment if the value is void; in C++ it can be if it's a throw. */
3853 if (!VOID_TYPE_P (TREE_TYPE (then_)))
3854 TREE_OPERAND (expr, 1) = build2 (MODIFY_EXPR, type, tmp, then_);
3856 /* Similarly, build the new else clause, `tmp = else_;'. */
3857 if (!VOID_TYPE_P (TREE_TYPE (else_)))
3858 TREE_OPERAND (expr, 2) = build2 (MODIFY_EXPR, type, tmp, else_);
3860 TREE_TYPE (expr) = void_type_node;
3861 recalculate_side_effects (expr);
3863 /* Move the COND_EXPR to the prequeue. */
3864 gimplify_stmt (&expr, pre_p);
3866 *expr_p = result;
3867 return GS_ALL_DONE;
3870 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
3871 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
3872 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
3873 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
3875 /* Make sure the condition has BOOLEAN_TYPE. */
3876 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3878 /* Break apart && and || conditions. */
3879 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
3880 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
3882 expr = shortcut_cond_expr (expr);
3884 if (expr != *expr_p)
3886 *expr_p = expr;
3888 /* We can't rely on gimplify_expr to re-gimplify the expanded
3889 form properly, as cleanups might cause the target labels to be
3890 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
3891 set up a conditional context. */
3892 gimple_push_condition ();
3893 gimplify_stmt (expr_p, &seq);
3894 gimple_pop_condition (pre_p);
3895 gimple_seq_add_seq (pre_p, seq);
3897 return GS_ALL_DONE;
3901 /* Now do the normal gimplification. */
3903 /* Gimplify condition. */
3904 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL, is_gimple_condexpr,
3905 fb_rvalue);
3906 if (ret == GS_ERROR)
3907 return GS_ERROR;
3908 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
3910 gimple_push_condition ();
3912 have_then_clause_p = have_else_clause_p = false;
3913 if (TREE_OPERAND (expr, 1) != NULL
3914 && TREE_CODE (TREE_OPERAND (expr, 1)) == GOTO_EXPR
3915 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr, 1))) == LABEL_DECL
3916 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr, 1)))
3917 == current_function_decl)
3918 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3919 have different locations, otherwise we end up with incorrect
3920 location information on the branches. */
3921 && (optimize
3922 || !EXPR_HAS_LOCATION (expr)
3923 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr, 1))
3924 || EXPR_LOCATION (expr) == EXPR_LOCATION (TREE_OPERAND (expr, 1))))
3926 label_true = GOTO_DESTINATION (TREE_OPERAND (expr, 1));
3927 have_then_clause_p = true;
3929 else
3930 label_true = create_artificial_label (UNKNOWN_LOCATION);
3931 if (TREE_OPERAND (expr, 2) != NULL
3932 && TREE_CODE (TREE_OPERAND (expr, 2)) == GOTO_EXPR
3933 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr, 2))) == LABEL_DECL
3934 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr, 2)))
3935 == current_function_decl)
3936 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3937 have different locations, otherwise we end up with incorrect
3938 location information on the branches. */
3939 && (optimize
3940 || !EXPR_HAS_LOCATION (expr)
3941 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr, 2))
3942 || EXPR_LOCATION (expr) == EXPR_LOCATION (TREE_OPERAND (expr, 2))))
3944 label_false = GOTO_DESTINATION (TREE_OPERAND (expr, 2));
3945 have_else_clause_p = true;
3947 else
3948 label_false = create_artificial_label (UNKNOWN_LOCATION);
3950 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
3951 &arm2);
3952 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
3953 label_false);
3954 gimple_set_no_warning (cond_stmt, TREE_NO_WARNING (COND_EXPR_COND (expr)));
3955 gimplify_seq_add_stmt (&seq, cond_stmt);
3956 gimple_stmt_iterator gsi = gsi_last (seq);
3957 maybe_fold_stmt (&gsi);
3959 label_cont = NULL_TREE;
3960 if (!have_then_clause_p)
3962 /* For if (...) {} else { code; } put label_true after
3963 the else block. */
3964 if (TREE_OPERAND (expr, 1) == NULL_TREE
3965 && !have_else_clause_p
3966 && TREE_OPERAND (expr, 2) != NULL_TREE)
3967 label_cont = label_true;
3968 else
3970 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
3971 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
3972 /* For if (...) { code; } else {} or
3973 if (...) { code; } else goto label; or
3974 if (...) { code; return; } else { ... }
3975 label_cont isn't needed. */
3976 if (!have_else_clause_p
3977 && TREE_OPERAND (expr, 2) != NULL_TREE
3978 && gimple_seq_may_fallthru (seq))
3980 gimple *g;
3981 label_cont = create_artificial_label (UNKNOWN_LOCATION);
3983 g = gimple_build_goto (label_cont);
3985 /* GIMPLE_COND's are very low level; they have embedded
3986 gotos. This particular embedded goto should not be marked
3987 with the location of the original COND_EXPR, as it would
3988 correspond to the COND_EXPR's condition, not the ELSE or the
3989 THEN arms. To avoid marking it with the wrong location, flag
3990 it as "no location". */
3991 gimple_set_do_not_emit_location (g);
3993 gimplify_seq_add_stmt (&seq, g);
3997 if (!have_else_clause_p)
3999 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
4000 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
4002 if (label_cont)
4003 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
4005 gimple_pop_condition (pre_p);
4006 gimple_seq_add_seq (pre_p, seq);
4008 if (ret == GS_ERROR)
4009 ; /* Do nothing. */
4010 else if (have_then_clause_p || have_else_clause_p)
4011 ret = GS_ALL_DONE;
4012 else
4014 /* Both arms are empty; replace the COND_EXPR with its predicate. */
4015 expr = TREE_OPERAND (expr, 0);
4016 gimplify_stmt (&expr, pre_p);
4019 *expr_p = NULL;
4020 return ret;
4023 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4024 to be marked addressable.
4026 We cannot rely on such an expression being directly markable if a temporary
4027 has been created by the gimplification. In this case, we create another
4028 temporary and initialize it with a copy, which will become a store after we
4029 mark it addressable. This can happen if the front-end passed us something
4030 that it could not mark addressable yet, like a Fortran pass-by-reference
4031 parameter (int) floatvar. */
4033 static void
4034 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4036 while (handled_component_p (*expr_p))
4037 expr_p = &TREE_OPERAND (*expr_p, 0);
4038 if (is_gimple_reg (*expr_p))
4040 /* Do not allow an SSA name as the temporary. */
4041 tree var = get_initialized_tmp_var (*expr_p, seq_p, NULL, false);
4042 DECL_GIMPLE_REG_P (var) = 0;
4043 *expr_p = var;
4047 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4048 a call to __builtin_memcpy. */
4050 static enum gimplify_status
4051 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4052 gimple_seq *seq_p)
4054 tree t, to, to_ptr, from, from_ptr;
4055 gcall *gs;
4056 location_t loc = EXPR_LOCATION (*expr_p);
4058 to = TREE_OPERAND (*expr_p, 0);
4059 from = TREE_OPERAND (*expr_p, 1);
4061 /* Mark the RHS addressable. Beware that it may not be possible to do so
4062 directly if a temporary has been created by the gimplification. */
4063 prepare_gimple_addressable (&from, seq_p);
4065 mark_addressable (from);
4066 from_ptr = build_fold_addr_expr_loc (loc, from);
4067 gimplify_arg (&from_ptr, seq_p, loc);
4069 mark_addressable (to);
4070 to_ptr = build_fold_addr_expr_loc (loc, to);
4071 gimplify_arg (&to_ptr, seq_p, loc);
4073 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4075 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4077 if (want_value)
4079 /* tmp = memcpy() */
4080 t = create_tmp_var (TREE_TYPE (to_ptr));
4081 gimple_call_set_lhs (gs, t);
4082 gimplify_seq_add_stmt (seq_p, gs);
4084 *expr_p = build_simple_mem_ref (t);
4085 return GS_ALL_DONE;
4088 gimplify_seq_add_stmt (seq_p, gs);
4089 *expr_p = NULL;
4090 return GS_ALL_DONE;
4093 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4094 a call to __builtin_memset. In this case we know that the RHS is
4095 a CONSTRUCTOR with an empty element list. */
4097 static enum gimplify_status
4098 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4099 gimple_seq *seq_p)
4101 tree t, from, to, to_ptr;
4102 gcall *gs;
4103 location_t loc = EXPR_LOCATION (*expr_p);
4105 /* Assert our assumptions, to abort instead of producing wrong code
4106 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4107 not be immediately exposed. */
4108 from = TREE_OPERAND (*expr_p, 1);
4109 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4110 from = TREE_OPERAND (from, 0);
4112 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4113 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4115 /* Now proceed. */
4116 to = TREE_OPERAND (*expr_p, 0);
4118 to_ptr = build_fold_addr_expr_loc (loc, to);
4119 gimplify_arg (&to_ptr, seq_p, loc);
4120 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4122 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4124 if (want_value)
4126 /* tmp = memset() */
4127 t = create_tmp_var (TREE_TYPE (to_ptr));
4128 gimple_call_set_lhs (gs, t);
4129 gimplify_seq_add_stmt (seq_p, gs);
4131 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4132 return GS_ALL_DONE;
4135 gimplify_seq_add_stmt (seq_p, gs);
4136 *expr_p = NULL;
4137 return GS_ALL_DONE;
4140 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4141 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4142 assignment. Return non-null if we detect a potential overlap. */
4144 struct gimplify_init_ctor_preeval_data
4146 /* The base decl of the lhs object. May be NULL, in which case we
4147 have to assume the lhs is indirect. */
4148 tree lhs_base_decl;
4150 /* The alias set of the lhs object. */
4151 alias_set_type lhs_alias_set;
4154 static tree
4155 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4157 struct gimplify_init_ctor_preeval_data *data
4158 = (struct gimplify_init_ctor_preeval_data *) xdata;
4159 tree t = *tp;
4161 /* If we find the base object, obviously we have overlap. */
4162 if (data->lhs_base_decl == t)
4163 return t;
4165 /* If the constructor component is indirect, determine if we have a
4166 potential overlap with the lhs. The only bits of information we
4167 have to go on at this point are addressability and alias sets. */
4168 if ((INDIRECT_REF_P (t)
4169 || TREE_CODE (t) == MEM_REF)
4170 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4171 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
4172 return t;
4174 /* If the constructor component is a call, determine if it can hide a
4175 potential overlap with the lhs through an INDIRECT_REF like above.
4176 ??? Ugh - this is completely broken. In fact this whole analysis
4177 doesn't look conservative. */
4178 if (TREE_CODE (t) == CALL_EXPR)
4180 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
4182 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
4183 if (POINTER_TYPE_P (TREE_VALUE (type))
4184 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4185 && alias_sets_conflict_p (data->lhs_alias_set,
4186 get_alias_set
4187 (TREE_TYPE (TREE_VALUE (type)))))
4188 return t;
4191 if (IS_TYPE_OR_DECL_P (t))
4192 *walk_subtrees = 0;
4193 return NULL;
4196 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
4197 force values that overlap with the lhs (as described by *DATA)
4198 into temporaries. */
4200 static void
4201 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4202 struct gimplify_init_ctor_preeval_data *data)
4204 enum gimplify_status one;
4206 /* If the value is constant, then there's nothing to pre-evaluate. */
4207 if (TREE_CONSTANT (*expr_p))
4209 /* Ensure it does not have side effects, it might contain a reference to
4210 the object we're initializing. */
4211 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
4212 return;
4215 /* If the type has non-trivial constructors, we can't pre-evaluate. */
4216 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
4217 return;
4219 /* Recurse for nested constructors. */
4220 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
4222 unsigned HOST_WIDE_INT ix;
4223 constructor_elt *ce;
4224 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
4226 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
4227 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
4229 return;
4232 /* If this is a variable sized type, we must remember the size. */
4233 maybe_with_size_expr (expr_p);
4235 /* Gimplify the constructor element to something appropriate for the rhs
4236 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
4237 the gimplifier will consider this a store to memory. Doing this
4238 gimplification now means that we won't have to deal with complicated
4239 language-specific trees, nor trees like SAVE_EXPR that can induce
4240 exponential search behavior. */
4241 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
4242 if (one == GS_ERROR)
4244 *expr_p = NULL;
4245 return;
4248 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
4249 with the lhs, since "a = { .x=a }" doesn't make sense. This will
4250 always be true for all scalars, since is_gimple_mem_rhs insists on a
4251 temporary variable for them. */
4252 if (DECL_P (*expr_p))
4253 return;
4255 /* If this is of variable size, we have no choice but to assume it doesn't
4256 overlap since we can't make a temporary for it. */
4257 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
4258 return;
4260 /* Otherwise, we must search for overlap ... */
4261 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
4262 return;
4264 /* ... and if found, force the value into a temporary. */
4265 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
4268 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
4269 a RANGE_EXPR in a CONSTRUCTOR for an array.
4271 var = lower;
4272 loop_entry:
4273 object[var] = value;
4274 if (var == upper)
4275 goto loop_exit;
4276 var = var + 1;
4277 goto loop_entry;
4278 loop_exit:
4280 We increment var _after_ the loop exit check because we might otherwise
4281 fail if upper == TYPE_MAX_VALUE (type for upper).
4283 Note that we never have to deal with SAVE_EXPRs here, because this has
4284 already been taken care of for us, in gimplify_init_ctor_preeval(). */
4286 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
4287 gimple_seq *, bool);
4289 static void
4290 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
4291 tree value, tree array_elt_type,
4292 gimple_seq *pre_p, bool cleared)
4294 tree loop_entry_label, loop_exit_label, fall_thru_label;
4295 tree var, var_type, cref, tmp;
4297 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
4298 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
4299 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
4301 /* Create and initialize the index variable. */
4302 var_type = TREE_TYPE (upper);
4303 var = create_tmp_var (var_type);
4304 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
4306 /* Add the loop entry label. */
4307 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
4309 /* Build the reference. */
4310 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4311 var, NULL_TREE, NULL_TREE);
4313 /* If we are a constructor, just call gimplify_init_ctor_eval to do
4314 the store. Otherwise just assign value to the reference. */
4316 if (TREE_CODE (value) == CONSTRUCTOR)
4317 /* NB we might have to call ourself recursively through
4318 gimplify_init_ctor_eval if the value is a constructor. */
4319 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4320 pre_p, cleared);
4321 else
4322 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
4324 /* We exit the loop when the index var is equal to the upper bound. */
4325 gimplify_seq_add_stmt (pre_p,
4326 gimple_build_cond (EQ_EXPR, var, upper,
4327 loop_exit_label, fall_thru_label));
4329 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
4331 /* Otherwise, increment the index var... */
4332 tmp = build2 (PLUS_EXPR, var_type, var,
4333 fold_convert (var_type, integer_one_node));
4334 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
4336 /* ...and jump back to the loop entry. */
4337 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
4339 /* Add the loop exit label. */
4340 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
4343 /* Return true if FDECL is accessing a field that is zero sized. */
4345 static bool
4346 zero_sized_field_decl (const_tree fdecl)
4348 if (TREE_CODE (fdecl) == FIELD_DECL && DECL_SIZE (fdecl)
4349 && integer_zerop (DECL_SIZE (fdecl)))
4350 return true;
4351 return false;
4354 /* Return true if TYPE is zero sized. */
4356 static bool
4357 zero_sized_type (const_tree type)
4359 if (AGGREGATE_TYPE_P (type) && TYPE_SIZE (type)
4360 && integer_zerop (TYPE_SIZE (type)))
4361 return true;
4362 return false;
4365 /* A subroutine of gimplify_init_constructor. Generate individual
4366 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
4367 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
4368 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
4369 zeroed first. */
4371 static void
4372 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
4373 gimple_seq *pre_p, bool cleared)
4375 tree array_elt_type = NULL;
4376 unsigned HOST_WIDE_INT ix;
4377 tree purpose, value;
4379 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
4380 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
4382 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
4384 tree cref;
4386 /* NULL values are created above for gimplification errors. */
4387 if (value == NULL)
4388 continue;
4390 if (cleared && initializer_zerop (value))
4391 continue;
4393 /* ??? Here's to hoping the front end fills in all of the indices,
4394 so we don't have to figure out what's missing ourselves. */
4395 gcc_assert (purpose);
4397 /* Skip zero-sized fields, unless value has side-effects. This can
4398 happen with calls to functions returning a zero-sized type, which
4399 we shouldn't discard. As a number of downstream passes don't
4400 expect sets of zero-sized fields, we rely on the gimplification of
4401 the MODIFY_EXPR we make below to drop the assignment statement. */
4402 if (! TREE_SIDE_EFFECTS (value) && zero_sized_field_decl (purpose))
4403 continue;
4405 /* If we have a RANGE_EXPR, we have to build a loop to assign the
4406 whole range. */
4407 if (TREE_CODE (purpose) == RANGE_EXPR)
4409 tree lower = TREE_OPERAND (purpose, 0);
4410 tree upper = TREE_OPERAND (purpose, 1);
4412 /* If the lower bound is equal to upper, just treat it as if
4413 upper was the index. */
4414 if (simple_cst_equal (lower, upper))
4415 purpose = upper;
4416 else
4418 gimplify_init_ctor_eval_range (object, lower, upper, value,
4419 array_elt_type, pre_p, cleared);
4420 continue;
4424 if (array_elt_type)
4426 /* Do not use bitsizetype for ARRAY_REF indices. */
4427 if (TYPE_DOMAIN (TREE_TYPE (object)))
4428 purpose
4429 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
4430 purpose);
4431 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4432 purpose, NULL_TREE, NULL_TREE);
4434 else
4436 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
4437 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
4438 unshare_expr (object), purpose, NULL_TREE);
4441 if (TREE_CODE (value) == CONSTRUCTOR
4442 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
4443 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4444 pre_p, cleared);
4445 else
4447 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
4448 gimplify_and_add (init, pre_p);
4449 ggc_free (init);
4454 /* Return the appropriate RHS predicate for this LHS. */
4456 gimple_predicate
4457 rhs_predicate_for (tree lhs)
4459 if (is_gimple_reg (lhs))
4460 return is_gimple_reg_rhs_or_call;
4461 else
4462 return is_gimple_mem_rhs_or_call;
4465 /* Return the initial guess for an appropriate RHS predicate for this LHS,
4466 before the LHS has been gimplified. */
4468 static gimple_predicate
4469 initial_rhs_predicate_for (tree lhs)
4471 if (is_gimple_reg_type (TREE_TYPE (lhs)))
4472 return is_gimple_reg_rhs_or_call;
4473 else
4474 return is_gimple_mem_rhs_or_call;
4477 /* Gimplify a C99 compound literal expression. This just means adding
4478 the DECL_EXPR before the current statement and using its anonymous
4479 decl instead. */
4481 static enum gimplify_status
4482 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
4483 bool (*gimple_test_f) (tree),
4484 fallback_t fallback)
4486 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
4487 tree decl = DECL_EXPR_DECL (decl_s);
4488 tree init = DECL_INITIAL (decl);
4489 /* Mark the decl as addressable if the compound literal
4490 expression is addressable now, otherwise it is marked too late
4491 after we gimplify the initialization expression. */
4492 if (TREE_ADDRESSABLE (*expr_p))
4493 TREE_ADDRESSABLE (decl) = 1;
4494 /* Otherwise, if we don't need an lvalue and have a literal directly
4495 substitute it. Check if it matches the gimple predicate, as
4496 otherwise we'd generate a new temporary, and we can as well just
4497 use the decl we already have. */
4498 else if (!TREE_ADDRESSABLE (decl)
4499 && init
4500 && (fallback & fb_lvalue) == 0
4501 && gimple_test_f (init))
4503 *expr_p = init;
4504 return GS_OK;
4507 /* Preliminarily mark non-addressed complex variables as eligible
4508 for promotion to gimple registers. We'll transform their uses
4509 as we find them. */
4510 if ((TREE_CODE (TREE_TYPE (decl)) == COMPLEX_TYPE
4511 || TREE_CODE (TREE_TYPE (decl)) == VECTOR_TYPE)
4512 && !TREE_THIS_VOLATILE (decl)
4513 && !needs_to_live_in_memory (decl))
4514 DECL_GIMPLE_REG_P (decl) = 1;
4516 /* If the decl is not addressable, then it is being used in some
4517 expression or on the right hand side of a statement, and it can
4518 be put into a readonly data section. */
4519 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
4520 TREE_READONLY (decl) = 1;
4522 /* This decl isn't mentioned in the enclosing block, so add it to the
4523 list of temps. FIXME it seems a bit of a kludge to say that
4524 anonymous artificial vars aren't pushed, but everything else is. */
4525 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
4526 gimple_add_tmp_var (decl);
4528 gimplify_and_add (decl_s, pre_p);
4529 *expr_p = decl;
4530 return GS_OK;
4533 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
4534 return a new CONSTRUCTOR if something changed. */
4536 static tree
4537 optimize_compound_literals_in_ctor (tree orig_ctor)
4539 tree ctor = orig_ctor;
4540 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
4541 unsigned int idx, num = vec_safe_length (elts);
4543 for (idx = 0; idx < num; idx++)
4545 tree value = (*elts)[idx].value;
4546 tree newval = value;
4547 if (TREE_CODE (value) == CONSTRUCTOR)
4548 newval = optimize_compound_literals_in_ctor (value);
4549 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
4551 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
4552 tree decl = DECL_EXPR_DECL (decl_s);
4553 tree init = DECL_INITIAL (decl);
4555 if (!TREE_ADDRESSABLE (value)
4556 && !TREE_ADDRESSABLE (decl)
4557 && init
4558 && TREE_CODE (init) == CONSTRUCTOR)
4559 newval = optimize_compound_literals_in_ctor (init);
4561 if (newval == value)
4562 continue;
4564 if (ctor == orig_ctor)
4566 ctor = copy_node (orig_ctor);
4567 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
4568 elts = CONSTRUCTOR_ELTS (ctor);
4570 (*elts)[idx].value = newval;
4572 return ctor;
4575 /* A subroutine of gimplify_modify_expr. Break out elements of a
4576 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
4578 Note that we still need to clear any elements that don't have explicit
4579 initializers, so if not all elements are initialized we keep the
4580 original MODIFY_EXPR, we just remove all of the constructor elements.
4582 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
4583 GS_ERROR if we would have to create a temporary when gimplifying
4584 this constructor. Otherwise, return GS_OK.
4586 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
4588 static enum gimplify_status
4589 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4590 bool want_value, bool notify_temp_creation)
4592 tree object, ctor, type;
4593 enum gimplify_status ret;
4594 vec<constructor_elt, va_gc> *elts;
4596 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
4598 if (!notify_temp_creation)
4600 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
4601 is_gimple_lvalue, fb_lvalue);
4602 if (ret == GS_ERROR)
4603 return ret;
4606 object = TREE_OPERAND (*expr_p, 0);
4607 ctor = TREE_OPERAND (*expr_p, 1)
4608 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
4609 type = TREE_TYPE (ctor);
4610 elts = CONSTRUCTOR_ELTS (ctor);
4611 ret = GS_ALL_DONE;
4613 switch (TREE_CODE (type))
4615 case RECORD_TYPE:
4616 case UNION_TYPE:
4617 case QUAL_UNION_TYPE:
4618 case ARRAY_TYPE:
4620 struct gimplify_init_ctor_preeval_data preeval_data;
4621 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
4622 bool cleared, complete_p, valid_const_initializer;
4624 /* Aggregate types must lower constructors to initialization of
4625 individual elements. The exception is that a CONSTRUCTOR node
4626 with no elements indicates zero-initialization of the whole. */
4627 if (vec_safe_is_empty (elts))
4629 if (notify_temp_creation)
4630 return GS_OK;
4631 break;
4634 /* Fetch information about the constructor to direct later processing.
4635 We might want to make static versions of it in various cases, and
4636 can only do so if it known to be a valid constant initializer. */
4637 valid_const_initializer
4638 = categorize_ctor_elements (ctor, &num_nonzero_elements,
4639 &num_ctor_elements, &complete_p);
4641 /* If a const aggregate variable is being initialized, then it
4642 should never be a lose to promote the variable to be static. */
4643 if (valid_const_initializer
4644 && num_nonzero_elements > 1
4645 && TREE_READONLY (object)
4646 && VAR_P (object)
4647 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object)))
4649 if (notify_temp_creation)
4650 return GS_ERROR;
4651 DECL_INITIAL (object) = ctor;
4652 TREE_STATIC (object) = 1;
4653 if (!DECL_NAME (object))
4654 DECL_NAME (object) = create_tmp_var_name ("C");
4655 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
4657 /* ??? C++ doesn't automatically append a .<number> to the
4658 assembler name, and even when it does, it looks at FE private
4659 data structures to figure out what that number should be,
4660 which are not set for this variable. I suppose this is
4661 important for local statics for inline functions, which aren't
4662 "local" in the object file sense. So in order to get a unique
4663 TU-local symbol, we must invoke the lhd version now. */
4664 lhd_set_decl_assembler_name (object);
4666 *expr_p = NULL_TREE;
4667 break;
4670 /* If there are "lots" of initialized elements, even discounting
4671 those that are not address constants (and thus *must* be
4672 computed at runtime), then partition the constructor into
4673 constant and non-constant parts. Block copy the constant
4674 parts in, then generate code for the non-constant parts. */
4675 /* TODO. There's code in cp/typeck.c to do this. */
4677 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
4678 /* store_constructor will ignore the clearing of variable-sized
4679 objects. Initializers for such objects must explicitly set
4680 every field that needs to be set. */
4681 cleared = false;
4682 else if (!complete_p && !CONSTRUCTOR_NO_CLEARING (ctor))
4683 /* If the constructor isn't complete, clear the whole object
4684 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
4686 ??? This ought not to be needed. For any element not present
4687 in the initializer, we should simply set them to zero. Except
4688 we'd need to *find* the elements that are not present, and that
4689 requires trickery to avoid quadratic compile-time behavior in
4690 large cases or excessive memory use in small cases. */
4691 cleared = true;
4692 else if (num_ctor_elements - num_nonzero_elements
4693 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
4694 && num_nonzero_elements < num_ctor_elements / 4)
4695 /* If there are "lots" of zeros, it's more efficient to clear
4696 the memory and then set the nonzero elements. */
4697 cleared = true;
4698 else
4699 cleared = false;
4701 /* If there are "lots" of initialized elements, and all of them
4702 are valid address constants, then the entire initializer can
4703 be dropped to memory, and then memcpy'd out. Don't do this
4704 for sparse arrays, though, as it's more efficient to follow
4705 the standard CONSTRUCTOR behavior of memset followed by
4706 individual element initialization. Also don't do this for small
4707 all-zero initializers (which aren't big enough to merit
4708 clearing), and don't try to make bitwise copies of
4709 TREE_ADDRESSABLE types.
4711 We cannot apply such transformation when compiling chkp static
4712 initializer because creation of initializer image in the memory
4713 will require static initialization of bounds for it. It should
4714 result in another gimplification of similar initializer and we
4715 may fall into infinite loop. */
4716 if (valid_const_initializer
4717 && !(cleared || num_nonzero_elements == 0)
4718 && !TREE_ADDRESSABLE (type)
4719 && (!current_function_decl
4720 || !lookup_attribute ("chkp ctor",
4721 DECL_ATTRIBUTES (current_function_decl))))
4723 HOST_WIDE_INT size = int_size_in_bytes (type);
4724 unsigned int align;
4726 /* ??? We can still get unbounded array types, at least
4727 from the C++ front end. This seems wrong, but attempt
4728 to work around it for now. */
4729 if (size < 0)
4731 size = int_size_in_bytes (TREE_TYPE (object));
4732 if (size >= 0)
4733 TREE_TYPE (ctor) = type = TREE_TYPE (object);
4736 /* Find the maximum alignment we can assume for the object. */
4737 /* ??? Make use of DECL_OFFSET_ALIGN. */
4738 if (DECL_P (object))
4739 align = DECL_ALIGN (object);
4740 else
4741 align = TYPE_ALIGN (type);
4743 /* Do a block move either if the size is so small as to make
4744 each individual move a sub-unit move on average, or if it
4745 is so large as to make individual moves inefficient. */
4746 if (size > 0
4747 && num_nonzero_elements > 1
4748 && (size < num_nonzero_elements
4749 || !can_move_by_pieces (size, align)))
4751 if (notify_temp_creation)
4752 return GS_ERROR;
4754 walk_tree (&ctor, force_labels_r, NULL, NULL);
4755 ctor = tree_output_constant_def (ctor);
4756 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
4757 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
4758 TREE_OPERAND (*expr_p, 1) = ctor;
4760 /* This is no longer an assignment of a CONSTRUCTOR, but
4761 we still may have processing to do on the LHS. So
4762 pretend we didn't do anything here to let that happen. */
4763 return GS_UNHANDLED;
4767 /* If the target is volatile, we have non-zero elements and more than
4768 one field to assign, initialize the target from a temporary. */
4769 if (TREE_THIS_VOLATILE (object)
4770 && !TREE_ADDRESSABLE (type)
4771 && num_nonzero_elements > 0
4772 && vec_safe_length (elts) > 1)
4774 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
4775 TREE_OPERAND (*expr_p, 0) = temp;
4776 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
4777 *expr_p,
4778 build2 (MODIFY_EXPR, void_type_node,
4779 object, temp));
4780 return GS_OK;
4783 if (notify_temp_creation)
4784 return GS_OK;
4786 /* If there are nonzero elements and if needed, pre-evaluate to capture
4787 elements overlapping with the lhs into temporaries. We must do this
4788 before clearing to fetch the values before they are zeroed-out. */
4789 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
4791 preeval_data.lhs_base_decl = get_base_address (object);
4792 if (!DECL_P (preeval_data.lhs_base_decl))
4793 preeval_data.lhs_base_decl = NULL;
4794 preeval_data.lhs_alias_set = get_alias_set (object);
4796 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
4797 pre_p, post_p, &preeval_data);
4800 bool ctor_has_side_effects_p
4801 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
4803 if (cleared)
4805 /* Zap the CONSTRUCTOR element list, which simplifies this case.
4806 Note that we still have to gimplify, in order to handle the
4807 case of variable sized types. Avoid shared tree structures. */
4808 CONSTRUCTOR_ELTS (ctor) = NULL;
4809 TREE_SIDE_EFFECTS (ctor) = 0;
4810 object = unshare_expr (object);
4811 gimplify_stmt (expr_p, pre_p);
4814 /* If we have not block cleared the object, or if there are nonzero
4815 elements in the constructor, or if the constructor has side effects,
4816 add assignments to the individual scalar fields of the object. */
4817 if (!cleared
4818 || num_nonzero_elements > 0
4819 || ctor_has_side_effects_p)
4820 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
4822 *expr_p = NULL_TREE;
4824 break;
4826 case COMPLEX_TYPE:
4828 tree r, i;
4830 if (notify_temp_creation)
4831 return GS_OK;
4833 /* Extract the real and imaginary parts out of the ctor. */
4834 gcc_assert (elts->length () == 2);
4835 r = (*elts)[0].value;
4836 i = (*elts)[1].value;
4837 if (r == NULL || i == NULL)
4839 tree zero = build_zero_cst (TREE_TYPE (type));
4840 if (r == NULL)
4841 r = zero;
4842 if (i == NULL)
4843 i = zero;
4846 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
4847 represent creation of a complex value. */
4848 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
4850 ctor = build_complex (type, r, i);
4851 TREE_OPERAND (*expr_p, 1) = ctor;
4853 else
4855 ctor = build2 (COMPLEX_EXPR, type, r, i);
4856 TREE_OPERAND (*expr_p, 1) = ctor;
4857 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
4858 pre_p,
4859 post_p,
4860 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
4861 fb_rvalue);
4864 break;
4866 case VECTOR_TYPE:
4868 unsigned HOST_WIDE_INT ix;
4869 constructor_elt *ce;
4871 if (notify_temp_creation)
4872 return GS_OK;
4874 /* Go ahead and simplify constant constructors to VECTOR_CST. */
4875 if (TREE_CONSTANT (ctor))
4877 bool constant_p = true;
4878 tree value;
4880 /* Even when ctor is constant, it might contain non-*_CST
4881 elements, such as addresses or trapping values like
4882 1.0/0.0 - 1.0/0.0. Such expressions don't belong
4883 in VECTOR_CST nodes. */
4884 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
4885 if (!CONSTANT_CLASS_P (value))
4887 constant_p = false;
4888 break;
4891 if (constant_p)
4893 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
4894 break;
4897 TREE_CONSTANT (ctor) = 0;
4900 /* Vector types use CONSTRUCTOR all the way through gimple
4901 compilation as a general initializer. */
4902 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
4904 enum gimplify_status tret;
4905 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
4906 fb_rvalue);
4907 if (tret == GS_ERROR)
4908 ret = GS_ERROR;
4909 else if (TREE_STATIC (ctor)
4910 && !initializer_constant_valid_p (ce->value,
4911 TREE_TYPE (ce->value)))
4912 TREE_STATIC (ctor) = 0;
4914 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
4915 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
4917 break;
4919 default:
4920 /* So how did we get a CONSTRUCTOR for a scalar type? */
4921 gcc_unreachable ();
4924 if (ret == GS_ERROR)
4925 return GS_ERROR;
4926 /* If we have gimplified both sides of the initializer but have
4927 not emitted an assignment, do so now. */
4928 if (*expr_p)
4930 tree lhs = TREE_OPERAND (*expr_p, 0);
4931 tree rhs = TREE_OPERAND (*expr_p, 1);
4932 if (want_value && object == lhs)
4933 lhs = unshare_expr (lhs);
4934 gassign *init = gimple_build_assign (lhs, rhs);
4935 gimplify_seq_add_stmt (pre_p, init);
4937 if (want_value)
4939 *expr_p = object;
4940 return GS_OK;
4942 else
4944 *expr_p = NULL;
4945 return GS_ALL_DONE;
4949 /* Given a pointer value OP0, return a simplified version of an
4950 indirection through OP0, or NULL_TREE if no simplification is
4951 possible. This may only be applied to a rhs of an expression.
4952 Note that the resulting type may be different from the type pointed
4953 to in the sense that it is still compatible from the langhooks
4954 point of view. */
4956 static tree
4957 gimple_fold_indirect_ref_rhs (tree t)
4959 return gimple_fold_indirect_ref (t);
4962 /* Subroutine of gimplify_modify_expr to do simplifications of
4963 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
4964 something changes. */
4966 static enum gimplify_status
4967 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
4968 gimple_seq *pre_p, gimple_seq *post_p,
4969 bool want_value)
4971 enum gimplify_status ret = GS_UNHANDLED;
4972 bool changed;
4976 changed = false;
4977 switch (TREE_CODE (*from_p))
4979 case VAR_DECL:
4980 /* If we're assigning from a read-only variable initialized with
4981 a constructor, do the direct assignment from the constructor,
4982 but only if neither source nor target are volatile since this
4983 latter assignment might end up being done on a per-field basis. */
4984 if (DECL_INITIAL (*from_p)
4985 && TREE_READONLY (*from_p)
4986 && !TREE_THIS_VOLATILE (*from_p)
4987 && !TREE_THIS_VOLATILE (*to_p)
4988 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR)
4990 tree old_from = *from_p;
4991 enum gimplify_status subret;
4993 /* Move the constructor into the RHS. */
4994 *from_p = unshare_expr (DECL_INITIAL (*from_p));
4996 /* Let's see if gimplify_init_constructor will need to put
4997 it in memory. */
4998 subret = gimplify_init_constructor (expr_p, NULL, NULL,
4999 false, true);
5000 if (subret == GS_ERROR)
5002 /* If so, revert the change. */
5003 *from_p = old_from;
5005 else
5007 ret = GS_OK;
5008 changed = true;
5011 break;
5012 case INDIRECT_REF:
5014 /* If we have code like
5016 *(const A*)(A*)&x
5018 where the type of "x" is a (possibly cv-qualified variant
5019 of "A"), treat the entire expression as identical to "x".
5020 This kind of code arises in C++ when an object is bound
5021 to a const reference, and if "x" is a TARGET_EXPR we want
5022 to take advantage of the optimization below. */
5023 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5024 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
5025 if (t)
5027 if (TREE_THIS_VOLATILE (t) != volatile_p)
5029 if (DECL_P (t))
5030 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5031 build_fold_addr_expr (t));
5032 if (REFERENCE_CLASS_P (t))
5033 TREE_THIS_VOLATILE (t) = volatile_p;
5035 *from_p = t;
5036 ret = GS_OK;
5037 changed = true;
5039 break;
5042 case TARGET_EXPR:
5044 /* If we are initializing something from a TARGET_EXPR, strip the
5045 TARGET_EXPR and initialize it directly, if possible. This can't
5046 be done if the initializer is void, since that implies that the
5047 temporary is set in some non-trivial way.
5049 ??? What about code that pulls out the temp and uses it
5050 elsewhere? I think that such code never uses the TARGET_EXPR as
5051 an initializer. If I'm wrong, we'll die because the temp won't
5052 have any RTL. In that case, I guess we'll need to replace
5053 references somehow. */
5054 tree init = TARGET_EXPR_INITIAL (*from_p);
5056 if (init
5057 && !VOID_TYPE_P (TREE_TYPE (init)))
5059 *from_p = init;
5060 ret = GS_OK;
5061 changed = true;
5064 break;
5066 case COMPOUND_EXPR:
5067 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5068 caught. */
5069 gimplify_compound_expr (from_p, pre_p, true);
5070 ret = GS_OK;
5071 changed = true;
5072 break;
5074 case CONSTRUCTOR:
5075 /* If we already made some changes, let the front end have a
5076 crack at this before we break it down. */
5077 if (ret != GS_UNHANDLED)
5078 break;
5079 /* If we're initializing from a CONSTRUCTOR, break this into
5080 individual MODIFY_EXPRs. */
5081 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5082 false);
5084 case COND_EXPR:
5085 /* If we're assigning to a non-register type, push the assignment
5086 down into the branches. This is mandatory for ADDRESSABLE types,
5087 since we cannot generate temporaries for such, but it saves a
5088 copy in other cases as well. */
5089 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5091 /* This code should mirror the code in gimplify_cond_expr. */
5092 enum tree_code code = TREE_CODE (*expr_p);
5093 tree cond = *from_p;
5094 tree result = *to_p;
5096 ret = gimplify_expr (&result, pre_p, post_p,
5097 is_gimple_lvalue, fb_lvalue);
5098 if (ret != GS_ERROR)
5099 ret = GS_OK;
5101 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
5102 TREE_OPERAND (cond, 1)
5103 = build2 (code, void_type_node, result,
5104 TREE_OPERAND (cond, 1));
5105 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5106 TREE_OPERAND (cond, 2)
5107 = build2 (code, void_type_node, unshare_expr (result),
5108 TREE_OPERAND (cond, 2));
5110 TREE_TYPE (cond) = void_type_node;
5111 recalculate_side_effects (cond);
5113 if (want_value)
5115 gimplify_and_add (cond, pre_p);
5116 *expr_p = unshare_expr (result);
5118 else
5119 *expr_p = cond;
5120 return ret;
5122 break;
5124 case CALL_EXPR:
5125 /* For calls that return in memory, give *to_p as the CALL_EXPR's
5126 return slot so that we don't generate a temporary. */
5127 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
5128 && aggregate_value_p (*from_p, *from_p))
5130 bool use_target;
5132 if (!(rhs_predicate_for (*to_p))(*from_p))
5133 /* If we need a temporary, *to_p isn't accurate. */
5134 use_target = false;
5135 /* It's OK to use the return slot directly unless it's an NRV. */
5136 else if (TREE_CODE (*to_p) == RESULT_DECL
5137 && DECL_NAME (*to_p) == NULL_TREE
5138 && needs_to_live_in_memory (*to_p))
5139 use_target = true;
5140 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
5141 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
5142 /* Don't force regs into memory. */
5143 use_target = false;
5144 else if (TREE_CODE (*expr_p) == INIT_EXPR)
5145 /* It's OK to use the target directly if it's being
5146 initialized. */
5147 use_target = true;
5148 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
5149 != INTEGER_CST)
5150 /* Always use the target and thus RSO for variable-sized types.
5151 GIMPLE cannot deal with a variable-sized assignment
5152 embedded in a call statement. */
5153 use_target = true;
5154 else if (TREE_CODE (*to_p) != SSA_NAME
5155 && (!is_gimple_variable (*to_p)
5156 || needs_to_live_in_memory (*to_p)))
5157 /* Don't use the original target if it's already addressable;
5158 if its address escapes, and the called function uses the
5159 NRV optimization, a conforming program could see *to_p
5160 change before the called function returns; see c++/19317.
5161 When optimizing, the return_slot pass marks more functions
5162 as safe after we have escape info. */
5163 use_target = false;
5164 else
5165 use_target = true;
5167 if (use_target)
5169 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
5170 mark_addressable (*to_p);
5173 break;
5175 case WITH_SIZE_EXPR:
5176 /* Likewise for calls that return an aggregate of non-constant size,
5177 since we would not be able to generate a temporary at all. */
5178 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
5180 *from_p = TREE_OPERAND (*from_p, 0);
5181 /* We don't change ret in this case because the
5182 WITH_SIZE_EXPR might have been added in
5183 gimplify_modify_expr, so returning GS_OK would lead to an
5184 infinite loop. */
5185 changed = true;
5187 break;
5189 /* If we're initializing from a container, push the initialization
5190 inside it. */
5191 case CLEANUP_POINT_EXPR:
5192 case BIND_EXPR:
5193 case STATEMENT_LIST:
5195 tree wrap = *from_p;
5196 tree t;
5198 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
5199 fb_lvalue);
5200 if (ret != GS_ERROR)
5201 ret = GS_OK;
5203 t = voidify_wrapper_expr (wrap, *expr_p);
5204 gcc_assert (t == *expr_p);
5206 if (want_value)
5208 gimplify_and_add (wrap, pre_p);
5209 *expr_p = unshare_expr (*to_p);
5211 else
5212 *expr_p = wrap;
5213 return GS_OK;
5216 case COMPOUND_LITERAL_EXPR:
5218 tree complit = TREE_OPERAND (*expr_p, 1);
5219 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
5220 tree decl = DECL_EXPR_DECL (decl_s);
5221 tree init = DECL_INITIAL (decl);
5223 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
5224 into struct T x = { 0, 1, 2 } if the address of the
5225 compound literal has never been taken. */
5226 if (!TREE_ADDRESSABLE (complit)
5227 && !TREE_ADDRESSABLE (decl)
5228 && init)
5230 *expr_p = copy_node (*expr_p);
5231 TREE_OPERAND (*expr_p, 1) = init;
5232 return GS_OK;
5236 default:
5237 break;
5240 while (changed);
5242 return ret;
5246 /* Return true if T looks like a valid GIMPLE statement. */
5248 static bool
5249 is_gimple_stmt (tree t)
5251 const enum tree_code code = TREE_CODE (t);
5253 switch (code)
5255 case NOP_EXPR:
5256 /* The only valid NOP_EXPR is the empty statement. */
5257 return IS_EMPTY_STMT (t);
5259 case BIND_EXPR:
5260 case COND_EXPR:
5261 /* These are only valid if they're void. */
5262 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
5264 case SWITCH_EXPR:
5265 case GOTO_EXPR:
5266 case RETURN_EXPR:
5267 case LABEL_EXPR:
5268 case CASE_LABEL_EXPR:
5269 case TRY_CATCH_EXPR:
5270 case TRY_FINALLY_EXPR:
5271 case EH_FILTER_EXPR:
5272 case CATCH_EXPR:
5273 case ASM_EXPR:
5274 case STATEMENT_LIST:
5275 case OACC_PARALLEL:
5276 case OACC_KERNELS:
5277 case OACC_DATA:
5278 case OACC_HOST_DATA:
5279 case OACC_DECLARE:
5280 case OACC_UPDATE:
5281 case OACC_ENTER_DATA:
5282 case OACC_EXIT_DATA:
5283 case OACC_CACHE:
5284 case OMP_PARALLEL:
5285 case OMP_FOR:
5286 case OMP_SIMD:
5287 case CILK_SIMD:
5288 case OMP_DISTRIBUTE:
5289 case OACC_LOOP:
5290 case OMP_SECTIONS:
5291 case OMP_SECTION:
5292 case OMP_SINGLE:
5293 case OMP_MASTER:
5294 case OMP_TASKGROUP:
5295 case OMP_ORDERED:
5296 case OMP_CRITICAL:
5297 case OMP_TASK:
5298 case OMP_TARGET:
5299 case OMP_TARGET_DATA:
5300 case OMP_TARGET_UPDATE:
5301 case OMP_TARGET_ENTER_DATA:
5302 case OMP_TARGET_EXIT_DATA:
5303 case OMP_TASKLOOP:
5304 case OMP_TEAMS:
5305 /* These are always void. */
5306 return true;
5308 case CALL_EXPR:
5309 case MODIFY_EXPR:
5310 case PREDICT_EXPR:
5311 /* These are valid regardless of their type. */
5312 return true;
5314 default:
5315 return false;
5320 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
5321 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
5322 DECL_GIMPLE_REG_P set.
5324 IMPORTANT NOTE: This promotion is performed by introducing a load of the
5325 other, unmodified part of the complex object just before the total store.
5326 As a consequence, if the object is still uninitialized, an undefined value
5327 will be loaded into a register, which may result in a spurious exception
5328 if the register is floating-point and the value happens to be a signaling
5329 NaN for example. Then the fully-fledged complex operations lowering pass
5330 followed by a DCE pass are necessary in order to fix things up. */
5332 static enum gimplify_status
5333 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
5334 bool want_value)
5336 enum tree_code code, ocode;
5337 tree lhs, rhs, new_rhs, other, realpart, imagpart;
5339 lhs = TREE_OPERAND (*expr_p, 0);
5340 rhs = TREE_OPERAND (*expr_p, 1);
5341 code = TREE_CODE (lhs);
5342 lhs = TREE_OPERAND (lhs, 0);
5344 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
5345 other = build1 (ocode, TREE_TYPE (rhs), lhs);
5346 TREE_NO_WARNING (other) = 1;
5347 other = get_formal_tmp_var (other, pre_p);
5349 realpart = code == REALPART_EXPR ? rhs : other;
5350 imagpart = code == REALPART_EXPR ? other : rhs;
5352 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
5353 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
5354 else
5355 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
5357 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
5358 *expr_p = (want_value) ? rhs : NULL_TREE;
5360 return GS_ALL_DONE;
5363 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
5365 modify_expr
5366 : varname '=' rhs
5367 | '*' ID '=' rhs
5369 PRE_P points to the list where side effects that must happen before
5370 *EXPR_P should be stored.
5372 POST_P points to the list where side effects that must happen after
5373 *EXPR_P should be stored.
5375 WANT_VALUE is nonzero iff we want to use the value of this expression
5376 in another expression. */
5378 static enum gimplify_status
5379 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5380 bool want_value)
5382 tree *from_p = &TREE_OPERAND (*expr_p, 1);
5383 tree *to_p = &TREE_OPERAND (*expr_p, 0);
5384 enum gimplify_status ret = GS_UNHANDLED;
5385 gimple *assign;
5386 location_t loc = EXPR_LOCATION (*expr_p);
5387 gimple_stmt_iterator gsi;
5389 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
5390 || TREE_CODE (*expr_p) == INIT_EXPR);
5392 /* Trying to simplify a clobber using normal logic doesn't work,
5393 so handle it here. */
5394 if (TREE_CLOBBER_P (*from_p))
5396 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5397 if (ret == GS_ERROR)
5398 return ret;
5399 gcc_assert (!want_value
5400 && (VAR_P (*to_p) || TREE_CODE (*to_p) == MEM_REF));
5401 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
5402 *expr_p = NULL;
5403 return GS_ALL_DONE;
5406 /* Insert pointer conversions required by the middle-end that are not
5407 required by the frontend. This fixes middle-end type checking for
5408 for example gcc.dg/redecl-6.c. */
5409 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
5411 STRIP_USELESS_TYPE_CONVERSION (*from_p);
5412 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
5413 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
5416 /* See if any simplifications can be done based on what the RHS is. */
5417 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5418 want_value);
5419 if (ret != GS_UNHANDLED)
5420 return ret;
5422 /* For zero sized types only gimplify the left hand side and right hand
5423 side as statements and throw away the assignment. Do this after
5424 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
5425 types properly. */
5426 if (zero_sized_type (TREE_TYPE (*from_p)) && !want_value)
5428 gimplify_stmt (from_p, pre_p);
5429 gimplify_stmt (to_p, pre_p);
5430 *expr_p = NULL_TREE;
5431 return GS_ALL_DONE;
5434 /* If the value being copied is of variable width, compute the length
5435 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
5436 before gimplifying any of the operands so that we can resolve any
5437 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
5438 the size of the expression to be copied, not of the destination, so
5439 that is what we must do here. */
5440 maybe_with_size_expr (from_p);
5442 /* As a special case, we have to temporarily allow for assignments
5443 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
5444 a toplevel statement, when gimplifying the GENERIC expression
5445 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
5446 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
5448 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
5449 prevent gimplify_expr from trying to create a new temporary for
5450 foo's LHS, we tell it that it should only gimplify until it
5451 reaches the CALL_EXPR. On return from gimplify_expr, the newly
5452 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
5453 and all we need to do here is set 'a' to be its LHS. */
5455 /* Gimplify the RHS first for C++17 and bug 71104. */
5456 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
5457 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
5458 if (ret == GS_ERROR)
5459 return ret;
5461 /* Then gimplify the LHS. */
5462 /* If we gimplified the RHS to a CALL_EXPR and that call may return
5463 twice we have to make sure to gimplify into non-SSA as otherwise
5464 the abnormal edge added later will make those defs not dominate
5465 their uses.
5466 ??? Technically this applies only to the registers used in the
5467 resulting non-register *TO_P. */
5468 bool saved_into_ssa = gimplify_ctxp->into_ssa;
5469 if (saved_into_ssa
5470 && TREE_CODE (*from_p) == CALL_EXPR
5471 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
5472 gimplify_ctxp->into_ssa = false;
5473 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5474 gimplify_ctxp->into_ssa = saved_into_ssa;
5475 if (ret == GS_ERROR)
5476 return ret;
5478 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
5479 guess for the predicate was wrong. */
5480 gimple_predicate final_pred = rhs_predicate_for (*to_p);
5481 if (final_pred != initial_pred)
5483 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
5484 if (ret == GS_ERROR)
5485 return ret;
5488 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
5489 size as argument to the call. */
5490 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5492 tree call = TREE_OPERAND (*from_p, 0);
5493 tree vlasize = TREE_OPERAND (*from_p, 1);
5495 if (TREE_CODE (call) == CALL_EXPR
5496 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
5498 int nargs = call_expr_nargs (call);
5499 tree type = TREE_TYPE (call);
5500 tree ap = CALL_EXPR_ARG (call, 0);
5501 tree tag = CALL_EXPR_ARG (call, 1);
5502 tree aptag = CALL_EXPR_ARG (call, 2);
5503 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
5504 IFN_VA_ARG, type,
5505 nargs + 1, ap, tag,
5506 aptag, vlasize);
5507 TREE_OPERAND (*from_p, 0) = newcall;
5511 /* Now see if the above changed *from_p to something we handle specially. */
5512 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5513 want_value);
5514 if (ret != GS_UNHANDLED)
5515 return ret;
5517 /* If we've got a variable sized assignment between two lvalues (i.e. does
5518 not involve a call), then we can make things a bit more straightforward
5519 by converting the assignment to memcpy or memset. */
5520 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5522 tree from = TREE_OPERAND (*from_p, 0);
5523 tree size = TREE_OPERAND (*from_p, 1);
5525 if (TREE_CODE (from) == CONSTRUCTOR)
5526 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
5528 if (is_gimple_addressable (from))
5530 *from_p = from;
5531 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
5532 pre_p);
5536 /* Transform partial stores to non-addressable complex variables into
5537 total stores. This allows us to use real instead of virtual operands
5538 for these variables, which improves optimization. */
5539 if ((TREE_CODE (*to_p) == REALPART_EXPR
5540 || TREE_CODE (*to_p) == IMAGPART_EXPR)
5541 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
5542 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
5544 /* Try to alleviate the effects of the gimplification creating artificial
5545 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
5546 make sure not to create DECL_DEBUG_EXPR links across functions. */
5547 if (!gimplify_ctxp->into_ssa
5548 && VAR_P (*from_p)
5549 && DECL_IGNORED_P (*from_p)
5550 && DECL_P (*to_p)
5551 && !DECL_IGNORED_P (*to_p)
5552 && decl_function_context (*to_p) == current_function_decl)
5554 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
5555 DECL_NAME (*from_p)
5556 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
5557 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
5558 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
5561 if (want_value && TREE_THIS_VOLATILE (*to_p))
5562 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
5564 if (TREE_CODE (*from_p) == CALL_EXPR)
5566 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
5567 instead of a GIMPLE_ASSIGN. */
5568 gcall *call_stmt;
5569 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
5571 /* Gimplify internal functions created in the FEs. */
5572 int nargs = call_expr_nargs (*from_p), i;
5573 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
5574 auto_vec<tree> vargs (nargs);
5576 for (i = 0; i < nargs; i++)
5578 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
5579 EXPR_LOCATION (*from_p));
5580 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
5582 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
5583 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
5585 else
5587 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
5588 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
5589 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
5590 tree fndecl = get_callee_fndecl (*from_p);
5591 if (fndecl
5592 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL
5593 && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_EXPECT
5594 && call_expr_nargs (*from_p) == 3)
5595 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
5596 CALL_EXPR_ARG (*from_p, 0),
5597 CALL_EXPR_ARG (*from_p, 1),
5598 CALL_EXPR_ARG (*from_p, 2));
5599 else
5601 call_stmt = gimple_build_call_from_tree (*from_p);
5602 gimple_call_set_fntype (call_stmt, TREE_TYPE (fnptrtype));
5605 notice_special_calls (call_stmt);
5606 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
5607 gimple_call_set_lhs (call_stmt, *to_p);
5608 else if (TREE_CODE (*to_p) == SSA_NAME)
5609 /* The above is somewhat premature, avoid ICEing later for a
5610 SSA name w/o a definition. We may have uses in the GIMPLE IL.
5611 ??? This doesn't make it a default-def. */
5612 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
5613 assign = call_stmt;
5615 else
5617 assign = gimple_build_assign (*to_p, *from_p);
5618 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
5619 if (COMPARISON_CLASS_P (*from_p))
5620 gimple_set_no_warning (assign, TREE_NO_WARNING (*from_p));
5623 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
5625 /* We should have got an SSA name from the start. */
5626 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
5627 || ! gimple_in_ssa_p (cfun));
5630 gimplify_seq_add_stmt (pre_p, assign);
5631 gsi = gsi_last (*pre_p);
5632 maybe_fold_stmt (&gsi);
5634 if (want_value)
5636 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
5637 return GS_OK;
5639 else
5640 *expr_p = NULL;
5642 return GS_ALL_DONE;
5645 /* Gimplify a comparison between two variable-sized objects. Do this
5646 with a call to BUILT_IN_MEMCMP. */
5648 static enum gimplify_status
5649 gimplify_variable_sized_compare (tree *expr_p)
5651 location_t loc = EXPR_LOCATION (*expr_p);
5652 tree op0 = TREE_OPERAND (*expr_p, 0);
5653 tree op1 = TREE_OPERAND (*expr_p, 1);
5654 tree t, arg, dest, src, expr;
5656 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
5657 arg = unshare_expr (arg);
5658 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
5659 src = build_fold_addr_expr_loc (loc, op1);
5660 dest = build_fold_addr_expr_loc (loc, op0);
5661 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
5662 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
5664 expr
5665 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
5666 SET_EXPR_LOCATION (expr, loc);
5667 *expr_p = expr;
5669 return GS_OK;
5672 /* Gimplify a comparison between two aggregate objects of integral scalar
5673 mode as a comparison between the bitwise equivalent scalar values. */
5675 static enum gimplify_status
5676 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
5678 location_t loc = EXPR_LOCATION (*expr_p);
5679 tree op0 = TREE_OPERAND (*expr_p, 0);
5680 tree op1 = TREE_OPERAND (*expr_p, 1);
5682 tree type = TREE_TYPE (op0);
5683 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
5685 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
5686 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
5688 *expr_p
5689 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
5691 return GS_OK;
5694 /* Gimplify an expression sequence. This function gimplifies each
5695 expression and rewrites the original expression with the last
5696 expression of the sequence in GIMPLE form.
5698 PRE_P points to the list where the side effects for all the
5699 expressions in the sequence will be emitted.
5701 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
5703 static enum gimplify_status
5704 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
5706 tree t = *expr_p;
5710 tree *sub_p = &TREE_OPERAND (t, 0);
5712 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
5713 gimplify_compound_expr (sub_p, pre_p, false);
5714 else
5715 gimplify_stmt (sub_p, pre_p);
5717 t = TREE_OPERAND (t, 1);
5719 while (TREE_CODE (t) == COMPOUND_EXPR);
5721 *expr_p = t;
5722 if (want_value)
5723 return GS_OK;
5724 else
5726 gimplify_stmt (expr_p, pre_p);
5727 return GS_ALL_DONE;
5731 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
5732 gimplify. After gimplification, EXPR_P will point to a new temporary
5733 that holds the original value of the SAVE_EXPR node.
5735 PRE_P points to the list where side effects that must happen before
5736 *EXPR_P should be stored. */
5738 static enum gimplify_status
5739 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5741 enum gimplify_status ret = GS_ALL_DONE;
5742 tree val;
5744 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
5745 val = TREE_OPERAND (*expr_p, 0);
5747 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
5748 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
5750 /* The operand may be a void-valued expression such as SAVE_EXPRs
5751 generated by the Java frontend for class initialization. It is
5752 being executed only for its side-effects. */
5753 if (TREE_TYPE (val) == void_type_node)
5755 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5756 is_gimple_stmt, fb_none);
5757 val = NULL;
5759 else
5760 /* The temporary may not be an SSA name as later abnormal and EH
5761 control flow may invalidate use/def domination. */
5762 val = get_initialized_tmp_var (val, pre_p, post_p, false);
5764 TREE_OPERAND (*expr_p, 0) = val;
5765 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
5768 *expr_p = val;
5770 return ret;
5773 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
5775 unary_expr
5776 : ...
5777 | '&' varname
5780 PRE_P points to the list where side effects that must happen before
5781 *EXPR_P should be stored.
5783 POST_P points to the list where side effects that must happen after
5784 *EXPR_P should be stored. */
5786 static enum gimplify_status
5787 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5789 tree expr = *expr_p;
5790 tree op0 = TREE_OPERAND (expr, 0);
5791 enum gimplify_status ret;
5792 location_t loc = EXPR_LOCATION (*expr_p);
5794 switch (TREE_CODE (op0))
5796 case INDIRECT_REF:
5797 do_indirect_ref:
5798 /* Check if we are dealing with an expression of the form '&*ptr'.
5799 While the front end folds away '&*ptr' into 'ptr', these
5800 expressions may be generated internally by the compiler (e.g.,
5801 builtins like __builtin_va_end). */
5802 /* Caution: the silent array decomposition semantics we allow for
5803 ADDR_EXPR means we can't always discard the pair. */
5804 /* Gimplification of the ADDR_EXPR operand may drop
5805 cv-qualification conversions, so make sure we add them if
5806 needed. */
5808 tree op00 = TREE_OPERAND (op0, 0);
5809 tree t_expr = TREE_TYPE (expr);
5810 tree t_op00 = TREE_TYPE (op00);
5812 if (!useless_type_conversion_p (t_expr, t_op00))
5813 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
5814 *expr_p = op00;
5815 ret = GS_OK;
5817 break;
5819 case VIEW_CONVERT_EXPR:
5820 /* Take the address of our operand and then convert it to the type of
5821 this ADDR_EXPR.
5823 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
5824 all clear. The impact of this transformation is even less clear. */
5826 /* If the operand is a useless conversion, look through it. Doing so
5827 guarantees that the ADDR_EXPR and its operand will remain of the
5828 same type. */
5829 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
5830 op0 = TREE_OPERAND (op0, 0);
5832 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
5833 build_fold_addr_expr_loc (loc,
5834 TREE_OPERAND (op0, 0)));
5835 ret = GS_OK;
5836 break;
5838 case MEM_REF:
5839 if (integer_zerop (TREE_OPERAND (op0, 1)))
5840 goto do_indirect_ref;
5842 /* fall through */
5844 default:
5845 /* If we see a call to a declared builtin or see its address
5846 being taken (we can unify those cases here) then we can mark
5847 the builtin for implicit generation by GCC. */
5848 if (TREE_CODE (op0) == FUNCTION_DECL
5849 && DECL_BUILT_IN_CLASS (op0) == BUILT_IN_NORMAL
5850 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
5851 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
5853 /* We use fb_either here because the C frontend sometimes takes
5854 the address of a call that returns a struct; see
5855 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
5856 the implied temporary explicit. */
5858 /* Make the operand addressable. */
5859 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
5860 is_gimple_addressable, fb_either);
5861 if (ret == GS_ERROR)
5862 break;
5864 /* Then mark it. Beware that it may not be possible to do so directly
5865 if a temporary has been created by the gimplification. */
5866 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
5868 op0 = TREE_OPERAND (expr, 0);
5870 /* For various reasons, the gimplification of the expression
5871 may have made a new INDIRECT_REF. */
5872 if (TREE_CODE (op0) == INDIRECT_REF)
5873 goto do_indirect_ref;
5875 mark_addressable (TREE_OPERAND (expr, 0));
5877 /* The FEs may end up building ADDR_EXPRs early on a decl with
5878 an incomplete type. Re-build ADDR_EXPRs in canonical form
5879 here. */
5880 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
5881 *expr_p = build_fold_addr_expr (op0);
5883 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
5884 recompute_tree_invariant_for_addr_expr (*expr_p);
5886 /* If we re-built the ADDR_EXPR add a conversion to the original type
5887 if required. */
5888 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
5889 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
5891 break;
5894 return ret;
5897 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
5898 value; output operands should be a gimple lvalue. */
5900 static enum gimplify_status
5901 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5903 tree expr;
5904 int noutputs;
5905 const char **oconstraints;
5906 int i;
5907 tree link;
5908 const char *constraint;
5909 bool allows_mem, allows_reg, is_inout;
5910 enum gimplify_status ret, tret;
5911 gasm *stmt;
5912 vec<tree, va_gc> *inputs;
5913 vec<tree, va_gc> *outputs;
5914 vec<tree, va_gc> *clobbers;
5915 vec<tree, va_gc> *labels;
5916 tree link_next;
5918 expr = *expr_p;
5919 noutputs = list_length (ASM_OUTPUTS (expr));
5920 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
5922 inputs = NULL;
5923 outputs = NULL;
5924 clobbers = NULL;
5925 labels = NULL;
5927 ret = GS_ALL_DONE;
5928 link_next = NULL_TREE;
5929 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
5931 bool ok;
5932 size_t constraint_len;
5934 link_next = TREE_CHAIN (link);
5936 oconstraints[i]
5937 = constraint
5938 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
5939 constraint_len = strlen (constraint);
5940 if (constraint_len == 0)
5941 continue;
5943 ok = parse_output_constraint (&constraint, i, 0, 0,
5944 &allows_mem, &allows_reg, &is_inout);
5945 if (!ok)
5947 ret = GS_ERROR;
5948 is_inout = false;
5951 if (!allows_reg && allows_mem)
5952 mark_addressable (TREE_VALUE (link));
5954 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5955 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
5956 fb_lvalue | fb_mayfail);
5957 if (tret == GS_ERROR)
5959 error ("invalid lvalue in asm output %d", i);
5960 ret = tret;
5963 /* If the constraint does not allow memory make sure we gimplify
5964 it to a register if it is not already but its base is. This
5965 happens for complex and vector components. */
5966 if (!allows_mem)
5968 tree op = TREE_VALUE (link);
5969 if (! is_gimple_val (op)
5970 && is_gimple_reg_type (TREE_TYPE (op))
5971 && is_gimple_reg (get_base_address (op)))
5973 tree tem = create_tmp_reg (TREE_TYPE (op));
5974 tree ass;
5975 if (is_inout)
5977 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
5978 tem, unshare_expr (op));
5979 gimplify_and_add (ass, pre_p);
5981 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
5982 gimplify_and_add (ass, post_p);
5984 TREE_VALUE (link) = tem;
5985 tret = GS_OK;
5989 vec_safe_push (outputs, link);
5990 TREE_CHAIN (link) = NULL_TREE;
5992 if (is_inout)
5994 /* An input/output operand. To give the optimizers more
5995 flexibility, split it into separate input and output
5996 operands. */
5997 tree input;
5998 /* Buffer big enough to format a 32-bit UINT_MAX into. */
5999 char buf[11];
6001 /* Turn the in/out constraint into an output constraint. */
6002 char *p = xstrdup (constraint);
6003 p[0] = '=';
6004 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
6006 /* And add a matching input constraint. */
6007 if (allows_reg)
6009 sprintf (buf, "%u", i);
6011 /* If there are multiple alternatives in the constraint,
6012 handle each of them individually. Those that allow register
6013 will be replaced with operand number, the others will stay
6014 unchanged. */
6015 if (strchr (p, ',') != NULL)
6017 size_t len = 0, buflen = strlen (buf);
6018 char *beg, *end, *str, *dst;
6020 for (beg = p + 1;;)
6022 end = strchr (beg, ',');
6023 if (end == NULL)
6024 end = strchr (beg, '\0');
6025 if ((size_t) (end - beg) < buflen)
6026 len += buflen + 1;
6027 else
6028 len += end - beg + 1;
6029 if (*end)
6030 beg = end + 1;
6031 else
6032 break;
6035 str = (char *) alloca (len);
6036 for (beg = p + 1, dst = str;;)
6038 const char *tem;
6039 bool mem_p, reg_p, inout_p;
6041 end = strchr (beg, ',');
6042 if (end)
6043 *end = '\0';
6044 beg[-1] = '=';
6045 tem = beg - 1;
6046 parse_output_constraint (&tem, i, 0, 0,
6047 &mem_p, &reg_p, &inout_p);
6048 if (dst != str)
6049 *dst++ = ',';
6050 if (reg_p)
6052 memcpy (dst, buf, buflen);
6053 dst += buflen;
6055 else
6057 if (end)
6058 len = end - beg;
6059 else
6060 len = strlen (beg);
6061 memcpy (dst, beg, len);
6062 dst += len;
6064 if (end)
6065 beg = end + 1;
6066 else
6067 break;
6069 *dst = '\0';
6070 input = build_string (dst - str, str);
6072 else
6073 input = build_string (strlen (buf), buf);
6075 else
6076 input = build_string (constraint_len - 1, constraint + 1);
6078 free (p);
6080 input = build_tree_list (build_tree_list (NULL_TREE, input),
6081 unshare_expr (TREE_VALUE (link)));
6082 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
6086 link_next = NULL_TREE;
6087 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
6089 link_next = TREE_CHAIN (link);
6090 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6091 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
6092 oconstraints, &allows_mem, &allows_reg);
6094 /* If we can't make copies, we can only accept memory. */
6095 if (TREE_ADDRESSABLE (TREE_TYPE (TREE_VALUE (link))))
6097 if (allows_mem)
6098 allows_reg = 0;
6099 else
6101 error ("impossible constraint in %<asm%>");
6102 error ("non-memory input %d must stay in memory", i);
6103 return GS_ERROR;
6107 /* If the operand is a memory input, it should be an lvalue. */
6108 if (!allows_reg && allows_mem)
6110 tree inputv = TREE_VALUE (link);
6111 STRIP_NOPS (inputv);
6112 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
6113 || TREE_CODE (inputv) == PREINCREMENT_EXPR
6114 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
6115 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
6116 || TREE_CODE (inputv) == MODIFY_EXPR)
6117 TREE_VALUE (link) = error_mark_node;
6118 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6119 is_gimple_lvalue, fb_lvalue | fb_mayfail);
6120 if (tret != GS_ERROR)
6122 /* Unlike output operands, memory inputs are not guaranteed
6123 to be lvalues by the FE, and while the expressions are
6124 marked addressable there, if it is e.g. a statement
6125 expression, temporaries in it might not end up being
6126 addressable. They might be already used in the IL and thus
6127 it is too late to make them addressable now though. */
6128 tree x = TREE_VALUE (link);
6129 while (handled_component_p (x))
6130 x = TREE_OPERAND (x, 0);
6131 if (TREE_CODE (x) == MEM_REF
6132 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
6133 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
6134 if ((VAR_P (x)
6135 || TREE_CODE (x) == PARM_DECL
6136 || TREE_CODE (x) == RESULT_DECL)
6137 && !TREE_ADDRESSABLE (x)
6138 && is_gimple_reg (x))
6140 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
6141 input_location), 0,
6142 "memory input %d is not directly addressable",
6144 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
6147 mark_addressable (TREE_VALUE (link));
6148 if (tret == GS_ERROR)
6150 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
6151 "memory input %d is not directly addressable", i);
6152 ret = tret;
6155 else
6157 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6158 is_gimple_asm_val, fb_rvalue);
6159 if (tret == GS_ERROR)
6160 ret = tret;
6163 TREE_CHAIN (link) = NULL_TREE;
6164 vec_safe_push (inputs, link);
6167 link_next = NULL_TREE;
6168 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
6170 link_next = TREE_CHAIN (link);
6171 TREE_CHAIN (link) = NULL_TREE;
6172 vec_safe_push (clobbers, link);
6175 link_next = NULL_TREE;
6176 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
6178 link_next = TREE_CHAIN (link);
6179 TREE_CHAIN (link) = NULL_TREE;
6180 vec_safe_push (labels, link);
6183 /* Do not add ASMs with errors to the gimple IL stream. */
6184 if (ret != GS_ERROR)
6186 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
6187 inputs, outputs, clobbers, labels);
6189 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
6190 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
6192 gimplify_seq_add_stmt (pre_p, stmt);
6195 return ret;
6198 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
6199 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
6200 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
6201 return to this function.
6203 FIXME should we complexify the prequeue handling instead? Or use flags
6204 for all the cleanups and let the optimizer tighten them up? The current
6205 code seems pretty fragile; it will break on a cleanup within any
6206 non-conditional nesting. But any such nesting would be broken, anyway;
6207 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
6208 and continues out of it. We can do that at the RTL level, though, so
6209 having an optimizer to tighten up try/finally regions would be a Good
6210 Thing. */
6212 static enum gimplify_status
6213 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
6215 gimple_stmt_iterator iter;
6216 gimple_seq body_sequence = NULL;
6218 tree temp = voidify_wrapper_expr (*expr_p, NULL);
6220 /* We only care about the number of conditions between the innermost
6221 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
6222 any cleanups collected outside the CLEANUP_POINT_EXPR. */
6223 int old_conds = gimplify_ctxp->conditions;
6224 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
6225 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
6226 gimplify_ctxp->conditions = 0;
6227 gimplify_ctxp->conditional_cleanups = NULL;
6228 gimplify_ctxp->in_cleanup_point_expr = true;
6230 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
6232 gimplify_ctxp->conditions = old_conds;
6233 gimplify_ctxp->conditional_cleanups = old_cleanups;
6234 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
6236 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
6238 gimple *wce = gsi_stmt (iter);
6240 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
6242 if (gsi_one_before_end_p (iter))
6244 /* Note that gsi_insert_seq_before and gsi_remove do not
6245 scan operands, unlike some other sequence mutators. */
6246 if (!gimple_wce_cleanup_eh_only (wce))
6247 gsi_insert_seq_before_without_update (&iter,
6248 gimple_wce_cleanup (wce),
6249 GSI_SAME_STMT);
6250 gsi_remove (&iter, true);
6251 break;
6253 else
6255 gtry *gtry;
6256 gimple_seq seq;
6257 enum gimple_try_flags kind;
6259 if (gimple_wce_cleanup_eh_only (wce))
6260 kind = GIMPLE_TRY_CATCH;
6261 else
6262 kind = GIMPLE_TRY_FINALLY;
6263 seq = gsi_split_seq_after (iter);
6265 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
6266 /* Do not use gsi_replace here, as it may scan operands.
6267 We want to do a simple structural modification only. */
6268 gsi_set_stmt (&iter, gtry);
6269 iter = gsi_start (gtry->eval);
6272 else
6273 gsi_next (&iter);
6276 gimplify_seq_add_seq (pre_p, body_sequence);
6277 if (temp)
6279 *expr_p = temp;
6280 return GS_OK;
6282 else
6284 *expr_p = NULL;
6285 return GS_ALL_DONE;
6289 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
6290 is the cleanup action required. EH_ONLY is true if the cleanup should
6291 only be executed if an exception is thrown, not on normal exit. */
6293 static void
6294 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p)
6296 gimple *wce;
6297 gimple_seq cleanup_stmts = NULL;
6299 /* Errors can result in improperly nested cleanups. Which results in
6300 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
6301 if (seen_error ())
6302 return;
6304 if (gimple_conditional_context ())
6306 /* If we're in a conditional context, this is more complex. We only
6307 want to run the cleanup if we actually ran the initialization that
6308 necessitates it, but we want to run it after the end of the
6309 conditional context. So we wrap the try/finally around the
6310 condition and use a flag to determine whether or not to actually
6311 run the destructor. Thus
6313 test ? f(A()) : 0
6315 becomes (approximately)
6317 flag = 0;
6318 try {
6319 if (test) { A::A(temp); flag = 1; val = f(temp); }
6320 else { val = 0; }
6321 } finally {
6322 if (flag) A::~A(temp);
6326 tree flag = create_tmp_var (boolean_type_node, "cleanup");
6327 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
6328 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
6330 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
6331 gimplify_stmt (&cleanup, &cleanup_stmts);
6332 wce = gimple_build_wce (cleanup_stmts);
6334 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
6335 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6336 gimplify_seq_add_stmt (pre_p, ftrue);
6338 /* Because of this manipulation, and the EH edges that jump
6339 threading cannot redirect, the temporary (VAR) will appear
6340 to be used uninitialized. Don't warn. */
6341 TREE_NO_WARNING (var) = 1;
6343 else
6345 gimplify_stmt (&cleanup, &cleanup_stmts);
6346 wce = gimple_build_wce (cleanup_stmts);
6347 gimple_wce_set_cleanup_eh_only (wce, eh_only);
6348 gimplify_seq_add_stmt (pre_p, wce);
6352 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
6354 static enum gimplify_status
6355 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6357 tree targ = *expr_p;
6358 tree temp = TARGET_EXPR_SLOT (targ);
6359 tree init = TARGET_EXPR_INITIAL (targ);
6360 enum gimplify_status ret;
6362 bool unpoison_empty_seq = false;
6363 gimple_stmt_iterator unpoison_it;
6365 if (init)
6367 tree cleanup = NULL_TREE;
6369 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
6370 to the temps list. Handle also variable length TARGET_EXPRs. */
6371 if (TREE_CODE (DECL_SIZE (temp)) != INTEGER_CST)
6373 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
6374 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
6375 gimplify_vla_decl (temp, pre_p);
6377 else
6379 /* Save location where we need to place unpoisoning. It's possible
6380 that a variable will be converted to needs_to_live_in_memory. */
6381 unpoison_it = gsi_last (*pre_p);
6382 unpoison_empty_seq = gsi_end_p (unpoison_it);
6384 gimple_add_tmp_var (temp);
6387 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
6388 expression is supposed to initialize the slot. */
6389 if (VOID_TYPE_P (TREE_TYPE (init)))
6390 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6391 else
6393 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
6394 init = init_expr;
6395 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6396 init = NULL;
6397 ggc_free (init_expr);
6399 if (ret == GS_ERROR)
6401 /* PR c++/28266 Make sure this is expanded only once. */
6402 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6403 return GS_ERROR;
6405 if (init)
6406 gimplify_and_add (init, pre_p);
6408 /* If needed, push the cleanup for the temp. */
6409 if (TARGET_EXPR_CLEANUP (targ))
6411 if (CLEANUP_EH_ONLY (targ))
6412 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
6413 CLEANUP_EH_ONLY (targ), pre_p);
6414 else
6415 cleanup = TARGET_EXPR_CLEANUP (targ);
6418 /* Add a clobber for the temporary going out of scope, like
6419 gimplify_bind_expr. */
6420 if (gimplify_ctxp->in_cleanup_point_expr
6421 && needs_to_live_in_memory (temp))
6423 if (flag_stack_reuse == SR_ALL)
6425 tree clobber = build_constructor (TREE_TYPE (temp),
6426 NULL);
6427 TREE_THIS_VOLATILE (clobber) = true;
6428 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
6429 if (cleanup)
6430 cleanup = build2 (COMPOUND_EXPR, void_type_node, cleanup,
6431 clobber);
6432 else
6433 cleanup = clobber;
6435 if (asan_poisoned_variables && dbg_cnt (asan_use_after_scope))
6437 tree asan_cleanup = build_asan_poison_call_expr (temp);
6438 if (asan_cleanup)
6440 if (unpoison_empty_seq)
6441 unpoison_it = gsi_start (*pre_p);
6443 asan_poison_variable (temp, false, &unpoison_it,
6444 unpoison_empty_seq);
6445 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
6449 if (cleanup)
6450 gimple_push_cleanup (temp, cleanup, false, pre_p);
6452 /* Only expand this once. */
6453 TREE_OPERAND (targ, 3) = init;
6454 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6456 else
6457 /* We should have expanded this before. */
6458 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
6460 *expr_p = temp;
6461 return GS_OK;
6464 /* Gimplification of expression trees. */
6466 /* Gimplify an expression which appears at statement context. The
6467 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
6468 NULL, a new sequence is allocated.
6470 Return true if we actually added a statement to the queue. */
6472 bool
6473 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
6475 gimple_seq_node last;
6477 last = gimple_seq_last (*seq_p);
6478 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
6479 return last != gimple_seq_last (*seq_p);
6482 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
6483 to CTX. If entries already exist, force them to be some flavor of private.
6484 If there is no enclosing parallel, do nothing. */
6486 void
6487 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
6489 splay_tree_node n;
6491 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
6492 return;
6496 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6497 if (n != NULL)
6499 if (n->value & GOVD_SHARED)
6500 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
6501 else if (n->value & GOVD_MAP)
6502 n->value |= GOVD_MAP_TO_ONLY;
6503 else
6504 return;
6506 else if ((ctx->region_type & ORT_TARGET) != 0)
6508 if (ctx->target_map_scalars_firstprivate)
6509 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
6510 else
6511 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
6513 else if (ctx->region_type != ORT_WORKSHARE
6514 && ctx->region_type != ORT_SIMD
6515 && ctx->region_type != ORT_ACC
6516 && !(ctx->region_type & ORT_TARGET_DATA))
6517 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
6519 ctx = ctx->outer_context;
6521 while (ctx);
6524 /* Similarly for each of the type sizes of TYPE. */
6526 static void
6527 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
6529 if (type == NULL || type == error_mark_node)
6530 return;
6531 type = TYPE_MAIN_VARIANT (type);
6533 if (ctx->privatized_types->add (type))
6534 return;
6536 switch (TREE_CODE (type))
6538 case INTEGER_TYPE:
6539 case ENUMERAL_TYPE:
6540 case BOOLEAN_TYPE:
6541 case REAL_TYPE:
6542 case FIXED_POINT_TYPE:
6543 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
6544 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
6545 break;
6547 case ARRAY_TYPE:
6548 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
6549 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
6550 break;
6552 case RECORD_TYPE:
6553 case UNION_TYPE:
6554 case QUAL_UNION_TYPE:
6556 tree field;
6557 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
6558 if (TREE_CODE (field) == FIELD_DECL)
6560 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
6561 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
6564 break;
6566 case POINTER_TYPE:
6567 case REFERENCE_TYPE:
6568 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
6569 break;
6571 default:
6572 break;
6575 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
6576 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
6577 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
6580 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
6582 static void
6583 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
6585 splay_tree_node n;
6586 unsigned int nflags;
6587 tree t;
6589 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
6590 return;
6592 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
6593 there are constructors involved somewhere. */
6594 if (TREE_ADDRESSABLE (TREE_TYPE (decl))
6595 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
6596 flags |= GOVD_SEEN;
6598 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6599 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
6601 /* We shouldn't be re-adding the decl with the same data
6602 sharing class. */
6603 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
6604 nflags = n->value | flags;
6605 /* The only combination of data sharing classes we should see is
6606 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
6607 reduction variables to be used in data sharing clauses. */
6608 gcc_assert ((ctx->region_type & ORT_ACC) != 0
6609 || ((nflags & GOVD_DATA_SHARE_CLASS)
6610 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
6611 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
6612 n->value = nflags;
6613 return;
6616 /* When adding a variable-sized variable, we have to handle all sorts
6617 of additional bits of data: the pointer replacement variable, and
6618 the parameters of the type. */
6619 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
6621 /* Add the pointer replacement variable as PRIVATE if the variable
6622 replacement is private, else FIRSTPRIVATE since we'll need the
6623 address of the original variable either for SHARED, or for the
6624 copy into or out of the context. */
6625 if (!(flags & GOVD_LOCAL))
6627 if (flags & GOVD_MAP)
6628 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
6629 else if (flags & GOVD_PRIVATE)
6630 nflags = GOVD_PRIVATE;
6631 else if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
6632 && (flags & GOVD_FIRSTPRIVATE))
6633 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
6634 else
6635 nflags = GOVD_FIRSTPRIVATE;
6636 nflags |= flags & GOVD_SEEN;
6637 t = DECL_VALUE_EXPR (decl);
6638 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
6639 t = TREE_OPERAND (t, 0);
6640 gcc_assert (DECL_P (t));
6641 omp_add_variable (ctx, t, nflags);
6644 /* Add all of the variable and type parameters (which should have
6645 been gimplified to a formal temporary) as FIRSTPRIVATE. */
6646 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
6647 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
6648 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
6650 /* The variable-sized variable itself is never SHARED, only some form
6651 of PRIVATE. The sharing would take place via the pointer variable
6652 which we remapped above. */
6653 if (flags & GOVD_SHARED)
6654 flags = GOVD_PRIVATE | GOVD_DEBUG_PRIVATE
6655 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
6657 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
6658 alloca statement we generate for the variable, so make sure it
6659 is available. This isn't automatically needed for the SHARED
6660 case, since we won't be allocating local storage then.
6661 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
6662 in this case omp_notice_variable will be called later
6663 on when it is gimplified. */
6664 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
6665 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
6666 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
6668 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
6669 && lang_hooks.decls.omp_privatize_by_reference (decl))
6671 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
6673 /* Similar to the direct variable sized case above, we'll need the
6674 size of references being privatized. */
6675 if ((flags & GOVD_SHARED) == 0)
6677 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
6678 if (DECL_P (t))
6679 omp_notice_variable (ctx, t, true);
6683 if (n != NULL)
6684 n->value |= flags;
6685 else
6686 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
6688 /* For reductions clauses in OpenACC loop directives, by default create a
6689 copy clause on the enclosing parallel construct for carrying back the
6690 results. */
6691 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
6693 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
6694 while (outer_ctx)
6696 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
6697 if (n != NULL)
6699 /* Ignore local variables and explicitly declared clauses. */
6700 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
6701 break;
6702 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
6704 /* According to the OpenACC spec, such a reduction variable
6705 should already have a copy map on a kernels construct,
6706 verify that here. */
6707 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
6708 && (n->value & GOVD_MAP));
6710 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
6712 /* Remove firstprivate and make it a copy map. */
6713 n->value &= ~GOVD_FIRSTPRIVATE;
6714 n->value |= GOVD_MAP;
6717 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
6719 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
6720 GOVD_MAP | GOVD_SEEN);
6721 break;
6723 outer_ctx = outer_ctx->outer_context;
6728 /* Notice a threadprivate variable DECL used in OMP context CTX.
6729 This just prints out diagnostics about threadprivate variable uses
6730 in untied tasks. If DECL2 is non-NULL, prevent this warning
6731 on that variable. */
6733 static bool
6734 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
6735 tree decl2)
6737 splay_tree_node n;
6738 struct gimplify_omp_ctx *octx;
6740 for (octx = ctx; octx; octx = octx->outer_context)
6741 if ((octx->region_type & ORT_TARGET) != 0)
6743 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
6744 if (n == NULL)
6746 error ("threadprivate variable %qE used in target region",
6747 DECL_NAME (decl));
6748 error_at (octx->location, "enclosing target region");
6749 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
6751 if (decl2)
6752 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
6755 if (ctx->region_type != ORT_UNTIED_TASK)
6756 return false;
6757 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6758 if (n == NULL)
6760 error ("threadprivate variable %qE used in untied task",
6761 DECL_NAME (decl));
6762 error_at (ctx->location, "enclosing task");
6763 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
6765 if (decl2)
6766 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
6767 return false;
6770 /* Return true if global var DECL is device resident. */
6772 static bool
6773 device_resident_p (tree decl)
6775 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
6777 if (!attr)
6778 return false;
6780 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
6782 tree c = TREE_VALUE (t);
6783 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
6784 return true;
6787 return false;
6790 /* Determine outer default flags for DECL mentioned in an OMP region
6791 but not declared in an enclosing clause.
6793 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
6794 remapped firstprivate instead of shared. To some extent this is
6795 addressed in omp_firstprivatize_type_sizes, but not
6796 effectively. */
6798 static unsigned
6799 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
6800 bool in_code, unsigned flags)
6802 enum omp_clause_default_kind default_kind = ctx->default_kind;
6803 enum omp_clause_default_kind kind;
6805 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
6806 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
6807 default_kind = kind;
6809 switch (default_kind)
6811 case OMP_CLAUSE_DEFAULT_NONE:
6813 const char *rtype;
6815 if (ctx->region_type & ORT_PARALLEL)
6816 rtype = "parallel";
6817 else if (ctx->region_type & ORT_TASK)
6818 rtype = "task";
6819 else if (ctx->region_type & ORT_TEAMS)
6820 rtype = "teams";
6821 else
6822 gcc_unreachable ();
6824 error ("%qE not specified in enclosing %s",
6825 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
6826 error_at (ctx->location, "enclosing %s", rtype);
6828 /* FALLTHRU */
6829 case OMP_CLAUSE_DEFAULT_SHARED:
6830 flags |= GOVD_SHARED;
6831 break;
6832 case OMP_CLAUSE_DEFAULT_PRIVATE:
6833 flags |= GOVD_PRIVATE;
6834 break;
6835 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
6836 flags |= GOVD_FIRSTPRIVATE;
6837 break;
6838 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
6839 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
6840 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
6841 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
6843 omp_notice_variable (octx, decl, in_code);
6844 for (; octx; octx = octx->outer_context)
6846 splay_tree_node n2;
6848 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
6849 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
6850 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
6851 continue;
6852 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
6854 flags |= GOVD_FIRSTPRIVATE;
6855 goto found_outer;
6857 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
6859 flags |= GOVD_SHARED;
6860 goto found_outer;
6865 if (TREE_CODE (decl) == PARM_DECL
6866 || (!is_global_var (decl)
6867 && DECL_CONTEXT (decl) == current_function_decl))
6868 flags |= GOVD_FIRSTPRIVATE;
6869 else
6870 flags |= GOVD_SHARED;
6871 found_outer:
6872 break;
6874 default:
6875 gcc_unreachable ();
6878 return flags;
6882 /* Determine outer default flags for DECL mentioned in an OACC region
6883 but not declared in an enclosing clause. */
6885 static unsigned
6886 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
6888 const char *rkind;
6889 bool on_device = false;
6890 tree type = TREE_TYPE (decl);
6892 if (lang_hooks.decls.omp_privatize_by_reference (decl))
6893 type = TREE_TYPE (type);
6895 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
6896 && is_global_var (decl)
6897 && device_resident_p (decl))
6899 on_device = true;
6900 flags |= GOVD_MAP_TO_ONLY;
6903 switch (ctx->region_type)
6905 default:
6906 gcc_unreachable ();
6908 case ORT_ACC_KERNELS:
6909 /* Scalars are default 'copy' under kernels, non-scalars are default
6910 'present_or_copy'. */
6911 flags |= GOVD_MAP;
6912 if (!AGGREGATE_TYPE_P (type))
6913 flags |= GOVD_MAP_FORCE;
6915 rkind = "kernels";
6916 break;
6918 case ORT_ACC_PARALLEL:
6920 if (on_device || AGGREGATE_TYPE_P (type))
6921 /* Aggregates default to 'present_or_copy'. */
6922 flags |= GOVD_MAP;
6923 else
6924 /* Scalars default to 'firstprivate'. */
6925 flags |= GOVD_FIRSTPRIVATE;
6926 rkind = "parallel";
6928 break;
6931 if (DECL_ARTIFICIAL (decl))
6932 ; /* We can get compiler-generated decls, and should not complain
6933 about them. */
6934 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_NONE)
6936 error ("%qE not specified in enclosing OpenACC %qs construct",
6937 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rkind);
6938 inform (ctx->location, "enclosing OpenACC %qs construct", rkind);
6940 else
6941 gcc_checking_assert (ctx->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
6943 return flags;
6946 /* Record the fact that DECL was used within the OMP context CTX.
6947 IN_CODE is true when real code uses DECL, and false when we should
6948 merely emit default(none) errors. Return true if DECL is going to
6949 be remapped and thus DECL shouldn't be gimplified into its
6950 DECL_VALUE_EXPR (if any). */
6952 static bool
6953 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
6955 splay_tree_node n;
6956 unsigned flags = in_code ? GOVD_SEEN : 0;
6957 bool ret = false, shared;
6959 if (error_operand_p (decl))
6960 return false;
6962 if (ctx->region_type == ORT_NONE)
6963 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
6965 if (is_global_var (decl))
6967 /* Threadprivate variables are predetermined. */
6968 if (DECL_THREAD_LOCAL_P (decl))
6969 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
6971 if (DECL_HAS_VALUE_EXPR_P (decl))
6973 tree value = get_base_address (DECL_VALUE_EXPR (decl));
6975 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
6976 return omp_notice_threadprivate_variable (ctx, decl, value);
6979 if (gimplify_omp_ctxp->outer_context == NULL
6980 && VAR_P (decl)
6981 && oacc_get_fn_attrib (current_function_decl))
6983 location_t loc = DECL_SOURCE_LOCATION (decl);
6985 if (lookup_attribute ("omp declare target link",
6986 DECL_ATTRIBUTES (decl)))
6988 error_at (loc,
6989 "%qE with %<link%> clause used in %<routine%> function",
6990 DECL_NAME (decl));
6991 return false;
6993 else if (!lookup_attribute ("omp declare target",
6994 DECL_ATTRIBUTES (decl)))
6996 error_at (loc,
6997 "%qE requires a %<declare%> directive for use "
6998 "in a %<routine%> function", DECL_NAME (decl));
6999 return false;
7004 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7005 if ((ctx->region_type & ORT_TARGET) != 0)
7007 ret = lang_hooks.decls.omp_disregard_value_expr (decl, true);
7008 if (n == NULL)
7010 unsigned nflags = flags;
7011 if (ctx->target_map_pointers_as_0len_arrays
7012 || ctx->target_map_scalars_firstprivate)
7014 bool is_declare_target = false;
7015 bool is_scalar = false;
7016 if (is_global_var (decl)
7017 && varpool_node::get_create (decl)->offloadable)
7019 struct gimplify_omp_ctx *octx;
7020 for (octx = ctx->outer_context;
7021 octx; octx = octx->outer_context)
7023 n = splay_tree_lookup (octx->variables,
7024 (splay_tree_key)decl);
7025 if (n
7026 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
7027 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7028 break;
7030 is_declare_target = octx == NULL;
7032 if (!is_declare_target && ctx->target_map_scalars_firstprivate)
7033 is_scalar = lang_hooks.decls.omp_scalar_p (decl);
7034 if (is_declare_target)
7036 else if (ctx->target_map_pointers_as_0len_arrays
7037 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
7038 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
7039 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
7040 == POINTER_TYPE)))
7041 nflags |= GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
7042 else if (is_scalar)
7043 nflags |= GOVD_FIRSTPRIVATE;
7046 struct gimplify_omp_ctx *octx = ctx->outer_context;
7047 if ((ctx->region_type & ORT_ACC) && octx)
7049 /* Look in outer OpenACC contexts, to see if there's a
7050 data attribute for this variable. */
7051 omp_notice_variable (octx, decl, in_code);
7053 for (; octx; octx = octx->outer_context)
7055 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
7056 break;
7057 splay_tree_node n2
7058 = splay_tree_lookup (octx->variables,
7059 (splay_tree_key) decl);
7060 if (n2)
7062 if (octx->region_type == ORT_ACC_HOST_DATA)
7063 error ("variable %qE declared in enclosing "
7064 "%<host_data%> region", DECL_NAME (decl));
7065 nflags |= GOVD_MAP;
7066 if (octx->region_type == ORT_ACC_DATA
7067 && (n2->value & GOVD_MAP_0LEN_ARRAY))
7068 nflags |= GOVD_MAP_0LEN_ARRAY;
7069 goto found_outer;
7075 tree type = TREE_TYPE (decl);
7077 if (nflags == flags
7078 && gimplify_omp_ctxp->target_firstprivatize_array_bases
7079 && lang_hooks.decls.omp_privatize_by_reference (decl))
7080 type = TREE_TYPE (type);
7081 if (nflags == flags
7082 && !lang_hooks.types.omp_mappable_type (type))
7084 error ("%qD referenced in target region does not have "
7085 "a mappable type", decl);
7086 nflags |= GOVD_MAP | GOVD_EXPLICIT;
7088 else if (nflags == flags)
7090 if ((ctx->region_type & ORT_ACC) != 0)
7091 nflags = oacc_default_clause (ctx, decl, flags);
7092 else
7093 nflags |= GOVD_MAP;
7096 found_outer:
7097 omp_add_variable (ctx, decl, nflags);
7099 else
7101 /* If nothing changed, there's nothing left to do. */
7102 if ((n->value & flags) == flags)
7103 return ret;
7104 flags |= n->value;
7105 n->value = flags;
7107 goto do_outer;
7110 if (n == NULL)
7112 if (ctx->region_type == ORT_WORKSHARE
7113 || ctx->region_type == ORT_SIMD
7114 || ctx->region_type == ORT_ACC
7115 || (ctx->region_type & ORT_TARGET_DATA) != 0)
7116 goto do_outer;
7118 flags = omp_default_clause (ctx, decl, in_code, flags);
7120 if ((flags & GOVD_PRIVATE)
7121 && lang_hooks.decls.omp_private_outer_ref (decl))
7122 flags |= GOVD_PRIVATE_OUTER_REF;
7124 omp_add_variable (ctx, decl, flags);
7126 shared = (flags & GOVD_SHARED) != 0;
7127 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7128 goto do_outer;
7131 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
7132 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
7133 && DECL_SIZE (decl))
7135 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7137 splay_tree_node n2;
7138 tree t = DECL_VALUE_EXPR (decl);
7139 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7140 t = TREE_OPERAND (t, 0);
7141 gcc_assert (DECL_P (t));
7142 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7143 n2->value |= GOVD_SEEN;
7145 else if (lang_hooks.decls.omp_privatize_by_reference (decl)
7146 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
7147 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
7148 != INTEGER_CST))
7150 splay_tree_node n2;
7151 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7152 gcc_assert (DECL_P (t));
7153 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7154 if (n2)
7155 omp_notice_variable (ctx, t, true);
7159 shared = ((flags | n->value) & GOVD_SHARED) != 0;
7160 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7162 /* If nothing changed, there's nothing left to do. */
7163 if ((n->value & flags) == flags)
7164 return ret;
7165 flags |= n->value;
7166 n->value = flags;
7168 do_outer:
7169 /* If the variable is private in the current context, then we don't
7170 need to propagate anything to an outer context. */
7171 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
7172 return ret;
7173 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7174 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7175 return ret;
7176 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
7177 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7178 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7179 return ret;
7180 if (ctx->outer_context
7181 && omp_notice_variable (ctx->outer_context, decl, in_code))
7182 return true;
7183 return ret;
7186 /* Verify that DECL is private within CTX. If there's specific information
7187 to the contrary in the innermost scope, generate an error. */
7189 static bool
7190 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
7192 splay_tree_node n;
7194 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7195 if (n != NULL)
7197 if (n->value & GOVD_SHARED)
7199 if (ctx == gimplify_omp_ctxp)
7201 if (simd)
7202 error ("iteration variable %qE is predetermined linear",
7203 DECL_NAME (decl));
7204 else
7205 error ("iteration variable %qE should be private",
7206 DECL_NAME (decl));
7207 n->value = GOVD_PRIVATE;
7208 return true;
7210 else
7211 return false;
7213 else if ((n->value & GOVD_EXPLICIT) != 0
7214 && (ctx == gimplify_omp_ctxp
7215 || (ctx->region_type == ORT_COMBINED_PARALLEL
7216 && gimplify_omp_ctxp->outer_context == ctx)))
7218 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
7219 error ("iteration variable %qE should not be firstprivate",
7220 DECL_NAME (decl));
7221 else if ((n->value & GOVD_REDUCTION) != 0)
7222 error ("iteration variable %qE should not be reduction",
7223 DECL_NAME (decl));
7224 else if (simd == 0 && (n->value & GOVD_LINEAR) != 0)
7225 error ("iteration variable %qE should not be linear",
7226 DECL_NAME (decl));
7227 else if (simd == 1 && (n->value & GOVD_LASTPRIVATE) != 0)
7228 error ("iteration variable %qE should not be lastprivate",
7229 DECL_NAME (decl));
7230 else if (simd && (n->value & GOVD_PRIVATE) != 0)
7231 error ("iteration variable %qE should not be private",
7232 DECL_NAME (decl));
7233 else if (simd == 2 && (n->value & GOVD_LINEAR) != 0)
7234 error ("iteration variable %qE is predetermined linear",
7235 DECL_NAME (decl));
7237 return (ctx == gimplify_omp_ctxp
7238 || (ctx->region_type == ORT_COMBINED_PARALLEL
7239 && gimplify_omp_ctxp->outer_context == ctx));
7242 if (ctx->region_type != ORT_WORKSHARE
7243 && ctx->region_type != ORT_SIMD
7244 && ctx->region_type != ORT_ACC)
7245 return false;
7246 else if (ctx->outer_context)
7247 return omp_is_private (ctx->outer_context, decl, simd);
7248 return false;
7251 /* Return true if DECL is private within a parallel region
7252 that binds to the current construct's context or in parallel
7253 region's REDUCTION clause. */
7255 static bool
7256 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
7258 splay_tree_node n;
7262 ctx = ctx->outer_context;
7263 if (ctx == NULL)
7265 if (is_global_var (decl))
7266 return false;
7268 /* References might be private, but might be shared too,
7269 when checking for copyprivate, assume they might be
7270 private, otherwise assume they might be shared. */
7271 if (copyprivate)
7272 return true;
7274 if (lang_hooks.decls.omp_privatize_by_reference (decl))
7275 return false;
7277 /* Treat C++ privatized non-static data members outside
7278 of the privatization the same. */
7279 if (omp_member_access_dummy_var (decl))
7280 return false;
7282 return true;
7285 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
7287 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7288 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
7289 continue;
7291 if (n != NULL)
7293 if ((n->value & GOVD_LOCAL) != 0
7294 && omp_member_access_dummy_var (decl))
7295 return false;
7296 return (n->value & GOVD_SHARED) == 0;
7299 while (ctx->region_type == ORT_WORKSHARE
7300 || ctx->region_type == ORT_SIMD
7301 || ctx->region_type == ORT_ACC);
7302 return false;
7305 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
7307 static tree
7308 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
7310 tree t = *tp;
7312 /* If this node has been visited, unmark it and keep looking. */
7313 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
7314 return t;
7316 if (IS_TYPE_OR_DECL_P (t))
7317 *walk_subtrees = 0;
7318 return NULL_TREE;
7321 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
7322 and previous omp contexts. */
7324 static void
7325 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
7326 enum omp_region_type region_type,
7327 enum tree_code code)
7329 struct gimplify_omp_ctx *ctx, *outer_ctx;
7330 tree c;
7331 hash_map<tree, tree> *struct_map_to_clause = NULL;
7332 tree *prev_list_p = NULL;
7334 ctx = new_omp_context (region_type);
7335 outer_ctx = ctx->outer_context;
7336 if (code == OMP_TARGET)
7338 if (!lang_GNU_Fortran ())
7339 ctx->target_map_pointers_as_0len_arrays = true;
7340 ctx->target_map_scalars_firstprivate = true;
7342 if (!lang_GNU_Fortran ())
7343 switch (code)
7345 case OMP_TARGET:
7346 case OMP_TARGET_DATA:
7347 case OMP_TARGET_ENTER_DATA:
7348 case OMP_TARGET_EXIT_DATA:
7349 case OACC_HOST_DATA:
7350 ctx->target_firstprivatize_array_bases = true;
7351 default:
7352 break;
7355 while ((c = *list_p) != NULL)
7357 bool remove = false;
7358 bool notice_outer = true;
7359 const char *check_non_private = NULL;
7360 unsigned int flags;
7361 tree decl;
7363 switch (OMP_CLAUSE_CODE (c))
7365 case OMP_CLAUSE_PRIVATE:
7366 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
7367 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
7369 flags |= GOVD_PRIVATE_OUTER_REF;
7370 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
7372 else
7373 notice_outer = false;
7374 goto do_add;
7375 case OMP_CLAUSE_SHARED:
7376 flags = GOVD_SHARED | GOVD_EXPLICIT;
7377 goto do_add;
7378 case OMP_CLAUSE_FIRSTPRIVATE:
7379 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
7380 check_non_private = "firstprivate";
7381 goto do_add;
7382 case OMP_CLAUSE_LASTPRIVATE:
7383 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
7384 check_non_private = "lastprivate";
7385 decl = OMP_CLAUSE_DECL (c);
7386 if (error_operand_p (decl))
7387 goto do_add;
7388 else if (outer_ctx
7389 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
7390 || outer_ctx->region_type == ORT_COMBINED_TEAMS)
7391 && splay_tree_lookup (outer_ctx->variables,
7392 (splay_tree_key) decl) == NULL)
7394 omp_add_variable (outer_ctx, decl, GOVD_SHARED | GOVD_SEEN);
7395 if (outer_ctx->outer_context)
7396 omp_notice_variable (outer_ctx->outer_context, decl, true);
7398 else if (outer_ctx
7399 && (outer_ctx->region_type & ORT_TASK) != 0
7400 && outer_ctx->combined_loop
7401 && splay_tree_lookup (outer_ctx->variables,
7402 (splay_tree_key) decl) == NULL)
7404 omp_add_variable (outer_ctx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
7405 if (outer_ctx->outer_context)
7406 omp_notice_variable (outer_ctx->outer_context, decl, true);
7408 else if (outer_ctx
7409 && (outer_ctx->region_type == ORT_WORKSHARE
7410 || outer_ctx->region_type == ORT_ACC)
7411 && outer_ctx->combined_loop
7412 && splay_tree_lookup (outer_ctx->variables,
7413 (splay_tree_key) decl) == NULL
7414 && !omp_check_private (outer_ctx, decl, false))
7416 omp_add_variable (outer_ctx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
7417 if (outer_ctx->outer_context
7418 && (outer_ctx->outer_context->region_type
7419 == ORT_COMBINED_PARALLEL)
7420 && splay_tree_lookup (outer_ctx->outer_context->variables,
7421 (splay_tree_key) decl) == NULL)
7423 struct gimplify_omp_ctx *octx = outer_ctx->outer_context;
7424 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
7425 if (octx->outer_context)
7427 octx = octx->outer_context;
7428 if (octx->region_type == ORT_WORKSHARE
7429 && octx->combined_loop
7430 && splay_tree_lookup (octx->variables,
7431 (splay_tree_key) decl) == NULL
7432 && !omp_check_private (octx, decl, false))
7434 omp_add_variable (octx, decl,
7435 GOVD_LASTPRIVATE | GOVD_SEEN);
7436 octx = octx->outer_context;
7437 if (octx
7438 && octx->region_type == ORT_COMBINED_TEAMS
7439 && (splay_tree_lookup (octx->variables,
7440 (splay_tree_key) decl)
7441 == NULL))
7443 omp_add_variable (octx, decl,
7444 GOVD_SHARED | GOVD_SEEN);
7445 octx = octx->outer_context;
7448 if (octx)
7449 omp_notice_variable (octx, decl, true);
7452 else if (outer_ctx->outer_context)
7453 omp_notice_variable (outer_ctx->outer_context, decl, true);
7455 goto do_add;
7456 case OMP_CLAUSE_REDUCTION:
7457 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
7458 /* OpenACC permits reductions on private variables. */
7459 if (!(region_type & ORT_ACC))
7460 check_non_private = "reduction";
7461 decl = OMP_CLAUSE_DECL (c);
7462 if (TREE_CODE (decl) == MEM_REF)
7464 tree type = TREE_TYPE (decl);
7465 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
7466 NULL, is_gimple_val, fb_rvalue, false)
7467 == GS_ERROR)
7469 remove = true;
7470 break;
7472 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
7473 if (DECL_P (v))
7475 omp_firstprivatize_variable (ctx, v);
7476 omp_notice_variable (ctx, v, true);
7478 decl = TREE_OPERAND (decl, 0);
7479 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
7481 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
7482 NULL, is_gimple_val, fb_rvalue, false)
7483 == GS_ERROR)
7485 remove = true;
7486 break;
7488 v = TREE_OPERAND (decl, 1);
7489 if (DECL_P (v))
7491 omp_firstprivatize_variable (ctx, v);
7492 omp_notice_variable (ctx, v, true);
7494 decl = TREE_OPERAND (decl, 0);
7496 if (TREE_CODE (decl) == ADDR_EXPR
7497 || TREE_CODE (decl) == INDIRECT_REF)
7498 decl = TREE_OPERAND (decl, 0);
7500 goto do_add_decl;
7501 case OMP_CLAUSE_LINEAR:
7502 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
7503 is_gimple_val, fb_rvalue) == GS_ERROR)
7505 remove = true;
7506 break;
7508 else
7510 if (code == OMP_SIMD
7511 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
7513 struct gimplify_omp_ctx *octx = outer_ctx;
7514 if (octx
7515 && octx->region_type == ORT_WORKSHARE
7516 && octx->combined_loop
7517 && !octx->distribute)
7519 if (octx->outer_context
7520 && (octx->outer_context->region_type
7521 == ORT_COMBINED_PARALLEL))
7522 octx = octx->outer_context->outer_context;
7523 else
7524 octx = octx->outer_context;
7526 if (octx
7527 && octx->region_type == ORT_WORKSHARE
7528 && octx->combined_loop
7529 && octx->distribute)
7531 error_at (OMP_CLAUSE_LOCATION (c),
7532 "%<linear%> clause for variable other than "
7533 "loop iterator specified on construct "
7534 "combined with %<distribute%>");
7535 remove = true;
7536 break;
7539 /* For combined #pragma omp parallel for simd, need to put
7540 lastprivate and perhaps firstprivate too on the
7541 parallel. Similarly for #pragma omp for simd. */
7542 struct gimplify_omp_ctx *octx = outer_ctx;
7543 decl = NULL_TREE;
7546 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
7547 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
7548 break;
7549 decl = OMP_CLAUSE_DECL (c);
7550 if (error_operand_p (decl))
7552 decl = NULL_TREE;
7553 break;
7555 flags = GOVD_SEEN;
7556 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
7557 flags |= GOVD_FIRSTPRIVATE;
7558 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
7559 flags |= GOVD_LASTPRIVATE;
7560 if (octx
7561 && octx->region_type == ORT_WORKSHARE
7562 && octx->combined_loop)
7564 if (octx->outer_context
7565 && (octx->outer_context->region_type
7566 == ORT_COMBINED_PARALLEL))
7567 octx = octx->outer_context;
7568 else if (omp_check_private (octx, decl, false))
7569 break;
7571 else if (octx
7572 && (octx->region_type & ORT_TASK) != 0
7573 && octx->combined_loop)
7575 else if (octx
7576 && octx->region_type == ORT_COMBINED_PARALLEL
7577 && ctx->region_type == ORT_WORKSHARE
7578 && octx == outer_ctx)
7579 flags = GOVD_SEEN | GOVD_SHARED;
7580 else if (octx
7581 && octx->region_type == ORT_COMBINED_TEAMS)
7582 flags = GOVD_SEEN | GOVD_SHARED;
7583 else if (octx
7584 && octx->region_type == ORT_COMBINED_TARGET)
7586 flags &= ~GOVD_LASTPRIVATE;
7587 if (flags == GOVD_SEEN)
7588 break;
7590 else
7591 break;
7592 splay_tree_node on
7593 = splay_tree_lookup (octx->variables,
7594 (splay_tree_key) decl);
7595 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
7597 octx = NULL;
7598 break;
7600 omp_add_variable (octx, decl, flags);
7601 if (octx->outer_context == NULL)
7602 break;
7603 octx = octx->outer_context;
7605 while (1);
7606 if (octx
7607 && decl
7608 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
7609 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
7610 omp_notice_variable (octx, decl, true);
7612 flags = GOVD_LINEAR | GOVD_EXPLICIT;
7613 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
7614 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
7616 notice_outer = false;
7617 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
7619 goto do_add;
7621 case OMP_CLAUSE_MAP:
7622 decl = OMP_CLAUSE_DECL (c);
7623 if (error_operand_p (decl))
7624 remove = true;
7625 switch (code)
7627 case OMP_TARGET:
7628 break;
7629 case OACC_DATA:
7630 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
7631 break;
7632 /* FALLTHRU */
7633 case OMP_TARGET_DATA:
7634 case OMP_TARGET_ENTER_DATA:
7635 case OMP_TARGET_EXIT_DATA:
7636 case OACC_ENTER_DATA:
7637 case OACC_EXIT_DATA:
7638 case OACC_HOST_DATA:
7639 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
7640 || (OMP_CLAUSE_MAP_KIND (c)
7641 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
7642 /* For target {,enter ,exit }data only the array slice is
7643 mapped, but not the pointer to it. */
7644 remove = true;
7645 break;
7646 default:
7647 break;
7649 if (remove)
7650 break;
7651 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
7653 struct gimplify_omp_ctx *octx;
7654 for (octx = outer_ctx; octx; octx = octx->outer_context)
7656 if (octx->region_type != ORT_ACC_HOST_DATA)
7657 break;
7658 splay_tree_node n2
7659 = splay_tree_lookup (octx->variables,
7660 (splay_tree_key) decl);
7661 if (n2)
7662 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
7663 "declared in enclosing %<host_data%> region",
7664 DECL_NAME (decl));
7667 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
7668 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
7669 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
7670 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
7671 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
7673 remove = true;
7674 break;
7676 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
7677 || (OMP_CLAUSE_MAP_KIND (c)
7678 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
7679 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
7681 OMP_CLAUSE_SIZE (c)
7682 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
7683 false);
7684 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
7685 GOVD_FIRSTPRIVATE | GOVD_SEEN);
7687 if (!DECL_P (decl))
7689 tree d = decl, *pd;
7690 if (TREE_CODE (d) == ARRAY_REF)
7692 while (TREE_CODE (d) == ARRAY_REF)
7693 d = TREE_OPERAND (d, 0);
7694 if (TREE_CODE (d) == COMPONENT_REF
7695 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
7696 decl = d;
7698 pd = &OMP_CLAUSE_DECL (c);
7699 if (d == decl
7700 && TREE_CODE (decl) == INDIRECT_REF
7701 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
7702 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
7703 == REFERENCE_TYPE))
7705 pd = &TREE_OPERAND (decl, 0);
7706 decl = TREE_OPERAND (decl, 0);
7708 if (TREE_CODE (decl) == COMPONENT_REF)
7710 while (TREE_CODE (decl) == COMPONENT_REF)
7711 decl = TREE_OPERAND (decl, 0);
7712 if (TREE_CODE (decl) == INDIRECT_REF
7713 && DECL_P (TREE_OPERAND (decl, 0))
7714 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
7715 == REFERENCE_TYPE))
7716 decl = TREE_OPERAND (decl, 0);
7718 if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue, fb_lvalue)
7719 == GS_ERROR)
7721 remove = true;
7722 break;
7724 if (DECL_P (decl))
7726 if (error_operand_p (decl))
7728 remove = true;
7729 break;
7732 tree stype = TREE_TYPE (decl);
7733 if (TREE_CODE (stype) == REFERENCE_TYPE)
7734 stype = TREE_TYPE (stype);
7735 if (TYPE_SIZE_UNIT (stype) == NULL
7736 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
7738 error_at (OMP_CLAUSE_LOCATION (c),
7739 "mapping field %qE of variable length "
7740 "structure", OMP_CLAUSE_DECL (c));
7741 remove = true;
7742 break;
7745 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
7747 /* Error recovery. */
7748 if (prev_list_p == NULL)
7750 remove = true;
7751 break;
7753 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
7755 tree ch = OMP_CLAUSE_CHAIN (*prev_list_p);
7756 if (ch == NULL_TREE || OMP_CLAUSE_CHAIN (ch) != c)
7758 remove = true;
7759 break;
7764 tree offset;
7765 HOST_WIDE_INT bitsize, bitpos;
7766 machine_mode mode;
7767 int unsignedp, reversep, volatilep = 0;
7768 tree base = OMP_CLAUSE_DECL (c);
7769 while (TREE_CODE (base) == ARRAY_REF)
7770 base = TREE_OPERAND (base, 0);
7771 if (TREE_CODE (base) == INDIRECT_REF)
7772 base = TREE_OPERAND (base, 0);
7773 base = get_inner_reference (base, &bitsize, &bitpos, &offset,
7774 &mode, &unsignedp, &reversep,
7775 &volatilep);
7776 tree orig_base = base;
7777 if ((TREE_CODE (base) == INDIRECT_REF
7778 || (TREE_CODE (base) == MEM_REF
7779 && integer_zerop (TREE_OPERAND (base, 1))))
7780 && DECL_P (TREE_OPERAND (base, 0))
7781 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0)))
7782 == REFERENCE_TYPE))
7783 base = TREE_OPERAND (base, 0);
7784 gcc_assert (base == decl
7785 && (offset == NULL_TREE
7786 || TREE_CODE (offset) == INTEGER_CST));
7788 splay_tree_node n
7789 = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7790 bool ptr = (OMP_CLAUSE_MAP_KIND (c)
7791 == GOMP_MAP_ALWAYS_POINTER);
7792 if (n == NULL || (n->value & GOVD_MAP) == 0)
7794 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7795 OMP_CLAUSE_MAP);
7796 OMP_CLAUSE_SET_MAP_KIND (l, GOMP_MAP_STRUCT);
7797 if (orig_base != base)
7798 OMP_CLAUSE_DECL (l) = unshare_expr (orig_base);
7799 else
7800 OMP_CLAUSE_DECL (l) = decl;
7801 OMP_CLAUSE_SIZE (l) = size_int (1);
7802 if (struct_map_to_clause == NULL)
7803 struct_map_to_clause = new hash_map<tree, tree>;
7804 struct_map_to_clause->put (decl, l);
7805 if (ptr)
7807 enum gomp_map_kind mkind
7808 = code == OMP_TARGET_EXIT_DATA
7809 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
7810 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7811 OMP_CLAUSE_MAP);
7812 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
7813 OMP_CLAUSE_DECL (c2)
7814 = unshare_expr (OMP_CLAUSE_DECL (c));
7815 OMP_CLAUSE_CHAIN (c2) = *prev_list_p;
7816 OMP_CLAUSE_SIZE (c2)
7817 = TYPE_SIZE_UNIT (ptr_type_node);
7818 OMP_CLAUSE_CHAIN (l) = c2;
7819 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
7821 tree c4 = OMP_CLAUSE_CHAIN (*prev_list_p);
7822 tree c3
7823 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7824 OMP_CLAUSE_MAP);
7825 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
7826 OMP_CLAUSE_DECL (c3)
7827 = unshare_expr (OMP_CLAUSE_DECL (c4));
7828 OMP_CLAUSE_SIZE (c3)
7829 = TYPE_SIZE_UNIT (ptr_type_node);
7830 OMP_CLAUSE_CHAIN (c3) = *prev_list_p;
7831 OMP_CLAUSE_CHAIN (c2) = c3;
7833 *prev_list_p = l;
7834 prev_list_p = NULL;
7836 else
7838 OMP_CLAUSE_CHAIN (l) = c;
7839 *list_p = l;
7840 list_p = &OMP_CLAUSE_CHAIN (l);
7842 if (orig_base != base && code == OMP_TARGET)
7844 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7845 OMP_CLAUSE_MAP);
7846 enum gomp_map_kind mkind
7847 = GOMP_MAP_FIRSTPRIVATE_REFERENCE;
7848 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
7849 OMP_CLAUSE_DECL (c2) = decl;
7850 OMP_CLAUSE_SIZE (c2) = size_zero_node;
7851 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
7852 OMP_CLAUSE_CHAIN (l) = c2;
7854 flags = GOVD_MAP | GOVD_EXPLICIT;
7855 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) || ptr)
7856 flags |= GOVD_SEEN;
7857 goto do_add_decl;
7859 else
7861 tree *osc = struct_map_to_clause->get (decl);
7862 tree *sc = NULL, *scp = NULL;
7863 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) || ptr)
7864 n->value |= GOVD_SEEN;
7865 offset_int o1, o2;
7866 if (offset)
7867 o1 = wi::to_offset (offset);
7868 else
7869 o1 = 0;
7870 if (bitpos)
7871 o1 = o1 + bitpos / BITS_PER_UNIT;
7872 sc = &OMP_CLAUSE_CHAIN (*osc);
7873 if (*sc != c
7874 && (OMP_CLAUSE_MAP_KIND (*sc)
7875 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
7876 sc = &OMP_CLAUSE_CHAIN (*sc);
7877 for (; *sc != c; sc = &OMP_CLAUSE_CHAIN (*sc))
7878 if (ptr && sc == prev_list_p)
7879 break;
7880 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc))
7881 != COMPONENT_REF
7882 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
7883 != INDIRECT_REF)
7884 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
7885 != ARRAY_REF))
7886 break;
7887 else
7889 tree offset2;
7890 HOST_WIDE_INT bitsize2, bitpos2;
7891 base = OMP_CLAUSE_DECL (*sc);
7892 if (TREE_CODE (base) == ARRAY_REF)
7894 while (TREE_CODE (base) == ARRAY_REF)
7895 base = TREE_OPERAND (base, 0);
7896 if (TREE_CODE (base) != COMPONENT_REF
7897 || (TREE_CODE (TREE_TYPE (base))
7898 != ARRAY_TYPE))
7899 break;
7901 else if (TREE_CODE (base) == INDIRECT_REF
7902 && (TREE_CODE (TREE_OPERAND (base, 0))
7903 == COMPONENT_REF)
7904 && (TREE_CODE (TREE_TYPE
7905 (TREE_OPERAND (base, 0)))
7906 == REFERENCE_TYPE))
7907 base = TREE_OPERAND (base, 0);
7908 base = get_inner_reference (base, &bitsize2,
7909 &bitpos2, &offset2,
7910 &mode, &unsignedp,
7911 &reversep, &volatilep);
7912 if ((TREE_CODE (base) == INDIRECT_REF
7913 || (TREE_CODE (base) == MEM_REF
7914 && integer_zerop (TREE_OPERAND (base,
7915 1))))
7916 && DECL_P (TREE_OPERAND (base, 0))
7917 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base,
7918 0)))
7919 == REFERENCE_TYPE))
7920 base = TREE_OPERAND (base, 0);
7921 if (base != decl)
7922 break;
7923 if (scp)
7924 continue;
7925 gcc_assert (offset == NULL_TREE
7926 || TREE_CODE (offset) == INTEGER_CST);
7927 tree d1 = OMP_CLAUSE_DECL (*sc);
7928 tree d2 = OMP_CLAUSE_DECL (c);
7929 while (TREE_CODE (d1) == ARRAY_REF)
7930 d1 = TREE_OPERAND (d1, 0);
7931 while (TREE_CODE (d2) == ARRAY_REF)
7932 d2 = TREE_OPERAND (d2, 0);
7933 if (TREE_CODE (d1) == INDIRECT_REF)
7934 d1 = TREE_OPERAND (d1, 0);
7935 if (TREE_CODE (d2) == INDIRECT_REF)
7936 d2 = TREE_OPERAND (d2, 0);
7937 while (TREE_CODE (d1) == COMPONENT_REF)
7938 if (TREE_CODE (d2) == COMPONENT_REF
7939 && TREE_OPERAND (d1, 1)
7940 == TREE_OPERAND (d2, 1))
7942 d1 = TREE_OPERAND (d1, 0);
7943 d2 = TREE_OPERAND (d2, 0);
7945 else
7946 break;
7947 if (d1 == d2)
7949 error_at (OMP_CLAUSE_LOCATION (c),
7950 "%qE appears more than once in map "
7951 "clauses", OMP_CLAUSE_DECL (c));
7952 remove = true;
7953 break;
7955 if (offset2)
7956 o2 = wi::to_offset (offset2);
7957 else
7958 o2 = 0;
7959 if (bitpos2)
7960 o2 = o2 + bitpos2 / BITS_PER_UNIT;
7961 if (wi::ltu_p (o1, o2)
7962 || (wi::eq_p (o1, o2) && bitpos < bitpos2))
7964 if (ptr)
7965 scp = sc;
7966 else
7967 break;
7970 if (remove)
7971 break;
7972 OMP_CLAUSE_SIZE (*osc)
7973 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc),
7974 size_one_node);
7975 if (ptr)
7977 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7978 OMP_CLAUSE_MAP);
7979 tree cl = NULL_TREE;
7980 enum gomp_map_kind mkind
7981 = code == OMP_TARGET_EXIT_DATA
7982 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
7983 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
7984 OMP_CLAUSE_DECL (c2)
7985 = unshare_expr (OMP_CLAUSE_DECL (c));
7986 OMP_CLAUSE_CHAIN (c2) = scp ? *scp : *prev_list_p;
7987 OMP_CLAUSE_SIZE (c2)
7988 = TYPE_SIZE_UNIT (ptr_type_node);
7989 cl = scp ? *prev_list_p : c2;
7990 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
7992 tree c4 = OMP_CLAUSE_CHAIN (*prev_list_p);
7993 tree c3
7994 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7995 OMP_CLAUSE_MAP);
7996 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
7997 OMP_CLAUSE_DECL (c3)
7998 = unshare_expr (OMP_CLAUSE_DECL (c4));
7999 OMP_CLAUSE_SIZE (c3)
8000 = TYPE_SIZE_UNIT (ptr_type_node);
8001 OMP_CLAUSE_CHAIN (c3) = *prev_list_p;
8002 if (!scp)
8003 OMP_CLAUSE_CHAIN (c2) = c3;
8004 else
8005 cl = c3;
8007 if (scp)
8008 *scp = c2;
8009 if (sc == prev_list_p)
8011 *sc = cl;
8012 prev_list_p = NULL;
8014 else
8016 *prev_list_p = OMP_CLAUSE_CHAIN (c);
8017 list_p = prev_list_p;
8018 prev_list_p = NULL;
8019 OMP_CLAUSE_CHAIN (c) = *sc;
8020 *sc = cl;
8021 continue;
8024 else if (*sc != c)
8026 *list_p = OMP_CLAUSE_CHAIN (c);
8027 OMP_CLAUSE_CHAIN (c) = *sc;
8028 *sc = c;
8029 continue;
8033 if (!remove
8034 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ALWAYS_POINTER
8035 && OMP_CLAUSE_CHAIN (c)
8036 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c)) == OMP_CLAUSE_MAP
8037 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
8038 == GOMP_MAP_ALWAYS_POINTER))
8039 prev_list_p = list_p;
8040 break;
8042 flags = GOVD_MAP | GOVD_EXPLICIT;
8043 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
8044 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM)
8045 flags |= GOVD_MAP_ALWAYS_TO;
8046 goto do_add;
8048 case OMP_CLAUSE_DEPEND:
8049 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
8051 tree deps = OMP_CLAUSE_DECL (c);
8052 while (deps && TREE_CODE (deps) == TREE_LIST)
8054 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
8055 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
8056 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
8057 pre_p, NULL, is_gimple_val, fb_rvalue);
8058 deps = TREE_CHAIN (deps);
8060 break;
8062 else if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
8063 break;
8064 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8066 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8067 NULL, is_gimple_val, fb_rvalue);
8068 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8070 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8072 remove = true;
8073 break;
8075 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
8076 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8077 is_gimple_val, fb_rvalue) == GS_ERROR)
8079 remove = true;
8080 break;
8082 break;
8084 case OMP_CLAUSE_TO:
8085 case OMP_CLAUSE_FROM:
8086 case OMP_CLAUSE__CACHE_:
8087 decl = OMP_CLAUSE_DECL (c);
8088 if (error_operand_p (decl))
8090 remove = true;
8091 break;
8093 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
8094 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
8095 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
8096 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
8097 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
8099 remove = true;
8100 break;
8102 if (!DECL_P (decl))
8104 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
8105 NULL, is_gimple_lvalue, fb_lvalue)
8106 == GS_ERROR)
8108 remove = true;
8109 break;
8111 break;
8113 goto do_notice;
8115 case OMP_CLAUSE_USE_DEVICE_PTR:
8116 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
8117 goto do_add;
8118 case OMP_CLAUSE_IS_DEVICE_PTR:
8119 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
8120 goto do_add;
8122 do_add:
8123 decl = OMP_CLAUSE_DECL (c);
8124 do_add_decl:
8125 if (error_operand_p (decl))
8127 remove = true;
8128 break;
8130 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
8132 tree t = omp_member_access_dummy_var (decl);
8133 if (t)
8135 tree v = DECL_VALUE_EXPR (decl);
8136 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
8137 if (outer_ctx)
8138 omp_notice_variable (outer_ctx, t, true);
8141 if (code == OACC_DATA
8142 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
8143 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
8144 flags |= GOVD_MAP_0LEN_ARRAY;
8145 omp_add_variable (ctx, decl, flags);
8146 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
8147 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
8149 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
8150 GOVD_LOCAL | GOVD_SEEN);
8151 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
8152 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
8153 find_decl_expr,
8154 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
8155 NULL) == NULL_TREE)
8156 omp_add_variable (ctx,
8157 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
8158 GOVD_LOCAL | GOVD_SEEN);
8159 gimplify_omp_ctxp = ctx;
8160 push_gimplify_context ();
8162 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
8163 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
8165 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
8166 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
8167 pop_gimplify_context
8168 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
8169 push_gimplify_context ();
8170 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
8171 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
8172 pop_gimplify_context
8173 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
8174 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
8175 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
8177 gimplify_omp_ctxp = outer_ctx;
8179 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
8180 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
8182 gimplify_omp_ctxp = ctx;
8183 push_gimplify_context ();
8184 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
8186 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
8187 NULL, NULL);
8188 TREE_SIDE_EFFECTS (bind) = 1;
8189 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
8190 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
8192 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
8193 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
8194 pop_gimplify_context
8195 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
8196 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
8198 gimplify_omp_ctxp = outer_ctx;
8200 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
8201 && OMP_CLAUSE_LINEAR_STMT (c))
8203 gimplify_omp_ctxp = ctx;
8204 push_gimplify_context ();
8205 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
8207 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
8208 NULL, NULL);
8209 TREE_SIDE_EFFECTS (bind) = 1;
8210 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
8211 OMP_CLAUSE_LINEAR_STMT (c) = bind;
8213 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
8214 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
8215 pop_gimplify_context
8216 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
8217 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
8219 gimplify_omp_ctxp = outer_ctx;
8221 if (notice_outer)
8222 goto do_notice;
8223 break;
8225 case OMP_CLAUSE_COPYIN:
8226 case OMP_CLAUSE_COPYPRIVATE:
8227 decl = OMP_CLAUSE_DECL (c);
8228 if (error_operand_p (decl))
8230 remove = true;
8231 break;
8233 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
8234 && !remove
8235 && !omp_check_private (ctx, decl, true))
8237 remove = true;
8238 if (is_global_var (decl))
8240 if (DECL_THREAD_LOCAL_P (decl))
8241 remove = false;
8242 else if (DECL_HAS_VALUE_EXPR_P (decl))
8244 tree value = get_base_address (DECL_VALUE_EXPR (decl));
8246 if (value
8247 && DECL_P (value)
8248 && DECL_THREAD_LOCAL_P (value))
8249 remove = false;
8252 if (remove)
8253 error_at (OMP_CLAUSE_LOCATION (c),
8254 "copyprivate variable %qE is not threadprivate"
8255 " or private in outer context", DECL_NAME (decl));
8257 do_notice:
8258 if (outer_ctx)
8259 omp_notice_variable (outer_ctx, decl, true);
8260 if (check_non_private
8261 && region_type == ORT_WORKSHARE
8262 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
8263 || decl == OMP_CLAUSE_DECL (c)
8264 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
8265 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
8266 == ADDR_EXPR
8267 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
8268 == POINTER_PLUS_EXPR
8269 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
8270 (OMP_CLAUSE_DECL (c), 0), 0))
8271 == ADDR_EXPR)))))
8272 && omp_check_private (ctx, decl, false))
8274 error ("%s variable %qE is private in outer context",
8275 check_non_private, DECL_NAME (decl));
8276 remove = true;
8278 break;
8280 case OMP_CLAUSE_IF:
8281 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
8282 && OMP_CLAUSE_IF_MODIFIER (c) != code)
8284 const char *p[2];
8285 for (int i = 0; i < 2; i++)
8286 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
8288 case OMP_PARALLEL: p[i] = "parallel"; break;
8289 case OMP_TASK: p[i] = "task"; break;
8290 case OMP_TASKLOOP: p[i] = "taskloop"; break;
8291 case OMP_TARGET_DATA: p[i] = "target data"; break;
8292 case OMP_TARGET: p[i] = "target"; break;
8293 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
8294 case OMP_TARGET_ENTER_DATA:
8295 p[i] = "target enter data"; break;
8296 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
8297 default: gcc_unreachable ();
8299 error_at (OMP_CLAUSE_LOCATION (c),
8300 "expected %qs %<if%> clause modifier rather than %qs",
8301 p[0], p[1]);
8302 remove = true;
8304 /* Fall through. */
8306 case OMP_CLAUSE_FINAL:
8307 OMP_CLAUSE_OPERAND (c, 0)
8308 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
8309 /* Fall through. */
8311 case OMP_CLAUSE_SCHEDULE:
8312 case OMP_CLAUSE_NUM_THREADS:
8313 case OMP_CLAUSE_NUM_TEAMS:
8314 case OMP_CLAUSE_THREAD_LIMIT:
8315 case OMP_CLAUSE_DIST_SCHEDULE:
8316 case OMP_CLAUSE_DEVICE:
8317 case OMP_CLAUSE_PRIORITY:
8318 case OMP_CLAUSE_GRAINSIZE:
8319 case OMP_CLAUSE_NUM_TASKS:
8320 case OMP_CLAUSE_HINT:
8321 case OMP_CLAUSE__CILK_FOR_COUNT_:
8322 case OMP_CLAUSE_ASYNC:
8323 case OMP_CLAUSE_WAIT:
8324 case OMP_CLAUSE_NUM_GANGS:
8325 case OMP_CLAUSE_NUM_WORKERS:
8326 case OMP_CLAUSE_VECTOR_LENGTH:
8327 case OMP_CLAUSE_WORKER:
8328 case OMP_CLAUSE_VECTOR:
8329 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
8330 is_gimple_val, fb_rvalue) == GS_ERROR)
8331 remove = true;
8332 break;
8334 case OMP_CLAUSE_GANG:
8335 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
8336 is_gimple_val, fb_rvalue) == GS_ERROR)
8337 remove = true;
8338 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
8339 is_gimple_val, fb_rvalue) == GS_ERROR)
8340 remove = true;
8341 break;
8343 case OMP_CLAUSE_NOWAIT:
8344 case OMP_CLAUSE_ORDERED:
8345 case OMP_CLAUSE_UNTIED:
8346 case OMP_CLAUSE_COLLAPSE:
8347 case OMP_CLAUSE_TILE:
8348 case OMP_CLAUSE_AUTO:
8349 case OMP_CLAUSE_SEQ:
8350 case OMP_CLAUSE_INDEPENDENT:
8351 case OMP_CLAUSE_MERGEABLE:
8352 case OMP_CLAUSE_PROC_BIND:
8353 case OMP_CLAUSE_SAFELEN:
8354 case OMP_CLAUSE_SIMDLEN:
8355 case OMP_CLAUSE_NOGROUP:
8356 case OMP_CLAUSE_THREADS:
8357 case OMP_CLAUSE_SIMD:
8358 break;
8360 case OMP_CLAUSE_DEFAULTMAP:
8361 ctx->target_map_scalars_firstprivate = false;
8362 break;
8364 case OMP_CLAUSE_ALIGNED:
8365 decl = OMP_CLAUSE_DECL (c);
8366 if (error_operand_p (decl))
8368 remove = true;
8369 break;
8371 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
8372 is_gimple_val, fb_rvalue) == GS_ERROR)
8374 remove = true;
8375 break;
8377 if (!is_global_var (decl)
8378 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
8379 omp_add_variable (ctx, decl, GOVD_ALIGNED);
8380 break;
8382 case OMP_CLAUSE_DEFAULT:
8383 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
8384 break;
8386 default:
8387 gcc_unreachable ();
8390 if (code == OACC_DATA
8391 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
8392 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
8393 remove = true;
8394 if (remove)
8395 *list_p = OMP_CLAUSE_CHAIN (c);
8396 else
8397 list_p = &OMP_CLAUSE_CHAIN (c);
8400 gimplify_omp_ctxp = ctx;
8401 if (struct_map_to_clause)
8402 delete struct_map_to_clause;
8405 /* Return true if DECL is a candidate for shared to firstprivate
8406 optimization. We only consider non-addressable scalars, not
8407 too big, and not references. */
8409 static bool
8410 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
8412 if (TREE_ADDRESSABLE (decl))
8413 return false;
8414 tree type = TREE_TYPE (decl);
8415 if (!is_gimple_reg_type (type)
8416 || TREE_CODE (type) == REFERENCE_TYPE
8417 || TREE_ADDRESSABLE (type))
8418 return false;
8419 /* Don't optimize too large decls, as each thread/task will have
8420 its own. */
8421 HOST_WIDE_INT len = int_size_in_bytes (type);
8422 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
8423 return false;
8424 if (lang_hooks.decls.omp_privatize_by_reference (decl))
8425 return false;
8426 return true;
8429 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
8430 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
8431 GOVD_WRITTEN in outer contexts. */
8433 static void
8434 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
8436 for (; ctx; ctx = ctx->outer_context)
8438 splay_tree_node n = splay_tree_lookup (ctx->variables,
8439 (splay_tree_key) decl);
8440 if (n == NULL)
8441 continue;
8442 else if (n->value & GOVD_SHARED)
8444 n->value |= GOVD_WRITTEN;
8445 return;
8447 else if (n->value & GOVD_DATA_SHARE_CLASS)
8448 return;
8452 /* Helper callback for walk_gimple_seq to discover possible stores
8453 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
8454 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
8455 for those. */
8457 static tree
8458 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
8460 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
8462 *walk_subtrees = 0;
8463 if (!wi->is_lhs)
8464 return NULL_TREE;
8466 tree op = *tp;
8469 if (handled_component_p (op))
8470 op = TREE_OPERAND (op, 0);
8471 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
8472 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
8473 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
8474 else
8475 break;
8477 while (1);
8478 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
8479 return NULL_TREE;
8481 omp_mark_stores (gimplify_omp_ctxp, op);
8482 return NULL_TREE;
8485 /* Helper callback for walk_gimple_seq to discover possible stores
8486 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
8487 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
8488 for those. */
8490 static tree
8491 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
8492 bool *handled_ops_p,
8493 struct walk_stmt_info *wi)
8495 gimple *stmt = gsi_stmt (*gsi_p);
8496 switch (gimple_code (stmt))
8498 /* Don't recurse on OpenMP constructs for which
8499 gimplify_adjust_omp_clauses already handled the bodies,
8500 except handle gimple_omp_for_pre_body. */
8501 case GIMPLE_OMP_FOR:
8502 *handled_ops_p = true;
8503 if (gimple_omp_for_pre_body (stmt))
8504 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
8505 omp_find_stores_stmt, omp_find_stores_op, wi);
8506 break;
8507 case GIMPLE_OMP_PARALLEL:
8508 case GIMPLE_OMP_TASK:
8509 case GIMPLE_OMP_SECTIONS:
8510 case GIMPLE_OMP_SINGLE:
8511 case GIMPLE_OMP_TARGET:
8512 case GIMPLE_OMP_TEAMS:
8513 case GIMPLE_OMP_CRITICAL:
8514 *handled_ops_p = true;
8515 break;
8516 default:
8517 break;
8519 return NULL_TREE;
8522 struct gimplify_adjust_omp_clauses_data
8524 tree *list_p;
8525 gimple_seq *pre_p;
8528 /* For all variables that were not actually used within the context,
8529 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
8531 static int
8532 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
8534 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
8535 gimple_seq *pre_p
8536 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
8537 tree decl = (tree) n->key;
8538 unsigned flags = n->value;
8539 enum omp_clause_code code;
8540 tree clause;
8541 bool private_debug;
8543 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
8544 return 0;
8545 if ((flags & GOVD_SEEN) == 0)
8546 return 0;
8547 if (flags & GOVD_DEBUG_PRIVATE)
8549 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_PRIVATE);
8550 private_debug = true;
8552 else if (flags & GOVD_MAP)
8553 private_debug = false;
8554 else
8555 private_debug
8556 = lang_hooks.decls.omp_private_debug_clause (decl,
8557 !!(flags & GOVD_SHARED));
8558 if (private_debug)
8559 code = OMP_CLAUSE_PRIVATE;
8560 else if (flags & GOVD_MAP)
8562 code = OMP_CLAUSE_MAP;
8563 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
8564 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
8566 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
8567 return 0;
8570 else if (flags & GOVD_SHARED)
8572 if (is_global_var (decl))
8574 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
8575 while (ctx != NULL)
8577 splay_tree_node on
8578 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8579 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
8580 | GOVD_PRIVATE | GOVD_REDUCTION
8581 | GOVD_LINEAR | GOVD_MAP)) != 0)
8582 break;
8583 ctx = ctx->outer_context;
8585 if (ctx == NULL)
8586 return 0;
8588 code = OMP_CLAUSE_SHARED;
8590 else if (flags & GOVD_PRIVATE)
8591 code = OMP_CLAUSE_PRIVATE;
8592 else if (flags & GOVD_FIRSTPRIVATE)
8594 code = OMP_CLAUSE_FIRSTPRIVATE;
8595 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
8596 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
8597 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
8599 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
8600 "%<target%> construct", decl);
8601 return 0;
8604 else if (flags & GOVD_LASTPRIVATE)
8605 code = OMP_CLAUSE_LASTPRIVATE;
8606 else if (flags & GOVD_ALIGNED)
8607 return 0;
8608 else
8609 gcc_unreachable ();
8611 if (((flags & GOVD_LASTPRIVATE)
8612 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
8613 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8614 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8616 tree chain = *list_p;
8617 clause = build_omp_clause (input_location, code);
8618 OMP_CLAUSE_DECL (clause) = decl;
8619 OMP_CLAUSE_CHAIN (clause) = chain;
8620 if (private_debug)
8621 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
8622 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
8623 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
8624 else if (code == OMP_CLAUSE_SHARED
8625 && (flags & GOVD_WRITTEN) == 0
8626 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8627 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
8628 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
8629 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
8630 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
8632 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
8633 OMP_CLAUSE_DECL (nc) = decl;
8634 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
8635 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
8636 OMP_CLAUSE_DECL (clause)
8637 = build_simple_mem_ref_loc (input_location, decl);
8638 OMP_CLAUSE_DECL (clause)
8639 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
8640 build_int_cst (build_pointer_type (char_type_node), 0));
8641 OMP_CLAUSE_SIZE (clause) = size_zero_node;
8642 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8643 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
8644 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
8645 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
8646 OMP_CLAUSE_CHAIN (nc) = chain;
8647 OMP_CLAUSE_CHAIN (clause) = nc;
8648 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8649 gimplify_omp_ctxp = ctx->outer_context;
8650 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
8651 pre_p, NULL, is_gimple_val, fb_rvalue);
8652 gimplify_omp_ctxp = ctx;
8654 else if (code == OMP_CLAUSE_MAP)
8656 int kind = (flags & GOVD_MAP_TO_ONLY
8657 ? GOMP_MAP_TO
8658 : GOMP_MAP_TOFROM);
8659 if (flags & GOVD_MAP_FORCE)
8660 kind |= GOMP_MAP_FLAG_FORCE;
8661 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
8662 if (DECL_SIZE (decl)
8663 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
8665 tree decl2 = DECL_VALUE_EXPR (decl);
8666 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
8667 decl2 = TREE_OPERAND (decl2, 0);
8668 gcc_assert (DECL_P (decl2));
8669 tree mem = build_simple_mem_ref (decl2);
8670 OMP_CLAUSE_DECL (clause) = mem;
8671 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
8672 if (gimplify_omp_ctxp->outer_context)
8674 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
8675 omp_notice_variable (ctx, decl2, true);
8676 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
8678 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
8679 OMP_CLAUSE_MAP);
8680 OMP_CLAUSE_DECL (nc) = decl;
8681 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8682 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
8683 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
8684 else
8685 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
8686 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
8687 OMP_CLAUSE_CHAIN (clause) = nc;
8689 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
8690 && lang_hooks.decls.omp_privatize_by_reference (decl))
8692 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
8693 OMP_CLAUSE_SIZE (clause)
8694 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
8695 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8696 gimplify_omp_ctxp = ctx->outer_context;
8697 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
8698 pre_p, NULL, is_gimple_val, fb_rvalue);
8699 gimplify_omp_ctxp = ctx;
8700 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
8701 OMP_CLAUSE_MAP);
8702 OMP_CLAUSE_DECL (nc) = decl;
8703 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8704 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
8705 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
8706 OMP_CLAUSE_CHAIN (clause) = nc;
8708 else
8709 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
8711 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
8713 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
8714 OMP_CLAUSE_DECL (nc) = decl;
8715 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
8716 OMP_CLAUSE_CHAIN (nc) = chain;
8717 OMP_CLAUSE_CHAIN (clause) = nc;
8718 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8719 gimplify_omp_ctxp = ctx->outer_context;
8720 lang_hooks.decls.omp_finish_clause (nc, pre_p);
8721 gimplify_omp_ctxp = ctx;
8723 *list_p = clause;
8724 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8725 gimplify_omp_ctxp = ctx->outer_context;
8726 lang_hooks.decls.omp_finish_clause (clause, pre_p);
8727 if (gimplify_omp_ctxp)
8728 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
8729 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
8730 && DECL_P (OMP_CLAUSE_SIZE (clause)))
8731 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
8732 true);
8733 gimplify_omp_ctxp = ctx;
8734 return 0;
8737 static void
8738 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
8739 enum tree_code code)
8741 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8742 tree c, decl;
8744 if (body)
8746 struct gimplify_omp_ctx *octx;
8747 for (octx = ctx; octx; octx = octx->outer_context)
8748 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
8749 break;
8750 if (octx)
8752 struct walk_stmt_info wi;
8753 memset (&wi, 0, sizeof (wi));
8754 walk_gimple_seq (body, omp_find_stores_stmt,
8755 omp_find_stores_op, &wi);
8758 while ((c = *list_p) != NULL)
8760 splay_tree_node n;
8761 bool remove = false;
8763 switch (OMP_CLAUSE_CODE (c))
8765 case OMP_CLAUSE_FIRSTPRIVATE:
8766 if ((ctx->region_type & ORT_TARGET)
8767 && (ctx->region_type & ORT_ACC) == 0
8768 && TYPE_ATOMIC (strip_array_types
8769 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
8771 error_at (OMP_CLAUSE_LOCATION (c),
8772 "%<_Atomic%> %qD in %<firstprivate%> clause on "
8773 "%<target%> construct", OMP_CLAUSE_DECL (c));
8774 remove = true;
8775 break;
8777 /* FALLTHRU */
8778 case OMP_CLAUSE_PRIVATE:
8779 case OMP_CLAUSE_SHARED:
8780 case OMP_CLAUSE_LINEAR:
8781 decl = OMP_CLAUSE_DECL (c);
8782 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8783 remove = !(n->value & GOVD_SEEN);
8784 if (! remove)
8786 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
8787 if ((n->value & GOVD_DEBUG_PRIVATE)
8788 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
8790 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
8791 || ((n->value & GOVD_DATA_SHARE_CLASS)
8792 == GOVD_PRIVATE));
8793 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
8794 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
8796 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
8797 && (n->value & GOVD_WRITTEN) == 0
8798 && DECL_P (decl)
8799 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8800 OMP_CLAUSE_SHARED_READONLY (c) = 1;
8801 else if (DECL_P (decl)
8802 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
8803 && (n->value & GOVD_WRITTEN) != 1)
8804 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
8805 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
8806 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8807 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8809 break;
8811 case OMP_CLAUSE_LASTPRIVATE:
8812 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
8813 accurately reflect the presence of a FIRSTPRIVATE clause. */
8814 decl = OMP_CLAUSE_DECL (c);
8815 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8816 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
8817 = (n->value & GOVD_FIRSTPRIVATE) != 0;
8818 if (code == OMP_DISTRIBUTE
8819 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
8821 remove = true;
8822 error_at (OMP_CLAUSE_LOCATION (c),
8823 "same variable used in %<firstprivate%> and "
8824 "%<lastprivate%> clauses on %<distribute%> "
8825 "construct");
8827 if (!remove
8828 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
8829 && DECL_P (decl)
8830 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8831 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8832 break;
8834 case OMP_CLAUSE_ALIGNED:
8835 decl = OMP_CLAUSE_DECL (c);
8836 if (!is_global_var (decl))
8838 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8839 remove = n == NULL || !(n->value & GOVD_SEEN);
8840 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
8842 struct gimplify_omp_ctx *octx;
8843 if (n != NULL
8844 && (n->value & (GOVD_DATA_SHARE_CLASS
8845 & ~GOVD_FIRSTPRIVATE)))
8846 remove = true;
8847 else
8848 for (octx = ctx->outer_context; octx;
8849 octx = octx->outer_context)
8851 n = splay_tree_lookup (octx->variables,
8852 (splay_tree_key) decl);
8853 if (n == NULL)
8854 continue;
8855 if (n->value & GOVD_LOCAL)
8856 break;
8857 /* We have to avoid assigning a shared variable
8858 to itself when trying to add
8859 __builtin_assume_aligned. */
8860 if (n->value & GOVD_SHARED)
8862 remove = true;
8863 break;
8868 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
8870 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8871 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
8872 remove = true;
8874 break;
8876 case OMP_CLAUSE_MAP:
8877 if (code == OMP_TARGET_EXIT_DATA
8878 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
8880 remove = true;
8881 break;
8883 decl = OMP_CLAUSE_DECL (c);
8884 /* Data clauses associated with acc parallel reductions must be
8885 compatible with present_or_copy. Warn and adjust the clause
8886 if that is not the case. */
8887 if (ctx->region_type == ORT_ACC_PARALLEL)
8889 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
8890 n = NULL;
8892 if (DECL_P (t))
8893 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
8895 if (n && (n->value & GOVD_REDUCTION))
8897 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
8899 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
8900 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
8901 && kind != GOMP_MAP_FORCE_PRESENT
8902 && kind != GOMP_MAP_POINTER)
8904 warning_at (OMP_CLAUSE_LOCATION (c), 0,
8905 "incompatible data clause with reduction "
8906 "on %qE; promoting to present_or_copy",
8907 DECL_NAME (t));
8908 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
8912 if (!DECL_P (decl))
8914 if ((ctx->region_type & ORT_TARGET) != 0
8915 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
8917 if (TREE_CODE (decl) == INDIRECT_REF
8918 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
8919 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
8920 == REFERENCE_TYPE))
8921 decl = TREE_OPERAND (decl, 0);
8922 if (TREE_CODE (decl) == COMPONENT_REF)
8924 while (TREE_CODE (decl) == COMPONENT_REF)
8925 decl = TREE_OPERAND (decl, 0);
8926 if (DECL_P (decl))
8928 n = splay_tree_lookup (ctx->variables,
8929 (splay_tree_key) decl);
8930 if (!(n->value & GOVD_SEEN))
8931 remove = true;
8935 break;
8937 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8938 if ((ctx->region_type & ORT_TARGET) != 0
8939 && !(n->value & GOVD_SEEN)
8940 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
8941 && (!is_global_var (decl)
8942 || !lookup_attribute ("omp declare target link",
8943 DECL_ATTRIBUTES (decl))))
8945 remove = true;
8946 /* For struct element mapping, if struct is never referenced
8947 in target block and none of the mapping has always modifier,
8948 remove all the struct element mappings, which immediately
8949 follow the GOMP_MAP_STRUCT map clause. */
8950 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
8952 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
8953 while (cnt--)
8954 OMP_CLAUSE_CHAIN (c)
8955 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
8958 else if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
8959 && code == OMP_TARGET_EXIT_DATA)
8960 remove = true;
8961 else if (DECL_SIZE (decl)
8962 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
8963 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
8964 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
8965 && (OMP_CLAUSE_MAP_KIND (c)
8966 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
8968 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
8969 for these, TREE_CODE (DECL_SIZE (decl)) will always be
8970 INTEGER_CST. */
8971 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
8973 tree decl2 = DECL_VALUE_EXPR (decl);
8974 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
8975 decl2 = TREE_OPERAND (decl2, 0);
8976 gcc_assert (DECL_P (decl2));
8977 tree mem = build_simple_mem_ref (decl2);
8978 OMP_CLAUSE_DECL (c) = mem;
8979 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
8980 if (ctx->outer_context)
8982 omp_notice_variable (ctx->outer_context, decl2, true);
8983 omp_notice_variable (ctx->outer_context,
8984 OMP_CLAUSE_SIZE (c), true);
8986 if (((ctx->region_type & ORT_TARGET) != 0
8987 || !ctx->target_firstprivatize_array_bases)
8988 && ((n->value & GOVD_SEEN) == 0
8989 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
8991 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
8992 OMP_CLAUSE_MAP);
8993 OMP_CLAUSE_DECL (nc) = decl;
8994 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8995 if (ctx->target_firstprivatize_array_bases)
8996 OMP_CLAUSE_SET_MAP_KIND (nc,
8997 GOMP_MAP_FIRSTPRIVATE_POINTER);
8998 else
8999 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
9000 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
9001 OMP_CLAUSE_CHAIN (c) = nc;
9002 c = nc;
9005 else
9007 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9008 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
9009 gcc_assert ((n->value & GOVD_SEEN) == 0
9010 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
9011 == 0));
9013 break;
9015 case OMP_CLAUSE_TO:
9016 case OMP_CLAUSE_FROM:
9017 case OMP_CLAUSE__CACHE_:
9018 decl = OMP_CLAUSE_DECL (c);
9019 if (!DECL_P (decl))
9020 break;
9021 if (DECL_SIZE (decl)
9022 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
9024 tree decl2 = DECL_VALUE_EXPR (decl);
9025 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
9026 decl2 = TREE_OPERAND (decl2, 0);
9027 gcc_assert (DECL_P (decl2));
9028 tree mem = build_simple_mem_ref (decl2);
9029 OMP_CLAUSE_DECL (c) = mem;
9030 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
9031 if (ctx->outer_context)
9033 omp_notice_variable (ctx->outer_context, decl2, true);
9034 omp_notice_variable (ctx->outer_context,
9035 OMP_CLAUSE_SIZE (c), true);
9038 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9039 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
9040 break;
9042 case OMP_CLAUSE_REDUCTION:
9043 decl = OMP_CLAUSE_DECL (c);
9044 /* OpenACC reductions need a present_or_copy data clause.
9045 Add one if necessary. Error is the reduction is private. */
9046 if (ctx->region_type == ORT_ACC_PARALLEL)
9048 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
9049 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
9050 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
9051 "reduction on %qE", DECL_NAME (decl));
9052 else if ((n->value & GOVD_MAP) == 0)
9054 tree next = OMP_CLAUSE_CHAIN (c);
9055 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
9056 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
9057 OMP_CLAUSE_DECL (nc) = decl;
9058 OMP_CLAUSE_CHAIN (c) = nc;
9059 lang_hooks.decls.omp_finish_clause (nc, pre_p);
9060 while (1)
9062 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
9063 if (OMP_CLAUSE_CHAIN (nc) == NULL)
9064 break;
9065 nc = OMP_CLAUSE_CHAIN (nc);
9067 OMP_CLAUSE_CHAIN (nc) = next;
9068 n->value |= GOVD_MAP;
9071 if (DECL_P (decl)
9072 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
9073 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
9074 break;
9075 case OMP_CLAUSE_COPYIN:
9076 case OMP_CLAUSE_COPYPRIVATE:
9077 case OMP_CLAUSE_IF:
9078 case OMP_CLAUSE_NUM_THREADS:
9079 case OMP_CLAUSE_NUM_TEAMS:
9080 case OMP_CLAUSE_THREAD_LIMIT:
9081 case OMP_CLAUSE_DIST_SCHEDULE:
9082 case OMP_CLAUSE_DEVICE:
9083 case OMP_CLAUSE_SCHEDULE:
9084 case OMP_CLAUSE_NOWAIT:
9085 case OMP_CLAUSE_ORDERED:
9086 case OMP_CLAUSE_DEFAULT:
9087 case OMP_CLAUSE_UNTIED:
9088 case OMP_CLAUSE_COLLAPSE:
9089 case OMP_CLAUSE_FINAL:
9090 case OMP_CLAUSE_MERGEABLE:
9091 case OMP_CLAUSE_PROC_BIND:
9092 case OMP_CLAUSE_SAFELEN:
9093 case OMP_CLAUSE_SIMDLEN:
9094 case OMP_CLAUSE_DEPEND:
9095 case OMP_CLAUSE_PRIORITY:
9096 case OMP_CLAUSE_GRAINSIZE:
9097 case OMP_CLAUSE_NUM_TASKS:
9098 case OMP_CLAUSE_NOGROUP:
9099 case OMP_CLAUSE_THREADS:
9100 case OMP_CLAUSE_SIMD:
9101 case OMP_CLAUSE_HINT:
9102 case OMP_CLAUSE_DEFAULTMAP:
9103 case OMP_CLAUSE_USE_DEVICE_PTR:
9104 case OMP_CLAUSE_IS_DEVICE_PTR:
9105 case OMP_CLAUSE__CILK_FOR_COUNT_:
9106 case OMP_CLAUSE_ASYNC:
9107 case OMP_CLAUSE_WAIT:
9108 case OMP_CLAUSE_INDEPENDENT:
9109 case OMP_CLAUSE_NUM_GANGS:
9110 case OMP_CLAUSE_NUM_WORKERS:
9111 case OMP_CLAUSE_VECTOR_LENGTH:
9112 case OMP_CLAUSE_GANG:
9113 case OMP_CLAUSE_WORKER:
9114 case OMP_CLAUSE_VECTOR:
9115 case OMP_CLAUSE_AUTO:
9116 case OMP_CLAUSE_SEQ:
9117 case OMP_CLAUSE_TILE:
9118 break;
9120 default:
9121 gcc_unreachable ();
9124 if (remove)
9125 *list_p = OMP_CLAUSE_CHAIN (c);
9126 else
9127 list_p = &OMP_CLAUSE_CHAIN (c);
9130 /* Add in any implicit data sharing. */
9131 struct gimplify_adjust_omp_clauses_data data;
9132 data.list_p = list_p;
9133 data.pre_p = pre_p;
9134 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
9136 gimplify_omp_ctxp = ctx->outer_context;
9137 delete_omp_context (ctx);
9140 /* Gimplify OACC_CACHE. */
9142 static void
9143 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
9145 tree expr = *expr_p;
9147 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
9148 OACC_CACHE);
9149 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
9150 OACC_CACHE);
9152 /* TODO: Do something sensible with this information. */
9154 *expr_p = NULL_TREE;
9157 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
9158 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
9159 kind. The entry kind will replace the one in CLAUSE, while the exit
9160 kind will be used in a new omp_clause and returned to the caller. */
9162 static tree
9163 gimplify_oacc_declare_1 (tree clause)
9165 HOST_WIDE_INT kind, new_op;
9166 bool ret = false;
9167 tree c = NULL;
9169 kind = OMP_CLAUSE_MAP_KIND (clause);
9171 switch (kind)
9173 case GOMP_MAP_ALLOC:
9174 case GOMP_MAP_FORCE_ALLOC:
9175 case GOMP_MAP_FORCE_TO:
9176 new_op = GOMP_MAP_DELETE;
9177 ret = true;
9178 break;
9180 case GOMP_MAP_FORCE_FROM:
9181 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
9182 new_op = GOMP_MAP_FORCE_FROM;
9183 ret = true;
9184 break;
9186 case GOMP_MAP_FORCE_TOFROM:
9187 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_TO);
9188 new_op = GOMP_MAP_FORCE_FROM;
9189 ret = true;
9190 break;
9192 case GOMP_MAP_FROM:
9193 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
9194 new_op = GOMP_MAP_FROM;
9195 ret = true;
9196 break;
9198 case GOMP_MAP_TOFROM:
9199 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
9200 new_op = GOMP_MAP_FROM;
9201 ret = true;
9202 break;
9204 case GOMP_MAP_DEVICE_RESIDENT:
9205 case GOMP_MAP_FORCE_DEVICEPTR:
9206 case GOMP_MAP_FORCE_PRESENT:
9207 case GOMP_MAP_LINK:
9208 case GOMP_MAP_POINTER:
9209 case GOMP_MAP_TO:
9210 break;
9212 default:
9213 gcc_unreachable ();
9214 break;
9217 if (ret)
9219 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
9220 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
9221 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
9224 return c;
9227 /* Gimplify OACC_DECLARE. */
9229 static void
9230 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
9232 tree expr = *expr_p;
9233 gomp_target *stmt;
9234 tree clauses, t;
9236 clauses = OACC_DECLARE_CLAUSES (expr);
9238 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
9240 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
9242 tree decl = OMP_CLAUSE_DECL (t);
9244 if (TREE_CODE (decl) == MEM_REF)
9245 continue;
9247 if (VAR_P (decl)
9248 && !is_global_var (decl)
9249 && DECL_CONTEXT (decl) == current_function_decl)
9251 tree c = gimplify_oacc_declare_1 (t);
9252 if (c)
9254 if (oacc_declare_returns == NULL)
9255 oacc_declare_returns = new hash_map<tree, tree>;
9257 oacc_declare_returns->put (decl, c);
9261 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
9264 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
9265 clauses);
9267 gimplify_seq_add_stmt (pre_p, stmt);
9269 *expr_p = NULL_TREE;
9272 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
9273 gimplification of the body, as well as scanning the body for used
9274 variables. We need to do this scan now, because variable-sized
9275 decls will be decomposed during gimplification. */
9277 static void
9278 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
9280 tree expr = *expr_p;
9281 gimple *g;
9282 gimple_seq body = NULL;
9284 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
9285 OMP_PARALLEL_COMBINED (expr)
9286 ? ORT_COMBINED_PARALLEL
9287 : ORT_PARALLEL, OMP_PARALLEL);
9289 push_gimplify_context ();
9291 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
9292 if (gimple_code (g) == GIMPLE_BIND)
9293 pop_gimplify_context (g);
9294 else
9295 pop_gimplify_context (NULL);
9297 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
9298 OMP_PARALLEL);
9300 g = gimple_build_omp_parallel (body,
9301 OMP_PARALLEL_CLAUSES (expr),
9302 NULL_TREE, NULL_TREE);
9303 if (OMP_PARALLEL_COMBINED (expr))
9304 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
9305 gimplify_seq_add_stmt (pre_p, g);
9306 *expr_p = NULL_TREE;
9309 /* Gimplify the contents of an OMP_TASK statement. This involves
9310 gimplification of the body, as well as scanning the body for used
9311 variables. We need to do this scan now, because variable-sized
9312 decls will be decomposed during gimplification. */
9314 static void
9315 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
9317 tree expr = *expr_p;
9318 gimple *g;
9319 gimple_seq body = NULL;
9321 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
9322 omp_find_clause (OMP_TASK_CLAUSES (expr),
9323 OMP_CLAUSE_UNTIED)
9324 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
9326 push_gimplify_context ();
9328 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
9329 if (gimple_code (g) == GIMPLE_BIND)
9330 pop_gimplify_context (g);
9331 else
9332 pop_gimplify_context (NULL);
9334 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
9335 OMP_TASK);
9337 g = gimple_build_omp_task (body,
9338 OMP_TASK_CLAUSES (expr),
9339 NULL_TREE, NULL_TREE,
9340 NULL_TREE, NULL_TREE, NULL_TREE);
9341 gimplify_seq_add_stmt (pre_p, g);
9342 *expr_p = NULL_TREE;
9345 /* Helper function of gimplify_omp_for, find OMP_FOR resp. OMP_SIMD
9346 with non-NULL OMP_FOR_INIT. */
9348 static tree
9349 find_combined_omp_for (tree *tp, int *walk_subtrees, void *)
9351 *walk_subtrees = 0;
9352 switch (TREE_CODE (*tp))
9354 case OMP_FOR:
9355 *walk_subtrees = 1;
9356 /* FALLTHRU */
9357 case OMP_SIMD:
9358 if (OMP_FOR_INIT (*tp) != NULL_TREE)
9359 return *tp;
9360 break;
9361 case BIND_EXPR:
9362 case STATEMENT_LIST:
9363 case OMP_PARALLEL:
9364 *walk_subtrees = 1;
9365 break;
9366 default:
9367 break;
9369 return NULL_TREE;
9372 /* Gimplify the gross structure of an OMP_FOR statement. */
9374 static enum gimplify_status
9375 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
9377 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
9378 enum gimplify_status ret = GS_ALL_DONE;
9379 enum gimplify_status tret;
9380 gomp_for *gfor;
9381 gimple_seq for_body, for_pre_body;
9382 int i;
9383 bitmap has_decl_expr = NULL;
9384 enum omp_region_type ort = ORT_WORKSHARE;
9386 orig_for_stmt = for_stmt = *expr_p;
9388 switch (TREE_CODE (for_stmt))
9390 case OMP_FOR:
9391 case CILK_FOR:
9392 case OMP_DISTRIBUTE:
9393 break;
9394 case OACC_LOOP:
9395 ort = ORT_ACC;
9396 break;
9397 case OMP_TASKLOOP:
9398 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
9399 ort = ORT_UNTIED_TASK;
9400 else
9401 ort = ORT_TASK;
9402 break;
9403 case OMP_SIMD:
9404 case CILK_SIMD:
9405 ort = ORT_SIMD;
9406 break;
9407 default:
9408 gcc_unreachable ();
9411 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
9412 clause for the IV. */
9413 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9415 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
9416 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
9417 decl = TREE_OPERAND (t, 0);
9418 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
9419 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
9420 && OMP_CLAUSE_DECL (c) == decl)
9422 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
9423 break;
9427 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
9429 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
9430 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
9431 find_combined_omp_for, NULL, NULL);
9432 if (inner_for_stmt == NULL_TREE)
9434 gcc_assert (seen_error ());
9435 *expr_p = NULL_TREE;
9436 return GS_ERROR;
9440 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
9441 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
9442 TREE_CODE (for_stmt));
9444 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
9445 gimplify_omp_ctxp->distribute = true;
9447 /* Handle OMP_FOR_INIT. */
9448 for_pre_body = NULL;
9449 if (ort == ORT_SIMD && OMP_FOR_PRE_BODY (for_stmt))
9451 has_decl_expr = BITMAP_ALLOC (NULL);
9452 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
9453 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
9454 == VAR_DECL)
9456 t = OMP_FOR_PRE_BODY (for_stmt);
9457 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
9459 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
9461 tree_stmt_iterator si;
9462 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
9463 tsi_next (&si))
9465 t = tsi_stmt (si);
9466 if (TREE_CODE (t) == DECL_EXPR
9467 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
9468 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
9472 if (OMP_FOR_PRE_BODY (for_stmt))
9474 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
9475 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
9476 else
9478 struct gimplify_omp_ctx ctx;
9479 memset (&ctx, 0, sizeof (ctx));
9480 ctx.region_type = ORT_NONE;
9481 gimplify_omp_ctxp = &ctx;
9482 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
9483 gimplify_omp_ctxp = NULL;
9486 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
9488 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
9489 for_stmt = inner_for_stmt;
9491 /* For taskloop, need to gimplify the start, end and step before the
9492 taskloop, outside of the taskloop omp context. */
9493 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
9495 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
9497 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
9498 if (!is_gimple_constant (TREE_OPERAND (t, 1)))
9500 TREE_OPERAND (t, 1)
9501 = get_initialized_tmp_var (TREE_OPERAND (t, 1),
9502 pre_p, NULL, false);
9503 tree c = build_omp_clause (input_location,
9504 OMP_CLAUSE_FIRSTPRIVATE);
9505 OMP_CLAUSE_DECL (c) = TREE_OPERAND (t, 1);
9506 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9507 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9510 /* Handle OMP_FOR_COND. */
9511 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
9512 if (!is_gimple_constant (TREE_OPERAND (t, 1)))
9514 TREE_OPERAND (t, 1)
9515 = get_initialized_tmp_var (TREE_OPERAND (t, 1),
9516 gimple_seq_empty_p (for_pre_body)
9517 ? pre_p : &for_pre_body, NULL,
9518 false);
9519 tree c = build_omp_clause (input_location,
9520 OMP_CLAUSE_FIRSTPRIVATE);
9521 OMP_CLAUSE_DECL (c) = TREE_OPERAND (t, 1);
9522 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9523 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9526 /* Handle OMP_FOR_INCR. */
9527 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
9528 if (TREE_CODE (t) == MODIFY_EXPR)
9530 decl = TREE_OPERAND (t, 0);
9531 t = TREE_OPERAND (t, 1);
9532 tree *tp = &TREE_OPERAND (t, 1);
9533 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
9534 tp = &TREE_OPERAND (t, 0);
9536 if (!is_gimple_constant (*tp))
9538 gimple_seq *seq = gimple_seq_empty_p (for_pre_body)
9539 ? pre_p : &for_pre_body;
9540 *tp = get_initialized_tmp_var (*tp, seq, NULL, false);
9541 tree c = build_omp_clause (input_location,
9542 OMP_CLAUSE_FIRSTPRIVATE);
9543 OMP_CLAUSE_DECL (c) = *tp;
9544 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9545 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9550 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
9551 OMP_TASKLOOP);
9554 if (orig_for_stmt != for_stmt)
9555 gimplify_omp_ctxp->combined_loop = true;
9557 for_body = NULL;
9558 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9559 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
9560 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9561 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
9563 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
9564 bool is_doacross = false;
9565 if (c && OMP_CLAUSE_ORDERED_EXPR (c))
9567 is_doacross = true;
9568 gimplify_omp_ctxp->loop_iter_var.create (TREE_VEC_LENGTH
9569 (OMP_FOR_INIT (for_stmt))
9570 * 2);
9572 int collapse = 1, tile = 0;
9573 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
9574 if (c)
9575 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
9576 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_TILE);
9577 if (c)
9578 tile = list_length (OMP_CLAUSE_TILE_LIST (c));
9579 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
9581 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
9582 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
9583 decl = TREE_OPERAND (t, 0);
9584 gcc_assert (DECL_P (decl));
9585 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
9586 || POINTER_TYPE_P (TREE_TYPE (decl)));
9587 if (is_doacross)
9589 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
9590 gimplify_omp_ctxp->loop_iter_var.quick_push
9591 (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i));
9592 else
9593 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
9594 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
9597 /* Make sure the iteration variable is private. */
9598 tree c = NULL_TREE;
9599 tree c2 = NULL_TREE;
9600 if (orig_for_stmt != for_stmt)
9601 /* Do this only on innermost construct for combined ones. */;
9602 else if (ort == ORT_SIMD)
9604 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
9605 (splay_tree_key) decl);
9606 omp_is_private (gimplify_omp_ctxp, decl,
9607 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9608 != 1));
9609 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
9610 omp_notice_variable (gimplify_omp_ctxp, decl, true);
9611 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9613 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
9614 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
9615 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
9616 if (has_decl_expr
9617 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
9619 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
9620 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9622 struct gimplify_omp_ctx *outer
9623 = gimplify_omp_ctxp->outer_context;
9624 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9626 if (outer->region_type == ORT_WORKSHARE
9627 && outer->combined_loop)
9629 n = splay_tree_lookup (outer->variables,
9630 (splay_tree_key)decl);
9631 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
9633 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
9634 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9636 else
9638 struct gimplify_omp_ctx *octx = outer->outer_context;
9639 if (octx
9640 && octx->region_type == ORT_COMBINED_PARALLEL
9641 && octx->outer_context
9642 && (octx->outer_context->region_type
9643 == ORT_WORKSHARE)
9644 && octx->outer_context->combined_loop)
9646 octx = octx->outer_context;
9647 n = splay_tree_lookup (octx->variables,
9648 (splay_tree_key)decl);
9649 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
9651 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
9652 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9659 OMP_CLAUSE_DECL (c) = decl;
9660 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
9661 OMP_FOR_CLAUSES (for_stmt) = c;
9662 omp_add_variable (gimplify_omp_ctxp, decl, flags);
9663 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9665 if (outer->region_type == ORT_WORKSHARE
9666 && outer->combined_loop)
9668 if (outer->outer_context
9669 && (outer->outer_context->region_type
9670 == ORT_COMBINED_PARALLEL))
9671 outer = outer->outer_context;
9672 else if (omp_check_private (outer, decl, false))
9673 outer = NULL;
9675 else if (((outer->region_type & ORT_TASK) != 0)
9676 && outer->combined_loop
9677 && !omp_check_private (gimplify_omp_ctxp,
9678 decl, false))
9680 else if (outer->region_type != ORT_COMBINED_PARALLEL)
9682 omp_notice_variable (outer, decl, true);
9683 outer = NULL;
9685 if (outer)
9687 n = splay_tree_lookup (outer->variables,
9688 (splay_tree_key)decl);
9689 if (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9691 omp_add_variable (outer, decl,
9692 GOVD_LASTPRIVATE | GOVD_SEEN);
9693 if (outer->region_type == ORT_COMBINED_PARALLEL
9694 && outer->outer_context
9695 && (outer->outer_context->region_type
9696 == ORT_WORKSHARE)
9697 && outer->outer_context->combined_loop)
9699 outer = outer->outer_context;
9700 n = splay_tree_lookup (outer->variables,
9701 (splay_tree_key)decl);
9702 if (omp_check_private (outer, decl, false))
9703 outer = NULL;
9704 else if (n == NULL
9705 || ((n->value & GOVD_DATA_SHARE_CLASS)
9706 == 0))
9707 omp_add_variable (outer, decl,
9708 GOVD_LASTPRIVATE
9709 | GOVD_SEEN);
9710 else
9711 outer = NULL;
9713 if (outer && outer->outer_context
9714 && (outer->outer_context->region_type
9715 == ORT_COMBINED_TEAMS))
9717 outer = outer->outer_context;
9718 n = splay_tree_lookup (outer->variables,
9719 (splay_tree_key)decl);
9720 if (n == NULL
9721 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9722 omp_add_variable (outer, decl,
9723 GOVD_SHARED | GOVD_SEEN);
9724 else
9725 outer = NULL;
9727 if (outer && outer->outer_context)
9728 omp_notice_variable (outer->outer_context, decl,
9729 true);
9734 else
9736 bool lastprivate
9737 = (!has_decl_expr
9738 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
9739 struct gimplify_omp_ctx *outer
9740 = gimplify_omp_ctxp->outer_context;
9741 if (outer && lastprivate)
9743 if (outer->region_type == ORT_WORKSHARE
9744 && outer->combined_loop)
9746 n = splay_tree_lookup (outer->variables,
9747 (splay_tree_key)decl);
9748 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
9750 lastprivate = false;
9751 outer = NULL;
9753 else if (outer->outer_context
9754 && (outer->outer_context->region_type
9755 == ORT_COMBINED_PARALLEL))
9756 outer = outer->outer_context;
9757 else if (omp_check_private (outer, decl, false))
9758 outer = NULL;
9760 else if (((outer->region_type & ORT_TASK) != 0)
9761 && outer->combined_loop
9762 && !omp_check_private (gimplify_omp_ctxp,
9763 decl, false))
9765 else if (outer->region_type != ORT_COMBINED_PARALLEL)
9767 omp_notice_variable (outer, decl, true);
9768 outer = NULL;
9770 if (outer)
9772 n = splay_tree_lookup (outer->variables,
9773 (splay_tree_key)decl);
9774 if (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9776 omp_add_variable (outer, decl,
9777 GOVD_LASTPRIVATE | GOVD_SEEN);
9778 if (outer->region_type == ORT_COMBINED_PARALLEL
9779 && outer->outer_context
9780 && (outer->outer_context->region_type
9781 == ORT_WORKSHARE)
9782 && outer->outer_context->combined_loop)
9784 outer = outer->outer_context;
9785 n = splay_tree_lookup (outer->variables,
9786 (splay_tree_key)decl);
9787 if (omp_check_private (outer, decl, false))
9788 outer = NULL;
9789 else if (n == NULL
9790 || ((n->value & GOVD_DATA_SHARE_CLASS)
9791 == 0))
9792 omp_add_variable (outer, decl,
9793 GOVD_LASTPRIVATE
9794 | GOVD_SEEN);
9795 else
9796 outer = NULL;
9798 if (outer && outer->outer_context
9799 && (outer->outer_context->region_type
9800 == ORT_COMBINED_TEAMS))
9802 outer = outer->outer_context;
9803 n = splay_tree_lookup (outer->variables,
9804 (splay_tree_key)decl);
9805 if (n == NULL
9806 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9807 omp_add_variable (outer, decl,
9808 GOVD_SHARED | GOVD_SEEN);
9809 else
9810 outer = NULL;
9812 if (outer && outer->outer_context)
9813 omp_notice_variable (outer->outer_context, decl,
9814 true);
9819 c = build_omp_clause (input_location,
9820 lastprivate ? OMP_CLAUSE_LASTPRIVATE
9821 : OMP_CLAUSE_PRIVATE);
9822 OMP_CLAUSE_DECL (c) = decl;
9823 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
9824 OMP_FOR_CLAUSES (for_stmt) = c;
9825 omp_add_variable (gimplify_omp_ctxp, decl,
9826 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
9827 | GOVD_EXPLICIT | GOVD_SEEN);
9828 c = NULL_TREE;
9831 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
9832 omp_notice_variable (gimplify_omp_ctxp, decl, true);
9833 else
9834 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
9836 /* If DECL is not a gimple register, create a temporary variable to act
9837 as an iteration counter. This is valid, since DECL cannot be
9838 modified in the body of the loop. Similarly for any iteration vars
9839 in simd with collapse > 1 where the iterator vars must be
9840 lastprivate. */
9841 if (orig_for_stmt != for_stmt)
9842 var = decl;
9843 else if (!is_gimple_reg (decl)
9844 || (ort == ORT_SIMD
9845 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1))
9847 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
9848 /* Make sure omp_add_variable is not called on it prematurely.
9849 We call it ourselves a few lines later. */
9850 gimplify_omp_ctxp = NULL;
9851 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
9852 gimplify_omp_ctxp = ctx;
9853 TREE_OPERAND (t, 0) = var;
9855 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
9857 if (ort == ORT_SIMD
9858 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9860 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
9861 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
9862 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
9863 OMP_CLAUSE_DECL (c2) = var;
9864 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
9865 OMP_FOR_CLAUSES (for_stmt) = c2;
9866 omp_add_variable (gimplify_omp_ctxp, var,
9867 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
9868 if (c == NULL_TREE)
9870 c = c2;
9871 c2 = NULL_TREE;
9874 else
9875 omp_add_variable (gimplify_omp_ctxp, var,
9876 GOVD_PRIVATE | GOVD_SEEN);
9878 else
9879 var = decl;
9881 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
9882 is_gimple_val, fb_rvalue, false);
9883 ret = MIN (ret, tret);
9884 if (ret == GS_ERROR)
9885 return ret;
9887 /* Handle OMP_FOR_COND. */
9888 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
9889 gcc_assert (COMPARISON_CLASS_P (t));
9890 gcc_assert (TREE_OPERAND (t, 0) == decl);
9892 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
9893 is_gimple_val, fb_rvalue, false);
9894 ret = MIN (ret, tret);
9896 /* Handle OMP_FOR_INCR. */
9897 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
9898 switch (TREE_CODE (t))
9900 case PREINCREMENT_EXPR:
9901 case POSTINCREMENT_EXPR:
9903 tree decl = TREE_OPERAND (t, 0);
9904 /* c_omp_for_incr_canonicalize_ptr() should have been
9905 called to massage things appropriately. */
9906 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
9908 if (orig_for_stmt != for_stmt)
9909 break;
9910 t = build_int_cst (TREE_TYPE (decl), 1);
9911 if (c)
9912 OMP_CLAUSE_LINEAR_STEP (c) = t;
9913 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
9914 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
9915 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
9916 break;
9919 case PREDECREMENT_EXPR:
9920 case POSTDECREMENT_EXPR:
9921 /* c_omp_for_incr_canonicalize_ptr() should have been
9922 called to massage things appropriately. */
9923 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
9924 if (orig_for_stmt != for_stmt)
9925 break;
9926 t = build_int_cst (TREE_TYPE (decl), -1);
9927 if (c)
9928 OMP_CLAUSE_LINEAR_STEP (c) = t;
9929 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
9930 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
9931 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
9932 break;
9934 case MODIFY_EXPR:
9935 gcc_assert (TREE_OPERAND (t, 0) == decl);
9936 TREE_OPERAND (t, 0) = var;
9938 t = TREE_OPERAND (t, 1);
9939 switch (TREE_CODE (t))
9941 case PLUS_EXPR:
9942 if (TREE_OPERAND (t, 1) == decl)
9944 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
9945 TREE_OPERAND (t, 0) = var;
9946 break;
9949 /* Fallthru. */
9950 case MINUS_EXPR:
9951 case POINTER_PLUS_EXPR:
9952 gcc_assert (TREE_OPERAND (t, 0) == decl);
9953 TREE_OPERAND (t, 0) = var;
9954 break;
9955 default:
9956 gcc_unreachable ();
9959 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
9960 is_gimple_val, fb_rvalue, false);
9961 ret = MIN (ret, tret);
9962 if (c)
9964 tree step = TREE_OPERAND (t, 1);
9965 tree stept = TREE_TYPE (decl);
9966 if (POINTER_TYPE_P (stept))
9967 stept = sizetype;
9968 step = fold_convert (stept, step);
9969 if (TREE_CODE (t) == MINUS_EXPR)
9970 step = fold_build1 (NEGATE_EXPR, stept, step);
9971 OMP_CLAUSE_LINEAR_STEP (c) = step;
9972 if (step != TREE_OPERAND (t, 1))
9974 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
9975 &for_pre_body, NULL,
9976 is_gimple_val, fb_rvalue, false);
9977 ret = MIN (ret, tret);
9980 break;
9982 default:
9983 gcc_unreachable ();
9986 if (c2)
9988 gcc_assert (c);
9989 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
9992 if ((var != decl || collapse > 1 || tile) && orig_for_stmt == for_stmt)
9994 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
9995 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
9996 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
9997 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
9998 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
9999 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
10000 && OMP_CLAUSE_DECL (c) == decl)
10002 if (is_doacross && (collapse == 1 || i >= collapse))
10003 t = var;
10004 else
10006 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10007 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
10008 gcc_assert (TREE_OPERAND (t, 0) == var);
10009 t = TREE_OPERAND (t, 1);
10010 gcc_assert (TREE_CODE (t) == PLUS_EXPR
10011 || TREE_CODE (t) == MINUS_EXPR
10012 || TREE_CODE (t) == POINTER_PLUS_EXPR);
10013 gcc_assert (TREE_OPERAND (t, 0) == var);
10014 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
10015 is_doacross ? var : decl,
10016 TREE_OPERAND (t, 1));
10018 gimple_seq *seq;
10019 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
10020 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
10021 else
10022 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
10023 gimplify_assign (decl, t, seq);
10028 BITMAP_FREE (has_decl_expr);
10030 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10032 push_gimplify_context ();
10033 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
10035 OMP_FOR_BODY (orig_for_stmt)
10036 = build3 (BIND_EXPR, void_type_node, NULL,
10037 OMP_FOR_BODY (orig_for_stmt), NULL);
10038 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
10042 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
10043 &for_body);
10045 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10047 if (gimple_code (g) == GIMPLE_BIND)
10048 pop_gimplify_context (g);
10049 else
10050 pop_gimplify_context (NULL);
10053 if (orig_for_stmt != for_stmt)
10054 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
10056 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
10057 decl = TREE_OPERAND (t, 0);
10058 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10059 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10060 gimplify_omp_ctxp = ctx->outer_context;
10061 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
10062 gimplify_omp_ctxp = ctx;
10063 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
10064 TREE_OPERAND (t, 0) = var;
10065 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10066 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
10067 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
10070 gimplify_adjust_omp_clauses (pre_p, for_body,
10071 &OMP_FOR_CLAUSES (orig_for_stmt),
10072 TREE_CODE (orig_for_stmt));
10074 int kind;
10075 switch (TREE_CODE (orig_for_stmt))
10077 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
10078 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
10079 case CILK_SIMD: kind = GF_OMP_FOR_KIND_CILKSIMD; break;
10080 case CILK_FOR: kind = GF_OMP_FOR_KIND_CILKFOR; break;
10081 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
10082 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
10083 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
10084 default:
10085 gcc_unreachable ();
10087 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
10088 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
10089 for_pre_body);
10090 if (orig_for_stmt != for_stmt)
10091 gimple_omp_for_set_combined_p (gfor, true);
10092 if (gimplify_omp_ctxp
10093 && (gimplify_omp_ctxp->combined_loop
10094 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
10095 && gimplify_omp_ctxp->outer_context
10096 && gimplify_omp_ctxp->outer_context->combined_loop)))
10098 gimple_omp_for_set_combined_into_p (gfor, true);
10099 if (gimplify_omp_ctxp->combined_loop)
10100 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
10101 else
10102 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
10105 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
10107 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
10108 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
10109 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
10110 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
10111 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
10112 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
10113 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10114 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
10117 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
10118 constructs with GIMPLE_OMP_TASK sandwiched in between them.
10119 The outer taskloop stands for computing the number of iterations,
10120 counts for collapsed loops and holding taskloop specific clauses.
10121 The task construct stands for the effect of data sharing on the
10122 explicit task it creates and the inner taskloop stands for expansion
10123 of the static loop inside of the explicit task construct. */
10124 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10126 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
10127 tree task_clauses = NULL_TREE;
10128 tree c = *gfor_clauses_ptr;
10129 tree *gtask_clauses_ptr = &task_clauses;
10130 tree outer_for_clauses = NULL_TREE;
10131 tree *gforo_clauses_ptr = &outer_for_clauses;
10132 for (; c; c = OMP_CLAUSE_CHAIN (c))
10133 switch (OMP_CLAUSE_CODE (c))
10135 /* These clauses are allowed on task, move them there. */
10136 case OMP_CLAUSE_SHARED:
10137 case OMP_CLAUSE_FIRSTPRIVATE:
10138 case OMP_CLAUSE_DEFAULT:
10139 case OMP_CLAUSE_IF:
10140 case OMP_CLAUSE_UNTIED:
10141 case OMP_CLAUSE_FINAL:
10142 case OMP_CLAUSE_MERGEABLE:
10143 case OMP_CLAUSE_PRIORITY:
10144 *gtask_clauses_ptr = c;
10145 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10146 break;
10147 case OMP_CLAUSE_PRIVATE:
10148 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
10150 /* We want private on outer for and firstprivate
10151 on task. */
10152 *gtask_clauses_ptr
10153 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10154 OMP_CLAUSE_FIRSTPRIVATE);
10155 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10156 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL);
10157 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10158 *gforo_clauses_ptr = c;
10159 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10161 else
10163 *gtask_clauses_ptr = c;
10164 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10166 break;
10167 /* These clauses go into outer taskloop clauses. */
10168 case OMP_CLAUSE_GRAINSIZE:
10169 case OMP_CLAUSE_NUM_TASKS:
10170 case OMP_CLAUSE_NOGROUP:
10171 *gforo_clauses_ptr = c;
10172 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10173 break;
10174 /* Taskloop clause we duplicate on both taskloops. */
10175 case OMP_CLAUSE_COLLAPSE:
10176 *gfor_clauses_ptr = c;
10177 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10178 *gforo_clauses_ptr = copy_node (c);
10179 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
10180 break;
10181 /* For lastprivate, keep the clause on inner taskloop, and add
10182 a shared clause on task. If the same decl is also firstprivate,
10183 add also firstprivate clause on the inner taskloop. */
10184 case OMP_CLAUSE_LASTPRIVATE:
10185 if (OMP_CLAUSE_LASTPRIVATE_TASKLOOP_IV (c))
10187 /* For taskloop C++ lastprivate IVs, we want:
10188 1) private on outer taskloop
10189 2) firstprivate and shared on task
10190 3) lastprivate on inner taskloop */
10191 *gtask_clauses_ptr
10192 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10193 OMP_CLAUSE_FIRSTPRIVATE);
10194 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10195 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL);
10196 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10197 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
10198 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10199 OMP_CLAUSE_PRIVATE);
10200 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
10201 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
10202 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
10203 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
10205 *gfor_clauses_ptr = c;
10206 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10207 *gtask_clauses_ptr
10208 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
10209 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10210 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
10211 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
10212 gtask_clauses_ptr
10213 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10214 break;
10215 default:
10216 gcc_unreachable ();
10218 *gfor_clauses_ptr = NULL_TREE;
10219 *gtask_clauses_ptr = NULL_TREE;
10220 *gforo_clauses_ptr = NULL_TREE;
10221 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
10222 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
10223 NULL_TREE, NULL_TREE, NULL_TREE);
10224 gimple_omp_task_set_taskloop_p (g, true);
10225 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
10226 gomp_for *gforo
10227 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
10228 gimple_omp_for_collapse (gfor),
10229 gimple_omp_for_pre_body (gfor));
10230 gimple_omp_for_set_pre_body (gfor, NULL);
10231 gimple_omp_for_set_combined_p (gforo, true);
10232 gimple_omp_for_set_combined_into_p (gfor, true);
10233 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
10235 t = unshare_expr (gimple_omp_for_index (gfor, i));
10236 gimple_omp_for_set_index (gforo, i, t);
10237 t = unshare_expr (gimple_omp_for_initial (gfor, i));
10238 gimple_omp_for_set_initial (gforo, i, t);
10239 gimple_omp_for_set_cond (gforo, i,
10240 gimple_omp_for_cond (gfor, i));
10241 t = unshare_expr (gimple_omp_for_final (gfor, i));
10242 gimple_omp_for_set_final (gforo, i, t);
10243 t = unshare_expr (gimple_omp_for_incr (gfor, i));
10244 gimple_omp_for_set_incr (gforo, i, t);
10246 gimplify_seq_add_stmt (pre_p, gforo);
10248 else
10249 gimplify_seq_add_stmt (pre_p, gfor);
10250 if (ret != GS_ALL_DONE)
10251 return GS_ERROR;
10252 *expr_p = NULL_TREE;
10253 return GS_ALL_DONE;
10256 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
10257 of OMP_TARGET's body. */
10259 static tree
10260 find_omp_teams (tree *tp, int *walk_subtrees, void *)
10262 *walk_subtrees = 0;
10263 switch (TREE_CODE (*tp))
10265 case OMP_TEAMS:
10266 return *tp;
10267 case BIND_EXPR:
10268 case STATEMENT_LIST:
10269 *walk_subtrees = 1;
10270 break;
10271 default:
10272 break;
10274 return NULL_TREE;
10277 /* Helper function of optimize_target_teams, determine if the expression
10278 can be computed safely before the target construct on the host. */
10280 static tree
10281 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
10283 splay_tree_node n;
10285 if (TYPE_P (*tp))
10287 *walk_subtrees = 0;
10288 return NULL_TREE;
10290 switch (TREE_CODE (*tp))
10292 case VAR_DECL:
10293 case PARM_DECL:
10294 case RESULT_DECL:
10295 *walk_subtrees = 0;
10296 if (error_operand_p (*tp)
10297 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
10298 || DECL_HAS_VALUE_EXPR_P (*tp)
10299 || DECL_THREAD_LOCAL_P (*tp)
10300 || TREE_SIDE_EFFECTS (*tp)
10301 || TREE_THIS_VOLATILE (*tp))
10302 return *tp;
10303 if (is_global_var (*tp)
10304 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
10305 || lookup_attribute ("omp declare target link",
10306 DECL_ATTRIBUTES (*tp))))
10307 return *tp;
10308 if (VAR_P (*tp)
10309 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
10310 && !is_global_var (*tp)
10311 && decl_function_context (*tp) == current_function_decl)
10312 return *tp;
10313 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
10314 (splay_tree_key) *tp);
10315 if (n == NULL)
10317 if (gimplify_omp_ctxp->target_map_scalars_firstprivate)
10318 return NULL_TREE;
10319 return *tp;
10321 else if (n->value & GOVD_LOCAL)
10322 return *tp;
10323 else if (n->value & GOVD_FIRSTPRIVATE)
10324 return NULL_TREE;
10325 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
10326 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
10327 return NULL_TREE;
10328 return *tp;
10329 case INTEGER_CST:
10330 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
10331 return *tp;
10332 return NULL_TREE;
10333 case TARGET_EXPR:
10334 if (TARGET_EXPR_INITIAL (*tp)
10335 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
10336 return *tp;
10337 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
10338 walk_subtrees, NULL);
10339 /* Allow some reasonable subset of integral arithmetics. */
10340 case PLUS_EXPR:
10341 case MINUS_EXPR:
10342 case MULT_EXPR:
10343 case TRUNC_DIV_EXPR:
10344 case CEIL_DIV_EXPR:
10345 case FLOOR_DIV_EXPR:
10346 case ROUND_DIV_EXPR:
10347 case TRUNC_MOD_EXPR:
10348 case CEIL_MOD_EXPR:
10349 case FLOOR_MOD_EXPR:
10350 case ROUND_MOD_EXPR:
10351 case RDIV_EXPR:
10352 case EXACT_DIV_EXPR:
10353 case MIN_EXPR:
10354 case MAX_EXPR:
10355 case LSHIFT_EXPR:
10356 case RSHIFT_EXPR:
10357 case BIT_IOR_EXPR:
10358 case BIT_XOR_EXPR:
10359 case BIT_AND_EXPR:
10360 case NEGATE_EXPR:
10361 case ABS_EXPR:
10362 case BIT_NOT_EXPR:
10363 case NON_LVALUE_EXPR:
10364 CASE_CONVERT:
10365 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
10366 return *tp;
10367 return NULL_TREE;
10368 /* And disallow anything else, except for comparisons. */
10369 default:
10370 if (COMPARISON_CLASS_P (*tp))
10371 return NULL_TREE;
10372 return *tp;
10376 /* Try to determine if the num_teams and/or thread_limit expressions
10377 can have their values determined already before entering the
10378 target construct.
10379 INTEGER_CSTs trivially are,
10380 integral decls that are firstprivate (explicitly or implicitly)
10381 or explicitly map(always, to:) or map(always, tofrom:) on the target
10382 region too, and expressions involving simple arithmetics on those
10383 too, function calls are not ok, dereferencing something neither etc.
10384 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
10385 EXPR based on what we find:
10386 0 stands for clause not specified at all, use implementation default
10387 -1 stands for value that can't be determined easily before entering
10388 the target construct.
10389 If teams construct is not present at all, use 1 for num_teams
10390 and 0 for thread_limit (only one team is involved, and the thread
10391 limit is implementation defined. */
10393 static void
10394 optimize_target_teams (tree target, gimple_seq *pre_p)
10396 tree body = OMP_BODY (target);
10397 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
10398 tree num_teams = integer_zero_node;
10399 tree thread_limit = integer_zero_node;
10400 location_t num_teams_loc = EXPR_LOCATION (target);
10401 location_t thread_limit_loc = EXPR_LOCATION (target);
10402 tree c, *p, expr;
10403 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
10405 if (teams == NULL_TREE)
10406 num_teams = integer_one_node;
10407 else
10408 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
10410 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
10412 p = &num_teams;
10413 num_teams_loc = OMP_CLAUSE_LOCATION (c);
10415 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
10417 p = &thread_limit;
10418 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
10420 else
10421 continue;
10422 expr = OMP_CLAUSE_OPERAND (c, 0);
10423 if (TREE_CODE (expr) == INTEGER_CST)
10425 *p = expr;
10426 continue;
10428 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
10430 *p = integer_minus_one_node;
10431 continue;
10433 *p = expr;
10434 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
10435 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
10436 == GS_ERROR)
10438 gimplify_omp_ctxp = target_ctx;
10439 *p = integer_minus_one_node;
10440 continue;
10442 gimplify_omp_ctxp = target_ctx;
10443 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
10444 OMP_CLAUSE_OPERAND (c, 0) = *p;
10446 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
10447 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
10448 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
10449 OMP_TARGET_CLAUSES (target) = c;
10450 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
10451 OMP_CLAUSE_NUM_TEAMS_EXPR (c) = num_teams;
10452 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
10453 OMP_TARGET_CLAUSES (target) = c;
10456 /* Gimplify the gross structure of several OMP constructs. */
10458 static void
10459 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
10461 tree expr = *expr_p;
10462 gimple *stmt;
10463 gimple_seq body = NULL;
10464 enum omp_region_type ort;
10466 switch (TREE_CODE (expr))
10468 case OMP_SECTIONS:
10469 case OMP_SINGLE:
10470 ort = ORT_WORKSHARE;
10471 break;
10472 case OMP_TARGET:
10473 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
10474 break;
10475 case OACC_KERNELS:
10476 ort = ORT_ACC_KERNELS;
10477 break;
10478 case OACC_PARALLEL:
10479 ort = ORT_ACC_PARALLEL;
10480 break;
10481 case OACC_DATA:
10482 ort = ORT_ACC_DATA;
10483 break;
10484 case OMP_TARGET_DATA:
10485 ort = ORT_TARGET_DATA;
10486 break;
10487 case OMP_TEAMS:
10488 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
10489 break;
10490 case OACC_HOST_DATA:
10491 ort = ORT_ACC_HOST_DATA;
10492 break;
10493 default:
10494 gcc_unreachable ();
10496 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
10497 TREE_CODE (expr));
10498 if (TREE_CODE (expr) == OMP_TARGET)
10499 optimize_target_teams (expr, pre_p);
10500 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0)
10502 push_gimplify_context ();
10503 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
10504 if (gimple_code (g) == GIMPLE_BIND)
10505 pop_gimplify_context (g);
10506 else
10507 pop_gimplify_context (NULL);
10508 if ((ort & ORT_TARGET_DATA) != 0)
10510 enum built_in_function end_ix;
10511 switch (TREE_CODE (expr))
10513 case OACC_DATA:
10514 case OACC_HOST_DATA:
10515 end_ix = BUILT_IN_GOACC_DATA_END;
10516 break;
10517 case OMP_TARGET_DATA:
10518 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
10519 break;
10520 default:
10521 gcc_unreachable ();
10523 tree fn = builtin_decl_explicit (end_ix);
10524 g = gimple_build_call (fn, 0);
10525 gimple_seq cleanup = NULL;
10526 gimple_seq_add_stmt (&cleanup, g);
10527 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
10528 body = NULL;
10529 gimple_seq_add_stmt (&body, g);
10532 else
10533 gimplify_and_add (OMP_BODY (expr), &body);
10534 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
10535 TREE_CODE (expr));
10537 switch (TREE_CODE (expr))
10539 case OACC_DATA:
10540 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
10541 OMP_CLAUSES (expr));
10542 break;
10543 case OACC_KERNELS:
10544 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
10545 OMP_CLAUSES (expr));
10546 break;
10547 case OACC_HOST_DATA:
10548 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
10549 OMP_CLAUSES (expr));
10550 break;
10551 case OACC_PARALLEL:
10552 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
10553 OMP_CLAUSES (expr));
10554 break;
10555 case OMP_SECTIONS:
10556 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
10557 break;
10558 case OMP_SINGLE:
10559 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
10560 break;
10561 case OMP_TARGET:
10562 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
10563 OMP_CLAUSES (expr));
10564 break;
10565 case OMP_TARGET_DATA:
10566 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
10567 OMP_CLAUSES (expr));
10568 break;
10569 case OMP_TEAMS:
10570 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
10571 break;
10572 default:
10573 gcc_unreachable ();
10576 gimplify_seq_add_stmt (pre_p, stmt);
10577 *expr_p = NULL_TREE;
10580 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
10581 target update constructs. */
10583 static void
10584 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
10586 tree expr = *expr_p;
10587 int kind;
10588 gomp_target *stmt;
10589 enum omp_region_type ort = ORT_WORKSHARE;
10591 switch (TREE_CODE (expr))
10593 case OACC_ENTER_DATA:
10594 case OACC_EXIT_DATA:
10595 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
10596 ort = ORT_ACC;
10597 break;
10598 case OACC_UPDATE:
10599 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
10600 ort = ORT_ACC;
10601 break;
10602 case OMP_TARGET_UPDATE:
10603 kind = GF_OMP_TARGET_KIND_UPDATE;
10604 break;
10605 case OMP_TARGET_ENTER_DATA:
10606 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
10607 break;
10608 case OMP_TARGET_EXIT_DATA:
10609 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
10610 break;
10611 default:
10612 gcc_unreachable ();
10614 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
10615 ort, TREE_CODE (expr));
10616 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
10617 TREE_CODE (expr));
10618 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
10620 gimplify_seq_add_stmt (pre_p, stmt);
10621 *expr_p = NULL_TREE;
10624 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
10625 stabilized the lhs of the atomic operation as *ADDR. Return true if
10626 EXPR is this stabilized form. */
10628 static bool
10629 goa_lhs_expr_p (tree expr, tree addr)
10631 /* Also include casts to other type variants. The C front end is fond
10632 of adding these for e.g. volatile variables. This is like
10633 STRIP_TYPE_NOPS but includes the main variant lookup. */
10634 STRIP_USELESS_TYPE_CONVERSION (expr);
10636 if (TREE_CODE (expr) == INDIRECT_REF)
10638 expr = TREE_OPERAND (expr, 0);
10639 while (expr != addr
10640 && (CONVERT_EXPR_P (expr)
10641 || TREE_CODE (expr) == NON_LVALUE_EXPR)
10642 && TREE_CODE (expr) == TREE_CODE (addr)
10643 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
10645 expr = TREE_OPERAND (expr, 0);
10646 addr = TREE_OPERAND (addr, 0);
10648 if (expr == addr)
10649 return true;
10650 return (TREE_CODE (addr) == ADDR_EXPR
10651 && TREE_CODE (expr) == ADDR_EXPR
10652 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
10654 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
10655 return true;
10656 return false;
10659 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
10660 expression does not involve the lhs, evaluate it into a temporary.
10661 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
10662 or -1 if an error was encountered. */
10664 static int
10665 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
10666 tree lhs_var)
10668 tree expr = *expr_p;
10669 int saw_lhs;
10671 if (goa_lhs_expr_p (expr, lhs_addr))
10673 *expr_p = lhs_var;
10674 return 1;
10676 if (is_gimple_val (expr))
10677 return 0;
10679 saw_lhs = 0;
10680 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
10682 case tcc_binary:
10683 case tcc_comparison:
10684 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
10685 lhs_var);
10686 /* FALLTHRU */
10687 case tcc_unary:
10688 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
10689 lhs_var);
10690 break;
10691 case tcc_expression:
10692 switch (TREE_CODE (expr))
10694 case TRUTH_ANDIF_EXPR:
10695 case TRUTH_ORIF_EXPR:
10696 case TRUTH_AND_EXPR:
10697 case TRUTH_OR_EXPR:
10698 case TRUTH_XOR_EXPR:
10699 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
10700 lhs_addr, lhs_var);
10701 /* FALLTHRU */
10702 case TRUTH_NOT_EXPR:
10703 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
10704 lhs_addr, lhs_var);
10705 break;
10706 case COMPOUND_EXPR:
10707 /* Break out any preevaluations from cp_build_modify_expr. */
10708 for (; TREE_CODE (expr) == COMPOUND_EXPR;
10709 expr = TREE_OPERAND (expr, 1))
10710 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
10711 *expr_p = expr;
10712 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var);
10713 default:
10714 break;
10716 break;
10717 default:
10718 break;
10721 if (saw_lhs == 0)
10723 enum gimplify_status gs;
10724 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
10725 if (gs != GS_ALL_DONE)
10726 saw_lhs = -1;
10729 return saw_lhs;
10732 /* Gimplify an OMP_ATOMIC statement. */
10734 static enum gimplify_status
10735 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
10737 tree addr = TREE_OPERAND (*expr_p, 0);
10738 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
10739 ? NULL : TREE_OPERAND (*expr_p, 1);
10740 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
10741 tree tmp_load;
10742 gomp_atomic_load *loadstmt;
10743 gomp_atomic_store *storestmt;
10745 tmp_load = create_tmp_reg (type);
10746 if (rhs && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load) < 0)
10747 return GS_ERROR;
10749 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
10750 != GS_ALL_DONE)
10751 return GS_ERROR;
10753 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr);
10754 gimplify_seq_add_stmt (pre_p, loadstmt);
10755 if (rhs && gimplify_expr (&rhs, pre_p, NULL, is_gimple_val, fb_rvalue)
10756 != GS_ALL_DONE)
10757 return GS_ERROR;
10759 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
10760 rhs = tmp_load;
10761 storestmt = gimple_build_omp_atomic_store (rhs);
10762 gimplify_seq_add_stmt (pre_p, storestmt);
10763 if (OMP_ATOMIC_SEQ_CST (*expr_p))
10765 gimple_omp_atomic_set_seq_cst (loadstmt);
10766 gimple_omp_atomic_set_seq_cst (storestmt);
10768 switch (TREE_CODE (*expr_p))
10770 case OMP_ATOMIC_READ:
10771 case OMP_ATOMIC_CAPTURE_OLD:
10772 *expr_p = tmp_load;
10773 gimple_omp_atomic_set_need_value (loadstmt);
10774 break;
10775 case OMP_ATOMIC_CAPTURE_NEW:
10776 *expr_p = rhs;
10777 gimple_omp_atomic_set_need_value (storestmt);
10778 break;
10779 default:
10780 *expr_p = NULL;
10781 break;
10784 return GS_ALL_DONE;
10787 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
10788 body, and adding some EH bits. */
10790 static enum gimplify_status
10791 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
10793 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
10794 gimple *body_stmt;
10795 gtransaction *trans_stmt;
10796 gimple_seq body = NULL;
10797 int subcode = 0;
10799 /* Wrap the transaction body in a BIND_EXPR so we have a context
10800 where to put decls for OMP. */
10801 if (TREE_CODE (tbody) != BIND_EXPR)
10803 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
10804 TREE_SIDE_EFFECTS (bind) = 1;
10805 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
10806 TRANSACTION_EXPR_BODY (expr) = bind;
10809 push_gimplify_context ();
10810 temp = voidify_wrapper_expr (*expr_p, NULL);
10812 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
10813 pop_gimplify_context (body_stmt);
10815 trans_stmt = gimple_build_transaction (body);
10816 if (TRANSACTION_EXPR_OUTER (expr))
10817 subcode = GTMA_IS_OUTER;
10818 else if (TRANSACTION_EXPR_RELAXED (expr))
10819 subcode = GTMA_IS_RELAXED;
10820 gimple_transaction_set_subcode (trans_stmt, subcode);
10822 gimplify_seq_add_stmt (pre_p, trans_stmt);
10824 if (temp)
10826 *expr_p = temp;
10827 return GS_OK;
10830 *expr_p = NULL_TREE;
10831 return GS_ALL_DONE;
10834 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
10835 is the OMP_BODY of the original EXPR (which has already been
10836 gimplified so it's not present in the EXPR).
10838 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
10840 static gimple *
10841 gimplify_omp_ordered (tree expr, gimple_seq body)
10843 tree c, decls;
10844 int failures = 0;
10845 unsigned int i;
10846 tree source_c = NULL_TREE;
10847 tree sink_c = NULL_TREE;
10849 if (gimplify_omp_ctxp)
10851 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
10852 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10853 && gimplify_omp_ctxp->loop_iter_var.is_empty ()
10854 && (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK
10855 || OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE))
10857 error_at (OMP_CLAUSE_LOCATION (c),
10858 "%<ordered%> construct with %<depend%> clause must be "
10859 "closely nested inside a loop with %<ordered%> clause "
10860 "with a parameter");
10861 failures++;
10863 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10864 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
10866 bool fail = false;
10867 for (decls = OMP_CLAUSE_DECL (c), i = 0;
10868 decls && TREE_CODE (decls) == TREE_LIST;
10869 decls = TREE_CHAIN (decls), ++i)
10870 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
10871 continue;
10872 else if (TREE_VALUE (decls)
10873 != gimplify_omp_ctxp->loop_iter_var[2 * i])
10875 error_at (OMP_CLAUSE_LOCATION (c),
10876 "variable %qE is not an iteration "
10877 "of outermost loop %d, expected %qE",
10878 TREE_VALUE (decls), i + 1,
10879 gimplify_omp_ctxp->loop_iter_var[2 * i]);
10880 fail = true;
10881 failures++;
10883 else
10884 TREE_VALUE (decls)
10885 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
10886 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
10888 error_at (OMP_CLAUSE_LOCATION (c),
10889 "number of variables in %<depend(sink)%> "
10890 "clause does not match number of "
10891 "iteration variables");
10892 failures++;
10894 sink_c = c;
10896 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10897 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
10899 if (source_c)
10901 error_at (OMP_CLAUSE_LOCATION (c),
10902 "more than one %<depend(source)%> clause on an "
10903 "%<ordered%> construct");
10904 failures++;
10906 else
10907 source_c = c;
10910 if (source_c && sink_c)
10912 error_at (OMP_CLAUSE_LOCATION (source_c),
10913 "%<depend(source)%> clause specified together with "
10914 "%<depend(sink:)%> clauses on the same construct");
10915 failures++;
10918 if (failures)
10919 return gimple_build_nop ();
10920 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
10923 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
10924 expression produces a value to be used as an operand inside a GIMPLE
10925 statement, the value will be stored back in *EXPR_P. This value will
10926 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
10927 an SSA_NAME. The corresponding sequence of GIMPLE statements is
10928 emitted in PRE_P and POST_P.
10930 Additionally, this process may overwrite parts of the input
10931 expression during gimplification. Ideally, it should be
10932 possible to do non-destructive gimplification.
10934 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
10935 the expression needs to evaluate to a value to be used as
10936 an operand in a GIMPLE statement, this value will be stored in
10937 *EXPR_P on exit. This happens when the caller specifies one
10938 of fb_lvalue or fb_rvalue fallback flags.
10940 PRE_P will contain the sequence of GIMPLE statements corresponding
10941 to the evaluation of EXPR and all the side-effects that must
10942 be executed before the main expression. On exit, the last
10943 statement of PRE_P is the core statement being gimplified. For
10944 instance, when gimplifying 'if (++a)' the last statement in
10945 PRE_P will be 'if (t.1)' where t.1 is the result of
10946 pre-incrementing 'a'.
10948 POST_P will contain the sequence of GIMPLE statements corresponding
10949 to the evaluation of all the side-effects that must be executed
10950 after the main expression. If this is NULL, the post
10951 side-effects are stored at the end of PRE_P.
10953 The reason why the output is split in two is to handle post
10954 side-effects explicitly. In some cases, an expression may have
10955 inner and outer post side-effects which need to be emitted in
10956 an order different from the one given by the recursive
10957 traversal. For instance, for the expression (*p--)++ the post
10958 side-effects of '--' must actually occur *after* the post
10959 side-effects of '++'. However, gimplification will first visit
10960 the inner expression, so if a separate POST sequence was not
10961 used, the resulting sequence would be:
10963 1 t.1 = *p
10964 2 p = p - 1
10965 3 t.2 = t.1 + 1
10966 4 *p = t.2
10968 However, the post-decrement operation in line #2 must not be
10969 evaluated until after the store to *p at line #4, so the
10970 correct sequence should be:
10972 1 t.1 = *p
10973 2 t.2 = t.1 + 1
10974 3 *p = t.2
10975 4 p = p - 1
10977 So, by specifying a separate post queue, it is possible
10978 to emit the post side-effects in the correct order.
10979 If POST_P is NULL, an internal queue will be used. Before
10980 returning to the caller, the sequence POST_P is appended to
10981 the main output sequence PRE_P.
10983 GIMPLE_TEST_F points to a function that takes a tree T and
10984 returns nonzero if T is in the GIMPLE form requested by the
10985 caller. The GIMPLE predicates are in gimple.c.
10987 FALLBACK tells the function what sort of a temporary we want if
10988 gimplification cannot produce an expression that complies with
10989 GIMPLE_TEST_F.
10991 fb_none means that no temporary should be generated
10992 fb_rvalue means that an rvalue is OK to generate
10993 fb_lvalue means that an lvalue is OK to generate
10994 fb_either means that either is OK, but an lvalue is preferable.
10995 fb_mayfail means that gimplification may fail (in which case
10996 GS_ERROR will be returned)
10998 The return value is either GS_ERROR or GS_ALL_DONE, since this
10999 function iterates until EXPR is completely gimplified or an error
11000 occurs. */
11002 enum gimplify_status
11003 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
11004 bool (*gimple_test_f) (tree), fallback_t fallback)
11006 tree tmp;
11007 gimple_seq internal_pre = NULL;
11008 gimple_seq internal_post = NULL;
11009 tree save_expr;
11010 bool is_statement;
11011 location_t saved_location;
11012 enum gimplify_status ret;
11013 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
11014 tree label;
11016 save_expr = *expr_p;
11017 if (save_expr == NULL_TREE)
11018 return GS_ALL_DONE;
11020 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
11021 is_statement = gimple_test_f == is_gimple_stmt;
11022 if (is_statement)
11023 gcc_assert (pre_p);
11025 /* Consistency checks. */
11026 if (gimple_test_f == is_gimple_reg)
11027 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
11028 else if (gimple_test_f == is_gimple_val
11029 || gimple_test_f == is_gimple_call_addr
11030 || gimple_test_f == is_gimple_condexpr
11031 || gimple_test_f == is_gimple_mem_rhs
11032 || gimple_test_f == is_gimple_mem_rhs_or_call
11033 || gimple_test_f == is_gimple_reg_rhs
11034 || gimple_test_f == is_gimple_reg_rhs_or_call
11035 || gimple_test_f == is_gimple_asm_val
11036 || gimple_test_f == is_gimple_mem_ref_addr)
11037 gcc_assert (fallback & fb_rvalue);
11038 else if (gimple_test_f == is_gimple_min_lval
11039 || gimple_test_f == is_gimple_lvalue)
11040 gcc_assert (fallback & fb_lvalue);
11041 else if (gimple_test_f == is_gimple_addressable)
11042 gcc_assert (fallback & fb_either);
11043 else if (gimple_test_f == is_gimple_stmt)
11044 gcc_assert (fallback == fb_none);
11045 else
11047 /* We should have recognized the GIMPLE_TEST_F predicate to
11048 know what kind of fallback to use in case a temporary is
11049 needed to hold the value or address of *EXPR_P. */
11050 gcc_unreachable ();
11053 /* We used to check the predicate here and return immediately if it
11054 succeeds. This is wrong; the design is for gimplification to be
11055 idempotent, and for the predicates to only test for valid forms, not
11056 whether they are fully simplified. */
11057 if (pre_p == NULL)
11058 pre_p = &internal_pre;
11060 if (post_p == NULL)
11061 post_p = &internal_post;
11063 /* Remember the last statements added to PRE_P and POST_P. Every
11064 new statement added by the gimplification helpers needs to be
11065 annotated with location information. To centralize the
11066 responsibility, we remember the last statement that had been
11067 added to both queues before gimplifying *EXPR_P. If
11068 gimplification produces new statements in PRE_P and POST_P, those
11069 statements will be annotated with the same location information
11070 as *EXPR_P. */
11071 pre_last_gsi = gsi_last (*pre_p);
11072 post_last_gsi = gsi_last (*post_p);
11074 saved_location = input_location;
11075 if (save_expr != error_mark_node
11076 && EXPR_HAS_LOCATION (*expr_p))
11077 input_location = EXPR_LOCATION (*expr_p);
11079 /* Loop over the specific gimplifiers until the toplevel node
11080 remains the same. */
11083 /* Strip away as many useless type conversions as possible
11084 at the toplevel. */
11085 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
11087 /* Remember the expr. */
11088 save_expr = *expr_p;
11090 /* Die, die, die, my darling. */
11091 if (save_expr == error_mark_node
11092 || (TREE_TYPE (save_expr)
11093 && TREE_TYPE (save_expr) == error_mark_node))
11095 ret = GS_ERROR;
11096 break;
11099 /* Do any language-specific gimplification. */
11100 ret = ((enum gimplify_status)
11101 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
11102 if (ret == GS_OK)
11104 if (*expr_p == NULL_TREE)
11105 break;
11106 if (*expr_p != save_expr)
11107 continue;
11109 else if (ret != GS_UNHANDLED)
11110 break;
11112 /* Make sure that all the cases set 'ret' appropriately. */
11113 ret = GS_UNHANDLED;
11114 switch (TREE_CODE (*expr_p))
11116 /* First deal with the special cases. */
11118 case POSTINCREMENT_EXPR:
11119 case POSTDECREMENT_EXPR:
11120 case PREINCREMENT_EXPR:
11121 case PREDECREMENT_EXPR:
11122 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
11123 fallback != fb_none,
11124 TREE_TYPE (*expr_p));
11125 break;
11127 case VIEW_CONVERT_EXPR:
11128 if (is_gimple_reg_type (TREE_TYPE (*expr_p))
11129 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
11131 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11132 post_p, is_gimple_val, fb_rvalue);
11133 recalculate_side_effects (*expr_p);
11134 break;
11136 /* Fallthru. */
11138 case ARRAY_REF:
11139 case ARRAY_RANGE_REF:
11140 case REALPART_EXPR:
11141 case IMAGPART_EXPR:
11142 case COMPONENT_REF:
11143 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
11144 fallback ? fallback : fb_rvalue);
11145 break;
11147 case COND_EXPR:
11148 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
11150 /* C99 code may assign to an array in a structure value of a
11151 conditional expression, and this has undefined behavior
11152 only on execution, so create a temporary if an lvalue is
11153 required. */
11154 if (fallback == fb_lvalue)
11156 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11157 mark_addressable (*expr_p);
11158 ret = GS_OK;
11160 break;
11162 case CALL_EXPR:
11163 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
11165 /* C99 code may assign to an array in a structure returned
11166 from a function, and this has undefined behavior only on
11167 execution, so create a temporary if an lvalue is
11168 required. */
11169 if (fallback == fb_lvalue)
11171 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11172 mark_addressable (*expr_p);
11173 ret = GS_OK;
11175 break;
11177 case TREE_LIST:
11178 gcc_unreachable ();
11180 case COMPOUND_EXPR:
11181 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
11182 break;
11184 case COMPOUND_LITERAL_EXPR:
11185 ret = gimplify_compound_literal_expr (expr_p, pre_p,
11186 gimple_test_f, fallback);
11187 break;
11189 case MODIFY_EXPR:
11190 case INIT_EXPR:
11191 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
11192 fallback != fb_none);
11193 break;
11195 case TRUTH_ANDIF_EXPR:
11196 case TRUTH_ORIF_EXPR:
11198 /* Preserve the original type of the expression and the
11199 source location of the outer expression. */
11200 tree org_type = TREE_TYPE (*expr_p);
11201 *expr_p = gimple_boolify (*expr_p);
11202 *expr_p = build3_loc (input_location, COND_EXPR,
11203 org_type, *expr_p,
11204 fold_convert_loc
11205 (input_location,
11206 org_type, boolean_true_node),
11207 fold_convert_loc
11208 (input_location,
11209 org_type, boolean_false_node));
11210 ret = GS_OK;
11211 break;
11214 case TRUTH_NOT_EXPR:
11216 tree type = TREE_TYPE (*expr_p);
11217 /* The parsers are careful to generate TRUTH_NOT_EXPR
11218 only with operands that are always zero or one.
11219 We do not fold here but handle the only interesting case
11220 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
11221 *expr_p = gimple_boolify (*expr_p);
11222 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
11223 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
11224 TREE_TYPE (*expr_p),
11225 TREE_OPERAND (*expr_p, 0));
11226 else
11227 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
11228 TREE_TYPE (*expr_p),
11229 TREE_OPERAND (*expr_p, 0),
11230 build_int_cst (TREE_TYPE (*expr_p), 1));
11231 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
11232 *expr_p = fold_convert_loc (input_location, type, *expr_p);
11233 ret = GS_OK;
11234 break;
11237 case ADDR_EXPR:
11238 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
11239 break;
11241 case ANNOTATE_EXPR:
11243 tree cond = TREE_OPERAND (*expr_p, 0);
11244 tree kind = TREE_OPERAND (*expr_p, 1);
11245 tree type = TREE_TYPE (cond);
11246 if (!INTEGRAL_TYPE_P (type))
11248 *expr_p = cond;
11249 ret = GS_OK;
11250 break;
11252 tree tmp = create_tmp_var (type);
11253 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
11254 gcall *call
11255 = gimple_build_call_internal (IFN_ANNOTATE, 2, cond, kind);
11256 gimple_call_set_lhs (call, tmp);
11257 gimplify_seq_add_stmt (pre_p, call);
11258 *expr_p = tmp;
11259 ret = GS_ALL_DONE;
11260 break;
11263 case VA_ARG_EXPR:
11264 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
11265 break;
11267 CASE_CONVERT:
11268 if (IS_EMPTY_STMT (*expr_p))
11270 ret = GS_ALL_DONE;
11271 break;
11274 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
11275 || fallback == fb_none)
11277 /* Just strip a conversion to void (or in void context) and
11278 try again. */
11279 *expr_p = TREE_OPERAND (*expr_p, 0);
11280 ret = GS_OK;
11281 break;
11284 ret = gimplify_conversion (expr_p);
11285 if (ret == GS_ERROR)
11286 break;
11287 if (*expr_p != save_expr)
11288 break;
11289 /* FALLTHRU */
11291 case FIX_TRUNC_EXPR:
11292 /* unary_expr: ... | '(' cast ')' val | ... */
11293 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11294 is_gimple_val, fb_rvalue);
11295 recalculate_side_effects (*expr_p);
11296 break;
11298 case INDIRECT_REF:
11300 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
11301 bool notrap = TREE_THIS_NOTRAP (*expr_p);
11302 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
11304 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
11305 if (*expr_p != save_expr)
11307 ret = GS_OK;
11308 break;
11311 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11312 is_gimple_reg, fb_rvalue);
11313 if (ret == GS_ERROR)
11314 break;
11316 recalculate_side_effects (*expr_p);
11317 *expr_p = fold_build2_loc (input_location, MEM_REF,
11318 TREE_TYPE (*expr_p),
11319 TREE_OPERAND (*expr_p, 0),
11320 build_int_cst (saved_ptr_type, 0));
11321 TREE_THIS_VOLATILE (*expr_p) = volatilep;
11322 TREE_THIS_NOTRAP (*expr_p) = notrap;
11323 ret = GS_OK;
11324 break;
11327 /* We arrive here through the various re-gimplifcation paths. */
11328 case MEM_REF:
11329 /* First try re-folding the whole thing. */
11330 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
11331 TREE_OPERAND (*expr_p, 0),
11332 TREE_OPERAND (*expr_p, 1));
11333 if (tmp)
11335 REF_REVERSE_STORAGE_ORDER (tmp)
11336 = REF_REVERSE_STORAGE_ORDER (*expr_p);
11337 *expr_p = tmp;
11338 recalculate_side_effects (*expr_p);
11339 ret = GS_OK;
11340 break;
11342 /* Avoid re-gimplifying the address operand if it is already
11343 in suitable form. Re-gimplifying would mark the address
11344 operand addressable. Always gimplify when not in SSA form
11345 as we still may have to gimplify decls with value-exprs. */
11346 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
11347 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
11349 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11350 is_gimple_mem_ref_addr, fb_rvalue);
11351 if (ret == GS_ERROR)
11352 break;
11354 recalculate_side_effects (*expr_p);
11355 ret = GS_ALL_DONE;
11356 break;
11358 /* Constants need not be gimplified. */
11359 case INTEGER_CST:
11360 case REAL_CST:
11361 case FIXED_CST:
11362 case STRING_CST:
11363 case COMPLEX_CST:
11364 case VECTOR_CST:
11365 /* Drop the overflow flag on constants, we do not want
11366 that in the GIMPLE IL. */
11367 if (TREE_OVERFLOW_P (*expr_p))
11368 *expr_p = drop_tree_overflow (*expr_p);
11369 ret = GS_ALL_DONE;
11370 break;
11372 case CONST_DECL:
11373 /* If we require an lvalue, such as for ADDR_EXPR, retain the
11374 CONST_DECL node. Otherwise the decl is replaceable by its
11375 value. */
11376 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
11377 if (fallback & fb_lvalue)
11378 ret = GS_ALL_DONE;
11379 else
11381 *expr_p = DECL_INITIAL (*expr_p);
11382 ret = GS_OK;
11384 break;
11386 case DECL_EXPR:
11387 ret = gimplify_decl_expr (expr_p, pre_p);
11388 break;
11390 case BIND_EXPR:
11391 ret = gimplify_bind_expr (expr_p, pre_p);
11392 break;
11394 case LOOP_EXPR:
11395 ret = gimplify_loop_expr (expr_p, pre_p);
11396 break;
11398 case SWITCH_EXPR:
11399 ret = gimplify_switch_expr (expr_p, pre_p);
11400 break;
11402 case EXIT_EXPR:
11403 ret = gimplify_exit_expr (expr_p);
11404 break;
11406 case GOTO_EXPR:
11407 /* If the target is not LABEL, then it is a computed jump
11408 and the target needs to be gimplified. */
11409 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
11411 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
11412 NULL, is_gimple_val, fb_rvalue);
11413 if (ret == GS_ERROR)
11414 break;
11416 gimplify_seq_add_stmt (pre_p,
11417 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
11418 ret = GS_ALL_DONE;
11419 break;
11421 case PREDICT_EXPR:
11422 gimplify_seq_add_stmt (pre_p,
11423 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
11424 PREDICT_EXPR_OUTCOME (*expr_p)));
11425 ret = GS_ALL_DONE;
11426 break;
11428 case LABEL_EXPR:
11429 ret = gimplify_label_expr (expr_p, pre_p);
11430 label = LABEL_EXPR_LABEL (*expr_p);
11431 gcc_assert (decl_function_context (label) == current_function_decl);
11433 /* If the label is used in a goto statement, or address of the label
11434 is taken, we need to unpoison all variables that were seen so far.
11435 Doing so would prevent us from reporting a false positives. */
11436 if (asan_poisoned_variables
11437 && asan_used_labels != NULL
11438 && asan_used_labels->contains (label))
11439 asan_poison_variables (asan_poisoned_variables, false, pre_p);
11440 break;
11442 case CASE_LABEL_EXPR:
11443 ret = gimplify_case_label_expr (expr_p, pre_p);
11445 if (gimplify_ctxp->live_switch_vars)
11446 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
11447 pre_p);
11448 break;
11450 case RETURN_EXPR:
11451 ret = gimplify_return_expr (*expr_p, pre_p);
11452 break;
11454 case CONSTRUCTOR:
11455 /* Don't reduce this in place; let gimplify_init_constructor work its
11456 magic. Buf if we're just elaborating this for side effects, just
11457 gimplify any element that has side-effects. */
11458 if (fallback == fb_none)
11460 unsigned HOST_WIDE_INT ix;
11461 tree val;
11462 tree temp = NULL_TREE;
11463 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
11464 if (TREE_SIDE_EFFECTS (val))
11465 append_to_statement_list (val, &temp);
11467 *expr_p = temp;
11468 ret = temp ? GS_OK : GS_ALL_DONE;
11470 /* C99 code may assign to an array in a constructed
11471 structure or union, and this has undefined behavior only
11472 on execution, so create a temporary if an lvalue is
11473 required. */
11474 else if (fallback == fb_lvalue)
11476 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11477 mark_addressable (*expr_p);
11478 ret = GS_OK;
11480 else
11481 ret = GS_ALL_DONE;
11482 break;
11484 /* The following are special cases that are not handled by the
11485 original GIMPLE grammar. */
11487 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
11488 eliminated. */
11489 case SAVE_EXPR:
11490 ret = gimplify_save_expr (expr_p, pre_p, post_p);
11491 break;
11493 case BIT_FIELD_REF:
11494 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11495 post_p, is_gimple_lvalue, fb_either);
11496 recalculate_side_effects (*expr_p);
11497 break;
11499 case TARGET_MEM_REF:
11501 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
11503 if (TMR_BASE (*expr_p))
11504 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
11505 post_p, is_gimple_mem_ref_addr, fb_either);
11506 if (TMR_INDEX (*expr_p))
11507 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
11508 post_p, is_gimple_val, fb_rvalue);
11509 if (TMR_INDEX2 (*expr_p))
11510 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
11511 post_p, is_gimple_val, fb_rvalue);
11512 /* TMR_STEP and TMR_OFFSET are always integer constants. */
11513 ret = MIN (r0, r1);
11515 break;
11517 case NON_LVALUE_EXPR:
11518 /* This should have been stripped above. */
11519 gcc_unreachable ();
11521 case ASM_EXPR:
11522 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
11523 break;
11525 case TRY_FINALLY_EXPR:
11526 case TRY_CATCH_EXPR:
11528 gimple_seq eval, cleanup;
11529 gtry *try_;
11531 /* Calls to destructors are generated automatically in FINALLY/CATCH
11532 block. They should have location as UNKNOWN_LOCATION. However,
11533 gimplify_call_expr will reset these call stmts to input_location
11534 if it finds stmt's location is unknown. To prevent resetting for
11535 destructors, we set the input_location to unknown.
11536 Note that this only affects the destructor calls in FINALLY/CATCH
11537 block, and will automatically reset to its original value by the
11538 end of gimplify_expr. */
11539 input_location = UNKNOWN_LOCATION;
11540 eval = cleanup = NULL;
11541 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
11542 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
11543 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
11544 if (gimple_seq_empty_p (cleanup))
11546 gimple_seq_add_seq (pre_p, eval);
11547 ret = GS_ALL_DONE;
11548 break;
11550 try_ = gimple_build_try (eval, cleanup,
11551 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
11552 ? GIMPLE_TRY_FINALLY
11553 : GIMPLE_TRY_CATCH);
11554 if (EXPR_HAS_LOCATION (save_expr))
11555 gimple_set_location (try_, EXPR_LOCATION (save_expr));
11556 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
11557 gimple_set_location (try_, saved_location);
11558 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
11559 gimple_try_set_catch_is_cleanup (try_,
11560 TRY_CATCH_IS_CLEANUP (*expr_p));
11561 gimplify_seq_add_stmt (pre_p, try_);
11562 ret = GS_ALL_DONE;
11563 break;
11566 case CLEANUP_POINT_EXPR:
11567 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
11568 break;
11570 case TARGET_EXPR:
11571 ret = gimplify_target_expr (expr_p, pre_p, post_p);
11572 break;
11574 case CATCH_EXPR:
11576 gimple *c;
11577 gimple_seq handler = NULL;
11578 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
11579 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
11580 gimplify_seq_add_stmt (pre_p, c);
11581 ret = GS_ALL_DONE;
11582 break;
11585 case EH_FILTER_EXPR:
11587 gimple *ehf;
11588 gimple_seq failure = NULL;
11590 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
11591 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
11592 gimple_set_no_warning (ehf, TREE_NO_WARNING (*expr_p));
11593 gimplify_seq_add_stmt (pre_p, ehf);
11594 ret = GS_ALL_DONE;
11595 break;
11598 case OBJ_TYPE_REF:
11600 enum gimplify_status r0, r1;
11601 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
11602 post_p, is_gimple_val, fb_rvalue);
11603 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
11604 post_p, is_gimple_val, fb_rvalue);
11605 TREE_SIDE_EFFECTS (*expr_p) = 0;
11606 ret = MIN (r0, r1);
11608 break;
11610 case LABEL_DECL:
11611 /* We get here when taking the address of a label. We mark
11612 the label as "forced"; meaning it can never be removed and
11613 it is a potential target for any computed goto. */
11614 FORCED_LABEL (*expr_p) = 1;
11615 ret = GS_ALL_DONE;
11616 break;
11618 case STATEMENT_LIST:
11619 ret = gimplify_statement_list (expr_p, pre_p);
11620 break;
11622 case WITH_SIZE_EXPR:
11624 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11625 post_p == &internal_post ? NULL : post_p,
11626 gimple_test_f, fallback);
11627 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
11628 is_gimple_val, fb_rvalue);
11629 ret = GS_ALL_DONE;
11631 break;
11633 case VAR_DECL:
11634 case PARM_DECL:
11635 ret = gimplify_var_or_parm_decl (expr_p);
11636 break;
11638 case RESULT_DECL:
11639 /* When within an OMP context, notice uses of variables. */
11640 if (gimplify_omp_ctxp)
11641 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
11642 ret = GS_ALL_DONE;
11643 break;
11645 case SSA_NAME:
11646 /* Allow callbacks into the gimplifier during optimization. */
11647 ret = GS_ALL_DONE;
11648 break;
11650 case OMP_PARALLEL:
11651 gimplify_omp_parallel (expr_p, pre_p);
11652 ret = GS_ALL_DONE;
11653 break;
11655 case OMP_TASK:
11656 gimplify_omp_task (expr_p, pre_p);
11657 ret = GS_ALL_DONE;
11658 break;
11660 case OMP_FOR:
11661 case OMP_SIMD:
11662 case CILK_SIMD:
11663 case CILK_FOR:
11664 case OMP_DISTRIBUTE:
11665 case OMP_TASKLOOP:
11666 case OACC_LOOP:
11667 ret = gimplify_omp_for (expr_p, pre_p);
11668 break;
11670 case OACC_CACHE:
11671 gimplify_oacc_cache (expr_p, pre_p);
11672 ret = GS_ALL_DONE;
11673 break;
11675 case OACC_DECLARE:
11676 gimplify_oacc_declare (expr_p, pre_p);
11677 ret = GS_ALL_DONE;
11678 break;
11680 case OACC_HOST_DATA:
11681 case OACC_DATA:
11682 case OACC_KERNELS:
11683 case OACC_PARALLEL:
11684 case OMP_SECTIONS:
11685 case OMP_SINGLE:
11686 case OMP_TARGET:
11687 case OMP_TARGET_DATA:
11688 case OMP_TEAMS:
11689 gimplify_omp_workshare (expr_p, pre_p);
11690 ret = GS_ALL_DONE;
11691 break;
11693 case OACC_ENTER_DATA:
11694 case OACC_EXIT_DATA:
11695 case OACC_UPDATE:
11696 case OMP_TARGET_UPDATE:
11697 case OMP_TARGET_ENTER_DATA:
11698 case OMP_TARGET_EXIT_DATA:
11699 gimplify_omp_target_update (expr_p, pre_p);
11700 ret = GS_ALL_DONE;
11701 break;
11703 case OMP_SECTION:
11704 case OMP_MASTER:
11705 case OMP_TASKGROUP:
11706 case OMP_ORDERED:
11707 case OMP_CRITICAL:
11709 gimple_seq body = NULL;
11710 gimple *g;
11712 gimplify_and_add (OMP_BODY (*expr_p), &body);
11713 switch (TREE_CODE (*expr_p))
11715 case OMP_SECTION:
11716 g = gimple_build_omp_section (body);
11717 break;
11718 case OMP_MASTER:
11719 g = gimple_build_omp_master (body);
11720 break;
11721 case OMP_TASKGROUP:
11723 gimple_seq cleanup = NULL;
11724 tree fn
11725 = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
11726 g = gimple_build_call (fn, 0);
11727 gimple_seq_add_stmt (&cleanup, g);
11728 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
11729 body = NULL;
11730 gimple_seq_add_stmt (&body, g);
11731 g = gimple_build_omp_taskgroup (body);
11733 break;
11734 case OMP_ORDERED:
11735 g = gimplify_omp_ordered (*expr_p, body);
11736 break;
11737 case OMP_CRITICAL:
11738 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
11739 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
11740 gimplify_adjust_omp_clauses (pre_p, body,
11741 &OMP_CRITICAL_CLAUSES (*expr_p),
11742 OMP_CRITICAL);
11743 g = gimple_build_omp_critical (body,
11744 OMP_CRITICAL_NAME (*expr_p),
11745 OMP_CRITICAL_CLAUSES (*expr_p));
11746 break;
11747 default:
11748 gcc_unreachable ();
11750 gimplify_seq_add_stmt (pre_p, g);
11751 ret = GS_ALL_DONE;
11752 break;
11755 case OMP_ATOMIC:
11756 case OMP_ATOMIC_READ:
11757 case OMP_ATOMIC_CAPTURE_OLD:
11758 case OMP_ATOMIC_CAPTURE_NEW:
11759 ret = gimplify_omp_atomic (expr_p, pre_p);
11760 break;
11762 case TRANSACTION_EXPR:
11763 ret = gimplify_transaction (expr_p, pre_p);
11764 break;
11766 case TRUTH_AND_EXPR:
11767 case TRUTH_OR_EXPR:
11768 case TRUTH_XOR_EXPR:
11770 tree orig_type = TREE_TYPE (*expr_p);
11771 tree new_type, xop0, xop1;
11772 *expr_p = gimple_boolify (*expr_p);
11773 new_type = TREE_TYPE (*expr_p);
11774 if (!useless_type_conversion_p (orig_type, new_type))
11776 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
11777 ret = GS_OK;
11778 break;
11781 /* Boolified binary truth expressions are semantically equivalent
11782 to bitwise binary expressions. Canonicalize them to the
11783 bitwise variant. */
11784 switch (TREE_CODE (*expr_p))
11786 case TRUTH_AND_EXPR:
11787 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
11788 break;
11789 case TRUTH_OR_EXPR:
11790 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
11791 break;
11792 case TRUTH_XOR_EXPR:
11793 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
11794 break;
11795 default:
11796 break;
11798 /* Now make sure that operands have compatible type to
11799 expression's new_type. */
11800 xop0 = TREE_OPERAND (*expr_p, 0);
11801 xop1 = TREE_OPERAND (*expr_p, 1);
11802 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
11803 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
11804 new_type,
11805 xop0);
11806 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
11807 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
11808 new_type,
11809 xop1);
11810 /* Continue classified as tcc_binary. */
11811 goto expr_2;
11814 case VEC_COND_EXPR:
11816 enum gimplify_status r0, r1, r2;
11818 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11819 post_p, is_gimple_condexpr, fb_rvalue);
11820 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11821 post_p, is_gimple_val, fb_rvalue);
11822 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
11823 post_p, is_gimple_val, fb_rvalue);
11825 ret = MIN (MIN (r0, r1), r2);
11826 recalculate_side_effects (*expr_p);
11828 break;
11830 case FMA_EXPR:
11831 case VEC_PERM_EXPR:
11832 /* Classified as tcc_expression. */
11833 goto expr_3;
11835 case BIT_INSERT_EXPR:
11836 /* Argument 3 is a constant. */
11837 goto expr_2;
11839 case POINTER_PLUS_EXPR:
11841 enum gimplify_status r0, r1;
11842 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11843 post_p, is_gimple_val, fb_rvalue);
11844 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11845 post_p, is_gimple_val, fb_rvalue);
11846 recalculate_side_effects (*expr_p);
11847 ret = MIN (r0, r1);
11848 break;
11851 case CILK_SYNC_STMT:
11853 if (!fn_contains_cilk_spawn_p (cfun))
11855 error_at (EXPR_LOCATION (*expr_p),
11856 "expected %<_Cilk_spawn%> before %<_Cilk_sync%>");
11857 ret = GS_ERROR;
11859 else
11861 gimplify_cilk_sync (expr_p, pre_p);
11862 ret = GS_ALL_DONE;
11864 break;
11867 default:
11868 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
11870 case tcc_comparison:
11871 /* Handle comparison of objects of non scalar mode aggregates
11872 with a call to memcmp. It would be nice to only have to do
11873 this for variable-sized objects, but then we'd have to allow
11874 the same nest of reference nodes we allow for MODIFY_EXPR and
11875 that's too complex.
11877 Compare scalar mode aggregates as scalar mode values. Using
11878 memcmp for them would be very inefficient at best, and is
11879 plain wrong if bitfields are involved. */
11881 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
11883 /* Vector comparisons need no boolification. */
11884 if (TREE_CODE (type) == VECTOR_TYPE)
11885 goto expr_2;
11886 else if (!AGGREGATE_TYPE_P (type))
11888 tree org_type = TREE_TYPE (*expr_p);
11889 *expr_p = gimple_boolify (*expr_p);
11890 if (!useless_type_conversion_p (org_type,
11891 TREE_TYPE (*expr_p)))
11893 *expr_p = fold_convert_loc (input_location,
11894 org_type, *expr_p);
11895 ret = GS_OK;
11897 else
11898 goto expr_2;
11900 else if (TYPE_MODE (type) != BLKmode)
11901 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
11902 else
11903 ret = gimplify_variable_sized_compare (expr_p);
11905 break;
11908 /* If *EXPR_P does not need to be special-cased, handle it
11909 according to its class. */
11910 case tcc_unary:
11911 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11912 post_p, is_gimple_val, fb_rvalue);
11913 break;
11915 case tcc_binary:
11916 expr_2:
11918 enum gimplify_status r0, r1;
11920 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11921 post_p, is_gimple_val, fb_rvalue);
11922 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11923 post_p, is_gimple_val, fb_rvalue);
11925 ret = MIN (r0, r1);
11926 break;
11929 expr_3:
11931 enum gimplify_status r0, r1, r2;
11933 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11934 post_p, is_gimple_val, fb_rvalue);
11935 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11936 post_p, is_gimple_val, fb_rvalue);
11937 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
11938 post_p, is_gimple_val, fb_rvalue);
11940 ret = MIN (MIN (r0, r1), r2);
11941 break;
11944 case tcc_declaration:
11945 case tcc_constant:
11946 ret = GS_ALL_DONE;
11947 goto dont_recalculate;
11949 default:
11950 gcc_unreachable ();
11953 recalculate_side_effects (*expr_p);
11955 dont_recalculate:
11956 break;
11959 gcc_assert (*expr_p || ret != GS_OK);
11961 while (ret == GS_OK);
11963 /* If we encountered an error_mark somewhere nested inside, either
11964 stub out the statement or propagate the error back out. */
11965 if (ret == GS_ERROR)
11967 if (is_statement)
11968 *expr_p = NULL;
11969 goto out;
11972 /* This was only valid as a return value from the langhook, which
11973 we handled. Make sure it doesn't escape from any other context. */
11974 gcc_assert (ret != GS_UNHANDLED);
11976 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
11978 /* We aren't looking for a value, and we don't have a valid
11979 statement. If it doesn't have side-effects, throw it away. */
11980 if (!TREE_SIDE_EFFECTS (*expr_p))
11981 *expr_p = NULL;
11982 else if (!TREE_THIS_VOLATILE (*expr_p))
11984 /* This is probably a _REF that contains something nested that
11985 has side effects. Recurse through the operands to find it. */
11986 enum tree_code code = TREE_CODE (*expr_p);
11988 switch (code)
11990 case COMPONENT_REF:
11991 case REALPART_EXPR:
11992 case IMAGPART_EXPR:
11993 case VIEW_CONVERT_EXPR:
11994 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11995 gimple_test_f, fallback);
11996 break;
11998 case ARRAY_REF:
11999 case ARRAY_RANGE_REF:
12000 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
12001 gimple_test_f, fallback);
12002 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
12003 gimple_test_f, fallback);
12004 break;
12006 default:
12007 /* Anything else with side-effects must be converted to
12008 a valid statement before we get here. */
12009 gcc_unreachable ();
12012 *expr_p = NULL;
12014 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
12015 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
12017 /* Historically, the compiler has treated a bare reference
12018 to a non-BLKmode volatile lvalue as forcing a load. */
12019 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
12021 /* Normally, we do not want to create a temporary for a
12022 TREE_ADDRESSABLE type because such a type should not be
12023 copied by bitwise-assignment. However, we make an
12024 exception here, as all we are doing here is ensuring that
12025 we read the bytes that make up the type. We use
12026 create_tmp_var_raw because create_tmp_var will abort when
12027 given a TREE_ADDRESSABLE type. */
12028 tree tmp = create_tmp_var_raw (type, "vol");
12029 gimple_add_tmp_var (tmp);
12030 gimplify_assign (tmp, *expr_p, pre_p);
12031 *expr_p = NULL;
12033 else
12034 /* We can't do anything useful with a volatile reference to
12035 an incomplete type, so just throw it away. Likewise for
12036 a BLKmode type, since any implicit inner load should
12037 already have been turned into an explicit one by the
12038 gimplification process. */
12039 *expr_p = NULL;
12042 /* If we are gimplifying at the statement level, we're done. Tack
12043 everything together and return. */
12044 if (fallback == fb_none || is_statement)
12046 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
12047 it out for GC to reclaim it. */
12048 *expr_p = NULL_TREE;
12050 if (!gimple_seq_empty_p (internal_pre)
12051 || !gimple_seq_empty_p (internal_post))
12053 gimplify_seq_add_seq (&internal_pre, internal_post);
12054 gimplify_seq_add_seq (pre_p, internal_pre);
12057 /* The result of gimplifying *EXPR_P is going to be the last few
12058 statements in *PRE_P and *POST_P. Add location information
12059 to all the statements that were added by the gimplification
12060 helpers. */
12061 if (!gimple_seq_empty_p (*pre_p))
12062 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
12064 if (!gimple_seq_empty_p (*post_p))
12065 annotate_all_with_location_after (*post_p, post_last_gsi,
12066 input_location);
12068 goto out;
12071 #ifdef ENABLE_GIMPLE_CHECKING
12072 if (*expr_p)
12074 enum tree_code code = TREE_CODE (*expr_p);
12075 /* These expressions should already be in gimple IR form. */
12076 gcc_assert (code != MODIFY_EXPR
12077 && code != ASM_EXPR
12078 && code != BIND_EXPR
12079 && code != CATCH_EXPR
12080 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
12081 && code != EH_FILTER_EXPR
12082 && code != GOTO_EXPR
12083 && code != LABEL_EXPR
12084 && code != LOOP_EXPR
12085 && code != SWITCH_EXPR
12086 && code != TRY_FINALLY_EXPR
12087 && code != OACC_PARALLEL
12088 && code != OACC_KERNELS
12089 && code != OACC_DATA
12090 && code != OACC_HOST_DATA
12091 && code != OACC_DECLARE
12092 && code != OACC_UPDATE
12093 && code != OACC_ENTER_DATA
12094 && code != OACC_EXIT_DATA
12095 && code != OACC_CACHE
12096 && code != OMP_CRITICAL
12097 && code != OMP_FOR
12098 && code != OACC_LOOP
12099 && code != OMP_MASTER
12100 && code != OMP_TASKGROUP
12101 && code != OMP_ORDERED
12102 && code != OMP_PARALLEL
12103 && code != OMP_SECTIONS
12104 && code != OMP_SECTION
12105 && code != OMP_SINGLE);
12107 #endif
12109 /* Otherwise we're gimplifying a subexpression, so the resulting
12110 value is interesting. If it's a valid operand that matches
12111 GIMPLE_TEST_F, we're done. Unless we are handling some
12112 post-effects internally; if that's the case, we need to copy into
12113 a temporary before adding the post-effects to POST_P. */
12114 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
12115 goto out;
12117 /* Otherwise, we need to create a new temporary for the gimplified
12118 expression. */
12120 /* We can't return an lvalue if we have an internal postqueue. The
12121 object the lvalue refers to would (probably) be modified by the
12122 postqueue; we need to copy the value out first, which means an
12123 rvalue. */
12124 if ((fallback & fb_lvalue)
12125 && gimple_seq_empty_p (internal_post)
12126 && is_gimple_addressable (*expr_p))
12128 /* An lvalue will do. Take the address of the expression, store it
12129 in a temporary, and replace the expression with an INDIRECT_REF of
12130 that temporary. */
12131 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
12132 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
12133 *expr_p = build_simple_mem_ref (tmp);
12135 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
12137 /* An rvalue will do. Assign the gimplified expression into a
12138 new temporary TMP and replace the original expression with
12139 TMP. First, make sure that the expression has a type so that
12140 it can be assigned into a temporary. */
12141 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
12142 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
12144 else
12146 #ifdef ENABLE_GIMPLE_CHECKING
12147 if (!(fallback & fb_mayfail))
12149 fprintf (stderr, "gimplification failed:\n");
12150 print_generic_expr (stderr, *expr_p, 0);
12151 debug_tree (*expr_p);
12152 internal_error ("gimplification failed");
12154 #endif
12155 gcc_assert (fallback & fb_mayfail);
12157 /* If this is an asm statement, and the user asked for the
12158 impossible, don't die. Fail and let gimplify_asm_expr
12159 issue an error. */
12160 ret = GS_ERROR;
12161 goto out;
12164 /* Make sure the temporary matches our predicate. */
12165 gcc_assert ((*gimple_test_f) (*expr_p));
12167 if (!gimple_seq_empty_p (internal_post))
12169 annotate_all_with_location (internal_post, input_location);
12170 gimplify_seq_add_seq (pre_p, internal_post);
12173 out:
12174 input_location = saved_location;
12175 return ret;
12178 /* Like gimplify_expr but make sure the gimplified result is not itself
12179 a SSA name (but a decl if it were). Temporaries required by
12180 evaluating *EXPR_P may be still SSA names. */
12182 static enum gimplify_status
12183 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
12184 bool (*gimple_test_f) (tree), fallback_t fallback,
12185 bool allow_ssa)
12187 bool was_ssa_name_p = TREE_CODE (*expr_p) == SSA_NAME;
12188 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
12189 gimple_test_f, fallback);
12190 if (! allow_ssa
12191 && TREE_CODE (*expr_p) == SSA_NAME)
12193 tree name = *expr_p;
12194 if (was_ssa_name_p)
12195 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
12196 else
12198 /* Avoid the extra copy if possible. */
12199 *expr_p = create_tmp_reg (TREE_TYPE (name));
12200 gimple_set_lhs (SSA_NAME_DEF_STMT (name), *expr_p);
12201 release_ssa_name (name);
12204 return ret;
12207 /* Look through TYPE for variable-sized objects and gimplify each such
12208 size that we find. Add to LIST_P any statements generated. */
12210 void
12211 gimplify_type_sizes (tree type, gimple_seq *list_p)
12213 tree field, t;
12215 if (type == NULL || type == error_mark_node)
12216 return;
12218 /* We first do the main variant, then copy into any other variants. */
12219 type = TYPE_MAIN_VARIANT (type);
12221 /* Avoid infinite recursion. */
12222 if (TYPE_SIZES_GIMPLIFIED (type))
12223 return;
12225 TYPE_SIZES_GIMPLIFIED (type) = 1;
12227 switch (TREE_CODE (type))
12229 case INTEGER_TYPE:
12230 case ENUMERAL_TYPE:
12231 case BOOLEAN_TYPE:
12232 case REAL_TYPE:
12233 case FIXED_POINT_TYPE:
12234 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
12235 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
12237 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
12239 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
12240 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
12242 break;
12244 case ARRAY_TYPE:
12245 /* These types may not have declarations, so handle them here. */
12246 gimplify_type_sizes (TREE_TYPE (type), list_p);
12247 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
12248 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
12249 with assigned stack slots, for -O1+ -g they should be tracked
12250 by VTA. */
12251 if (!(TYPE_NAME (type)
12252 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
12253 && DECL_IGNORED_P (TYPE_NAME (type)))
12254 && TYPE_DOMAIN (type)
12255 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
12257 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
12258 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
12259 DECL_IGNORED_P (t) = 0;
12260 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
12261 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
12262 DECL_IGNORED_P (t) = 0;
12264 break;
12266 case RECORD_TYPE:
12267 case UNION_TYPE:
12268 case QUAL_UNION_TYPE:
12269 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
12270 if (TREE_CODE (field) == FIELD_DECL)
12272 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
12273 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
12274 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
12275 gimplify_type_sizes (TREE_TYPE (field), list_p);
12277 break;
12279 case POINTER_TYPE:
12280 case REFERENCE_TYPE:
12281 /* We used to recurse on the pointed-to type here, which turned out to
12282 be incorrect because its definition might refer to variables not
12283 yet initialized at this point if a forward declaration is involved.
12285 It was actually useful for anonymous pointed-to types to ensure
12286 that the sizes evaluation dominates every possible later use of the
12287 values. Restricting to such types here would be safe since there
12288 is no possible forward declaration around, but would introduce an
12289 undesirable middle-end semantic to anonymity. We then defer to
12290 front-ends the responsibility of ensuring that the sizes are
12291 evaluated both early and late enough, e.g. by attaching artificial
12292 type declarations to the tree. */
12293 break;
12295 default:
12296 break;
12299 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
12300 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
12302 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
12304 TYPE_SIZE (t) = TYPE_SIZE (type);
12305 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
12306 TYPE_SIZES_GIMPLIFIED (t) = 1;
12310 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
12311 a size or position, has had all of its SAVE_EXPRs evaluated.
12312 We add any required statements to *STMT_P. */
12314 void
12315 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
12317 tree expr = *expr_p;
12319 /* We don't do anything if the value isn't there, is constant, or contains
12320 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
12321 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
12322 will want to replace it with a new variable, but that will cause problems
12323 if this type is from outside the function. It's OK to have that here. */
12324 if (is_gimple_sizepos (expr))
12325 return;
12327 *expr_p = unshare_expr (expr);
12329 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
12330 if the def vanishes. */
12331 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
12334 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
12335 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
12336 is true, also gimplify the parameters. */
12338 gbind *
12339 gimplify_body (tree fndecl, bool do_parms)
12341 location_t saved_location = input_location;
12342 gimple_seq parm_stmts, seq;
12343 gimple *outer_stmt;
12344 gbind *outer_bind;
12345 struct cgraph_node *cgn;
12347 timevar_push (TV_TREE_GIMPLIFY);
12349 init_tree_ssa (cfun);
12351 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
12352 gimplification. */
12353 default_rtl_profile ();
12355 gcc_assert (gimplify_ctxp == NULL);
12356 push_gimplify_context (true);
12358 if (flag_openacc || flag_openmp)
12360 gcc_assert (gimplify_omp_ctxp == NULL);
12361 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
12362 gimplify_omp_ctxp = new_omp_context (ORT_TARGET);
12365 /* Unshare most shared trees in the body and in that of any nested functions.
12366 It would seem we don't have to do this for nested functions because
12367 they are supposed to be output and then the outer function gimplified
12368 first, but the g++ front end doesn't always do it that way. */
12369 unshare_body (fndecl);
12370 unvisit_body (fndecl);
12372 cgn = cgraph_node::get (fndecl);
12373 if (cgn && cgn->origin)
12374 nonlocal_vlas = new hash_set<tree>;
12376 /* Make sure input_location isn't set to something weird. */
12377 input_location = DECL_SOURCE_LOCATION (fndecl);
12379 /* Resolve callee-copies. This has to be done before processing
12380 the body so that DECL_VALUE_EXPR gets processed correctly. */
12381 parm_stmts = do_parms ? gimplify_parameters () : NULL;
12383 /* Gimplify the function's body. */
12384 seq = NULL;
12385 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
12386 outer_stmt = gimple_seq_first_stmt (seq);
12387 if (!outer_stmt)
12389 outer_stmt = gimple_build_nop ();
12390 gimplify_seq_add_stmt (&seq, outer_stmt);
12393 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
12394 not the case, wrap everything in a GIMPLE_BIND to make it so. */
12395 if (gimple_code (outer_stmt) == GIMPLE_BIND
12396 && gimple_seq_first (seq) == gimple_seq_last (seq))
12397 outer_bind = as_a <gbind *> (outer_stmt);
12398 else
12399 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
12401 DECL_SAVED_TREE (fndecl) = NULL_TREE;
12403 /* If we had callee-copies statements, insert them at the beginning
12404 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
12405 if (!gimple_seq_empty_p (parm_stmts))
12407 tree parm;
12409 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
12410 gimple_bind_set_body (outer_bind, parm_stmts);
12412 for (parm = DECL_ARGUMENTS (current_function_decl);
12413 parm; parm = DECL_CHAIN (parm))
12414 if (DECL_HAS_VALUE_EXPR_P (parm))
12416 DECL_HAS_VALUE_EXPR_P (parm) = 0;
12417 DECL_IGNORED_P (parm) = 0;
12421 if (nonlocal_vlas)
12423 if (nonlocal_vla_vars)
12425 /* tree-nested.c may later on call declare_vars (..., true);
12426 which relies on BLOCK_VARS chain to be the tail of the
12427 gimple_bind_vars chain. Ensure we don't violate that
12428 assumption. */
12429 if (gimple_bind_block (outer_bind)
12430 == DECL_INITIAL (current_function_decl))
12431 declare_vars (nonlocal_vla_vars, outer_bind, true);
12432 else
12433 BLOCK_VARS (DECL_INITIAL (current_function_decl))
12434 = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl)),
12435 nonlocal_vla_vars);
12436 nonlocal_vla_vars = NULL_TREE;
12438 delete nonlocal_vlas;
12439 nonlocal_vlas = NULL;
12442 if ((flag_openacc || flag_openmp || flag_openmp_simd)
12443 && gimplify_omp_ctxp)
12445 delete_omp_context (gimplify_omp_ctxp);
12446 gimplify_omp_ctxp = NULL;
12449 pop_gimplify_context (outer_bind);
12450 gcc_assert (gimplify_ctxp == NULL);
12452 if (flag_checking && !seen_error ())
12453 verify_gimple_in_seq (gimple_bind_body (outer_bind));
12455 timevar_pop (TV_TREE_GIMPLIFY);
12456 input_location = saved_location;
12458 return outer_bind;
12461 typedef char *char_p; /* For DEF_VEC_P. */
12463 /* Return whether we should exclude FNDECL from instrumentation. */
12465 static bool
12466 flag_instrument_functions_exclude_p (tree fndecl)
12468 vec<char_p> *v;
12470 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
12471 if (v && v->length () > 0)
12473 const char *name;
12474 int i;
12475 char *s;
12477 name = lang_hooks.decl_printable_name (fndecl, 0);
12478 FOR_EACH_VEC_ELT (*v, i, s)
12479 if (strstr (name, s) != NULL)
12480 return true;
12483 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
12484 if (v && v->length () > 0)
12486 const char *name;
12487 int i;
12488 char *s;
12490 name = DECL_SOURCE_FILE (fndecl);
12491 FOR_EACH_VEC_ELT (*v, i, s)
12492 if (strstr (name, s) != NULL)
12493 return true;
12496 return false;
12499 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
12500 node for the function we want to gimplify.
12502 Return the sequence of GIMPLE statements corresponding to the body
12503 of FNDECL. */
12505 void
12506 gimplify_function_tree (tree fndecl)
12508 tree parm, ret;
12509 gimple_seq seq;
12510 gbind *bind;
12512 gcc_assert (!gimple_body (fndecl));
12514 if (DECL_STRUCT_FUNCTION (fndecl))
12515 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
12516 else
12517 push_struct_function (fndecl);
12519 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
12520 if necessary. */
12521 cfun->curr_properties |= PROP_gimple_lva;
12523 for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = DECL_CHAIN (parm))
12525 /* Preliminarily mark non-addressed complex variables as eligible
12526 for promotion to gimple registers. We'll transform their uses
12527 as we find them. */
12528 if ((TREE_CODE (TREE_TYPE (parm)) == COMPLEX_TYPE
12529 || TREE_CODE (TREE_TYPE (parm)) == VECTOR_TYPE)
12530 && !TREE_THIS_VOLATILE (parm)
12531 && !needs_to_live_in_memory (parm))
12532 DECL_GIMPLE_REG_P (parm) = 1;
12535 ret = DECL_RESULT (fndecl);
12536 if ((TREE_CODE (TREE_TYPE (ret)) == COMPLEX_TYPE
12537 || TREE_CODE (TREE_TYPE (ret)) == VECTOR_TYPE)
12538 && !needs_to_live_in_memory (ret))
12539 DECL_GIMPLE_REG_P (ret) = 1;
12541 if (asan_sanitize_use_after_scope () && !asan_no_sanitize_address_p ())
12542 asan_poisoned_variables = new hash_set<tree> ();
12543 bind = gimplify_body (fndecl, true);
12544 if (asan_poisoned_variables)
12546 delete asan_poisoned_variables;
12547 asan_poisoned_variables = NULL;
12550 /* The tree body of the function is no longer needed, replace it
12551 with the new GIMPLE body. */
12552 seq = NULL;
12553 gimple_seq_add_stmt (&seq, bind);
12554 gimple_set_body (fndecl, seq);
12556 /* If we're instrumenting function entry/exit, then prepend the call to
12557 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
12558 catch the exit hook. */
12559 /* ??? Add some way to ignore exceptions for this TFE. */
12560 if (flag_instrument_function_entry_exit
12561 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
12562 /* Do not instrument extern inline functions. */
12563 && !(DECL_DECLARED_INLINE_P (fndecl)
12564 && DECL_EXTERNAL (fndecl)
12565 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
12566 && !flag_instrument_functions_exclude_p (fndecl))
12568 tree x;
12569 gbind *new_bind;
12570 gimple *tf;
12571 gimple_seq cleanup = NULL, body = NULL;
12572 tree tmp_var;
12573 gcall *call;
12575 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
12576 call = gimple_build_call (x, 1, integer_zero_node);
12577 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
12578 gimple_call_set_lhs (call, tmp_var);
12579 gimplify_seq_add_stmt (&cleanup, call);
12580 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
12581 call = gimple_build_call (x, 2,
12582 build_fold_addr_expr (current_function_decl),
12583 tmp_var);
12584 gimplify_seq_add_stmt (&cleanup, call);
12585 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
12587 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
12588 call = gimple_build_call (x, 1, integer_zero_node);
12589 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
12590 gimple_call_set_lhs (call, tmp_var);
12591 gimplify_seq_add_stmt (&body, call);
12592 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
12593 call = gimple_build_call (x, 2,
12594 build_fold_addr_expr (current_function_decl),
12595 tmp_var);
12596 gimplify_seq_add_stmt (&body, call);
12597 gimplify_seq_add_stmt (&body, tf);
12598 new_bind = gimple_build_bind (NULL, body, NULL);
12600 /* Replace the current function body with the body
12601 wrapped in the try/finally TF. */
12602 seq = NULL;
12603 gimple_seq_add_stmt (&seq, new_bind);
12604 gimple_set_body (fndecl, seq);
12605 bind = new_bind;
12608 if ((flag_sanitize & SANITIZE_THREAD) != 0
12609 && !lookup_attribute ("no_sanitize_thread", DECL_ATTRIBUTES (fndecl)))
12611 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
12612 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
12613 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
12614 /* Replace the current function body with the body
12615 wrapped in the try/finally TF. */
12616 seq = NULL;
12617 gimple_seq_add_stmt (&seq, new_bind);
12618 gimple_set_body (fndecl, seq);
12621 DECL_SAVED_TREE (fndecl) = NULL_TREE;
12622 cfun->curr_properties |= PROP_gimple_any;
12624 pop_cfun ();
12626 dump_function (TDI_generic, fndecl);
12629 /* Return a dummy expression of type TYPE in order to keep going after an
12630 error. */
12632 static tree
12633 dummy_object (tree type)
12635 tree t = build_int_cst (build_pointer_type (type), 0);
12636 return build2 (MEM_REF, type, t, t);
12639 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
12640 builtin function, but a very special sort of operator. */
12642 enum gimplify_status
12643 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
12644 gimple_seq *post_p ATTRIBUTE_UNUSED)
12646 tree promoted_type, have_va_type;
12647 tree valist = TREE_OPERAND (*expr_p, 0);
12648 tree type = TREE_TYPE (*expr_p);
12649 tree t, tag, aptag;
12650 location_t loc = EXPR_LOCATION (*expr_p);
12652 /* Verify that valist is of the proper type. */
12653 have_va_type = TREE_TYPE (valist);
12654 if (have_va_type == error_mark_node)
12655 return GS_ERROR;
12656 have_va_type = targetm.canonical_va_list_type (have_va_type);
12657 if (have_va_type == NULL_TREE
12658 && POINTER_TYPE_P (TREE_TYPE (valist)))
12659 /* Handle 'Case 1: Not an array type' from c-common.c/build_va_arg. */
12660 have_va_type
12661 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
12662 gcc_assert (have_va_type != NULL_TREE);
12664 /* Generate a diagnostic for requesting data of a type that cannot
12665 be passed through `...' due to type promotion at the call site. */
12666 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
12667 != type)
12669 static bool gave_help;
12670 bool warned;
12671 /* Use the expansion point to handle cases such as passing bool (defined
12672 in a system header) through `...'. */
12673 source_location xloc
12674 = expansion_point_location_if_in_system_header (loc);
12676 /* Unfortunately, this is merely undefined, rather than a constraint
12677 violation, so we cannot make this an error. If this call is never
12678 executed, the program is still strictly conforming. */
12679 warned = warning_at (xloc, 0,
12680 "%qT is promoted to %qT when passed through %<...%>",
12681 type, promoted_type);
12682 if (!gave_help && warned)
12684 gave_help = true;
12685 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
12686 promoted_type, type);
12689 /* We can, however, treat "undefined" any way we please.
12690 Call abort to encourage the user to fix the program. */
12691 if (warned)
12692 inform (xloc, "if this code is reached, the program will abort");
12693 /* Before the abort, allow the evaluation of the va_list
12694 expression to exit or longjmp. */
12695 gimplify_and_add (valist, pre_p);
12696 t = build_call_expr_loc (loc,
12697 builtin_decl_implicit (BUILT_IN_TRAP), 0);
12698 gimplify_and_add (t, pre_p);
12700 /* This is dead code, but go ahead and finish so that the
12701 mode of the result comes out right. */
12702 *expr_p = dummy_object (type);
12703 return GS_ALL_DONE;
12706 tag = build_int_cst (build_pointer_type (type), 0);
12707 aptag = build_int_cst (TREE_TYPE (valist), 0);
12709 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
12710 valist, tag, aptag);
12712 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
12713 needs to be expanded. */
12714 cfun->curr_properties &= ~PROP_gimple_lva;
12716 return GS_OK;
12719 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
12721 DST/SRC are the destination and source respectively. You can pass
12722 ungimplified trees in DST or SRC, in which case they will be
12723 converted to a gimple operand if necessary.
12725 This function returns the newly created GIMPLE_ASSIGN tuple. */
12727 gimple *
12728 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
12730 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
12731 gimplify_and_add (t, seq_p);
12732 ggc_free (t);
12733 return gimple_seq_last_stmt (*seq_p);
12736 inline hashval_t
12737 gimplify_hasher::hash (const elt_t *p)
12739 tree t = p->val;
12740 return iterative_hash_expr (t, 0);
12743 inline bool
12744 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
12746 tree t1 = p1->val;
12747 tree t2 = p2->val;
12748 enum tree_code code = TREE_CODE (t1);
12750 if (TREE_CODE (t2) != code
12751 || TREE_TYPE (t1) != TREE_TYPE (t2))
12752 return false;
12754 if (!operand_equal_p (t1, t2, 0))
12755 return false;
12757 /* Only allow them to compare equal if they also hash equal; otherwise
12758 results are nondeterminate, and we fail bootstrap comparison. */
12759 gcc_checking_assert (hash (p1) == hash (p2));
12761 return true;