PR middle-end/32003 - Undocumented -fdump-tree options
[official-gcc.git] / gcc / gimplify.c
blobfeb5fa0f9e93aa6c5cb47ec7e00b17ddc5949570
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_TILE:
8344 for (tree list = OMP_CLAUSE_TILE_LIST (c); !remove && list;
8345 list = TREE_CHAIN (list))
8347 if (gimplify_expr (&TREE_VALUE (list), pre_p, NULL,
8348 is_gimple_val, fb_rvalue) == GS_ERROR)
8349 remove = true;
8351 break;
8353 case OMP_CLAUSE_NOWAIT:
8354 case OMP_CLAUSE_ORDERED:
8355 case OMP_CLAUSE_UNTIED:
8356 case OMP_CLAUSE_COLLAPSE:
8357 case OMP_CLAUSE_AUTO:
8358 case OMP_CLAUSE_SEQ:
8359 case OMP_CLAUSE_INDEPENDENT:
8360 case OMP_CLAUSE_MERGEABLE:
8361 case OMP_CLAUSE_PROC_BIND:
8362 case OMP_CLAUSE_SAFELEN:
8363 case OMP_CLAUSE_SIMDLEN:
8364 case OMP_CLAUSE_NOGROUP:
8365 case OMP_CLAUSE_THREADS:
8366 case OMP_CLAUSE_SIMD:
8367 break;
8369 case OMP_CLAUSE_DEFAULTMAP:
8370 ctx->target_map_scalars_firstprivate = false;
8371 break;
8373 case OMP_CLAUSE_ALIGNED:
8374 decl = OMP_CLAUSE_DECL (c);
8375 if (error_operand_p (decl))
8377 remove = true;
8378 break;
8380 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
8381 is_gimple_val, fb_rvalue) == GS_ERROR)
8383 remove = true;
8384 break;
8386 if (!is_global_var (decl)
8387 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
8388 omp_add_variable (ctx, decl, GOVD_ALIGNED);
8389 break;
8391 case OMP_CLAUSE_DEFAULT:
8392 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
8393 break;
8395 default:
8396 gcc_unreachable ();
8399 if (code == OACC_DATA
8400 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
8401 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
8402 remove = true;
8403 if (remove)
8404 *list_p = OMP_CLAUSE_CHAIN (c);
8405 else
8406 list_p = &OMP_CLAUSE_CHAIN (c);
8409 gimplify_omp_ctxp = ctx;
8410 if (struct_map_to_clause)
8411 delete struct_map_to_clause;
8414 /* Return true if DECL is a candidate for shared to firstprivate
8415 optimization. We only consider non-addressable scalars, not
8416 too big, and not references. */
8418 static bool
8419 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
8421 if (TREE_ADDRESSABLE (decl))
8422 return false;
8423 tree type = TREE_TYPE (decl);
8424 if (!is_gimple_reg_type (type)
8425 || TREE_CODE (type) == REFERENCE_TYPE
8426 || TREE_ADDRESSABLE (type))
8427 return false;
8428 /* Don't optimize too large decls, as each thread/task will have
8429 its own. */
8430 HOST_WIDE_INT len = int_size_in_bytes (type);
8431 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
8432 return false;
8433 if (lang_hooks.decls.omp_privatize_by_reference (decl))
8434 return false;
8435 return true;
8438 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
8439 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
8440 GOVD_WRITTEN in outer contexts. */
8442 static void
8443 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
8445 for (; ctx; ctx = ctx->outer_context)
8447 splay_tree_node n = splay_tree_lookup (ctx->variables,
8448 (splay_tree_key) decl);
8449 if (n == NULL)
8450 continue;
8451 else if (n->value & GOVD_SHARED)
8453 n->value |= GOVD_WRITTEN;
8454 return;
8456 else if (n->value & GOVD_DATA_SHARE_CLASS)
8457 return;
8461 /* Helper callback for walk_gimple_seq to discover possible stores
8462 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
8463 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
8464 for those. */
8466 static tree
8467 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
8469 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
8471 *walk_subtrees = 0;
8472 if (!wi->is_lhs)
8473 return NULL_TREE;
8475 tree op = *tp;
8478 if (handled_component_p (op))
8479 op = TREE_OPERAND (op, 0);
8480 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
8481 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
8482 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
8483 else
8484 break;
8486 while (1);
8487 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
8488 return NULL_TREE;
8490 omp_mark_stores (gimplify_omp_ctxp, op);
8491 return NULL_TREE;
8494 /* Helper callback for walk_gimple_seq to discover possible stores
8495 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
8496 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
8497 for those. */
8499 static tree
8500 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
8501 bool *handled_ops_p,
8502 struct walk_stmt_info *wi)
8504 gimple *stmt = gsi_stmt (*gsi_p);
8505 switch (gimple_code (stmt))
8507 /* Don't recurse on OpenMP constructs for which
8508 gimplify_adjust_omp_clauses already handled the bodies,
8509 except handle gimple_omp_for_pre_body. */
8510 case GIMPLE_OMP_FOR:
8511 *handled_ops_p = true;
8512 if (gimple_omp_for_pre_body (stmt))
8513 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
8514 omp_find_stores_stmt, omp_find_stores_op, wi);
8515 break;
8516 case GIMPLE_OMP_PARALLEL:
8517 case GIMPLE_OMP_TASK:
8518 case GIMPLE_OMP_SECTIONS:
8519 case GIMPLE_OMP_SINGLE:
8520 case GIMPLE_OMP_TARGET:
8521 case GIMPLE_OMP_TEAMS:
8522 case GIMPLE_OMP_CRITICAL:
8523 *handled_ops_p = true;
8524 break;
8525 default:
8526 break;
8528 return NULL_TREE;
8531 struct gimplify_adjust_omp_clauses_data
8533 tree *list_p;
8534 gimple_seq *pre_p;
8537 /* For all variables that were not actually used within the context,
8538 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
8540 static int
8541 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
8543 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
8544 gimple_seq *pre_p
8545 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
8546 tree decl = (tree) n->key;
8547 unsigned flags = n->value;
8548 enum omp_clause_code code;
8549 tree clause;
8550 bool private_debug;
8552 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
8553 return 0;
8554 if ((flags & GOVD_SEEN) == 0)
8555 return 0;
8556 if (flags & GOVD_DEBUG_PRIVATE)
8558 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_PRIVATE);
8559 private_debug = true;
8561 else if (flags & GOVD_MAP)
8562 private_debug = false;
8563 else
8564 private_debug
8565 = lang_hooks.decls.omp_private_debug_clause (decl,
8566 !!(flags & GOVD_SHARED));
8567 if (private_debug)
8568 code = OMP_CLAUSE_PRIVATE;
8569 else if (flags & GOVD_MAP)
8571 code = OMP_CLAUSE_MAP;
8572 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
8573 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
8575 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
8576 return 0;
8579 else if (flags & GOVD_SHARED)
8581 if (is_global_var (decl))
8583 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
8584 while (ctx != NULL)
8586 splay_tree_node on
8587 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8588 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
8589 | GOVD_PRIVATE | GOVD_REDUCTION
8590 | GOVD_LINEAR | GOVD_MAP)) != 0)
8591 break;
8592 ctx = ctx->outer_context;
8594 if (ctx == NULL)
8595 return 0;
8597 code = OMP_CLAUSE_SHARED;
8599 else if (flags & GOVD_PRIVATE)
8600 code = OMP_CLAUSE_PRIVATE;
8601 else if (flags & GOVD_FIRSTPRIVATE)
8603 code = OMP_CLAUSE_FIRSTPRIVATE;
8604 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
8605 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
8606 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
8608 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
8609 "%<target%> construct", decl);
8610 return 0;
8613 else if (flags & GOVD_LASTPRIVATE)
8614 code = OMP_CLAUSE_LASTPRIVATE;
8615 else if (flags & GOVD_ALIGNED)
8616 return 0;
8617 else
8618 gcc_unreachable ();
8620 if (((flags & GOVD_LASTPRIVATE)
8621 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
8622 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8623 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8625 tree chain = *list_p;
8626 clause = build_omp_clause (input_location, code);
8627 OMP_CLAUSE_DECL (clause) = decl;
8628 OMP_CLAUSE_CHAIN (clause) = chain;
8629 if (private_debug)
8630 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
8631 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
8632 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
8633 else if (code == OMP_CLAUSE_SHARED
8634 && (flags & GOVD_WRITTEN) == 0
8635 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8636 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
8637 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
8638 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
8639 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
8641 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
8642 OMP_CLAUSE_DECL (nc) = decl;
8643 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
8644 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
8645 OMP_CLAUSE_DECL (clause)
8646 = build_simple_mem_ref_loc (input_location, decl);
8647 OMP_CLAUSE_DECL (clause)
8648 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
8649 build_int_cst (build_pointer_type (char_type_node), 0));
8650 OMP_CLAUSE_SIZE (clause) = size_zero_node;
8651 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8652 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
8653 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
8654 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
8655 OMP_CLAUSE_CHAIN (nc) = chain;
8656 OMP_CLAUSE_CHAIN (clause) = nc;
8657 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8658 gimplify_omp_ctxp = ctx->outer_context;
8659 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
8660 pre_p, NULL, is_gimple_val, fb_rvalue);
8661 gimplify_omp_ctxp = ctx;
8663 else if (code == OMP_CLAUSE_MAP)
8665 int kind = (flags & GOVD_MAP_TO_ONLY
8666 ? GOMP_MAP_TO
8667 : GOMP_MAP_TOFROM);
8668 if (flags & GOVD_MAP_FORCE)
8669 kind |= GOMP_MAP_FLAG_FORCE;
8670 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
8671 if (DECL_SIZE (decl)
8672 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
8674 tree decl2 = DECL_VALUE_EXPR (decl);
8675 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
8676 decl2 = TREE_OPERAND (decl2, 0);
8677 gcc_assert (DECL_P (decl2));
8678 tree mem = build_simple_mem_ref (decl2);
8679 OMP_CLAUSE_DECL (clause) = mem;
8680 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
8681 if (gimplify_omp_ctxp->outer_context)
8683 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
8684 omp_notice_variable (ctx, decl2, true);
8685 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
8687 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
8688 OMP_CLAUSE_MAP);
8689 OMP_CLAUSE_DECL (nc) = decl;
8690 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8691 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
8692 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
8693 else
8694 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
8695 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
8696 OMP_CLAUSE_CHAIN (clause) = nc;
8698 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
8699 && lang_hooks.decls.omp_privatize_by_reference (decl))
8701 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
8702 OMP_CLAUSE_SIZE (clause)
8703 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
8704 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8705 gimplify_omp_ctxp = ctx->outer_context;
8706 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
8707 pre_p, NULL, is_gimple_val, fb_rvalue);
8708 gimplify_omp_ctxp = ctx;
8709 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
8710 OMP_CLAUSE_MAP);
8711 OMP_CLAUSE_DECL (nc) = decl;
8712 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8713 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
8714 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
8715 OMP_CLAUSE_CHAIN (clause) = nc;
8717 else
8718 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
8720 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
8722 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
8723 OMP_CLAUSE_DECL (nc) = decl;
8724 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
8725 OMP_CLAUSE_CHAIN (nc) = chain;
8726 OMP_CLAUSE_CHAIN (clause) = nc;
8727 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8728 gimplify_omp_ctxp = ctx->outer_context;
8729 lang_hooks.decls.omp_finish_clause (nc, pre_p);
8730 gimplify_omp_ctxp = ctx;
8732 *list_p = clause;
8733 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8734 gimplify_omp_ctxp = ctx->outer_context;
8735 lang_hooks.decls.omp_finish_clause (clause, pre_p);
8736 if (gimplify_omp_ctxp)
8737 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
8738 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
8739 && DECL_P (OMP_CLAUSE_SIZE (clause)))
8740 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
8741 true);
8742 gimplify_omp_ctxp = ctx;
8743 return 0;
8746 static void
8747 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
8748 enum tree_code code)
8750 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8751 tree c, decl;
8753 if (body)
8755 struct gimplify_omp_ctx *octx;
8756 for (octx = ctx; octx; octx = octx->outer_context)
8757 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
8758 break;
8759 if (octx)
8761 struct walk_stmt_info wi;
8762 memset (&wi, 0, sizeof (wi));
8763 walk_gimple_seq (body, omp_find_stores_stmt,
8764 omp_find_stores_op, &wi);
8767 while ((c = *list_p) != NULL)
8769 splay_tree_node n;
8770 bool remove = false;
8772 switch (OMP_CLAUSE_CODE (c))
8774 case OMP_CLAUSE_FIRSTPRIVATE:
8775 if ((ctx->region_type & ORT_TARGET)
8776 && (ctx->region_type & ORT_ACC) == 0
8777 && TYPE_ATOMIC (strip_array_types
8778 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
8780 error_at (OMP_CLAUSE_LOCATION (c),
8781 "%<_Atomic%> %qD in %<firstprivate%> clause on "
8782 "%<target%> construct", OMP_CLAUSE_DECL (c));
8783 remove = true;
8784 break;
8786 /* FALLTHRU */
8787 case OMP_CLAUSE_PRIVATE:
8788 case OMP_CLAUSE_SHARED:
8789 case OMP_CLAUSE_LINEAR:
8790 decl = OMP_CLAUSE_DECL (c);
8791 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8792 remove = !(n->value & GOVD_SEEN);
8793 if (! remove)
8795 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
8796 if ((n->value & GOVD_DEBUG_PRIVATE)
8797 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
8799 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
8800 || ((n->value & GOVD_DATA_SHARE_CLASS)
8801 == GOVD_PRIVATE));
8802 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
8803 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
8805 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
8806 && (n->value & GOVD_WRITTEN) == 0
8807 && DECL_P (decl)
8808 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8809 OMP_CLAUSE_SHARED_READONLY (c) = 1;
8810 else if (DECL_P (decl)
8811 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
8812 && (n->value & GOVD_WRITTEN) != 1)
8813 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
8814 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
8815 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8816 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8818 break;
8820 case OMP_CLAUSE_LASTPRIVATE:
8821 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
8822 accurately reflect the presence of a FIRSTPRIVATE clause. */
8823 decl = OMP_CLAUSE_DECL (c);
8824 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8825 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
8826 = (n->value & GOVD_FIRSTPRIVATE) != 0;
8827 if (code == OMP_DISTRIBUTE
8828 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
8830 remove = true;
8831 error_at (OMP_CLAUSE_LOCATION (c),
8832 "same variable used in %<firstprivate%> and "
8833 "%<lastprivate%> clauses on %<distribute%> "
8834 "construct");
8836 if (!remove
8837 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
8838 && DECL_P (decl)
8839 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8840 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8841 break;
8843 case OMP_CLAUSE_ALIGNED:
8844 decl = OMP_CLAUSE_DECL (c);
8845 if (!is_global_var (decl))
8847 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8848 remove = n == NULL || !(n->value & GOVD_SEEN);
8849 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
8851 struct gimplify_omp_ctx *octx;
8852 if (n != NULL
8853 && (n->value & (GOVD_DATA_SHARE_CLASS
8854 & ~GOVD_FIRSTPRIVATE)))
8855 remove = true;
8856 else
8857 for (octx = ctx->outer_context; octx;
8858 octx = octx->outer_context)
8860 n = splay_tree_lookup (octx->variables,
8861 (splay_tree_key) decl);
8862 if (n == NULL)
8863 continue;
8864 if (n->value & GOVD_LOCAL)
8865 break;
8866 /* We have to avoid assigning a shared variable
8867 to itself when trying to add
8868 __builtin_assume_aligned. */
8869 if (n->value & GOVD_SHARED)
8871 remove = true;
8872 break;
8877 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
8879 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8880 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
8881 remove = true;
8883 break;
8885 case OMP_CLAUSE_MAP:
8886 if (code == OMP_TARGET_EXIT_DATA
8887 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
8889 remove = true;
8890 break;
8892 decl = OMP_CLAUSE_DECL (c);
8893 /* Data clauses associated with acc parallel reductions must be
8894 compatible with present_or_copy. Warn and adjust the clause
8895 if that is not the case. */
8896 if (ctx->region_type == ORT_ACC_PARALLEL)
8898 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
8899 n = NULL;
8901 if (DECL_P (t))
8902 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
8904 if (n && (n->value & GOVD_REDUCTION))
8906 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
8908 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
8909 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
8910 && kind != GOMP_MAP_FORCE_PRESENT
8911 && kind != GOMP_MAP_POINTER)
8913 warning_at (OMP_CLAUSE_LOCATION (c), 0,
8914 "incompatible data clause with reduction "
8915 "on %qE; promoting to present_or_copy",
8916 DECL_NAME (t));
8917 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
8921 if (!DECL_P (decl))
8923 if ((ctx->region_type & ORT_TARGET) != 0
8924 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
8926 if (TREE_CODE (decl) == INDIRECT_REF
8927 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
8928 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
8929 == REFERENCE_TYPE))
8930 decl = TREE_OPERAND (decl, 0);
8931 if (TREE_CODE (decl) == COMPONENT_REF)
8933 while (TREE_CODE (decl) == COMPONENT_REF)
8934 decl = TREE_OPERAND (decl, 0);
8935 if (DECL_P (decl))
8937 n = splay_tree_lookup (ctx->variables,
8938 (splay_tree_key) decl);
8939 if (!(n->value & GOVD_SEEN))
8940 remove = true;
8944 break;
8946 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8947 if ((ctx->region_type & ORT_TARGET) != 0
8948 && !(n->value & GOVD_SEEN)
8949 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
8950 && !lookup_attribute ("omp declare target link",
8951 DECL_ATTRIBUTES (decl)))
8953 remove = true;
8954 /* For struct element mapping, if struct is never referenced
8955 in target block and none of the mapping has always modifier,
8956 remove all the struct element mappings, which immediately
8957 follow the GOMP_MAP_STRUCT map clause. */
8958 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
8960 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
8961 while (cnt--)
8962 OMP_CLAUSE_CHAIN (c)
8963 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
8966 else if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
8967 && code == OMP_TARGET_EXIT_DATA)
8968 remove = true;
8969 else if (DECL_SIZE (decl)
8970 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
8971 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
8972 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
8973 && (OMP_CLAUSE_MAP_KIND (c)
8974 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
8976 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
8977 for these, TREE_CODE (DECL_SIZE (decl)) will always be
8978 INTEGER_CST. */
8979 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
8981 tree decl2 = DECL_VALUE_EXPR (decl);
8982 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
8983 decl2 = TREE_OPERAND (decl2, 0);
8984 gcc_assert (DECL_P (decl2));
8985 tree mem = build_simple_mem_ref (decl2);
8986 OMP_CLAUSE_DECL (c) = mem;
8987 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
8988 if (ctx->outer_context)
8990 omp_notice_variable (ctx->outer_context, decl2, true);
8991 omp_notice_variable (ctx->outer_context,
8992 OMP_CLAUSE_SIZE (c), true);
8994 if (((ctx->region_type & ORT_TARGET) != 0
8995 || !ctx->target_firstprivatize_array_bases)
8996 && ((n->value & GOVD_SEEN) == 0
8997 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
8999 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9000 OMP_CLAUSE_MAP);
9001 OMP_CLAUSE_DECL (nc) = decl;
9002 OMP_CLAUSE_SIZE (nc) = size_zero_node;
9003 if (ctx->target_firstprivatize_array_bases)
9004 OMP_CLAUSE_SET_MAP_KIND (nc,
9005 GOMP_MAP_FIRSTPRIVATE_POINTER);
9006 else
9007 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
9008 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
9009 OMP_CLAUSE_CHAIN (c) = nc;
9010 c = nc;
9013 else
9015 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9016 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
9017 gcc_assert ((n->value & GOVD_SEEN) == 0
9018 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
9019 == 0));
9021 break;
9023 case OMP_CLAUSE_TO:
9024 case OMP_CLAUSE_FROM:
9025 case OMP_CLAUSE__CACHE_:
9026 decl = OMP_CLAUSE_DECL (c);
9027 if (!DECL_P (decl))
9028 break;
9029 if (DECL_SIZE (decl)
9030 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
9032 tree decl2 = DECL_VALUE_EXPR (decl);
9033 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
9034 decl2 = TREE_OPERAND (decl2, 0);
9035 gcc_assert (DECL_P (decl2));
9036 tree mem = build_simple_mem_ref (decl2);
9037 OMP_CLAUSE_DECL (c) = mem;
9038 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
9039 if (ctx->outer_context)
9041 omp_notice_variable (ctx->outer_context, decl2, true);
9042 omp_notice_variable (ctx->outer_context,
9043 OMP_CLAUSE_SIZE (c), true);
9046 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9047 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
9048 break;
9050 case OMP_CLAUSE_REDUCTION:
9051 decl = OMP_CLAUSE_DECL (c);
9052 /* OpenACC reductions need a present_or_copy data clause.
9053 Add one if necessary. Error is the reduction is private. */
9054 if (ctx->region_type == ORT_ACC_PARALLEL)
9056 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
9057 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
9058 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
9059 "reduction on %qE", DECL_NAME (decl));
9060 else if ((n->value & GOVD_MAP) == 0)
9062 tree next = OMP_CLAUSE_CHAIN (c);
9063 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
9064 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
9065 OMP_CLAUSE_DECL (nc) = decl;
9066 OMP_CLAUSE_CHAIN (c) = nc;
9067 lang_hooks.decls.omp_finish_clause (nc, pre_p);
9068 while (1)
9070 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
9071 if (OMP_CLAUSE_CHAIN (nc) == NULL)
9072 break;
9073 nc = OMP_CLAUSE_CHAIN (nc);
9075 OMP_CLAUSE_CHAIN (nc) = next;
9076 n->value |= GOVD_MAP;
9079 if (DECL_P (decl)
9080 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
9081 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
9082 break;
9083 case OMP_CLAUSE_COPYIN:
9084 case OMP_CLAUSE_COPYPRIVATE:
9085 case OMP_CLAUSE_IF:
9086 case OMP_CLAUSE_NUM_THREADS:
9087 case OMP_CLAUSE_NUM_TEAMS:
9088 case OMP_CLAUSE_THREAD_LIMIT:
9089 case OMP_CLAUSE_DIST_SCHEDULE:
9090 case OMP_CLAUSE_DEVICE:
9091 case OMP_CLAUSE_SCHEDULE:
9092 case OMP_CLAUSE_NOWAIT:
9093 case OMP_CLAUSE_ORDERED:
9094 case OMP_CLAUSE_DEFAULT:
9095 case OMP_CLAUSE_UNTIED:
9096 case OMP_CLAUSE_COLLAPSE:
9097 case OMP_CLAUSE_FINAL:
9098 case OMP_CLAUSE_MERGEABLE:
9099 case OMP_CLAUSE_PROC_BIND:
9100 case OMP_CLAUSE_SAFELEN:
9101 case OMP_CLAUSE_SIMDLEN:
9102 case OMP_CLAUSE_DEPEND:
9103 case OMP_CLAUSE_PRIORITY:
9104 case OMP_CLAUSE_GRAINSIZE:
9105 case OMP_CLAUSE_NUM_TASKS:
9106 case OMP_CLAUSE_NOGROUP:
9107 case OMP_CLAUSE_THREADS:
9108 case OMP_CLAUSE_SIMD:
9109 case OMP_CLAUSE_HINT:
9110 case OMP_CLAUSE_DEFAULTMAP:
9111 case OMP_CLAUSE_USE_DEVICE_PTR:
9112 case OMP_CLAUSE_IS_DEVICE_PTR:
9113 case OMP_CLAUSE__CILK_FOR_COUNT_:
9114 case OMP_CLAUSE_ASYNC:
9115 case OMP_CLAUSE_WAIT:
9116 case OMP_CLAUSE_INDEPENDENT:
9117 case OMP_CLAUSE_NUM_GANGS:
9118 case OMP_CLAUSE_NUM_WORKERS:
9119 case OMP_CLAUSE_VECTOR_LENGTH:
9120 case OMP_CLAUSE_GANG:
9121 case OMP_CLAUSE_WORKER:
9122 case OMP_CLAUSE_VECTOR:
9123 case OMP_CLAUSE_AUTO:
9124 case OMP_CLAUSE_SEQ:
9125 break;
9127 case OMP_CLAUSE_TILE:
9128 /* We're not yet making use of the information provided by OpenACC
9129 tile clauses. Discard these here, to simplify later middle end
9130 processing. */
9131 remove = true;
9132 break;
9134 default:
9135 gcc_unreachable ();
9138 if (remove)
9139 *list_p = OMP_CLAUSE_CHAIN (c);
9140 else
9141 list_p = &OMP_CLAUSE_CHAIN (c);
9144 /* Add in any implicit data sharing. */
9145 struct gimplify_adjust_omp_clauses_data data;
9146 data.list_p = list_p;
9147 data.pre_p = pre_p;
9148 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
9150 gimplify_omp_ctxp = ctx->outer_context;
9151 delete_omp_context (ctx);
9154 /* Gimplify OACC_CACHE. */
9156 static void
9157 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
9159 tree expr = *expr_p;
9161 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
9162 OACC_CACHE);
9163 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
9164 OACC_CACHE);
9166 /* TODO: Do something sensible with this information. */
9168 *expr_p = NULL_TREE;
9171 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
9172 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
9173 kind. The entry kind will replace the one in CLAUSE, while the exit
9174 kind will be used in a new omp_clause and returned to the caller. */
9176 static tree
9177 gimplify_oacc_declare_1 (tree clause)
9179 HOST_WIDE_INT kind, new_op;
9180 bool ret = false;
9181 tree c = NULL;
9183 kind = OMP_CLAUSE_MAP_KIND (clause);
9185 switch (kind)
9187 case GOMP_MAP_ALLOC:
9188 case GOMP_MAP_FORCE_ALLOC:
9189 case GOMP_MAP_FORCE_TO:
9190 new_op = GOMP_MAP_DELETE;
9191 ret = true;
9192 break;
9194 case GOMP_MAP_FORCE_FROM:
9195 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
9196 new_op = GOMP_MAP_FORCE_FROM;
9197 ret = true;
9198 break;
9200 case GOMP_MAP_FORCE_TOFROM:
9201 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_TO);
9202 new_op = GOMP_MAP_FORCE_FROM;
9203 ret = true;
9204 break;
9206 case GOMP_MAP_FROM:
9207 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
9208 new_op = GOMP_MAP_FROM;
9209 ret = true;
9210 break;
9212 case GOMP_MAP_TOFROM:
9213 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
9214 new_op = GOMP_MAP_FROM;
9215 ret = true;
9216 break;
9218 case GOMP_MAP_DEVICE_RESIDENT:
9219 case GOMP_MAP_FORCE_DEVICEPTR:
9220 case GOMP_MAP_FORCE_PRESENT:
9221 case GOMP_MAP_LINK:
9222 case GOMP_MAP_POINTER:
9223 case GOMP_MAP_TO:
9224 break;
9226 default:
9227 gcc_unreachable ();
9228 break;
9231 if (ret)
9233 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
9234 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
9235 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
9238 return c;
9241 /* Gimplify OACC_DECLARE. */
9243 static void
9244 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
9246 tree expr = *expr_p;
9247 gomp_target *stmt;
9248 tree clauses, t;
9250 clauses = OACC_DECLARE_CLAUSES (expr);
9252 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
9254 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
9256 tree decl = OMP_CLAUSE_DECL (t);
9258 if (TREE_CODE (decl) == MEM_REF)
9259 continue;
9261 if (VAR_P (decl)
9262 && !is_global_var (decl)
9263 && DECL_CONTEXT (decl) == current_function_decl)
9265 tree c = gimplify_oacc_declare_1 (t);
9266 if (c)
9268 if (oacc_declare_returns == NULL)
9269 oacc_declare_returns = new hash_map<tree, tree>;
9271 oacc_declare_returns->put (decl, c);
9275 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
9278 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
9279 clauses);
9281 gimplify_seq_add_stmt (pre_p, stmt);
9283 *expr_p = NULL_TREE;
9286 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
9287 gimplification of the body, as well as scanning the body for used
9288 variables. We need to do this scan now, because variable-sized
9289 decls will be decomposed during gimplification. */
9291 static void
9292 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
9294 tree expr = *expr_p;
9295 gimple *g;
9296 gimple_seq body = NULL;
9298 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
9299 OMP_PARALLEL_COMBINED (expr)
9300 ? ORT_COMBINED_PARALLEL
9301 : ORT_PARALLEL, OMP_PARALLEL);
9303 push_gimplify_context ();
9305 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
9306 if (gimple_code (g) == GIMPLE_BIND)
9307 pop_gimplify_context (g);
9308 else
9309 pop_gimplify_context (NULL);
9311 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
9312 OMP_PARALLEL);
9314 g = gimple_build_omp_parallel (body,
9315 OMP_PARALLEL_CLAUSES (expr),
9316 NULL_TREE, NULL_TREE);
9317 if (OMP_PARALLEL_COMBINED (expr))
9318 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
9319 gimplify_seq_add_stmt (pre_p, g);
9320 *expr_p = NULL_TREE;
9323 /* Gimplify the contents of an OMP_TASK statement. This involves
9324 gimplification of the body, as well as scanning the body for used
9325 variables. We need to do this scan now, because variable-sized
9326 decls will be decomposed during gimplification. */
9328 static void
9329 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
9331 tree expr = *expr_p;
9332 gimple *g;
9333 gimple_seq body = NULL;
9335 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
9336 omp_find_clause (OMP_TASK_CLAUSES (expr),
9337 OMP_CLAUSE_UNTIED)
9338 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
9340 push_gimplify_context ();
9342 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
9343 if (gimple_code (g) == GIMPLE_BIND)
9344 pop_gimplify_context (g);
9345 else
9346 pop_gimplify_context (NULL);
9348 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
9349 OMP_TASK);
9351 g = gimple_build_omp_task (body,
9352 OMP_TASK_CLAUSES (expr),
9353 NULL_TREE, NULL_TREE,
9354 NULL_TREE, NULL_TREE, NULL_TREE);
9355 gimplify_seq_add_stmt (pre_p, g);
9356 *expr_p = NULL_TREE;
9359 /* Helper function of gimplify_omp_for, find OMP_FOR resp. OMP_SIMD
9360 with non-NULL OMP_FOR_INIT. */
9362 static tree
9363 find_combined_omp_for (tree *tp, int *walk_subtrees, void *)
9365 *walk_subtrees = 0;
9366 switch (TREE_CODE (*tp))
9368 case OMP_FOR:
9369 *walk_subtrees = 1;
9370 /* FALLTHRU */
9371 case OMP_SIMD:
9372 if (OMP_FOR_INIT (*tp) != NULL_TREE)
9373 return *tp;
9374 break;
9375 case BIND_EXPR:
9376 case STATEMENT_LIST:
9377 case OMP_PARALLEL:
9378 *walk_subtrees = 1;
9379 break;
9380 default:
9381 break;
9383 return NULL_TREE;
9386 /* Gimplify the gross structure of an OMP_FOR statement. */
9388 static enum gimplify_status
9389 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
9391 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
9392 enum gimplify_status ret = GS_ALL_DONE;
9393 enum gimplify_status tret;
9394 gomp_for *gfor;
9395 gimple_seq for_body, for_pre_body;
9396 int i;
9397 bitmap has_decl_expr = NULL;
9398 enum omp_region_type ort = ORT_WORKSHARE;
9400 orig_for_stmt = for_stmt = *expr_p;
9402 switch (TREE_CODE (for_stmt))
9404 case OMP_FOR:
9405 case CILK_FOR:
9406 case OMP_DISTRIBUTE:
9407 break;
9408 case OACC_LOOP:
9409 ort = ORT_ACC;
9410 break;
9411 case OMP_TASKLOOP:
9412 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
9413 ort = ORT_UNTIED_TASK;
9414 else
9415 ort = ORT_TASK;
9416 break;
9417 case OMP_SIMD:
9418 case CILK_SIMD:
9419 ort = ORT_SIMD;
9420 break;
9421 default:
9422 gcc_unreachable ();
9425 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
9426 clause for the IV. */
9427 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9429 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
9430 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
9431 decl = TREE_OPERAND (t, 0);
9432 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
9433 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
9434 && OMP_CLAUSE_DECL (c) == decl)
9436 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
9437 break;
9441 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
9443 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
9444 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
9445 find_combined_omp_for, NULL, NULL);
9446 if (inner_for_stmt == NULL_TREE)
9448 gcc_assert (seen_error ());
9449 *expr_p = NULL_TREE;
9450 return GS_ERROR;
9454 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
9455 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
9456 TREE_CODE (for_stmt));
9458 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
9459 gimplify_omp_ctxp->distribute = true;
9461 /* Handle OMP_FOR_INIT. */
9462 for_pre_body = NULL;
9463 if (ort == ORT_SIMD && OMP_FOR_PRE_BODY (for_stmt))
9465 has_decl_expr = BITMAP_ALLOC (NULL);
9466 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
9467 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
9468 == VAR_DECL)
9470 t = OMP_FOR_PRE_BODY (for_stmt);
9471 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
9473 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
9475 tree_stmt_iterator si;
9476 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
9477 tsi_next (&si))
9479 t = tsi_stmt (si);
9480 if (TREE_CODE (t) == DECL_EXPR
9481 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
9482 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
9486 if (OMP_FOR_PRE_BODY (for_stmt))
9488 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
9489 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
9490 else
9492 struct gimplify_omp_ctx ctx;
9493 memset (&ctx, 0, sizeof (ctx));
9494 ctx.region_type = ORT_NONE;
9495 gimplify_omp_ctxp = &ctx;
9496 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
9497 gimplify_omp_ctxp = NULL;
9500 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
9502 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
9503 for_stmt = inner_for_stmt;
9505 /* For taskloop, need to gimplify the start, end and step before the
9506 taskloop, outside of the taskloop omp context. */
9507 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
9509 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
9511 t = TREE_VEC_ELT (OMP_FOR_INIT (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 pre_p, NULL, false);
9517 tree c = build_omp_clause (input_location,
9518 OMP_CLAUSE_FIRSTPRIVATE);
9519 OMP_CLAUSE_DECL (c) = TREE_OPERAND (t, 1);
9520 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9521 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9524 /* Handle OMP_FOR_COND. */
9525 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
9526 if (!is_gimple_constant (TREE_OPERAND (t, 1)))
9528 TREE_OPERAND (t, 1)
9529 = get_initialized_tmp_var (TREE_OPERAND (t, 1),
9530 gimple_seq_empty_p (for_pre_body)
9531 ? pre_p : &for_pre_body, NULL,
9532 false);
9533 tree c = build_omp_clause (input_location,
9534 OMP_CLAUSE_FIRSTPRIVATE);
9535 OMP_CLAUSE_DECL (c) = TREE_OPERAND (t, 1);
9536 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9537 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9540 /* Handle OMP_FOR_INCR. */
9541 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
9542 if (TREE_CODE (t) == MODIFY_EXPR)
9544 decl = TREE_OPERAND (t, 0);
9545 t = TREE_OPERAND (t, 1);
9546 tree *tp = &TREE_OPERAND (t, 1);
9547 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
9548 tp = &TREE_OPERAND (t, 0);
9550 if (!is_gimple_constant (*tp))
9552 gimple_seq *seq = gimple_seq_empty_p (for_pre_body)
9553 ? pre_p : &for_pre_body;
9554 *tp = get_initialized_tmp_var (*tp, seq, NULL, false);
9555 tree c = build_omp_clause (input_location,
9556 OMP_CLAUSE_FIRSTPRIVATE);
9557 OMP_CLAUSE_DECL (c) = *tp;
9558 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9559 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9564 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
9565 OMP_TASKLOOP);
9568 if (orig_for_stmt != for_stmt)
9569 gimplify_omp_ctxp->combined_loop = true;
9571 for_body = NULL;
9572 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9573 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
9574 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9575 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
9577 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
9578 bool is_doacross = false;
9579 if (c && OMP_CLAUSE_ORDERED_EXPR (c))
9581 is_doacross = true;
9582 gimplify_omp_ctxp->loop_iter_var.create (TREE_VEC_LENGTH
9583 (OMP_FOR_INIT (for_stmt))
9584 * 2);
9586 int collapse = 1;
9587 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
9588 if (c)
9589 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
9590 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
9592 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
9593 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
9594 decl = TREE_OPERAND (t, 0);
9595 gcc_assert (DECL_P (decl));
9596 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
9597 || POINTER_TYPE_P (TREE_TYPE (decl)));
9598 if (is_doacross)
9600 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
9601 gimplify_omp_ctxp->loop_iter_var.quick_push
9602 (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i));
9603 else
9604 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
9605 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
9608 /* Make sure the iteration variable is private. */
9609 tree c = NULL_TREE;
9610 tree c2 = NULL_TREE;
9611 if (orig_for_stmt != for_stmt)
9612 /* Do this only on innermost construct for combined ones. */;
9613 else if (ort == ORT_SIMD)
9615 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
9616 (splay_tree_key) decl);
9617 omp_is_private (gimplify_omp_ctxp, decl,
9618 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9619 != 1));
9620 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
9621 omp_notice_variable (gimplify_omp_ctxp, decl, true);
9622 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9624 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
9625 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
9626 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
9627 if (has_decl_expr
9628 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
9630 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
9631 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9633 struct gimplify_omp_ctx *outer
9634 = gimplify_omp_ctxp->outer_context;
9635 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9637 if (outer->region_type == ORT_WORKSHARE
9638 && outer->combined_loop)
9640 n = splay_tree_lookup (outer->variables,
9641 (splay_tree_key)decl);
9642 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
9644 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
9645 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9647 else
9649 struct gimplify_omp_ctx *octx = outer->outer_context;
9650 if (octx
9651 && octx->region_type == ORT_COMBINED_PARALLEL
9652 && octx->outer_context
9653 && (octx->outer_context->region_type
9654 == ORT_WORKSHARE)
9655 && octx->outer_context->combined_loop)
9657 octx = octx->outer_context;
9658 n = splay_tree_lookup (octx->variables,
9659 (splay_tree_key)decl);
9660 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
9662 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
9663 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9670 OMP_CLAUSE_DECL (c) = decl;
9671 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
9672 OMP_FOR_CLAUSES (for_stmt) = c;
9673 omp_add_variable (gimplify_omp_ctxp, decl, flags);
9674 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9676 if (outer->region_type == ORT_WORKSHARE
9677 && outer->combined_loop)
9679 if (outer->outer_context
9680 && (outer->outer_context->region_type
9681 == ORT_COMBINED_PARALLEL))
9682 outer = outer->outer_context;
9683 else if (omp_check_private (outer, decl, false))
9684 outer = NULL;
9686 else if (((outer->region_type & ORT_TASK) != 0)
9687 && outer->combined_loop
9688 && !omp_check_private (gimplify_omp_ctxp,
9689 decl, false))
9691 else if (outer->region_type != ORT_COMBINED_PARALLEL)
9693 omp_notice_variable (outer, decl, true);
9694 outer = NULL;
9696 if (outer)
9698 n = splay_tree_lookup (outer->variables,
9699 (splay_tree_key)decl);
9700 if (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9702 omp_add_variable (outer, decl,
9703 GOVD_LASTPRIVATE | GOVD_SEEN);
9704 if (outer->region_type == ORT_COMBINED_PARALLEL
9705 && outer->outer_context
9706 && (outer->outer_context->region_type
9707 == ORT_WORKSHARE)
9708 && outer->outer_context->combined_loop)
9710 outer = outer->outer_context;
9711 n = splay_tree_lookup (outer->variables,
9712 (splay_tree_key)decl);
9713 if (omp_check_private (outer, decl, false))
9714 outer = NULL;
9715 else if (n == NULL
9716 || ((n->value & GOVD_DATA_SHARE_CLASS)
9717 == 0))
9718 omp_add_variable (outer, decl,
9719 GOVD_LASTPRIVATE
9720 | GOVD_SEEN);
9721 else
9722 outer = NULL;
9724 if (outer && outer->outer_context
9725 && (outer->outer_context->region_type
9726 == ORT_COMBINED_TEAMS))
9728 outer = outer->outer_context;
9729 n = splay_tree_lookup (outer->variables,
9730 (splay_tree_key)decl);
9731 if (n == NULL
9732 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9733 omp_add_variable (outer, decl,
9734 GOVD_SHARED | GOVD_SEEN);
9735 else
9736 outer = NULL;
9738 if (outer && outer->outer_context)
9739 omp_notice_variable (outer->outer_context, decl,
9740 true);
9745 else
9747 bool lastprivate
9748 = (!has_decl_expr
9749 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
9750 struct gimplify_omp_ctx *outer
9751 = gimplify_omp_ctxp->outer_context;
9752 if (outer && lastprivate)
9754 if (outer->region_type == ORT_WORKSHARE
9755 && outer->combined_loop)
9757 n = splay_tree_lookup (outer->variables,
9758 (splay_tree_key)decl);
9759 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
9761 lastprivate = false;
9762 outer = NULL;
9764 else if (outer->outer_context
9765 && (outer->outer_context->region_type
9766 == ORT_COMBINED_PARALLEL))
9767 outer = outer->outer_context;
9768 else if (omp_check_private (outer, decl, false))
9769 outer = NULL;
9771 else if (((outer->region_type & ORT_TASK) != 0)
9772 && outer->combined_loop
9773 && !omp_check_private (gimplify_omp_ctxp,
9774 decl, false))
9776 else if (outer->region_type != ORT_COMBINED_PARALLEL)
9778 omp_notice_variable (outer, decl, true);
9779 outer = NULL;
9781 if (outer)
9783 n = splay_tree_lookup (outer->variables,
9784 (splay_tree_key)decl);
9785 if (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9787 omp_add_variable (outer, decl,
9788 GOVD_LASTPRIVATE | GOVD_SEEN);
9789 if (outer->region_type == ORT_COMBINED_PARALLEL
9790 && outer->outer_context
9791 && (outer->outer_context->region_type
9792 == ORT_WORKSHARE)
9793 && outer->outer_context->combined_loop)
9795 outer = outer->outer_context;
9796 n = splay_tree_lookup (outer->variables,
9797 (splay_tree_key)decl);
9798 if (omp_check_private (outer, decl, false))
9799 outer = NULL;
9800 else if (n == NULL
9801 || ((n->value & GOVD_DATA_SHARE_CLASS)
9802 == 0))
9803 omp_add_variable (outer, decl,
9804 GOVD_LASTPRIVATE
9805 | GOVD_SEEN);
9806 else
9807 outer = NULL;
9809 if (outer && outer->outer_context
9810 && (outer->outer_context->region_type
9811 == ORT_COMBINED_TEAMS))
9813 outer = outer->outer_context;
9814 n = splay_tree_lookup (outer->variables,
9815 (splay_tree_key)decl);
9816 if (n == NULL
9817 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9818 omp_add_variable (outer, decl,
9819 GOVD_SHARED | GOVD_SEEN);
9820 else
9821 outer = NULL;
9823 if (outer && outer->outer_context)
9824 omp_notice_variable (outer->outer_context, decl,
9825 true);
9830 c = build_omp_clause (input_location,
9831 lastprivate ? OMP_CLAUSE_LASTPRIVATE
9832 : OMP_CLAUSE_PRIVATE);
9833 OMP_CLAUSE_DECL (c) = decl;
9834 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
9835 OMP_FOR_CLAUSES (for_stmt) = c;
9836 omp_add_variable (gimplify_omp_ctxp, decl,
9837 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
9838 | GOVD_EXPLICIT | GOVD_SEEN);
9839 c = NULL_TREE;
9842 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
9843 omp_notice_variable (gimplify_omp_ctxp, decl, true);
9844 else
9845 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
9847 /* If DECL is not a gimple register, create a temporary variable to act
9848 as an iteration counter. This is valid, since DECL cannot be
9849 modified in the body of the loop. Similarly for any iteration vars
9850 in simd with collapse > 1 where the iterator vars must be
9851 lastprivate. */
9852 if (orig_for_stmt != for_stmt)
9853 var = decl;
9854 else if (!is_gimple_reg (decl)
9855 || (ort == ORT_SIMD
9856 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1))
9858 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
9859 /* Make sure omp_add_variable is not called on it prematurely.
9860 We call it ourselves a few lines later. */
9861 gimplify_omp_ctxp = NULL;
9862 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
9863 gimplify_omp_ctxp = ctx;
9864 TREE_OPERAND (t, 0) = var;
9866 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
9868 if (ort == ORT_SIMD
9869 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9871 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
9872 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
9873 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
9874 OMP_CLAUSE_DECL (c2) = var;
9875 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
9876 OMP_FOR_CLAUSES (for_stmt) = c2;
9877 omp_add_variable (gimplify_omp_ctxp, var,
9878 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
9879 if (c == NULL_TREE)
9881 c = c2;
9882 c2 = NULL_TREE;
9885 else
9886 omp_add_variable (gimplify_omp_ctxp, var,
9887 GOVD_PRIVATE | GOVD_SEEN);
9889 else
9890 var = 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);
9895 if (ret == GS_ERROR)
9896 return ret;
9898 /* Handle OMP_FOR_COND. */
9899 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
9900 gcc_assert (COMPARISON_CLASS_P (t));
9901 gcc_assert (TREE_OPERAND (t, 0) == decl);
9903 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
9904 is_gimple_val, fb_rvalue, false);
9905 ret = MIN (ret, tret);
9907 /* Handle OMP_FOR_INCR. */
9908 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
9909 switch (TREE_CODE (t))
9911 case PREINCREMENT_EXPR:
9912 case POSTINCREMENT_EXPR:
9914 tree decl = TREE_OPERAND (t, 0);
9915 /* c_omp_for_incr_canonicalize_ptr() should have been
9916 called to massage things appropriately. */
9917 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
9919 if (orig_for_stmt != for_stmt)
9920 break;
9921 t = build_int_cst (TREE_TYPE (decl), 1);
9922 if (c)
9923 OMP_CLAUSE_LINEAR_STEP (c) = t;
9924 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
9925 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
9926 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
9927 break;
9930 case PREDECREMENT_EXPR:
9931 case POSTDECREMENT_EXPR:
9932 /* c_omp_for_incr_canonicalize_ptr() should have been
9933 called to massage things appropriately. */
9934 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
9935 if (orig_for_stmt != for_stmt)
9936 break;
9937 t = build_int_cst (TREE_TYPE (decl), -1);
9938 if (c)
9939 OMP_CLAUSE_LINEAR_STEP (c) = t;
9940 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
9941 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
9942 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
9943 break;
9945 case MODIFY_EXPR:
9946 gcc_assert (TREE_OPERAND (t, 0) == decl);
9947 TREE_OPERAND (t, 0) = var;
9949 t = TREE_OPERAND (t, 1);
9950 switch (TREE_CODE (t))
9952 case PLUS_EXPR:
9953 if (TREE_OPERAND (t, 1) == decl)
9955 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
9956 TREE_OPERAND (t, 0) = var;
9957 break;
9960 /* Fallthru. */
9961 case MINUS_EXPR:
9962 case POINTER_PLUS_EXPR:
9963 gcc_assert (TREE_OPERAND (t, 0) == decl);
9964 TREE_OPERAND (t, 0) = var;
9965 break;
9966 default:
9967 gcc_unreachable ();
9970 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
9971 is_gimple_val, fb_rvalue, false);
9972 ret = MIN (ret, tret);
9973 if (c)
9975 tree step = TREE_OPERAND (t, 1);
9976 tree stept = TREE_TYPE (decl);
9977 if (POINTER_TYPE_P (stept))
9978 stept = sizetype;
9979 step = fold_convert (stept, step);
9980 if (TREE_CODE (t) == MINUS_EXPR)
9981 step = fold_build1 (NEGATE_EXPR, stept, step);
9982 OMP_CLAUSE_LINEAR_STEP (c) = step;
9983 if (step != TREE_OPERAND (t, 1))
9985 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
9986 &for_pre_body, NULL,
9987 is_gimple_val, fb_rvalue, false);
9988 ret = MIN (ret, tret);
9991 break;
9993 default:
9994 gcc_unreachable ();
9997 if (c2)
9999 gcc_assert (c);
10000 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
10003 if ((var != decl || collapse > 1) && orig_for_stmt == for_stmt)
10005 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
10006 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10007 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
10008 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
10009 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
10010 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
10011 && OMP_CLAUSE_DECL (c) == decl)
10013 if (is_doacross && (collapse == 1 || i >= collapse))
10014 t = var;
10015 else
10017 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10018 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
10019 gcc_assert (TREE_OPERAND (t, 0) == var);
10020 t = TREE_OPERAND (t, 1);
10021 gcc_assert (TREE_CODE (t) == PLUS_EXPR
10022 || TREE_CODE (t) == MINUS_EXPR
10023 || TREE_CODE (t) == POINTER_PLUS_EXPR);
10024 gcc_assert (TREE_OPERAND (t, 0) == var);
10025 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
10026 is_doacross ? var : decl,
10027 TREE_OPERAND (t, 1));
10029 gimple_seq *seq;
10030 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
10031 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
10032 else
10033 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
10034 gimplify_assign (decl, t, seq);
10039 BITMAP_FREE (has_decl_expr);
10041 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10043 push_gimplify_context ();
10044 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
10046 OMP_FOR_BODY (orig_for_stmt)
10047 = build3 (BIND_EXPR, void_type_node, NULL,
10048 OMP_FOR_BODY (orig_for_stmt), NULL);
10049 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
10053 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
10054 &for_body);
10056 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10058 if (gimple_code (g) == GIMPLE_BIND)
10059 pop_gimplify_context (g);
10060 else
10061 pop_gimplify_context (NULL);
10064 if (orig_for_stmt != for_stmt)
10065 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
10067 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
10068 decl = TREE_OPERAND (t, 0);
10069 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10070 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10071 gimplify_omp_ctxp = ctx->outer_context;
10072 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
10073 gimplify_omp_ctxp = ctx;
10074 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
10075 TREE_OPERAND (t, 0) = var;
10076 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10077 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
10078 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
10081 gimplify_adjust_omp_clauses (pre_p, for_body,
10082 &OMP_FOR_CLAUSES (orig_for_stmt),
10083 TREE_CODE (orig_for_stmt));
10085 int kind;
10086 switch (TREE_CODE (orig_for_stmt))
10088 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
10089 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
10090 case CILK_SIMD: kind = GF_OMP_FOR_KIND_CILKSIMD; break;
10091 case CILK_FOR: kind = GF_OMP_FOR_KIND_CILKFOR; break;
10092 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
10093 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
10094 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
10095 default:
10096 gcc_unreachable ();
10098 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
10099 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
10100 for_pre_body);
10101 if (orig_for_stmt != for_stmt)
10102 gimple_omp_for_set_combined_p (gfor, true);
10103 if (gimplify_omp_ctxp
10104 && (gimplify_omp_ctxp->combined_loop
10105 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
10106 && gimplify_omp_ctxp->outer_context
10107 && gimplify_omp_ctxp->outer_context->combined_loop)))
10109 gimple_omp_for_set_combined_into_p (gfor, true);
10110 if (gimplify_omp_ctxp->combined_loop)
10111 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
10112 else
10113 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
10116 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
10118 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
10119 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
10120 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
10121 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
10122 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
10123 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
10124 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10125 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
10128 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
10129 constructs with GIMPLE_OMP_TASK sandwiched in between them.
10130 The outer taskloop stands for computing the number of iterations,
10131 counts for collapsed loops and holding taskloop specific clauses.
10132 The task construct stands for the effect of data sharing on the
10133 explicit task it creates and the inner taskloop stands for expansion
10134 of the static loop inside of the explicit task construct. */
10135 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10137 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
10138 tree task_clauses = NULL_TREE;
10139 tree c = *gfor_clauses_ptr;
10140 tree *gtask_clauses_ptr = &task_clauses;
10141 tree outer_for_clauses = NULL_TREE;
10142 tree *gforo_clauses_ptr = &outer_for_clauses;
10143 for (; c; c = OMP_CLAUSE_CHAIN (c))
10144 switch (OMP_CLAUSE_CODE (c))
10146 /* These clauses are allowed on task, move them there. */
10147 case OMP_CLAUSE_SHARED:
10148 case OMP_CLAUSE_FIRSTPRIVATE:
10149 case OMP_CLAUSE_DEFAULT:
10150 case OMP_CLAUSE_IF:
10151 case OMP_CLAUSE_UNTIED:
10152 case OMP_CLAUSE_FINAL:
10153 case OMP_CLAUSE_MERGEABLE:
10154 case OMP_CLAUSE_PRIORITY:
10155 *gtask_clauses_ptr = c;
10156 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10157 break;
10158 case OMP_CLAUSE_PRIVATE:
10159 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
10161 /* We want private on outer for and firstprivate
10162 on task. */
10163 *gtask_clauses_ptr
10164 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10165 OMP_CLAUSE_FIRSTPRIVATE);
10166 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10167 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL);
10168 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10169 *gforo_clauses_ptr = c;
10170 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10172 else
10174 *gtask_clauses_ptr = c;
10175 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10177 break;
10178 /* These clauses go into outer taskloop clauses. */
10179 case OMP_CLAUSE_GRAINSIZE:
10180 case OMP_CLAUSE_NUM_TASKS:
10181 case OMP_CLAUSE_NOGROUP:
10182 *gforo_clauses_ptr = c;
10183 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10184 break;
10185 /* Taskloop clause we duplicate on both taskloops. */
10186 case OMP_CLAUSE_COLLAPSE:
10187 *gfor_clauses_ptr = c;
10188 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10189 *gforo_clauses_ptr = copy_node (c);
10190 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
10191 break;
10192 /* For lastprivate, keep the clause on inner taskloop, and add
10193 a shared clause on task. If the same decl is also firstprivate,
10194 add also firstprivate clause on the inner taskloop. */
10195 case OMP_CLAUSE_LASTPRIVATE:
10196 if (OMP_CLAUSE_LASTPRIVATE_TASKLOOP_IV (c))
10198 /* For taskloop C++ lastprivate IVs, we want:
10199 1) private on outer taskloop
10200 2) firstprivate and shared on task
10201 3) lastprivate on inner taskloop */
10202 *gtask_clauses_ptr
10203 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10204 OMP_CLAUSE_FIRSTPRIVATE);
10205 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10206 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL);
10207 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10208 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
10209 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10210 OMP_CLAUSE_PRIVATE);
10211 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
10212 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
10213 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
10214 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
10216 *gfor_clauses_ptr = c;
10217 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10218 *gtask_clauses_ptr
10219 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
10220 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10221 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
10222 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
10223 gtask_clauses_ptr
10224 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10225 break;
10226 default:
10227 gcc_unreachable ();
10229 *gfor_clauses_ptr = NULL_TREE;
10230 *gtask_clauses_ptr = NULL_TREE;
10231 *gforo_clauses_ptr = NULL_TREE;
10232 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
10233 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
10234 NULL_TREE, NULL_TREE, NULL_TREE);
10235 gimple_omp_task_set_taskloop_p (g, true);
10236 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
10237 gomp_for *gforo
10238 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
10239 gimple_omp_for_collapse (gfor),
10240 gimple_omp_for_pre_body (gfor));
10241 gimple_omp_for_set_pre_body (gfor, NULL);
10242 gimple_omp_for_set_combined_p (gforo, true);
10243 gimple_omp_for_set_combined_into_p (gfor, true);
10244 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
10246 t = unshare_expr (gimple_omp_for_index (gfor, i));
10247 gimple_omp_for_set_index (gforo, i, t);
10248 t = unshare_expr (gimple_omp_for_initial (gfor, i));
10249 gimple_omp_for_set_initial (gforo, i, t);
10250 gimple_omp_for_set_cond (gforo, i,
10251 gimple_omp_for_cond (gfor, i));
10252 t = unshare_expr (gimple_omp_for_final (gfor, i));
10253 gimple_omp_for_set_final (gforo, i, t);
10254 t = unshare_expr (gimple_omp_for_incr (gfor, i));
10255 gimple_omp_for_set_incr (gforo, i, t);
10257 gimplify_seq_add_stmt (pre_p, gforo);
10259 else
10260 gimplify_seq_add_stmt (pre_p, gfor);
10261 if (ret != GS_ALL_DONE)
10262 return GS_ERROR;
10263 *expr_p = NULL_TREE;
10264 return GS_ALL_DONE;
10267 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
10268 of OMP_TARGET's body. */
10270 static tree
10271 find_omp_teams (tree *tp, int *walk_subtrees, void *)
10273 *walk_subtrees = 0;
10274 switch (TREE_CODE (*tp))
10276 case OMP_TEAMS:
10277 return *tp;
10278 case BIND_EXPR:
10279 case STATEMENT_LIST:
10280 *walk_subtrees = 1;
10281 break;
10282 default:
10283 break;
10285 return NULL_TREE;
10288 /* Helper function of optimize_target_teams, determine if the expression
10289 can be computed safely before the target construct on the host. */
10291 static tree
10292 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
10294 splay_tree_node n;
10296 if (TYPE_P (*tp))
10298 *walk_subtrees = 0;
10299 return NULL_TREE;
10301 switch (TREE_CODE (*tp))
10303 case VAR_DECL:
10304 case PARM_DECL:
10305 case RESULT_DECL:
10306 *walk_subtrees = 0;
10307 if (error_operand_p (*tp)
10308 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
10309 || DECL_HAS_VALUE_EXPR_P (*tp)
10310 || DECL_THREAD_LOCAL_P (*tp)
10311 || TREE_SIDE_EFFECTS (*tp)
10312 || TREE_THIS_VOLATILE (*tp))
10313 return *tp;
10314 if (is_global_var (*tp)
10315 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
10316 || lookup_attribute ("omp declare target link",
10317 DECL_ATTRIBUTES (*tp))))
10318 return *tp;
10319 if (VAR_P (*tp)
10320 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
10321 && !is_global_var (*tp)
10322 && decl_function_context (*tp) == current_function_decl)
10323 return *tp;
10324 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
10325 (splay_tree_key) *tp);
10326 if (n == NULL)
10328 if (gimplify_omp_ctxp->target_map_scalars_firstprivate)
10329 return NULL_TREE;
10330 return *tp;
10332 else if (n->value & GOVD_LOCAL)
10333 return *tp;
10334 else if (n->value & GOVD_FIRSTPRIVATE)
10335 return NULL_TREE;
10336 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
10337 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
10338 return NULL_TREE;
10339 return *tp;
10340 case INTEGER_CST:
10341 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
10342 return *tp;
10343 return NULL_TREE;
10344 case TARGET_EXPR:
10345 if (TARGET_EXPR_INITIAL (*tp)
10346 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
10347 return *tp;
10348 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
10349 walk_subtrees, NULL);
10350 /* Allow some reasonable subset of integral arithmetics. */
10351 case PLUS_EXPR:
10352 case MINUS_EXPR:
10353 case MULT_EXPR:
10354 case TRUNC_DIV_EXPR:
10355 case CEIL_DIV_EXPR:
10356 case FLOOR_DIV_EXPR:
10357 case ROUND_DIV_EXPR:
10358 case TRUNC_MOD_EXPR:
10359 case CEIL_MOD_EXPR:
10360 case FLOOR_MOD_EXPR:
10361 case ROUND_MOD_EXPR:
10362 case RDIV_EXPR:
10363 case EXACT_DIV_EXPR:
10364 case MIN_EXPR:
10365 case MAX_EXPR:
10366 case LSHIFT_EXPR:
10367 case RSHIFT_EXPR:
10368 case BIT_IOR_EXPR:
10369 case BIT_XOR_EXPR:
10370 case BIT_AND_EXPR:
10371 case NEGATE_EXPR:
10372 case ABS_EXPR:
10373 case BIT_NOT_EXPR:
10374 case NON_LVALUE_EXPR:
10375 CASE_CONVERT:
10376 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
10377 return *tp;
10378 return NULL_TREE;
10379 /* And disallow anything else, except for comparisons. */
10380 default:
10381 if (COMPARISON_CLASS_P (*tp))
10382 return NULL_TREE;
10383 return *tp;
10387 /* Try to determine if the num_teams and/or thread_limit expressions
10388 can have their values determined already before entering the
10389 target construct.
10390 INTEGER_CSTs trivially are,
10391 integral decls that are firstprivate (explicitly or implicitly)
10392 or explicitly map(always, to:) or map(always, tofrom:) on the target
10393 region too, and expressions involving simple arithmetics on those
10394 too, function calls are not ok, dereferencing something neither etc.
10395 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
10396 EXPR based on what we find:
10397 0 stands for clause not specified at all, use implementation default
10398 -1 stands for value that can't be determined easily before entering
10399 the target construct.
10400 If teams construct is not present at all, use 1 for num_teams
10401 and 0 for thread_limit (only one team is involved, and the thread
10402 limit is implementation defined. */
10404 static void
10405 optimize_target_teams (tree target, gimple_seq *pre_p)
10407 tree body = OMP_BODY (target);
10408 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
10409 tree num_teams = integer_zero_node;
10410 tree thread_limit = integer_zero_node;
10411 location_t num_teams_loc = EXPR_LOCATION (target);
10412 location_t thread_limit_loc = EXPR_LOCATION (target);
10413 tree c, *p, expr;
10414 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
10416 if (teams == NULL_TREE)
10417 num_teams = integer_one_node;
10418 else
10419 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
10421 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
10423 p = &num_teams;
10424 num_teams_loc = OMP_CLAUSE_LOCATION (c);
10426 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
10428 p = &thread_limit;
10429 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
10431 else
10432 continue;
10433 expr = OMP_CLAUSE_OPERAND (c, 0);
10434 if (TREE_CODE (expr) == INTEGER_CST)
10436 *p = expr;
10437 continue;
10439 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
10441 *p = integer_minus_one_node;
10442 continue;
10444 *p = expr;
10445 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
10446 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
10447 == GS_ERROR)
10449 gimplify_omp_ctxp = target_ctx;
10450 *p = integer_minus_one_node;
10451 continue;
10453 gimplify_omp_ctxp = target_ctx;
10454 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
10455 OMP_CLAUSE_OPERAND (c, 0) = *p;
10457 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
10458 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
10459 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
10460 OMP_TARGET_CLAUSES (target) = c;
10461 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
10462 OMP_CLAUSE_NUM_TEAMS_EXPR (c) = num_teams;
10463 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
10464 OMP_TARGET_CLAUSES (target) = c;
10467 /* Gimplify the gross structure of several OMP constructs. */
10469 static void
10470 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
10472 tree expr = *expr_p;
10473 gimple *stmt;
10474 gimple_seq body = NULL;
10475 enum omp_region_type ort;
10477 switch (TREE_CODE (expr))
10479 case OMP_SECTIONS:
10480 case OMP_SINGLE:
10481 ort = ORT_WORKSHARE;
10482 break;
10483 case OMP_TARGET:
10484 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
10485 break;
10486 case OACC_KERNELS:
10487 ort = ORT_ACC_KERNELS;
10488 break;
10489 case OACC_PARALLEL:
10490 ort = ORT_ACC_PARALLEL;
10491 break;
10492 case OACC_DATA:
10493 ort = ORT_ACC_DATA;
10494 break;
10495 case OMP_TARGET_DATA:
10496 ort = ORT_TARGET_DATA;
10497 break;
10498 case OMP_TEAMS:
10499 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
10500 break;
10501 case OACC_HOST_DATA:
10502 ort = ORT_ACC_HOST_DATA;
10503 break;
10504 default:
10505 gcc_unreachable ();
10507 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
10508 TREE_CODE (expr));
10509 if (TREE_CODE (expr) == OMP_TARGET)
10510 optimize_target_teams (expr, pre_p);
10511 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0)
10513 push_gimplify_context ();
10514 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
10515 if (gimple_code (g) == GIMPLE_BIND)
10516 pop_gimplify_context (g);
10517 else
10518 pop_gimplify_context (NULL);
10519 if ((ort & ORT_TARGET_DATA) != 0)
10521 enum built_in_function end_ix;
10522 switch (TREE_CODE (expr))
10524 case OACC_DATA:
10525 case OACC_HOST_DATA:
10526 end_ix = BUILT_IN_GOACC_DATA_END;
10527 break;
10528 case OMP_TARGET_DATA:
10529 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
10530 break;
10531 default:
10532 gcc_unreachable ();
10534 tree fn = builtin_decl_explicit (end_ix);
10535 g = gimple_build_call (fn, 0);
10536 gimple_seq cleanup = NULL;
10537 gimple_seq_add_stmt (&cleanup, g);
10538 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
10539 body = NULL;
10540 gimple_seq_add_stmt (&body, g);
10543 else
10544 gimplify_and_add (OMP_BODY (expr), &body);
10545 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
10546 TREE_CODE (expr));
10548 switch (TREE_CODE (expr))
10550 case OACC_DATA:
10551 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
10552 OMP_CLAUSES (expr));
10553 break;
10554 case OACC_KERNELS:
10555 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
10556 OMP_CLAUSES (expr));
10557 break;
10558 case OACC_HOST_DATA:
10559 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
10560 OMP_CLAUSES (expr));
10561 break;
10562 case OACC_PARALLEL:
10563 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
10564 OMP_CLAUSES (expr));
10565 break;
10566 case OMP_SECTIONS:
10567 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
10568 break;
10569 case OMP_SINGLE:
10570 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
10571 break;
10572 case OMP_TARGET:
10573 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
10574 OMP_CLAUSES (expr));
10575 break;
10576 case OMP_TARGET_DATA:
10577 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
10578 OMP_CLAUSES (expr));
10579 break;
10580 case OMP_TEAMS:
10581 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
10582 break;
10583 default:
10584 gcc_unreachable ();
10587 gimplify_seq_add_stmt (pre_p, stmt);
10588 *expr_p = NULL_TREE;
10591 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
10592 target update constructs. */
10594 static void
10595 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
10597 tree expr = *expr_p;
10598 int kind;
10599 gomp_target *stmt;
10600 enum omp_region_type ort = ORT_WORKSHARE;
10602 switch (TREE_CODE (expr))
10604 case OACC_ENTER_DATA:
10605 case OACC_EXIT_DATA:
10606 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
10607 ort = ORT_ACC;
10608 break;
10609 case OACC_UPDATE:
10610 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
10611 ort = ORT_ACC;
10612 break;
10613 case OMP_TARGET_UPDATE:
10614 kind = GF_OMP_TARGET_KIND_UPDATE;
10615 break;
10616 case OMP_TARGET_ENTER_DATA:
10617 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
10618 break;
10619 case OMP_TARGET_EXIT_DATA:
10620 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
10621 break;
10622 default:
10623 gcc_unreachable ();
10625 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
10626 ort, TREE_CODE (expr));
10627 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
10628 TREE_CODE (expr));
10629 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
10631 gimplify_seq_add_stmt (pre_p, stmt);
10632 *expr_p = NULL_TREE;
10635 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
10636 stabilized the lhs of the atomic operation as *ADDR. Return true if
10637 EXPR is this stabilized form. */
10639 static bool
10640 goa_lhs_expr_p (tree expr, tree addr)
10642 /* Also include casts to other type variants. The C front end is fond
10643 of adding these for e.g. volatile variables. This is like
10644 STRIP_TYPE_NOPS but includes the main variant lookup. */
10645 STRIP_USELESS_TYPE_CONVERSION (expr);
10647 if (TREE_CODE (expr) == INDIRECT_REF)
10649 expr = TREE_OPERAND (expr, 0);
10650 while (expr != addr
10651 && (CONVERT_EXPR_P (expr)
10652 || TREE_CODE (expr) == NON_LVALUE_EXPR)
10653 && TREE_CODE (expr) == TREE_CODE (addr)
10654 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
10656 expr = TREE_OPERAND (expr, 0);
10657 addr = TREE_OPERAND (addr, 0);
10659 if (expr == addr)
10660 return true;
10661 return (TREE_CODE (addr) == ADDR_EXPR
10662 && TREE_CODE (expr) == ADDR_EXPR
10663 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
10665 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
10666 return true;
10667 return false;
10670 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
10671 expression does not involve the lhs, evaluate it into a temporary.
10672 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
10673 or -1 if an error was encountered. */
10675 static int
10676 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
10677 tree lhs_var)
10679 tree expr = *expr_p;
10680 int saw_lhs;
10682 if (goa_lhs_expr_p (expr, lhs_addr))
10684 *expr_p = lhs_var;
10685 return 1;
10687 if (is_gimple_val (expr))
10688 return 0;
10690 saw_lhs = 0;
10691 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
10693 case tcc_binary:
10694 case tcc_comparison:
10695 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
10696 lhs_var);
10697 /* FALLTHRU */
10698 case tcc_unary:
10699 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
10700 lhs_var);
10701 break;
10702 case tcc_expression:
10703 switch (TREE_CODE (expr))
10705 case TRUTH_ANDIF_EXPR:
10706 case TRUTH_ORIF_EXPR:
10707 case TRUTH_AND_EXPR:
10708 case TRUTH_OR_EXPR:
10709 case TRUTH_XOR_EXPR:
10710 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
10711 lhs_addr, lhs_var);
10712 /* FALLTHRU */
10713 case TRUTH_NOT_EXPR:
10714 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
10715 lhs_addr, lhs_var);
10716 break;
10717 case COMPOUND_EXPR:
10718 /* Break out any preevaluations from cp_build_modify_expr. */
10719 for (; TREE_CODE (expr) == COMPOUND_EXPR;
10720 expr = TREE_OPERAND (expr, 1))
10721 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
10722 *expr_p = expr;
10723 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var);
10724 default:
10725 break;
10727 break;
10728 default:
10729 break;
10732 if (saw_lhs == 0)
10734 enum gimplify_status gs;
10735 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
10736 if (gs != GS_ALL_DONE)
10737 saw_lhs = -1;
10740 return saw_lhs;
10743 /* Gimplify an OMP_ATOMIC statement. */
10745 static enum gimplify_status
10746 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
10748 tree addr = TREE_OPERAND (*expr_p, 0);
10749 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
10750 ? NULL : TREE_OPERAND (*expr_p, 1);
10751 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
10752 tree tmp_load;
10753 gomp_atomic_load *loadstmt;
10754 gomp_atomic_store *storestmt;
10756 tmp_load = create_tmp_reg (type);
10757 if (rhs && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load) < 0)
10758 return GS_ERROR;
10760 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
10761 != GS_ALL_DONE)
10762 return GS_ERROR;
10764 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr);
10765 gimplify_seq_add_stmt (pre_p, loadstmt);
10766 if (rhs && gimplify_expr (&rhs, pre_p, NULL, is_gimple_val, fb_rvalue)
10767 != GS_ALL_DONE)
10768 return GS_ERROR;
10770 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
10771 rhs = tmp_load;
10772 storestmt = gimple_build_omp_atomic_store (rhs);
10773 gimplify_seq_add_stmt (pre_p, storestmt);
10774 if (OMP_ATOMIC_SEQ_CST (*expr_p))
10776 gimple_omp_atomic_set_seq_cst (loadstmt);
10777 gimple_omp_atomic_set_seq_cst (storestmt);
10779 switch (TREE_CODE (*expr_p))
10781 case OMP_ATOMIC_READ:
10782 case OMP_ATOMIC_CAPTURE_OLD:
10783 *expr_p = tmp_load;
10784 gimple_omp_atomic_set_need_value (loadstmt);
10785 break;
10786 case OMP_ATOMIC_CAPTURE_NEW:
10787 *expr_p = rhs;
10788 gimple_omp_atomic_set_need_value (storestmt);
10789 break;
10790 default:
10791 *expr_p = NULL;
10792 break;
10795 return GS_ALL_DONE;
10798 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
10799 body, and adding some EH bits. */
10801 static enum gimplify_status
10802 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
10804 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
10805 gimple *body_stmt;
10806 gtransaction *trans_stmt;
10807 gimple_seq body = NULL;
10808 int subcode = 0;
10810 /* Wrap the transaction body in a BIND_EXPR so we have a context
10811 where to put decls for OMP. */
10812 if (TREE_CODE (tbody) != BIND_EXPR)
10814 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
10815 TREE_SIDE_EFFECTS (bind) = 1;
10816 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
10817 TRANSACTION_EXPR_BODY (expr) = bind;
10820 push_gimplify_context ();
10821 temp = voidify_wrapper_expr (*expr_p, NULL);
10823 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
10824 pop_gimplify_context (body_stmt);
10826 trans_stmt = gimple_build_transaction (body);
10827 if (TRANSACTION_EXPR_OUTER (expr))
10828 subcode = GTMA_IS_OUTER;
10829 else if (TRANSACTION_EXPR_RELAXED (expr))
10830 subcode = GTMA_IS_RELAXED;
10831 gimple_transaction_set_subcode (trans_stmt, subcode);
10833 gimplify_seq_add_stmt (pre_p, trans_stmt);
10835 if (temp)
10837 *expr_p = temp;
10838 return GS_OK;
10841 *expr_p = NULL_TREE;
10842 return GS_ALL_DONE;
10845 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
10846 is the OMP_BODY of the original EXPR (which has already been
10847 gimplified so it's not present in the EXPR).
10849 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
10851 static gimple *
10852 gimplify_omp_ordered (tree expr, gimple_seq body)
10854 tree c, decls;
10855 int failures = 0;
10856 unsigned int i;
10857 tree source_c = NULL_TREE;
10858 tree sink_c = NULL_TREE;
10860 if (gimplify_omp_ctxp)
10862 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
10863 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10864 && gimplify_omp_ctxp->loop_iter_var.is_empty ()
10865 && (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK
10866 || OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE))
10868 error_at (OMP_CLAUSE_LOCATION (c),
10869 "%<ordered%> construct with %<depend%> clause must be "
10870 "closely nested inside a loop with %<ordered%> clause "
10871 "with a parameter");
10872 failures++;
10874 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10875 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
10877 bool fail = false;
10878 for (decls = OMP_CLAUSE_DECL (c), i = 0;
10879 decls && TREE_CODE (decls) == TREE_LIST;
10880 decls = TREE_CHAIN (decls), ++i)
10881 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
10882 continue;
10883 else if (TREE_VALUE (decls)
10884 != gimplify_omp_ctxp->loop_iter_var[2 * i])
10886 error_at (OMP_CLAUSE_LOCATION (c),
10887 "variable %qE is not an iteration "
10888 "of outermost loop %d, expected %qE",
10889 TREE_VALUE (decls), i + 1,
10890 gimplify_omp_ctxp->loop_iter_var[2 * i]);
10891 fail = true;
10892 failures++;
10894 else
10895 TREE_VALUE (decls)
10896 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
10897 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
10899 error_at (OMP_CLAUSE_LOCATION (c),
10900 "number of variables in %<depend(sink)%> "
10901 "clause does not match number of "
10902 "iteration variables");
10903 failures++;
10905 sink_c = c;
10907 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10908 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
10910 if (source_c)
10912 error_at (OMP_CLAUSE_LOCATION (c),
10913 "more than one %<depend(source)%> clause on an "
10914 "%<ordered%> construct");
10915 failures++;
10917 else
10918 source_c = c;
10921 if (source_c && sink_c)
10923 error_at (OMP_CLAUSE_LOCATION (source_c),
10924 "%<depend(source)%> clause specified together with "
10925 "%<depend(sink:)%> clauses on the same construct");
10926 failures++;
10929 if (failures)
10930 return gimple_build_nop ();
10931 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
10934 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
10935 expression produces a value to be used as an operand inside a GIMPLE
10936 statement, the value will be stored back in *EXPR_P. This value will
10937 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
10938 an SSA_NAME. The corresponding sequence of GIMPLE statements is
10939 emitted in PRE_P and POST_P.
10941 Additionally, this process may overwrite parts of the input
10942 expression during gimplification. Ideally, it should be
10943 possible to do non-destructive gimplification.
10945 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
10946 the expression needs to evaluate to a value to be used as
10947 an operand in a GIMPLE statement, this value will be stored in
10948 *EXPR_P on exit. This happens when the caller specifies one
10949 of fb_lvalue or fb_rvalue fallback flags.
10951 PRE_P will contain the sequence of GIMPLE statements corresponding
10952 to the evaluation of EXPR and all the side-effects that must
10953 be executed before the main expression. On exit, the last
10954 statement of PRE_P is the core statement being gimplified. For
10955 instance, when gimplifying 'if (++a)' the last statement in
10956 PRE_P will be 'if (t.1)' where t.1 is the result of
10957 pre-incrementing 'a'.
10959 POST_P will contain the sequence of GIMPLE statements corresponding
10960 to the evaluation of all the side-effects that must be executed
10961 after the main expression. If this is NULL, the post
10962 side-effects are stored at the end of PRE_P.
10964 The reason why the output is split in two is to handle post
10965 side-effects explicitly. In some cases, an expression may have
10966 inner and outer post side-effects which need to be emitted in
10967 an order different from the one given by the recursive
10968 traversal. For instance, for the expression (*p--)++ the post
10969 side-effects of '--' must actually occur *after* the post
10970 side-effects of '++'. However, gimplification will first visit
10971 the inner expression, so if a separate POST sequence was not
10972 used, the resulting sequence would be:
10974 1 t.1 = *p
10975 2 p = p - 1
10976 3 t.2 = t.1 + 1
10977 4 *p = t.2
10979 However, the post-decrement operation in line #2 must not be
10980 evaluated until after the store to *p at line #4, so the
10981 correct sequence should be:
10983 1 t.1 = *p
10984 2 t.2 = t.1 + 1
10985 3 *p = t.2
10986 4 p = p - 1
10988 So, by specifying a separate post queue, it is possible
10989 to emit the post side-effects in the correct order.
10990 If POST_P is NULL, an internal queue will be used. Before
10991 returning to the caller, the sequence POST_P is appended to
10992 the main output sequence PRE_P.
10994 GIMPLE_TEST_F points to a function that takes a tree T and
10995 returns nonzero if T is in the GIMPLE form requested by the
10996 caller. The GIMPLE predicates are in gimple.c.
10998 FALLBACK tells the function what sort of a temporary we want if
10999 gimplification cannot produce an expression that complies with
11000 GIMPLE_TEST_F.
11002 fb_none means that no temporary should be generated
11003 fb_rvalue means that an rvalue is OK to generate
11004 fb_lvalue means that an lvalue is OK to generate
11005 fb_either means that either is OK, but an lvalue is preferable.
11006 fb_mayfail means that gimplification may fail (in which case
11007 GS_ERROR will be returned)
11009 The return value is either GS_ERROR or GS_ALL_DONE, since this
11010 function iterates until EXPR is completely gimplified or an error
11011 occurs. */
11013 enum gimplify_status
11014 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
11015 bool (*gimple_test_f) (tree), fallback_t fallback)
11017 tree tmp;
11018 gimple_seq internal_pre = NULL;
11019 gimple_seq internal_post = NULL;
11020 tree save_expr;
11021 bool is_statement;
11022 location_t saved_location;
11023 enum gimplify_status ret;
11024 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
11025 tree label;
11027 save_expr = *expr_p;
11028 if (save_expr == NULL_TREE)
11029 return GS_ALL_DONE;
11031 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
11032 is_statement = gimple_test_f == is_gimple_stmt;
11033 if (is_statement)
11034 gcc_assert (pre_p);
11036 /* Consistency checks. */
11037 if (gimple_test_f == is_gimple_reg)
11038 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
11039 else if (gimple_test_f == is_gimple_val
11040 || gimple_test_f == is_gimple_call_addr
11041 || gimple_test_f == is_gimple_condexpr
11042 || gimple_test_f == is_gimple_mem_rhs
11043 || gimple_test_f == is_gimple_mem_rhs_or_call
11044 || gimple_test_f == is_gimple_reg_rhs
11045 || gimple_test_f == is_gimple_reg_rhs_or_call
11046 || gimple_test_f == is_gimple_asm_val
11047 || gimple_test_f == is_gimple_mem_ref_addr)
11048 gcc_assert (fallback & fb_rvalue);
11049 else if (gimple_test_f == is_gimple_min_lval
11050 || gimple_test_f == is_gimple_lvalue)
11051 gcc_assert (fallback & fb_lvalue);
11052 else if (gimple_test_f == is_gimple_addressable)
11053 gcc_assert (fallback & fb_either);
11054 else if (gimple_test_f == is_gimple_stmt)
11055 gcc_assert (fallback == fb_none);
11056 else
11058 /* We should have recognized the GIMPLE_TEST_F predicate to
11059 know what kind of fallback to use in case a temporary is
11060 needed to hold the value or address of *EXPR_P. */
11061 gcc_unreachable ();
11064 /* We used to check the predicate here and return immediately if it
11065 succeeds. This is wrong; the design is for gimplification to be
11066 idempotent, and for the predicates to only test for valid forms, not
11067 whether they are fully simplified. */
11068 if (pre_p == NULL)
11069 pre_p = &internal_pre;
11071 if (post_p == NULL)
11072 post_p = &internal_post;
11074 /* Remember the last statements added to PRE_P and POST_P. Every
11075 new statement added by the gimplification helpers needs to be
11076 annotated with location information. To centralize the
11077 responsibility, we remember the last statement that had been
11078 added to both queues before gimplifying *EXPR_P. If
11079 gimplification produces new statements in PRE_P and POST_P, those
11080 statements will be annotated with the same location information
11081 as *EXPR_P. */
11082 pre_last_gsi = gsi_last (*pre_p);
11083 post_last_gsi = gsi_last (*post_p);
11085 saved_location = input_location;
11086 if (save_expr != error_mark_node
11087 && EXPR_HAS_LOCATION (*expr_p))
11088 input_location = EXPR_LOCATION (*expr_p);
11090 /* Loop over the specific gimplifiers until the toplevel node
11091 remains the same. */
11094 /* Strip away as many useless type conversions as possible
11095 at the toplevel. */
11096 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
11098 /* Remember the expr. */
11099 save_expr = *expr_p;
11101 /* Die, die, die, my darling. */
11102 if (save_expr == error_mark_node
11103 || (TREE_TYPE (save_expr)
11104 && TREE_TYPE (save_expr) == error_mark_node))
11106 ret = GS_ERROR;
11107 break;
11110 /* Do any language-specific gimplification. */
11111 ret = ((enum gimplify_status)
11112 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
11113 if (ret == GS_OK)
11115 if (*expr_p == NULL_TREE)
11116 break;
11117 if (*expr_p != save_expr)
11118 continue;
11120 else if (ret != GS_UNHANDLED)
11121 break;
11123 /* Make sure that all the cases set 'ret' appropriately. */
11124 ret = GS_UNHANDLED;
11125 switch (TREE_CODE (*expr_p))
11127 /* First deal with the special cases. */
11129 case POSTINCREMENT_EXPR:
11130 case POSTDECREMENT_EXPR:
11131 case PREINCREMENT_EXPR:
11132 case PREDECREMENT_EXPR:
11133 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
11134 fallback != fb_none,
11135 TREE_TYPE (*expr_p));
11136 break;
11138 case VIEW_CONVERT_EXPR:
11139 if (is_gimple_reg_type (TREE_TYPE (*expr_p))
11140 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
11142 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11143 post_p, is_gimple_val, fb_rvalue);
11144 recalculate_side_effects (*expr_p);
11145 break;
11147 /* Fallthru. */
11149 case ARRAY_REF:
11150 case ARRAY_RANGE_REF:
11151 case REALPART_EXPR:
11152 case IMAGPART_EXPR:
11153 case COMPONENT_REF:
11154 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
11155 fallback ? fallback : fb_rvalue);
11156 break;
11158 case COND_EXPR:
11159 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
11161 /* C99 code may assign to an array in a structure value of a
11162 conditional expression, and this has undefined behavior
11163 only on execution, so create a temporary if an lvalue is
11164 required. */
11165 if (fallback == fb_lvalue)
11167 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11168 mark_addressable (*expr_p);
11169 ret = GS_OK;
11171 break;
11173 case CALL_EXPR:
11174 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
11176 /* C99 code may assign to an array in a structure returned
11177 from a function, and this has undefined behavior only on
11178 execution, so create a temporary if an lvalue is
11179 required. */
11180 if (fallback == fb_lvalue)
11182 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11183 mark_addressable (*expr_p);
11184 ret = GS_OK;
11186 break;
11188 case TREE_LIST:
11189 gcc_unreachable ();
11191 case COMPOUND_EXPR:
11192 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
11193 break;
11195 case COMPOUND_LITERAL_EXPR:
11196 ret = gimplify_compound_literal_expr (expr_p, pre_p,
11197 gimple_test_f, fallback);
11198 break;
11200 case MODIFY_EXPR:
11201 case INIT_EXPR:
11202 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
11203 fallback != fb_none);
11204 break;
11206 case TRUTH_ANDIF_EXPR:
11207 case TRUTH_ORIF_EXPR:
11209 /* Preserve the original type of the expression and the
11210 source location of the outer expression. */
11211 tree org_type = TREE_TYPE (*expr_p);
11212 *expr_p = gimple_boolify (*expr_p);
11213 *expr_p = build3_loc (input_location, COND_EXPR,
11214 org_type, *expr_p,
11215 fold_convert_loc
11216 (input_location,
11217 org_type, boolean_true_node),
11218 fold_convert_loc
11219 (input_location,
11220 org_type, boolean_false_node));
11221 ret = GS_OK;
11222 break;
11225 case TRUTH_NOT_EXPR:
11227 tree type = TREE_TYPE (*expr_p);
11228 /* The parsers are careful to generate TRUTH_NOT_EXPR
11229 only with operands that are always zero or one.
11230 We do not fold here but handle the only interesting case
11231 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
11232 *expr_p = gimple_boolify (*expr_p);
11233 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
11234 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
11235 TREE_TYPE (*expr_p),
11236 TREE_OPERAND (*expr_p, 0));
11237 else
11238 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
11239 TREE_TYPE (*expr_p),
11240 TREE_OPERAND (*expr_p, 0),
11241 build_int_cst (TREE_TYPE (*expr_p), 1));
11242 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
11243 *expr_p = fold_convert_loc (input_location, type, *expr_p);
11244 ret = GS_OK;
11245 break;
11248 case ADDR_EXPR:
11249 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
11250 break;
11252 case ANNOTATE_EXPR:
11254 tree cond = TREE_OPERAND (*expr_p, 0);
11255 tree kind = TREE_OPERAND (*expr_p, 1);
11256 tree type = TREE_TYPE (cond);
11257 if (!INTEGRAL_TYPE_P (type))
11259 *expr_p = cond;
11260 ret = GS_OK;
11261 break;
11263 tree tmp = create_tmp_var (type);
11264 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
11265 gcall *call
11266 = gimple_build_call_internal (IFN_ANNOTATE, 2, cond, kind);
11267 gimple_call_set_lhs (call, tmp);
11268 gimplify_seq_add_stmt (pre_p, call);
11269 *expr_p = tmp;
11270 ret = GS_ALL_DONE;
11271 break;
11274 case VA_ARG_EXPR:
11275 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
11276 break;
11278 CASE_CONVERT:
11279 if (IS_EMPTY_STMT (*expr_p))
11281 ret = GS_ALL_DONE;
11282 break;
11285 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
11286 || fallback == fb_none)
11288 /* Just strip a conversion to void (or in void context) and
11289 try again. */
11290 *expr_p = TREE_OPERAND (*expr_p, 0);
11291 ret = GS_OK;
11292 break;
11295 ret = gimplify_conversion (expr_p);
11296 if (ret == GS_ERROR)
11297 break;
11298 if (*expr_p != save_expr)
11299 break;
11300 /* FALLTHRU */
11302 case FIX_TRUNC_EXPR:
11303 /* unary_expr: ... | '(' cast ')' val | ... */
11304 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11305 is_gimple_val, fb_rvalue);
11306 recalculate_side_effects (*expr_p);
11307 break;
11309 case INDIRECT_REF:
11311 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
11312 bool notrap = TREE_THIS_NOTRAP (*expr_p);
11313 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
11315 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
11316 if (*expr_p != save_expr)
11318 ret = GS_OK;
11319 break;
11322 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11323 is_gimple_reg, fb_rvalue);
11324 if (ret == GS_ERROR)
11325 break;
11327 recalculate_side_effects (*expr_p);
11328 *expr_p = fold_build2_loc (input_location, MEM_REF,
11329 TREE_TYPE (*expr_p),
11330 TREE_OPERAND (*expr_p, 0),
11331 build_int_cst (saved_ptr_type, 0));
11332 TREE_THIS_VOLATILE (*expr_p) = volatilep;
11333 TREE_THIS_NOTRAP (*expr_p) = notrap;
11334 ret = GS_OK;
11335 break;
11338 /* We arrive here through the various re-gimplifcation paths. */
11339 case MEM_REF:
11340 /* First try re-folding the whole thing. */
11341 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
11342 TREE_OPERAND (*expr_p, 0),
11343 TREE_OPERAND (*expr_p, 1));
11344 if (tmp)
11346 REF_REVERSE_STORAGE_ORDER (tmp)
11347 = REF_REVERSE_STORAGE_ORDER (*expr_p);
11348 *expr_p = tmp;
11349 recalculate_side_effects (*expr_p);
11350 ret = GS_OK;
11351 break;
11353 /* Avoid re-gimplifying the address operand if it is already
11354 in suitable form. Re-gimplifying would mark the address
11355 operand addressable. Always gimplify when not in SSA form
11356 as we still may have to gimplify decls with value-exprs. */
11357 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
11358 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
11360 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11361 is_gimple_mem_ref_addr, fb_rvalue);
11362 if (ret == GS_ERROR)
11363 break;
11365 recalculate_side_effects (*expr_p);
11366 ret = GS_ALL_DONE;
11367 break;
11369 /* Constants need not be gimplified. */
11370 case INTEGER_CST:
11371 case REAL_CST:
11372 case FIXED_CST:
11373 case STRING_CST:
11374 case COMPLEX_CST:
11375 case VECTOR_CST:
11376 /* Drop the overflow flag on constants, we do not want
11377 that in the GIMPLE IL. */
11378 if (TREE_OVERFLOW_P (*expr_p))
11379 *expr_p = drop_tree_overflow (*expr_p);
11380 ret = GS_ALL_DONE;
11381 break;
11383 case CONST_DECL:
11384 /* If we require an lvalue, such as for ADDR_EXPR, retain the
11385 CONST_DECL node. Otherwise the decl is replaceable by its
11386 value. */
11387 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
11388 if (fallback & fb_lvalue)
11389 ret = GS_ALL_DONE;
11390 else
11392 *expr_p = DECL_INITIAL (*expr_p);
11393 ret = GS_OK;
11395 break;
11397 case DECL_EXPR:
11398 ret = gimplify_decl_expr (expr_p, pre_p);
11399 break;
11401 case BIND_EXPR:
11402 ret = gimplify_bind_expr (expr_p, pre_p);
11403 break;
11405 case LOOP_EXPR:
11406 ret = gimplify_loop_expr (expr_p, pre_p);
11407 break;
11409 case SWITCH_EXPR:
11410 ret = gimplify_switch_expr (expr_p, pre_p);
11411 break;
11413 case EXIT_EXPR:
11414 ret = gimplify_exit_expr (expr_p);
11415 break;
11417 case GOTO_EXPR:
11418 /* If the target is not LABEL, then it is a computed jump
11419 and the target needs to be gimplified. */
11420 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
11422 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
11423 NULL, is_gimple_val, fb_rvalue);
11424 if (ret == GS_ERROR)
11425 break;
11427 gimplify_seq_add_stmt (pre_p,
11428 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
11429 ret = GS_ALL_DONE;
11430 break;
11432 case PREDICT_EXPR:
11433 gimplify_seq_add_stmt (pre_p,
11434 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
11435 PREDICT_EXPR_OUTCOME (*expr_p)));
11436 ret = GS_ALL_DONE;
11437 break;
11439 case LABEL_EXPR:
11440 ret = gimplify_label_expr (expr_p, pre_p);
11441 label = LABEL_EXPR_LABEL (*expr_p);
11442 gcc_assert (decl_function_context (label) == current_function_decl);
11444 /* If the label is used in a goto statement, or address of the label
11445 is taken, we need to unpoison all variables that were seen so far.
11446 Doing so would prevent us from reporting a false positives. */
11447 if (asan_poisoned_variables
11448 && asan_used_labels != NULL
11449 && asan_used_labels->contains (label))
11450 asan_poison_variables (asan_poisoned_variables, false, pre_p);
11451 break;
11453 case CASE_LABEL_EXPR:
11454 ret = gimplify_case_label_expr (expr_p, pre_p);
11456 if (gimplify_ctxp->live_switch_vars)
11457 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
11458 pre_p);
11459 break;
11461 case RETURN_EXPR:
11462 ret = gimplify_return_expr (*expr_p, pre_p);
11463 break;
11465 case CONSTRUCTOR:
11466 /* Don't reduce this in place; let gimplify_init_constructor work its
11467 magic. Buf if we're just elaborating this for side effects, just
11468 gimplify any element that has side-effects. */
11469 if (fallback == fb_none)
11471 unsigned HOST_WIDE_INT ix;
11472 tree val;
11473 tree temp = NULL_TREE;
11474 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
11475 if (TREE_SIDE_EFFECTS (val))
11476 append_to_statement_list (val, &temp);
11478 *expr_p = temp;
11479 ret = temp ? GS_OK : GS_ALL_DONE;
11481 /* C99 code may assign to an array in a constructed
11482 structure or union, and this has undefined behavior only
11483 on execution, so create a temporary if an lvalue is
11484 required. */
11485 else if (fallback == fb_lvalue)
11487 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11488 mark_addressable (*expr_p);
11489 ret = GS_OK;
11491 else
11492 ret = GS_ALL_DONE;
11493 break;
11495 /* The following are special cases that are not handled by the
11496 original GIMPLE grammar. */
11498 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
11499 eliminated. */
11500 case SAVE_EXPR:
11501 ret = gimplify_save_expr (expr_p, pre_p, post_p);
11502 break;
11504 case BIT_FIELD_REF:
11505 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11506 post_p, is_gimple_lvalue, fb_either);
11507 recalculate_side_effects (*expr_p);
11508 break;
11510 case TARGET_MEM_REF:
11512 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
11514 if (TMR_BASE (*expr_p))
11515 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
11516 post_p, is_gimple_mem_ref_addr, fb_either);
11517 if (TMR_INDEX (*expr_p))
11518 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
11519 post_p, is_gimple_val, fb_rvalue);
11520 if (TMR_INDEX2 (*expr_p))
11521 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
11522 post_p, is_gimple_val, fb_rvalue);
11523 /* TMR_STEP and TMR_OFFSET are always integer constants. */
11524 ret = MIN (r0, r1);
11526 break;
11528 case NON_LVALUE_EXPR:
11529 /* This should have been stripped above. */
11530 gcc_unreachable ();
11532 case ASM_EXPR:
11533 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
11534 break;
11536 case TRY_FINALLY_EXPR:
11537 case TRY_CATCH_EXPR:
11539 gimple_seq eval, cleanup;
11540 gtry *try_;
11542 /* Calls to destructors are generated automatically in FINALLY/CATCH
11543 block. They should have location as UNKNOWN_LOCATION. However,
11544 gimplify_call_expr will reset these call stmts to input_location
11545 if it finds stmt's location is unknown. To prevent resetting for
11546 destructors, we set the input_location to unknown.
11547 Note that this only affects the destructor calls in FINALLY/CATCH
11548 block, and will automatically reset to its original value by the
11549 end of gimplify_expr. */
11550 input_location = UNKNOWN_LOCATION;
11551 eval = cleanup = NULL;
11552 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
11553 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
11554 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
11555 if (gimple_seq_empty_p (cleanup))
11557 gimple_seq_add_seq (pre_p, eval);
11558 ret = GS_ALL_DONE;
11559 break;
11561 try_ = gimple_build_try (eval, cleanup,
11562 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
11563 ? GIMPLE_TRY_FINALLY
11564 : GIMPLE_TRY_CATCH);
11565 if (EXPR_HAS_LOCATION (save_expr))
11566 gimple_set_location (try_, EXPR_LOCATION (save_expr));
11567 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
11568 gimple_set_location (try_, saved_location);
11569 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
11570 gimple_try_set_catch_is_cleanup (try_,
11571 TRY_CATCH_IS_CLEANUP (*expr_p));
11572 gimplify_seq_add_stmt (pre_p, try_);
11573 ret = GS_ALL_DONE;
11574 break;
11577 case CLEANUP_POINT_EXPR:
11578 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
11579 break;
11581 case TARGET_EXPR:
11582 ret = gimplify_target_expr (expr_p, pre_p, post_p);
11583 break;
11585 case CATCH_EXPR:
11587 gimple *c;
11588 gimple_seq handler = NULL;
11589 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
11590 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
11591 gimplify_seq_add_stmt (pre_p, c);
11592 ret = GS_ALL_DONE;
11593 break;
11596 case EH_FILTER_EXPR:
11598 gimple *ehf;
11599 gimple_seq failure = NULL;
11601 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
11602 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
11603 gimple_set_no_warning (ehf, TREE_NO_WARNING (*expr_p));
11604 gimplify_seq_add_stmt (pre_p, ehf);
11605 ret = GS_ALL_DONE;
11606 break;
11609 case OBJ_TYPE_REF:
11611 enum gimplify_status r0, r1;
11612 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
11613 post_p, is_gimple_val, fb_rvalue);
11614 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
11615 post_p, is_gimple_val, fb_rvalue);
11616 TREE_SIDE_EFFECTS (*expr_p) = 0;
11617 ret = MIN (r0, r1);
11619 break;
11621 case LABEL_DECL:
11622 /* We get here when taking the address of a label. We mark
11623 the label as "forced"; meaning it can never be removed and
11624 it is a potential target for any computed goto. */
11625 FORCED_LABEL (*expr_p) = 1;
11626 ret = GS_ALL_DONE;
11627 break;
11629 case STATEMENT_LIST:
11630 ret = gimplify_statement_list (expr_p, pre_p);
11631 break;
11633 case WITH_SIZE_EXPR:
11635 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11636 post_p == &internal_post ? NULL : post_p,
11637 gimple_test_f, fallback);
11638 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
11639 is_gimple_val, fb_rvalue);
11640 ret = GS_ALL_DONE;
11642 break;
11644 case VAR_DECL:
11645 case PARM_DECL:
11646 ret = gimplify_var_or_parm_decl (expr_p);
11647 break;
11649 case RESULT_DECL:
11650 /* When within an OMP context, notice uses of variables. */
11651 if (gimplify_omp_ctxp)
11652 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
11653 ret = GS_ALL_DONE;
11654 break;
11656 case SSA_NAME:
11657 /* Allow callbacks into the gimplifier during optimization. */
11658 ret = GS_ALL_DONE;
11659 break;
11661 case OMP_PARALLEL:
11662 gimplify_omp_parallel (expr_p, pre_p);
11663 ret = GS_ALL_DONE;
11664 break;
11666 case OMP_TASK:
11667 gimplify_omp_task (expr_p, pre_p);
11668 ret = GS_ALL_DONE;
11669 break;
11671 case OMP_FOR:
11672 case OMP_SIMD:
11673 case CILK_SIMD:
11674 case CILK_FOR:
11675 case OMP_DISTRIBUTE:
11676 case OMP_TASKLOOP:
11677 case OACC_LOOP:
11678 ret = gimplify_omp_for (expr_p, pre_p);
11679 break;
11681 case OACC_CACHE:
11682 gimplify_oacc_cache (expr_p, pre_p);
11683 ret = GS_ALL_DONE;
11684 break;
11686 case OACC_DECLARE:
11687 gimplify_oacc_declare (expr_p, pre_p);
11688 ret = GS_ALL_DONE;
11689 break;
11691 case OACC_HOST_DATA:
11692 case OACC_DATA:
11693 case OACC_KERNELS:
11694 case OACC_PARALLEL:
11695 case OMP_SECTIONS:
11696 case OMP_SINGLE:
11697 case OMP_TARGET:
11698 case OMP_TARGET_DATA:
11699 case OMP_TEAMS:
11700 gimplify_omp_workshare (expr_p, pre_p);
11701 ret = GS_ALL_DONE;
11702 break;
11704 case OACC_ENTER_DATA:
11705 case OACC_EXIT_DATA:
11706 case OACC_UPDATE:
11707 case OMP_TARGET_UPDATE:
11708 case OMP_TARGET_ENTER_DATA:
11709 case OMP_TARGET_EXIT_DATA:
11710 gimplify_omp_target_update (expr_p, pre_p);
11711 ret = GS_ALL_DONE;
11712 break;
11714 case OMP_SECTION:
11715 case OMP_MASTER:
11716 case OMP_TASKGROUP:
11717 case OMP_ORDERED:
11718 case OMP_CRITICAL:
11720 gimple_seq body = NULL;
11721 gimple *g;
11723 gimplify_and_add (OMP_BODY (*expr_p), &body);
11724 switch (TREE_CODE (*expr_p))
11726 case OMP_SECTION:
11727 g = gimple_build_omp_section (body);
11728 break;
11729 case OMP_MASTER:
11730 g = gimple_build_omp_master (body);
11731 break;
11732 case OMP_TASKGROUP:
11734 gimple_seq cleanup = NULL;
11735 tree fn
11736 = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
11737 g = gimple_build_call (fn, 0);
11738 gimple_seq_add_stmt (&cleanup, g);
11739 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
11740 body = NULL;
11741 gimple_seq_add_stmt (&body, g);
11742 g = gimple_build_omp_taskgroup (body);
11744 break;
11745 case OMP_ORDERED:
11746 g = gimplify_omp_ordered (*expr_p, body);
11747 break;
11748 case OMP_CRITICAL:
11749 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
11750 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
11751 gimplify_adjust_omp_clauses (pre_p, body,
11752 &OMP_CRITICAL_CLAUSES (*expr_p),
11753 OMP_CRITICAL);
11754 g = gimple_build_omp_critical (body,
11755 OMP_CRITICAL_NAME (*expr_p),
11756 OMP_CRITICAL_CLAUSES (*expr_p));
11757 break;
11758 default:
11759 gcc_unreachable ();
11761 gimplify_seq_add_stmt (pre_p, g);
11762 ret = GS_ALL_DONE;
11763 break;
11766 case OMP_ATOMIC:
11767 case OMP_ATOMIC_READ:
11768 case OMP_ATOMIC_CAPTURE_OLD:
11769 case OMP_ATOMIC_CAPTURE_NEW:
11770 ret = gimplify_omp_atomic (expr_p, pre_p);
11771 break;
11773 case TRANSACTION_EXPR:
11774 ret = gimplify_transaction (expr_p, pre_p);
11775 break;
11777 case TRUTH_AND_EXPR:
11778 case TRUTH_OR_EXPR:
11779 case TRUTH_XOR_EXPR:
11781 tree orig_type = TREE_TYPE (*expr_p);
11782 tree new_type, xop0, xop1;
11783 *expr_p = gimple_boolify (*expr_p);
11784 new_type = TREE_TYPE (*expr_p);
11785 if (!useless_type_conversion_p (orig_type, new_type))
11787 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
11788 ret = GS_OK;
11789 break;
11792 /* Boolified binary truth expressions are semantically equivalent
11793 to bitwise binary expressions. Canonicalize them to the
11794 bitwise variant. */
11795 switch (TREE_CODE (*expr_p))
11797 case TRUTH_AND_EXPR:
11798 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
11799 break;
11800 case TRUTH_OR_EXPR:
11801 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
11802 break;
11803 case TRUTH_XOR_EXPR:
11804 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
11805 break;
11806 default:
11807 break;
11809 /* Now make sure that operands have compatible type to
11810 expression's new_type. */
11811 xop0 = TREE_OPERAND (*expr_p, 0);
11812 xop1 = TREE_OPERAND (*expr_p, 1);
11813 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
11814 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
11815 new_type,
11816 xop0);
11817 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
11818 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
11819 new_type,
11820 xop1);
11821 /* Continue classified as tcc_binary. */
11822 goto expr_2;
11825 case VEC_COND_EXPR:
11827 enum gimplify_status r0, r1, r2;
11829 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11830 post_p, is_gimple_condexpr, fb_rvalue);
11831 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11832 post_p, is_gimple_val, fb_rvalue);
11833 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
11834 post_p, is_gimple_val, fb_rvalue);
11836 ret = MIN (MIN (r0, r1), r2);
11837 recalculate_side_effects (*expr_p);
11839 break;
11841 case FMA_EXPR:
11842 case VEC_PERM_EXPR:
11843 /* Classified as tcc_expression. */
11844 goto expr_3;
11846 case BIT_INSERT_EXPR:
11847 /* Argument 3 is a constant. */
11848 goto expr_2;
11850 case POINTER_PLUS_EXPR:
11852 enum gimplify_status r0, r1;
11853 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11854 post_p, is_gimple_val, fb_rvalue);
11855 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11856 post_p, is_gimple_val, fb_rvalue);
11857 recalculate_side_effects (*expr_p);
11858 ret = MIN (r0, r1);
11859 break;
11862 case CILK_SYNC_STMT:
11864 if (!fn_contains_cilk_spawn_p (cfun))
11866 error_at (EXPR_LOCATION (*expr_p),
11867 "expected %<_Cilk_spawn%> before %<_Cilk_sync%>");
11868 ret = GS_ERROR;
11870 else
11872 gimplify_cilk_sync (expr_p, pre_p);
11873 ret = GS_ALL_DONE;
11875 break;
11878 default:
11879 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
11881 case tcc_comparison:
11882 /* Handle comparison of objects of non scalar mode aggregates
11883 with a call to memcmp. It would be nice to only have to do
11884 this for variable-sized objects, but then we'd have to allow
11885 the same nest of reference nodes we allow for MODIFY_EXPR and
11886 that's too complex.
11888 Compare scalar mode aggregates as scalar mode values. Using
11889 memcmp for them would be very inefficient at best, and is
11890 plain wrong if bitfields are involved. */
11892 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
11894 /* Vector comparisons need no boolification. */
11895 if (TREE_CODE (type) == VECTOR_TYPE)
11896 goto expr_2;
11897 else if (!AGGREGATE_TYPE_P (type))
11899 tree org_type = TREE_TYPE (*expr_p);
11900 *expr_p = gimple_boolify (*expr_p);
11901 if (!useless_type_conversion_p (org_type,
11902 TREE_TYPE (*expr_p)))
11904 *expr_p = fold_convert_loc (input_location,
11905 org_type, *expr_p);
11906 ret = GS_OK;
11908 else
11909 goto expr_2;
11911 else if (TYPE_MODE (type) != BLKmode)
11912 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
11913 else
11914 ret = gimplify_variable_sized_compare (expr_p);
11916 break;
11919 /* If *EXPR_P does not need to be special-cased, handle it
11920 according to its class. */
11921 case tcc_unary:
11922 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11923 post_p, is_gimple_val, fb_rvalue);
11924 break;
11926 case tcc_binary:
11927 expr_2:
11929 enum gimplify_status r0, r1;
11931 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11932 post_p, is_gimple_val, fb_rvalue);
11933 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11934 post_p, is_gimple_val, fb_rvalue);
11936 ret = MIN (r0, r1);
11937 break;
11940 expr_3:
11942 enum gimplify_status r0, r1, r2;
11944 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11945 post_p, is_gimple_val, fb_rvalue);
11946 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11947 post_p, is_gimple_val, fb_rvalue);
11948 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
11949 post_p, is_gimple_val, fb_rvalue);
11951 ret = MIN (MIN (r0, r1), r2);
11952 break;
11955 case tcc_declaration:
11956 case tcc_constant:
11957 ret = GS_ALL_DONE;
11958 goto dont_recalculate;
11960 default:
11961 gcc_unreachable ();
11964 recalculate_side_effects (*expr_p);
11966 dont_recalculate:
11967 break;
11970 gcc_assert (*expr_p || ret != GS_OK);
11972 while (ret == GS_OK);
11974 /* If we encountered an error_mark somewhere nested inside, either
11975 stub out the statement or propagate the error back out. */
11976 if (ret == GS_ERROR)
11978 if (is_statement)
11979 *expr_p = NULL;
11980 goto out;
11983 /* This was only valid as a return value from the langhook, which
11984 we handled. Make sure it doesn't escape from any other context. */
11985 gcc_assert (ret != GS_UNHANDLED);
11987 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
11989 /* We aren't looking for a value, and we don't have a valid
11990 statement. If it doesn't have side-effects, throw it away. */
11991 if (!TREE_SIDE_EFFECTS (*expr_p))
11992 *expr_p = NULL;
11993 else if (!TREE_THIS_VOLATILE (*expr_p))
11995 /* This is probably a _REF that contains something nested that
11996 has side effects. Recurse through the operands to find it. */
11997 enum tree_code code = TREE_CODE (*expr_p);
11999 switch (code)
12001 case COMPONENT_REF:
12002 case REALPART_EXPR:
12003 case IMAGPART_EXPR:
12004 case VIEW_CONVERT_EXPR:
12005 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
12006 gimple_test_f, fallback);
12007 break;
12009 case ARRAY_REF:
12010 case ARRAY_RANGE_REF:
12011 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
12012 gimple_test_f, fallback);
12013 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
12014 gimple_test_f, fallback);
12015 break;
12017 default:
12018 /* Anything else with side-effects must be converted to
12019 a valid statement before we get here. */
12020 gcc_unreachable ();
12023 *expr_p = NULL;
12025 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
12026 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
12028 /* Historically, the compiler has treated a bare reference
12029 to a non-BLKmode volatile lvalue as forcing a load. */
12030 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
12032 /* Normally, we do not want to create a temporary for a
12033 TREE_ADDRESSABLE type because such a type should not be
12034 copied by bitwise-assignment. However, we make an
12035 exception here, as all we are doing here is ensuring that
12036 we read the bytes that make up the type. We use
12037 create_tmp_var_raw because create_tmp_var will abort when
12038 given a TREE_ADDRESSABLE type. */
12039 tree tmp = create_tmp_var_raw (type, "vol");
12040 gimple_add_tmp_var (tmp);
12041 gimplify_assign (tmp, *expr_p, pre_p);
12042 *expr_p = NULL;
12044 else
12045 /* We can't do anything useful with a volatile reference to
12046 an incomplete type, so just throw it away. Likewise for
12047 a BLKmode type, since any implicit inner load should
12048 already have been turned into an explicit one by the
12049 gimplification process. */
12050 *expr_p = NULL;
12053 /* If we are gimplifying at the statement level, we're done. Tack
12054 everything together and return. */
12055 if (fallback == fb_none || is_statement)
12057 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
12058 it out for GC to reclaim it. */
12059 *expr_p = NULL_TREE;
12061 if (!gimple_seq_empty_p (internal_pre)
12062 || !gimple_seq_empty_p (internal_post))
12064 gimplify_seq_add_seq (&internal_pre, internal_post);
12065 gimplify_seq_add_seq (pre_p, internal_pre);
12068 /* The result of gimplifying *EXPR_P is going to be the last few
12069 statements in *PRE_P and *POST_P. Add location information
12070 to all the statements that were added by the gimplification
12071 helpers. */
12072 if (!gimple_seq_empty_p (*pre_p))
12073 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
12075 if (!gimple_seq_empty_p (*post_p))
12076 annotate_all_with_location_after (*post_p, post_last_gsi,
12077 input_location);
12079 goto out;
12082 #ifdef ENABLE_GIMPLE_CHECKING
12083 if (*expr_p)
12085 enum tree_code code = TREE_CODE (*expr_p);
12086 /* These expressions should already be in gimple IR form. */
12087 gcc_assert (code != MODIFY_EXPR
12088 && code != ASM_EXPR
12089 && code != BIND_EXPR
12090 && code != CATCH_EXPR
12091 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
12092 && code != EH_FILTER_EXPR
12093 && code != GOTO_EXPR
12094 && code != LABEL_EXPR
12095 && code != LOOP_EXPR
12096 && code != SWITCH_EXPR
12097 && code != TRY_FINALLY_EXPR
12098 && code != OACC_PARALLEL
12099 && code != OACC_KERNELS
12100 && code != OACC_DATA
12101 && code != OACC_HOST_DATA
12102 && code != OACC_DECLARE
12103 && code != OACC_UPDATE
12104 && code != OACC_ENTER_DATA
12105 && code != OACC_EXIT_DATA
12106 && code != OACC_CACHE
12107 && code != OMP_CRITICAL
12108 && code != OMP_FOR
12109 && code != OACC_LOOP
12110 && code != OMP_MASTER
12111 && code != OMP_TASKGROUP
12112 && code != OMP_ORDERED
12113 && code != OMP_PARALLEL
12114 && code != OMP_SECTIONS
12115 && code != OMP_SECTION
12116 && code != OMP_SINGLE);
12118 #endif
12120 /* Otherwise we're gimplifying a subexpression, so the resulting
12121 value is interesting. If it's a valid operand that matches
12122 GIMPLE_TEST_F, we're done. Unless we are handling some
12123 post-effects internally; if that's the case, we need to copy into
12124 a temporary before adding the post-effects to POST_P. */
12125 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
12126 goto out;
12128 /* Otherwise, we need to create a new temporary for the gimplified
12129 expression. */
12131 /* We can't return an lvalue if we have an internal postqueue. The
12132 object the lvalue refers to would (probably) be modified by the
12133 postqueue; we need to copy the value out first, which means an
12134 rvalue. */
12135 if ((fallback & fb_lvalue)
12136 && gimple_seq_empty_p (internal_post)
12137 && is_gimple_addressable (*expr_p))
12139 /* An lvalue will do. Take the address of the expression, store it
12140 in a temporary, and replace the expression with an INDIRECT_REF of
12141 that temporary. */
12142 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
12143 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
12144 *expr_p = build_simple_mem_ref (tmp);
12146 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
12148 /* An rvalue will do. Assign the gimplified expression into a
12149 new temporary TMP and replace the original expression with
12150 TMP. First, make sure that the expression has a type so that
12151 it can be assigned into a temporary. */
12152 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
12153 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
12155 else
12157 #ifdef ENABLE_GIMPLE_CHECKING
12158 if (!(fallback & fb_mayfail))
12160 fprintf (stderr, "gimplification failed:\n");
12161 print_generic_expr (stderr, *expr_p, 0);
12162 debug_tree (*expr_p);
12163 internal_error ("gimplification failed");
12165 #endif
12166 gcc_assert (fallback & fb_mayfail);
12168 /* If this is an asm statement, and the user asked for the
12169 impossible, don't die. Fail and let gimplify_asm_expr
12170 issue an error. */
12171 ret = GS_ERROR;
12172 goto out;
12175 /* Make sure the temporary matches our predicate. */
12176 gcc_assert ((*gimple_test_f) (*expr_p));
12178 if (!gimple_seq_empty_p (internal_post))
12180 annotate_all_with_location (internal_post, input_location);
12181 gimplify_seq_add_seq (pre_p, internal_post);
12184 out:
12185 input_location = saved_location;
12186 return ret;
12189 /* Like gimplify_expr but make sure the gimplified result is not itself
12190 a SSA name (but a decl if it were). Temporaries required by
12191 evaluating *EXPR_P may be still SSA names. */
12193 static enum gimplify_status
12194 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
12195 bool (*gimple_test_f) (tree), fallback_t fallback,
12196 bool allow_ssa)
12198 bool was_ssa_name_p = TREE_CODE (*expr_p) == SSA_NAME;
12199 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
12200 gimple_test_f, fallback);
12201 if (! allow_ssa
12202 && TREE_CODE (*expr_p) == SSA_NAME)
12204 tree name = *expr_p;
12205 if (was_ssa_name_p)
12206 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
12207 else
12209 /* Avoid the extra copy if possible. */
12210 *expr_p = create_tmp_reg (TREE_TYPE (name));
12211 gimple_set_lhs (SSA_NAME_DEF_STMT (name), *expr_p);
12212 release_ssa_name (name);
12215 return ret;
12218 /* Look through TYPE for variable-sized objects and gimplify each such
12219 size that we find. Add to LIST_P any statements generated. */
12221 void
12222 gimplify_type_sizes (tree type, gimple_seq *list_p)
12224 tree field, t;
12226 if (type == NULL || type == error_mark_node)
12227 return;
12229 /* We first do the main variant, then copy into any other variants. */
12230 type = TYPE_MAIN_VARIANT (type);
12232 /* Avoid infinite recursion. */
12233 if (TYPE_SIZES_GIMPLIFIED (type))
12234 return;
12236 TYPE_SIZES_GIMPLIFIED (type) = 1;
12238 switch (TREE_CODE (type))
12240 case INTEGER_TYPE:
12241 case ENUMERAL_TYPE:
12242 case BOOLEAN_TYPE:
12243 case REAL_TYPE:
12244 case FIXED_POINT_TYPE:
12245 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
12246 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
12248 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
12250 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
12251 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
12253 break;
12255 case ARRAY_TYPE:
12256 /* These types may not have declarations, so handle them here. */
12257 gimplify_type_sizes (TREE_TYPE (type), list_p);
12258 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
12259 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
12260 with assigned stack slots, for -O1+ -g they should be tracked
12261 by VTA. */
12262 if (!(TYPE_NAME (type)
12263 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
12264 && DECL_IGNORED_P (TYPE_NAME (type)))
12265 && TYPE_DOMAIN (type)
12266 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
12268 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
12269 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
12270 DECL_IGNORED_P (t) = 0;
12271 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
12272 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
12273 DECL_IGNORED_P (t) = 0;
12275 break;
12277 case RECORD_TYPE:
12278 case UNION_TYPE:
12279 case QUAL_UNION_TYPE:
12280 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
12281 if (TREE_CODE (field) == FIELD_DECL)
12283 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
12284 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
12285 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
12286 gimplify_type_sizes (TREE_TYPE (field), list_p);
12288 break;
12290 case POINTER_TYPE:
12291 case REFERENCE_TYPE:
12292 /* We used to recurse on the pointed-to type here, which turned out to
12293 be incorrect because its definition might refer to variables not
12294 yet initialized at this point if a forward declaration is involved.
12296 It was actually useful for anonymous pointed-to types to ensure
12297 that the sizes evaluation dominates every possible later use of the
12298 values. Restricting to such types here would be safe since there
12299 is no possible forward declaration around, but would introduce an
12300 undesirable middle-end semantic to anonymity. We then defer to
12301 front-ends the responsibility of ensuring that the sizes are
12302 evaluated both early and late enough, e.g. by attaching artificial
12303 type declarations to the tree. */
12304 break;
12306 default:
12307 break;
12310 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
12311 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
12313 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
12315 TYPE_SIZE (t) = TYPE_SIZE (type);
12316 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
12317 TYPE_SIZES_GIMPLIFIED (t) = 1;
12321 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
12322 a size or position, has had all of its SAVE_EXPRs evaluated.
12323 We add any required statements to *STMT_P. */
12325 void
12326 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
12328 tree expr = *expr_p;
12330 /* We don't do anything if the value isn't there, is constant, or contains
12331 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
12332 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
12333 will want to replace it with a new variable, but that will cause problems
12334 if this type is from outside the function. It's OK to have that here. */
12335 if (is_gimple_sizepos (expr))
12336 return;
12338 *expr_p = unshare_expr (expr);
12340 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
12341 if the def vanishes. */
12342 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
12345 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
12346 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
12347 is true, also gimplify the parameters. */
12349 gbind *
12350 gimplify_body (tree fndecl, bool do_parms)
12352 location_t saved_location = input_location;
12353 gimple_seq parm_stmts, seq;
12354 gimple *outer_stmt;
12355 gbind *outer_bind;
12356 struct cgraph_node *cgn;
12358 timevar_push (TV_TREE_GIMPLIFY);
12360 init_tree_ssa (cfun);
12362 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
12363 gimplification. */
12364 default_rtl_profile ();
12366 gcc_assert (gimplify_ctxp == NULL);
12367 push_gimplify_context (true);
12369 if (flag_openacc || flag_openmp)
12371 gcc_assert (gimplify_omp_ctxp == NULL);
12372 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
12373 gimplify_omp_ctxp = new_omp_context (ORT_TARGET);
12376 /* Unshare most shared trees in the body and in that of any nested functions.
12377 It would seem we don't have to do this for nested functions because
12378 they are supposed to be output and then the outer function gimplified
12379 first, but the g++ front end doesn't always do it that way. */
12380 unshare_body (fndecl);
12381 unvisit_body (fndecl);
12383 cgn = cgraph_node::get (fndecl);
12384 if (cgn && cgn->origin)
12385 nonlocal_vlas = new hash_set<tree>;
12387 /* Make sure input_location isn't set to something weird. */
12388 input_location = DECL_SOURCE_LOCATION (fndecl);
12390 /* Resolve callee-copies. This has to be done before processing
12391 the body so that DECL_VALUE_EXPR gets processed correctly. */
12392 parm_stmts = do_parms ? gimplify_parameters () : NULL;
12394 /* Gimplify the function's body. */
12395 seq = NULL;
12396 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
12397 outer_stmt = gimple_seq_first_stmt (seq);
12398 if (!outer_stmt)
12400 outer_stmt = gimple_build_nop ();
12401 gimplify_seq_add_stmt (&seq, outer_stmt);
12404 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
12405 not the case, wrap everything in a GIMPLE_BIND to make it so. */
12406 if (gimple_code (outer_stmt) == GIMPLE_BIND
12407 && gimple_seq_first (seq) == gimple_seq_last (seq))
12408 outer_bind = as_a <gbind *> (outer_stmt);
12409 else
12410 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
12412 DECL_SAVED_TREE (fndecl) = NULL_TREE;
12414 /* If we had callee-copies statements, insert them at the beginning
12415 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
12416 if (!gimple_seq_empty_p (parm_stmts))
12418 tree parm;
12420 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
12421 gimple_bind_set_body (outer_bind, parm_stmts);
12423 for (parm = DECL_ARGUMENTS (current_function_decl);
12424 parm; parm = DECL_CHAIN (parm))
12425 if (DECL_HAS_VALUE_EXPR_P (parm))
12427 DECL_HAS_VALUE_EXPR_P (parm) = 0;
12428 DECL_IGNORED_P (parm) = 0;
12432 if (nonlocal_vlas)
12434 if (nonlocal_vla_vars)
12436 /* tree-nested.c may later on call declare_vars (..., true);
12437 which relies on BLOCK_VARS chain to be the tail of the
12438 gimple_bind_vars chain. Ensure we don't violate that
12439 assumption. */
12440 if (gimple_bind_block (outer_bind)
12441 == DECL_INITIAL (current_function_decl))
12442 declare_vars (nonlocal_vla_vars, outer_bind, true);
12443 else
12444 BLOCK_VARS (DECL_INITIAL (current_function_decl))
12445 = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl)),
12446 nonlocal_vla_vars);
12447 nonlocal_vla_vars = NULL_TREE;
12449 delete nonlocal_vlas;
12450 nonlocal_vlas = NULL;
12453 if ((flag_openacc || flag_openmp || flag_openmp_simd)
12454 && gimplify_omp_ctxp)
12456 delete_omp_context (gimplify_omp_ctxp);
12457 gimplify_omp_ctxp = NULL;
12460 pop_gimplify_context (outer_bind);
12461 gcc_assert (gimplify_ctxp == NULL);
12463 if (flag_checking && !seen_error ())
12464 verify_gimple_in_seq (gimple_bind_body (outer_bind));
12466 timevar_pop (TV_TREE_GIMPLIFY);
12467 input_location = saved_location;
12469 return outer_bind;
12472 typedef char *char_p; /* For DEF_VEC_P. */
12474 /* Return whether we should exclude FNDECL from instrumentation. */
12476 static bool
12477 flag_instrument_functions_exclude_p (tree fndecl)
12479 vec<char_p> *v;
12481 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
12482 if (v && v->length () > 0)
12484 const char *name;
12485 int i;
12486 char *s;
12488 name = lang_hooks.decl_printable_name (fndecl, 0);
12489 FOR_EACH_VEC_ELT (*v, i, s)
12490 if (strstr (name, s) != NULL)
12491 return true;
12494 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
12495 if (v && v->length () > 0)
12497 const char *name;
12498 int i;
12499 char *s;
12501 name = DECL_SOURCE_FILE (fndecl);
12502 FOR_EACH_VEC_ELT (*v, i, s)
12503 if (strstr (name, s) != NULL)
12504 return true;
12507 return false;
12510 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
12511 node for the function we want to gimplify.
12513 Return the sequence of GIMPLE statements corresponding to the body
12514 of FNDECL. */
12516 void
12517 gimplify_function_tree (tree fndecl)
12519 tree parm, ret;
12520 gimple_seq seq;
12521 gbind *bind;
12523 gcc_assert (!gimple_body (fndecl));
12525 if (DECL_STRUCT_FUNCTION (fndecl))
12526 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
12527 else
12528 push_struct_function (fndecl);
12530 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
12531 if necessary. */
12532 cfun->curr_properties |= PROP_gimple_lva;
12534 for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = DECL_CHAIN (parm))
12536 /* Preliminarily mark non-addressed complex variables as eligible
12537 for promotion to gimple registers. We'll transform their uses
12538 as we find them. */
12539 if ((TREE_CODE (TREE_TYPE (parm)) == COMPLEX_TYPE
12540 || TREE_CODE (TREE_TYPE (parm)) == VECTOR_TYPE)
12541 && !TREE_THIS_VOLATILE (parm)
12542 && !needs_to_live_in_memory (parm))
12543 DECL_GIMPLE_REG_P (parm) = 1;
12546 ret = DECL_RESULT (fndecl);
12547 if ((TREE_CODE (TREE_TYPE (ret)) == COMPLEX_TYPE
12548 || TREE_CODE (TREE_TYPE (ret)) == VECTOR_TYPE)
12549 && !needs_to_live_in_memory (ret))
12550 DECL_GIMPLE_REG_P (ret) = 1;
12552 if (asan_sanitize_use_after_scope () && !asan_no_sanitize_address_p ())
12553 asan_poisoned_variables = new hash_set<tree> ();
12554 bind = gimplify_body (fndecl, true);
12555 if (asan_poisoned_variables)
12557 delete asan_poisoned_variables;
12558 asan_poisoned_variables = NULL;
12561 /* The tree body of the function is no longer needed, replace it
12562 with the new GIMPLE body. */
12563 seq = NULL;
12564 gimple_seq_add_stmt (&seq, bind);
12565 gimple_set_body (fndecl, seq);
12567 /* If we're instrumenting function entry/exit, then prepend the call to
12568 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
12569 catch the exit hook. */
12570 /* ??? Add some way to ignore exceptions for this TFE. */
12571 if (flag_instrument_function_entry_exit
12572 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
12573 /* Do not instrument extern inline functions. */
12574 && !(DECL_DECLARED_INLINE_P (fndecl)
12575 && DECL_EXTERNAL (fndecl)
12576 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
12577 && !flag_instrument_functions_exclude_p (fndecl))
12579 tree x;
12580 gbind *new_bind;
12581 gimple *tf;
12582 gimple_seq cleanup = NULL, body = NULL;
12583 tree tmp_var;
12584 gcall *call;
12586 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
12587 call = gimple_build_call (x, 1, integer_zero_node);
12588 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
12589 gimple_call_set_lhs (call, tmp_var);
12590 gimplify_seq_add_stmt (&cleanup, call);
12591 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
12592 call = gimple_build_call (x, 2,
12593 build_fold_addr_expr (current_function_decl),
12594 tmp_var);
12595 gimplify_seq_add_stmt (&cleanup, call);
12596 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
12598 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
12599 call = gimple_build_call (x, 1, integer_zero_node);
12600 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
12601 gimple_call_set_lhs (call, tmp_var);
12602 gimplify_seq_add_stmt (&body, call);
12603 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
12604 call = gimple_build_call (x, 2,
12605 build_fold_addr_expr (current_function_decl),
12606 tmp_var);
12607 gimplify_seq_add_stmt (&body, call);
12608 gimplify_seq_add_stmt (&body, tf);
12609 new_bind = gimple_build_bind (NULL, body, NULL);
12611 /* Replace the current function body with the body
12612 wrapped in the try/finally TF. */
12613 seq = NULL;
12614 gimple_seq_add_stmt (&seq, new_bind);
12615 gimple_set_body (fndecl, seq);
12616 bind = new_bind;
12619 if ((flag_sanitize & SANITIZE_THREAD) != 0
12620 && !lookup_attribute ("no_sanitize_thread", DECL_ATTRIBUTES (fndecl)))
12622 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
12623 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
12624 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
12625 /* Replace the current function body with the body
12626 wrapped in the try/finally TF. */
12627 seq = NULL;
12628 gimple_seq_add_stmt (&seq, new_bind);
12629 gimple_set_body (fndecl, seq);
12632 DECL_SAVED_TREE (fndecl) = NULL_TREE;
12633 cfun->curr_properties |= PROP_gimple_any;
12635 pop_cfun ();
12637 dump_function (TDI_generic, fndecl);
12640 /* Return a dummy expression of type TYPE in order to keep going after an
12641 error. */
12643 static tree
12644 dummy_object (tree type)
12646 tree t = build_int_cst (build_pointer_type (type), 0);
12647 return build2 (MEM_REF, type, t, t);
12650 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
12651 builtin function, but a very special sort of operator. */
12653 enum gimplify_status
12654 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
12655 gimple_seq *post_p ATTRIBUTE_UNUSED)
12657 tree promoted_type, have_va_type;
12658 tree valist = TREE_OPERAND (*expr_p, 0);
12659 tree type = TREE_TYPE (*expr_p);
12660 tree t, tag, aptag;
12661 location_t loc = EXPR_LOCATION (*expr_p);
12663 /* Verify that valist is of the proper type. */
12664 have_va_type = TREE_TYPE (valist);
12665 if (have_va_type == error_mark_node)
12666 return GS_ERROR;
12667 have_va_type = targetm.canonical_va_list_type (have_va_type);
12668 if (have_va_type == NULL_TREE
12669 && POINTER_TYPE_P (TREE_TYPE (valist)))
12670 /* Handle 'Case 1: Not an array type' from c-common.c/build_va_arg. */
12671 have_va_type
12672 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
12673 gcc_assert (have_va_type != NULL_TREE);
12675 /* Generate a diagnostic for requesting data of a type that cannot
12676 be passed through `...' due to type promotion at the call site. */
12677 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
12678 != type)
12680 static bool gave_help;
12681 bool warned;
12682 /* Use the expansion point to handle cases such as passing bool (defined
12683 in a system header) through `...'. */
12684 source_location xloc
12685 = expansion_point_location_if_in_system_header (loc);
12687 /* Unfortunately, this is merely undefined, rather than a constraint
12688 violation, so we cannot make this an error. If this call is never
12689 executed, the program is still strictly conforming. */
12690 warned = warning_at (xloc, 0,
12691 "%qT is promoted to %qT when passed through %<...%>",
12692 type, promoted_type);
12693 if (!gave_help && warned)
12695 gave_help = true;
12696 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
12697 promoted_type, type);
12700 /* We can, however, treat "undefined" any way we please.
12701 Call abort to encourage the user to fix the program. */
12702 if (warned)
12703 inform (xloc, "if this code is reached, the program will abort");
12704 /* Before the abort, allow the evaluation of the va_list
12705 expression to exit or longjmp. */
12706 gimplify_and_add (valist, pre_p);
12707 t = build_call_expr_loc (loc,
12708 builtin_decl_implicit (BUILT_IN_TRAP), 0);
12709 gimplify_and_add (t, pre_p);
12711 /* This is dead code, but go ahead and finish so that the
12712 mode of the result comes out right. */
12713 *expr_p = dummy_object (type);
12714 return GS_ALL_DONE;
12717 tag = build_int_cst (build_pointer_type (type), 0);
12718 aptag = build_int_cst (TREE_TYPE (valist), 0);
12720 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
12721 valist, tag, aptag);
12723 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
12724 needs to be expanded. */
12725 cfun->curr_properties &= ~PROP_gimple_lva;
12727 return GS_OK;
12730 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
12732 DST/SRC are the destination and source respectively. You can pass
12733 ungimplified trees in DST or SRC, in which case they will be
12734 converted to a gimple operand if necessary.
12736 This function returns the newly created GIMPLE_ASSIGN tuple. */
12738 gimple *
12739 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
12741 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
12742 gimplify_and_add (t, seq_p);
12743 ggc_free (t);
12744 return gimple_seq_last_stmt (*seq_p);
12747 inline hashval_t
12748 gimplify_hasher::hash (const elt_t *p)
12750 tree t = p->val;
12751 return iterative_hash_expr (t, 0);
12754 inline bool
12755 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
12757 tree t1 = p1->val;
12758 tree t2 = p2->val;
12759 enum tree_code code = TREE_CODE (t1);
12761 if (TREE_CODE (t2) != code
12762 || TREE_TYPE (t1) != TREE_TYPE (t2))
12763 return false;
12765 if (!operand_equal_p (t1, t2, 0))
12766 return false;
12768 /* Only allow them to compare equal if they also hash equal; otherwise
12769 results are nondeterminate, and we fail bootstrap comparison. */
12770 gcc_checking_assert (hash (p1) == hash (p2));
12772 return true;