PR tree-optimization/78608 - gimple-ssa-sprintf.c:570:17: runtime error: negation...
[official-gcc.git] / gcc / gimplify.c
blob2777a23eb937f896d7dc87fba364fadb96fca6df
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 for (unsigned i = 0; i < sorted_variables.length (); i++)
1210 asan_poison_variable (sorted_variables[i], poison, seq_p);
1213 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1215 static enum gimplify_status
1216 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1218 tree bind_expr = *expr_p;
1219 bool old_keep_stack = gimplify_ctxp->keep_stack;
1220 bool old_save_stack = gimplify_ctxp->save_stack;
1221 tree t;
1222 gbind *bind_stmt;
1223 gimple_seq body, cleanup;
1224 gcall *stack_save;
1225 location_t start_locus = 0, end_locus = 0;
1226 tree ret_clauses = NULL;
1228 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1230 /* Mark variables seen in this bind expr. */
1231 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1233 if (VAR_P (t))
1235 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1237 /* Mark variable as local. */
1238 if (ctx && ctx->region_type != ORT_NONE && !DECL_EXTERNAL (t)
1239 && (! DECL_SEEN_IN_BIND_EXPR_P (t)
1240 || splay_tree_lookup (ctx->variables,
1241 (splay_tree_key) t) == NULL))
1243 if (ctx->region_type == ORT_SIMD
1244 && TREE_ADDRESSABLE (t)
1245 && !TREE_STATIC (t))
1246 omp_add_variable (ctx, t, GOVD_PRIVATE | GOVD_SEEN);
1247 else
1248 omp_add_variable (ctx, t, GOVD_LOCAL | GOVD_SEEN);
1251 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1253 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1254 cfun->has_local_explicit_reg_vars = true;
1257 /* Preliminarily mark non-addressed complex variables as eligible
1258 for promotion to gimple registers. We'll transform their uses
1259 as we find them. */
1260 if ((TREE_CODE (TREE_TYPE (t)) == COMPLEX_TYPE
1261 || TREE_CODE (TREE_TYPE (t)) == VECTOR_TYPE)
1262 && !TREE_THIS_VOLATILE (t)
1263 && (VAR_P (t) && !DECL_HARD_REGISTER (t))
1264 && !needs_to_live_in_memory (t))
1265 DECL_GIMPLE_REG_P (t) = 1;
1268 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1269 BIND_EXPR_BLOCK (bind_expr));
1270 gimple_push_bind_expr (bind_stmt);
1272 gimplify_ctxp->keep_stack = false;
1273 gimplify_ctxp->save_stack = false;
1275 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1276 body = NULL;
1277 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1278 gimple_bind_set_body (bind_stmt, body);
1280 /* Source location wise, the cleanup code (stack_restore and clobbers)
1281 belongs to the end of the block, so propagate what we have. The
1282 stack_save operation belongs to the beginning of block, which we can
1283 infer from the bind_expr directly if the block has no explicit
1284 assignment. */
1285 if (BIND_EXPR_BLOCK (bind_expr))
1287 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1288 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1290 if (start_locus == 0)
1291 start_locus = EXPR_LOCATION (bind_expr);
1293 cleanup = NULL;
1294 stack_save = NULL;
1296 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1297 the stack space allocated to the VLAs. */
1298 if (gimplify_ctxp->save_stack && !gimplify_ctxp->keep_stack)
1300 gcall *stack_restore;
1302 /* Save stack on entry and restore it on exit. Add a try_finally
1303 block to achieve this. */
1304 build_stack_save_restore (&stack_save, &stack_restore);
1306 gimple_set_location (stack_save, start_locus);
1307 gimple_set_location (stack_restore, end_locus);
1309 gimplify_seq_add_stmt (&cleanup, stack_restore);
1312 /* Add clobbers for all variables that go out of scope. */
1313 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1315 if (VAR_P (t)
1316 && !is_global_var (t)
1317 && DECL_CONTEXT (t) == current_function_decl)
1319 if (!DECL_HARD_REGISTER (t)
1320 && !TREE_THIS_VOLATILE (t)
1321 && !DECL_HAS_VALUE_EXPR_P (t)
1322 /* Only care for variables that have to be in memory. Others
1323 will be rewritten into SSA names, hence moved to the
1324 top-level. */
1325 && !is_gimple_reg (t)
1326 && flag_stack_reuse != SR_NONE)
1328 tree clobber = build_constructor (TREE_TYPE (t), NULL);
1329 gimple *clobber_stmt;
1330 TREE_THIS_VOLATILE (clobber) = 1;
1331 clobber_stmt = gimple_build_assign (t, clobber);
1332 gimple_set_location (clobber_stmt, end_locus);
1333 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1336 if (flag_openacc && oacc_declare_returns != NULL)
1338 tree *c = oacc_declare_returns->get (t);
1339 if (c != NULL)
1341 if (ret_clauses)
1342 OMP_CLAUSE_CHAIN (*c) = ret_clauses;
1344 ret_clauses = *c;
1346 oacc_declare_returns->remove (t);
1348 if (oacc_declare_returns->elements () == 0)
1350 delete oacc_declare_returns;
1351 oacc_declare_returns = NULL;
1357 if (asan_poisoned_variables != NULL
1358 && asan_poisoned_variables->contains (t))
1360 asan_poisoned_variables->remove (t);
1361 asan_poison_variable (t, true, &cleanup);
1364 if (gimplify_ctxp->live_switch_vars != NULL
1365 && gimplify_ctxp->live_switch_vars->contains (t))
1366 gimplify_ctxp->live_switch_vars->remove (t);
1369 if (ret_clauses)
1371 gomp_target *stmt;
1372 gimple_stmt_iterator si = gsi_start (cleanup);
1374 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
1375 ret_clauses);
1376 gsi_insert_seq_before_without_update (&si, stmt, GSI_NEW_STMT);
1379 if (cleanup)
1381 gtry *gs;
1382 gimple_seq new_body;
1384 new_body = NULL;
1385 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1386 GIMPLE_TRY_FINALLY);
1388 if (stack_save)
1389 gimplify_seq_add_stmt (&new_body, stack_save);
1390 gimplify_seq_add_stmt (&new_body, gs);
1391 gimple_bind_set_body (bind_stmt, new_body);
1394 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1395 if (!gimplify_ctxp->keep_stack)
1396 gimplify_ctxp->keep_stack = old_keep_stack;
1397 gimplify_ctxp->save_stack = old_save_stack;
1399 gimple_pop_bind_expr ();
1401 gimplify_seq_add_stmt (pre_p, bind_stmt);
1403 if (temp)
1405 *expr_p = temp;
1406 return GS_OK;
1409 *expr_p = NULL_TREE;
1410 return GS_ALL_DONE;
1413 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1414 GIMPLE value, it is assigned to a new temporary and the statement is
1415 re-written to return the temporary.
1417 PRE_P points to the sequence where side effects that must happen before
1418 STMT should be stored. */
1420 static enum gimplify_status
1421 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1423 greturn *ret;
1424 tree ret_expr = TREE_OPERAND (stmt, 0);
1425 tree result_decl, result;
1427 if (ret_expr == error_mark_node)
1428 return GS_ERROR;
1430 /* Implicit _Cilk_sync must be inserted right before any return statement
1431 if there is a _Cilk_spawn in the function. If the user has provided a
1432 _Cilk_sync, the optimizer should remove this duplicate one. */
1433 if (fn_contains_cilk_spawn_p (cfun))
1435 tree impl_sync = build0 (CILK_SYNC_STMT, void_type_node);
1436 gimplify_and_add (impl_sync, pre_p);
1439 if (!ret_expr
1440 || TREE_CODE (ret_expr) == RESULT_DECL
1441 || ret_expr == error_mark_node)
1443 greturn *ret = gimple_build_return (ret_expr);
1444 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1445 gimplify_seq_add_stmt (pre_p, ret);
1446 return GS_ALL_DONE;
1449 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1450 result_decl = NULL_TREE;
1451 else
1453 result_decl = TREE_OPERAND (ret_expr, 0);
1455 /* See through a return by reference. */
1456 if (TREE_CODE (result_decl) == INDIRECT_REF)
1457 result_decl = TREE_OPERAND (result_decl, 0);
1459 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1460 || TREE_CODE (ret_expr) == INIT_EXPR)
1461 && TREE_CODE (result_decl) == RESULT_DECL);
1464 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1465 Recall that aggregate_value_p is FALSE for any aggregate type that is
1466 returned in registers. If we're returning values in registers, then
1467 we don't want to extend the lifetime of the RESULT_DECL, particularly
1468 across another call. In addition, for those aggregates for which
1469 hard_function_value generates a PARALLEL, we'll die during normal
1470 expansion of structure assignments; there's special code in expand_return
1471 to handle this case that does not exist in expand_expr. */
1472 if (!result_decl)
1473 result = NULL_TREE;
1474 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1476 if (TREE_CODE (DECL_SIZE (result_decl)) != INTEGER_CST)
1478 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1479 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1480 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1481 should be effectively allocated by the caller, i.e. all calls to
1482 this function must be subject to the Return Slot Optimization. */
1483 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1484 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1486 result = result_decl;
1488 else if (gimplify_ctxp->return_temp)
1489 result = gimplify_ctxp->return_temp;
1490 else
1492 result = create_tmp_reg (TREE_TYPE (result_decl));
1494 /* ??? With complex control flow (usually involving abnormal edges),
1495 we can wind up warning about an uninitialized value for this. Due
1496 to how this variable is constructed and initialized, this is never
1497 true. Give up and never warn. */
1498 TREE_NO_WARNING (result) = 1;
1500 gimplify_ctxp->return_temp = result;
1503 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1504 Then gimplify the whole thing. */
1505 if (result != result_decl)
1506 TREE_OPERAND (ret_expr, 0) = result;
1508 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1510 ret = gimple_build_return (result);
1511 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1512 gimplify_seq_add_stmt (pre_p, ret);
1514 return GS_ALL_DONE;
1517 /* Gimplify a variable-length array DECL. */
1519 static void
1520 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1522 /* This is a variable-sized decl. Simplify its size and mark it
1523 for deferred expansion. */
1524 tree t, addr, ptr_type;
1526 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1527 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1529 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1530 if (DECL_HAS_VALUE_EXPR_P (decl))
1531 return;
1533 /* All occurrences of this decl in final gimplified code will be
1534 replaced by indirection. Setting DECL_VALUE_EXPR does two
1535 things: First, it lets the rest of the gimplifier know what
1536 replacement to use. Second, it lets the debug info know
1537 where to find the value. */
1538 ptr_type = build_pointer_type (TREE_TYPE (decl));
1539 addr = create_tmp_var (ptr_type, get_name (decl));
1540 DECL_IGNORED_P (addr) = 0;
1541 t = build_fold_indirect_ref (addr);
1542 TREE_THIS_NOTRAP (t) = 1;
1543 SET_DECL_VALUE_EXPR (decl, t);
1544 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1546 t = builtin_decl_explicit (BUILT_IN_ALLOCA_WITH_ALIGN);
1547 t = build_call_expr (t, 2, DECL_SIZE_UNIT (decl),
1548 size_int (DECL_ALIGN (decl)));
1549 /* The call has been built for a variable-sized object. */
1550 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1551 t = fold_convert (ptr_type, t);
1552 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1554 gimplify_and_add (t, seq_p);
1557 /* A helper function to be called via walk_tree. Mark all labels under *TP
1558 as being forced. To be called for DECL_INITIAL of static variables. */
1560 static tree
1561 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1563 if (TYPE_P (*tp))
1564 *walk_subtrees = 0;
1565 if (TREE_CODE (*tp) == LABEL_DECL)
1567 FORCED_LABEL (*tp) = 1;
1568 cfun->has_forced_label_in_static = 1;
1571 return NULL_TREE;
1574 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1575 and initialization explicit. */
1577 static enum gimplify_status
1578 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1580 tree stmt = *stmt_p;
1581 tree decl = DECL_EXPR_DECL (stmt);
1583 *stmt_p = NULL_TREE;
1585 if (TREE_TYPE (decl) == error_mark_node)
1586 return GS_ERROR;
1588 if ((TREE_CODE (decl) == TYPE_DECL
1589 || VAR_P (decl))
1590 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1592 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1593 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
1594 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
1597 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1598 in case its size expressions contain problematic nodes like CALL_EXPR. */
1599 if (TREE_CODE (decl) == TYPE_DECL
1600 && DECL_ORIGINAL_TYPE (decl)
1601 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1603 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1604 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
1605 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
1608 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
1610 tree init = DECL_INITIAL (decl);
1611 bool is_vla = false;
1613 if (TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
1614 || (!TREE_STATIC (decl)
1615 && flag_stack_check == GENERIC_STACK_CHECK
1616 && compare_tree_int (DECL_SIZE_UNIT (decl),
1617 STACK_CHECK_MAX_VAR_SIZE) > 0))
1619 gimplify_vla_decl (decl, seq_p);
1620 is_vla = true;
1623 if (asan_poisoned_variables
1624 && !is_vla
1625 && TREE_ADDRESSABLE (decl)
1626 && !TREE_STATIC (decl)
1627 && !DECL_HAS_VALUE_EXPR_P (decl)
1628 && dbg_cnt (asan_use_after_scope))
1630 asan_poisoned_variables->add (decl);
1631 asan_poison_variable (decl, false, seq_p);
1632 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
1633 gimplify_ctxp->live_switch_vars->add (decl);
1636 /* Some front ends do not explicitly declare all anonymous
1637 artificial variables. We compensate here by declaring the
1638 variables, though it would be better if the front ends would
1639 explicitly declare them. */
1640 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1641 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1642 gimple_add_tmp_var (decl);
1644 if (init && init != error_mark_node)
1646 if (!TREE_STATIC (decl))
1648 DECL_INITIAL (decl) = NULL_TREE;
1649 init = build2 (INIT_EXPR, void_type_node, decl, init);
1650 gimplify_and_add (init, seq_p);
1651 ggc_free (init);
1653 else
1654 /* We must still examine initializers for static variables
1655 as they may contain a label address. */
1656 walk_tree (&init, force_labels_r, NULL, NULL);
1660 return GS_ALL_DONE;
1663 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1664 and replacing the LOOP_EXPR with goto, but if the loop contains an
1665 EXIT_EXPR, we need to append a label for it to jump to. */
1667 static enum gimplify_status
1668 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1670 tree saved_label = gimplify_ctxp->exit_label;
1671 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1673 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1675 gimplify_ctxp->exit_label = NULL_TREE;
1677 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1679 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
1681 if (gimplify_ctxp->exit_label)
1682 gimplify_seq_add_stmt (pre_p,
1683 gimple_build_label (gimplify_ctxp->exit_label));
1685 gimplify_ctxp->exit_label = saved_label;
1687 *expr_p = NULL;
1688 return GS_ALL_DONE;
1691 /* Gimplify a statement list onto a sequence. These may be created either
1692 by an enlightened front-end, or by shortcut_cond_expr. */
1694 static enum gimplify_status
1695 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
1697 tree temp = voidify_wrapper_expr (*expr_p, NULL);
1699 tree_stmt_iterator i = tsi_start (*expr_p);
1701 while (!tsi_end_p (i))
1703 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
1704 tsi_delink (&i);
1707 if (temp)
1709 *expr_p = temp;
1710 return GS_OK;
1713 return GS_ALL_DONE;
1716 /* Callback for walk_gimple_seq. */
1718 static tree
1719 warn_switch_unreachable_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
1720 struct walk_stmt_info *wi)
1722 gimple *stmt = gsi_stmt (*gsi_p);
1724 *handled_ops_p = true;
1725 switch (gimple_code (stmt))
1727 case GIMPLE_TRY:
1728 /* A compiler-generated cleanup or a user-written try block.
1729 If it's empty, don't dive into it--that would result in
1730 worse location info. */
1731 if (gimple_try_eval (stmt) == NULL)
1733 wi->info = stmt;
1734 return integer_zero_node;
1736 /* Fall through. */
1737 case GIMPLE_BIND:
1738 case GIMPLE_CATCH:
1739 case GIMPLE_EH_FILTER:
1740 case GIMPLE_TRANSACTION:
1741 /* Walk the sub-statements. */
1742 *handled_ops_p = false;
1743 break;
1744 case GIMPLE_CALL:
1745 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
1747 *handled_ops_p = false;
1748 break;
1750 /* Fall through. */
1751 default:
1752 /* Save the first "real" statement (not a decl/lexical scope/...). */
1753 wi->info = stmt;
1754 return integer_zero_node;
1756 return NULL_TREE;
1759 /* Possibly warn about unreachable statements between switch's controlling
1760 expression and the first case. SEQ is the body of a switch expression. */
1762 static void
1763 maybe_warn_switch_unreachable (gimple_seq seq)
1765 if (!warn_switch_unreachable
1766 /* This warning doesn't play well with Fortran when optimizations
1767 are on. */
1768 || lang_GNU_Fortran ()
1769 || seq == NULL)
1770 return;
1772 struct walk_stmt_info wi;
1773 memset (&wi, 0, sizeof (wi));
1774 walk_gimple_seq (seq, warn_switch_unreachable_r, NULL, &wi);
1775 gimple *stmt = (gimple *) wi.info;
1777 if (stmt && gimple_code (stmt) != GIMPLE_LABEL)
1779 if (gimple_code (stmt) == GIMPLE_GOTO
1780 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
1781 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
1782 /* Don't warn for compiler-generated gotos. These occur
1783 in Duff's devices, for example. */;
1784 else
1785 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
1786 "statement will never be executed");
1791 /* A label entry that pairs label and a location. */
1792 struct label_entry
1794 tree label;
1795 location_t loc;
1798 /* Find LABEL in vector of label entries VEC. */
1800 static struct label_entry *
1801 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
1803 unsigned int i;
1804 struct label_entry *l;
1806 FOR_EACH_VEC_ELT (*vec, i, l)
1807 if (l->label == label)
1808 return l;
1809 return NULL;
1812 /* Return true if LABEL, a LABEL_DECL, represents a case label
1813 in a vector of labels CASES. */
1815 static bool
1816 case_label_p (const vec<tree> *cases, tree label)
1818 unsigned int i;
1819 tree l;
1821 FOR_EACH_VEC_ELT (*cases, i, l)
1822 if (CASE_LABEL (l) == label)
1823 return true;
1824 return false;
1827 /* Find the last statement in a scope STMT. */
1829 static gimple *
1830 last_stmt_in_scope (gimple *stmt)
1832 if (!stmt)
1833 return NULL;
1835 switch (gimple_code (stmt))
1837 case GIMPLE_BIND:
1839 gbind *bind = as_a <gbind *> (stmt);
1840 stmt = gimple_seq_last_stmt (gimple_bind_body (bind));
1841 return last_stmt_in_scope (stmt);
1844 case GIMPLE_TRY:
1846 gtry *try_stmt = as_a <gtry *> (stmt);
1847 stmt = gimple_seq_last_stmt (gimple_try_eval (try_stmt));
1848 gimple *last_eval = last_stmt_in_scope (stmt);
1849 if (gimple_stmt_may_fallthru (last_eval)
1850 && (last_eval == NULL
1851 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
1852 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
1854 stmt = gimple_seq_last_stmt (gimple_try_cleanup (try_stmt));
1855 return last_stmt_in_scope (stmt);
1857 else
1858 return last_eval;
1861 default:
1862 return stmt;
1866 /* Collect interesting labels in LABELS and return the statement preceding
1867 another case label, or a user-defined label. */
1869 static gimple *
1870 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
1871 auto_vec <struct label_entry> *labels)
1873 gimple *prev = NULL;
1877 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
1878 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
1880 /* Nested scope. Only look at the last statement of
1881 the innermost scope. */
1882 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
1883 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
1884 if (last)
1886 prev = last;
1887 /* It might be a label without a location. Use the
1888 location of the scope then. */
1889 if (!gimple_has_location (prev))
1890 gimple_set_location (prev, bind_loc);
1892 gsi_next (gsi_p);
1893 continue;
1896 /* Ifs are tricky. */
1897 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
1899 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
1900 tree false_lab = gimple_cond_false_label (cond_stmt);
1901 location_t if_loc = gimple_location (cond_stmt);
1903 /* If we have e.g.
1904 if (i > 1) goto <D.2259>; else goto D;
1905 we can't do much with the else-branch. */
1906 if (!DECL_ARTIFICIAL (false_lab))
1907 break;
1909 /* Go on until the false label, then one step back. */
1910 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
1912 gimple *stmt = gsi_stmt (*gsi_p);
1913 if (gimple_code (stmt) == GIMPLE_LABEL
1914 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
1915 break;
1918 /* Not found? Oops. */
1919 if (gsi_end_p (*gsi_p))
1920 break;
1922 struct label_entry l = { false_lab, if_loc };
1923 labels->safe_push (l);
1925 /* Go to the last statement of the then branch. */
1926 gsi_prev (gsi_p);
1928 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
1929 <D.1759>:
1930 <stmt>;
1931 goto <D.1761>;
1932 <D.1760>:
1934 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
1935 && !gimple_has_location (gsi_stmt (*gsi_p)))
1937 /* Look at the statement before, it might be
1938 attribute fallthrough, in which case don't warn. */
1939 gsi_prev (gsi_p);
1940 bool fallthru_before_dest
1941 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
1942 gsi_next (gsi_p);
1943 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
1944 if (!fallthru_before_dest)
1946 struct label_entry l = { goto_dest, if_loc };
1947 labels->safe_push (l);
1950 /* And move back. */
1951 gsi_next (gsi_p);
1954 /* Remember the last statement. Skip labels that are of no interest
1955 to us. */
1956 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
1958 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
1959 if (find_label_entry (labels, label))
1960 prev = gsi_stmt (*gsi_p);
1962 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
1964 else
1965 prev = gsi_stmt (*gsi_p);
1966 gsi_next (gsi_p);
1968 while (!gsi_end_p (*gsi_p)
1969 /* Stop if we find a case or a user-defined label. */
1970 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
1971 || !gimple_has_location (gsi_stmt (*gsi_p))));
1973 return prev;
1976 /* Return true if the switch fallthough warning should occur. LABEL is
1977 the label statement that we're falling through to. */
1979 static bool
1980 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
1982 gimple_stmt_iterator gsi = *gsi_p;
1984 /* Don't warn if the label is marked with a "falls through" comment. */
1985 if (FALLTHROUGH_LABEL_P (label))
1986 return false;
1988 /* Don't warn for a non-case label followed by a statement:
1989 case 0:
1990 foo ();
1991 label:
1992 bar ();
1993 as these are likely intentional. */
1994 if (!case_label_p (&gimplify_ctxp->case_labels, label))
1996 gsi_next (&gsi);
1997 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
1998 return false;
2001 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2002 immediately breaks. */
2003 gsi = *gsi_p;
2005 /* Skip all immediately following labels. */
2006 while (!gsi_end_p (gsi) && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL)
2007 gsi_next (&gsi);
2009 /* { ... something; default:; } */
2010 if (gsi_end_p (gsi)
2011 /* { ... something; default: break; } or
2012 { ... something; default: goto L; } */
2013 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2014 /* { ... something; default: return; } */
2015 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2016 return false;
2018 return true;
2021 /* Callback for walk_gimple_seq. */
2023 static tree
2024 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2025 struct walk_stmt_info *)
2027 gimple *stmt = gsi_stmt (*gsi_p);
2029 *handled_ops_p = true;
2030 switch (gimple_code (stmt))
2032 case GIMPLE_TRY:
2033 case GIMPLE_BIND:
2034 case GIMPLE_CATCH:
2035 case GIMPLE_EH_FILTER:
2036 case GIMPLE_TRANSACTION:
2037 /* Walk the sub-statements. */
2038 *handled_ops_p = false;
2039 break;
2041 /* Find a sequence of form:
2043 GIMPLE_LABEL
2044 [...]
2045 <may fallthru stmt>
2046 GIMPLE_LABEL
2048 and possibly warn. */
2049 case GIMPLE_LABEL:
2051 /* Found a label. Skip all immediately following labels. */
2052 while (!gsi_end_p (*gsi_p)
2053 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2054 gsi_next (gsi_p);
2056 /* There might be no more statements. */
2057 if (gsi_end_p (*gsi_p))
2058 return integer_zero_node;
2060 /* Vector of labels that fall through. */
2061 auto_vec <struct label_entry> labels;
2062 gimple *prev = collect_fallthrough_labels (gsi_p, &labels);
2064 /* There might be no more statements. */
2065 if (gsi_end_p (*gsi_p))
2066 return integer_zero_node;
2068 gimple *next = gsi_stmt (*gsi_p);
2069 tree label;
2070 /* If what follows is a label, then we may have a fallthrough. */
2071 if (gimple_code (next) == GIMPLE_LABEL
2072 && gimple_has_location (next)
2073 && (label = gimple_label_label (as_a <glabel *> (next)))
2074 && prev != NULL)
2076 struct label_entry *l;
2077 bool warned_p = false;
2078 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2079 /* Quiet. */;
2080 else if (gimple_code (prev) == GIMPLE_LABEL
2081 && (label = gimple_label_label (as_a <glabel *> (prev)))
2082 && (l = find_label_entry (&labels, label)))
2083 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2084 "this statement may fall through");
2085 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2086 /* Try to be clever and don't warn when the statement
2087 can't actually fall through. */
2088 && gimple_stmt_may_fallthru (prev)
2089 && gimple_has_location (prev))
2090 warned_p = warning_at (gimple_location (prev),
2091 OPT_Wimplicit_fallthrough_,
2092 "this statement may fall through");
2093 if (warned_p)
2094 inform (gimple_location (next), "here");
2096 /* Mark this label as processed so as to prevent multiple
2097 warnings in nested switches. */
2098 FALLTHROUGH_LABEL_P (label) = true;
2100 /* So that next warn_implicit_fallthrough_r will start looking for
2101 a new sequence starting with this label. */
2102 gsi_prev (gsi_p);
2105 break;
2106 default:
2107 break;
2109 return NULL_TREE;
2112 /* Warn when a switch case falls through. */
2114 static void
2115 maybe_warn_implicit_fallthrough (gimple_seq seq)
2117 if (!warn_implicit_fallthrough)
2118 return;
2120 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2121 if (!(lang_GNU_C ()
2122 || lang_GNU_CXX ()
2123 || lang_GNU_OBJC ()))
2124 return;
2126 struct walk_stmt_info wi;
2127 memset (&wi, 0, sizeof (wi));
2128 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2131 /* Callback for walk_gimple_seq. */
2133 static tree
2134 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2135 struct walk_stmt_info *)
2137 gimple *stmt = gsi_stmt (*gsi_p);
2139 *handled_ops_p = true;
2140 switch (gimple_code (stmt))
2142 case GIMPLE_TRY:
2143 case GIMPLE_BIND:
2144 case GIMPLE_CATCH:
2145 case GIMPLE_EH_FILTER:
2146 case GIMPLE_TRANSACTION:
2147 /* Walk the sub-statements. */
2148 *handled_ops_p = false;
2149 break;
2150 case GIMPLE_CALL:
2151 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2153 gsi_remove (gsi_p, true);
2154 if (gsi_end_p (*gsi_p))
2155 return integer_zero_node;
2157 bool found = false;
2158 location_t loc = gimple_location (stmt);
2160 gimple_stmt_iterator gsi2 = *gsi_p;
2161 stmt = gsi_stmt (gsi2);
2162 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2164 /* Go on until the artificial label. */
2165 tree goto_dest = gimple_goto_dest (stmt);
2166 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2168 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2169 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2170 == goto_dest)
2171 break;
2174 /* Not found? Stop. */
2175 if (gsi_end_p (gsi2))
2176 break;
2178 /* Look one past it. */
2179 gsi_next (&gsi2);
2182 /* We're looking for a case label or default label here. */
2183 while (!gsi_end_p (gsi2))
2185 stmt = gsi_stmt (gsi2);
2186 if (gimple_code (stmt) == GIMPLE_LABEL)
2188 tree label = gimple_label_label (as_a <glabel *> (stmt));
2189 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2191 found = true;
2192 break;
2195 else
2196 /* Something other than a label. That's not expected. */
2197 break;
2198 gsi_next (&gsi2);
2200 if (!found)
2201 warning_at (loc, 0, "attribute %<fallthrough%> not preceding "
2202 "a case label or default label");
2204 break;
2205 default:
2206 break;
2208 return NULL_TREE;
2211 /* Expand all FALLTHROUGH () calls in SEQ. */
2213 static void
2214 expand_FALLTHROUGH (gimple_seq *seq_p)
2216 struct walk_stmt_info wi;
2217 memset (&wi, 0, sizeof (wi));
2218 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2222 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2223 branch to. */
2225 static enum gimplify_status
2226 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2228 tree switch_expr = *expr_p;
2229 gimple_seq switch_body_seq = NULL;
2230 enum gimplify_status ret;
2231 tree index_type = TREE_TYPE (switch_expr);
2232 if (index_type == NULL_TREE)
2233 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2235 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2236 fb_rvalue);
2237 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2238 return ret;
2240 if (SWITCH_BODY (switch_expr))
2242 vec<tree> labels;
2243 vec<tree> saved_labels;
2244 hash_set<tree> *saved_live_switch_vars = NULL;
2245 tree default_case = NULL_TREE;
2246 gswitch *switch_stmt;
2248 /* If someone can be bothered to fill in the labels, they can
2249 be bothered to null out the body too. */
2250 gcc_assert (!SWITCH_LABELS (switch_expr));
2252 /* Save old labels, get new ones from body, then restore the old
2253 labels. Save all the things from the switch body to append after. */
2254 saved_labels = gimplify_ctxp->case_labels;
2255 gimplify_ctxp->case_labels.create (8);
2257 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2258 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2259 if (TREE_CODE (SWITCH_BODY (switch_expr)) == BIND_EXPR)
2260 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2261 else
2262 gimplify_ctxp->live_switch_vars = NULL;
2264 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2265 gimplify_ctxp->in_switch_expr = true;
2267 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2269 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2270 maybe_warn_switch_unreachable (switch_body_seq);
2271 maybe_warn_implicit_fallthrough (switch_body_seq);
2272 /* Only do this for the outermost GIMPLE_SWITCH. */
2273 if (!gimplify_ctxp->in_switch_expr)
2274 expand_FALLTHROUGH (&switch_body_seq);
2276 labels = gimplify_ctxp->case_labels;
2277 gimplify_ctxp->case_labels = saved_labels;
2279 if (gimplify_ctxp->live_switch_vars)
2281 gcc_assert (gimplify_ctxp->live_switch_vars->elements () == 0);
2282 delete gimplify_ctxp->live_switch_vars;
2284 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2286 preprocess_case_label_vec_for_gimple (labels, index_type,
2287 &default_case);
2289 if (!default_case)
2291 glabel *new_default;
2293 default_case
2294 = build_case_label (NULL_TREE, NULL_TREE,
2295 create_artificial_label (UNKNOWN_LOCATION));
2296 new_default = gimple_build_label (CASE_LABEL (default_case));
2297 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2300 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2301 default_case, labels);
2302 gimplify_seq_add_stmt (pre_p, switch_stmt);
2303 gimplify_seq_add_seq (pre_p, switch_body_seq);
2304 labels.release ();
2306 else
2307 gcc_assert (SWITCH_LABELS (switch_expr));
2309 return GS_ALL_DONE;
2312 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
2314 static enum gimplify_status
2315 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
2317 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
2318 == current_function_decl);
2320 glabel *label_stmt = gimple_build_label (LABEL_EXPR_LABEL (*expr_p));
2321 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2322 gimplify_seq_add_stmt (pre_p, label_stmt);
2324 return GS_ALL_DONE;
2327 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
2329 static enum gimplify_status
2330 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
2332 struct gimplify_ctx *ctxp;
2333 glabel *label_stmt;
2335 /* Invalid programs can play Duff's Device type games with, for example,
2336 #pragma omp parallel. At least in the C front end, we don't
2337 detect such invalid branches until after gimplification, in the
2338 diagnose_omp_blocks pass. */
2339 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
2340 if (ctxp->case_labels.exists ())
2341 break;
2343 label_stmt = gimple_build_label (CASE_LABEL (*expr_p));
2344 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2345 ctxp->case_labels.safe_push (*expr_p);
2346 gimplify_seq_add_stmt (pre_p, label_stmt);
2348 return GS_ALL_DONE;
2351 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
2352 if necessary. */
2354 tree
2355 build_and_jump (tree *label_p)
2357 if (label_p == NULL)
2358 /* If there's nowhere to jump, just fall through. */
2359 return NULL_TREE;
2361 if (*label_p == NULL_TREE)
2363 tree label = create_artificial_label (UNKNOWN_LOCATION);
2364 *label_p = label;
2367 return build1 (GOTO_EXPR, void_type_node, *label_p);
2370 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
2371 This also involves building a label to jump to and communicating it to
2372 gimplify_loop_expr through gimplify_ctxp->exit_label. */
2374 static enum gimplify_status
2375 gimplify_exit_expr (tree *expr_p)
2377 tree cond = TREE_OPERAND (*expr_p, 0);
2378 tree expr;
2380 expr = build_and_jump (&gimplify_ctxp->exit_label);
2381 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
2382 *expr_p = expr;
2384 return GS_OK;
2387 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
2388 different from its canonical type, wrap the whole thing inside a
2389 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
2390 type.
2392 The canonical type of a COMPONENT_REF is the type of the field being
2393 referenced--unless the field is a bit-field which can be read directly
2394 in a smaller mode, in which case the canonical type is the
2395 sign-appropriate type corresponding to that mode. */
2397 static void
2398 canonicalize_component_ref (tree *expr_p)
2400 tree expr = *expr_p;
2401 tree type;
2403 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
2405 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
2406 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
2407 else
2408 type = TREE_TYPE (TREE_OPERAND (expr, 1));
2410 /* One could argue that all the stuff below is not necessary for
2411 the non-bitfield case and declare it a FE error if type
2412 adjustment would be needed. */
2413 if (TREE_TYPE (expr) != type)
2415 #ifdef ENABLE_TYPES_CHECKING
2416 tree old_type = TREE_TYPE (expr);
2417 #endif
2418 int type_quals;
2420 /* We need to preserve qualifiers and propagate them from
2421 operand 0. */
2422 type_quals = TYPE_QUALS (type)
2423 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
2424 if (TYPE_QUALS (type) != type_quals)
2425 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
2427 /* Set the type of the COMPONENT_REF to the underlying type. */
2428 TREE_TYPE (expr) = type;
2430 #ifdef ENABLE_TYPES_CHECKING
2431 /* It is now a FE error, if the conversion from the canonical
2432 type to the original expression type is not useless. */
2433 gcc_assert (useless_type_conversion_p (old_type, type));
2434 #endif
2438 /* If a NOP conversion is changing a pointer to array of foo to a pointer
2439 to foo, embed that change in the ADDR_EXPR by converting
2440 T array[U];
2441 (T *)&array
2443 &array[L]
2444 where L is the lower bound. For simplicity, only do this for constant
2445 lower bound.
2446 The constraint is that the type of &array[L] is trivially convertible
2447 to T *. */
2449 static void
2450 canonicalize_addr_expr (tree *expr_p)
2452 tree expr = *expr_p;
2453 tree addr_expr = TREE_OPERAND (expr, 0);
2454 tree datype, ddatype, pddatype;
2456 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
2457 if (!POINTER_TYPE_P (TREE_TYPE (expr))
2458 || TREE_CODE (addr_expr) != ADDR_EXPR)
2459 return;
2461 /* The addr_expr type should be a pointer to an array. */
2462 datype = TREE_TYPE (TREE_TYPE (addr_expr));
2463 if (TREE_CODE (datype) != ARRAY_TYPE)
2464 return;
2466 /* The pointer to element type shall be trivially convertible to
2467 the expression pointer type. */
2468 ddatype = TREE_TYPE (datype);
2469 pddatype = build_pointer_type (ddatype);
2470 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
2471 pddatype))
2472 return;
2474 /* The lower bound and element sizes must be constant. */
2475 if (!TYPE_SIZE_UNIT (ddatype)
2476 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
2477 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
2478 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
2479 return;
2481 /* All checks succeeded. Build a new node to merge the cast. */
2482 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
2483 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
2484 NULL_TREE, NULL_TREE);
2485 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
2487 /* We can have stripped a required restrict qualifier above. */
2488 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
2489 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
2492 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
2493 underneath as appropriate. */
2495 static enum gimplify_status
2496 gimplify_conversion (tree *expr_p)
2498 location_t loc = EXPR_LOCATION (*expr_p);
2499 gcc_assert (CONVERT_EXPR_P (*expr_p));
2501 /* Then strip away all but the outermost conversion. */
2502 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
2504 /* And remove the outermost conversion if it's useless. */
2505 if (tree_ssa_useless_type_conversion (*expr_p))
2506 *expr_p = TREE_OPERAND (*expr_p, 0);
2508 /* If we still have a conversion at the toplevel,
2509 then canonicalize some constructs. */
2510 if (CONVERT_EXPR_P (*expr_p))
2512 tree sub = TREE_OPERAND (*expr_p, 0);
2514 /* If a NOP conversion is changing the type of a COMPONENT_REF
2515 expression, then canonicalize its type now in order to expose more
2516 redundant conversions. */
2517 if (TREE_CODE (sub) == COMPONENT_REF)
2518 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
2520 /* If a NOP conversion is changing a pointer to array of foo
2521 to a pointer to foo, embed that change in the ADDR_EXPR. */
2522 else if (TREE_CODE (sub) == ADDR_EXPR)
2523 canonicalize_addr_expr (expr_p);
2526 /* If we have a conversion to a non-register type force the
2527 use of a VIEW_CONVERT_EXPR instead. */
2528 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
2529 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
2530 TREE_OPERAND (*expr_p, 0));
2532 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
2533 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
2534 TREE_SET_CODE (*expr_p, NOP_EXPR);
2536 return GS_OK;
2539 /* Nonlocal VLAs seen in the current function. */
2540 static hash_set<tree> *nonlocal_vlas;
2542 /* The VAR_DECLs created for nonlocal VLAs for debug info purposes. */
2543 static tree nonlocal_vla_vars;
2545 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
2546 DECL_VALUE_EXPR, and it's worth re-examining things. */
2548 static enum gimplify_status
2549 gimplify_var_or_parm_decl (tree *expr_p)
2551 tree decl = *expr_p;
2553 /* ??? If this is a local variable, and it has not been seen in any
2554 outer BIND_EXPR, then it's probably the result of a duplicate
2555 declaration, for which we've already issued an error. It would
2556 be really nice if the front end wouldn't leak these at all.
2557 Currently the only known culprit is C++ destructors, as seen
2558 in g++.old-deja/g++.jason/binding.C. */
2559 if (VAR_P (decl)
2560 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
2561 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
2562 && decl_function_context (decl) == current_function_decl)
2564 gcc_assert (seen_error ());
2565 return GS_ERROR;
2568 /* When within an OMP context, notice uses of variables. */
2569 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
2570 return GS_ALL_DONE;
2572 /* If the decl is an alias for another expression, substitute it now. */
2573 if (DECL_HAS_VALUE_EXPR_P (decl))
2575 tree value_expr = DECL_VALUE_EXPR (decl);
2577 /* For referenced nonlocal VLAs add a decl for debugging purposes
2578 to the current function. */
2579 if (VAR_P (decl)
2580 && TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
2581 && nonlocal_vlas != NULL
2582 && TREE_CODE (value_expr) == INDIRECT_REF
2583 && TREE_CODE (TREE_OPERAND (value_expr, 0)) == VAR_DECL
2584 && decl_function_context (decl) != current_function_decl)
2586 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
2587 while (ctx
2588 && (ctx->region_type == ORT_WORKSHARE
2589 || ctx->region_type == ORT_SIMD
2590 || ctx->region_type == ORT_ACC))
2591 ctx = ctx->outer_context;
2592 if (!ctx && !nonlocal_vlas->add (decl))
2594 tree copy = copy_node (decl);
2596 lang_hooks.dup_lang_specific_decl (copy);
2597 SET_DECL_RTL (copy, 0);
2598 TREE_USED (copy) = 1;
2599 DECL_CHAIN (copy) = nonlocal_vla_vars;
2600 nonlocal_vla_vars = copy;
2601 SET_DECL_VALUE_EXPR (copy, unshare_expr (value_expr));
2602 DECL_HAS_VALUE_EXPR_P (copy) = 1;
2606 *expr_p = unshare_expr (value_expr);
2607 return GS_OK;
2610 return GS_ALL_DONE;
2613 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
2615 static void
2616 recalculate_side_effects (tree t)
2618 enum tree_code code = TREE_CODE (t);
2619 int len = TREE_OPERAND_LENGTH (t);
2620 int i;
2622 switch (TREE_CODE_CLASS (code))
2624 case tcc_expression:
2625 switch (code)
2627 case INIT_EXPR:
2628 case MODIFY_EXPR:
2629 case VA_ARG_EXPR:
2630 case PREDECREMENT_EXPR:
2631 case PREINCREMENT_EXPR:
2632 case POSTDECREMENT_EXPR:
2633 case POSTINCREMENT_EXPR:
2634 /* All of these have side-effects, no matter what their
2635 operands are. */
2636 return;
2638 default:
2639 break;
2641 /* Fall through. */
2643 case tcc_comparison: /* a comparison expression */
2644 case tcc_unary: /* a unary arithmetic expression */
2645 case tcc_binary: /* a binary arithmetic expression */
2646 case tcc_reference: /* a reference */
2647 case tcc_vl_exp: /* a function call */
2648 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
2649 for (i = 0; i < len; ++i)
2651 tree op = TREE_OPERAND (t, i);
2652 if (op && TREE_SIDE_EFFECTS (op))
2653 TREE_SIDE_EFFECTS (t) = 1;
2655 break;
2657 case tcc_constant:
2658 /* No side-effects. */
2659 return;
2661 default:
2662 gcc_unreachable ();
2666 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
2667 node *EXPR_P.
2669 compound_lval
2670 : min_lval '[' val ']'
2671 | min_lval '.' ID
2672 | compound_lval '[' val ']'
2673 | compound_lval '.' ID
2675 This is not part of the original SIMPLE definition, which separates
2676 array and member references, but it seems reasonable to handle them
2677 together. Also, this way we don't run into problems with union
2678 aliasing; gcc requires that for accesses through a union to alias, the
2679 union reference must be explicit, which was not always the case when we
2680 were splitting up array and member refs.
2682 PRE_P points to the sequence where side effects that must happen before
2683 *EXPR_P should be stored.
2685 POST_P points to the sequence where side effects that must happen after
2686 *EXPR_P should be stored. */
2688 static enum gimplify_status
2689 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
2690 fallback_t fallback)
2692 tree *p;
2693 enum gimplify_status ret = GS_ALL_DONE, tret;
2694 int i;
2695 location_t loc = EXPR_LOCATION (*expr_p);
2696 tree expr = *expr_p;
2698 /* Create a stack of the subexpressions so later we can walk them in
2699 order from inner to outer. */
2700 auto_vec<tree, 10> expr_stack;
2702 /* We can handle anything that get_inner_reference can deal with. */
2703 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
2705 restart:
2706 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
2707 if (TREE_CODE (*p) == INDIRECT_REF)
2708 *p = fold_indirect_ref_loc (loc, *p);
2710 if (handled_component_p (*p))
2712 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
2713 additional COMPONENT_REFs. */
2714 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
2715 && gimplify_var_or_parm_decl (p) == GS_OK)
2716 goto restart;
2717 else
2718 break;
2720 expr_stack.safe_push (*p);
2723 gcc_assert (expr_stack.length ());
2725 /* Now EXPR_STACK is a stack of pointers to all the refs we've
2726 walked through and P points to the innermost expression.
2728 Java requires that we elaborated nodes in source order. That
2729 means we must gimplify the inner expression followed by each of
2730 the indices, in order. But we can't gimplify the inner
2731 expression until we deal with any variable bounds, sizes, or
2732 positions in order to deal with PLACEHOLDER_EXPRs.
2734 So we do this in three steps. First we deal with the annotations
2735 for any variables in the components, then we gimplify the base,
2736 then we gimplify any indices, from left to right. */
2737 for (i = expr_stack.length () - 1; i >= 0; i--)
2739 tree t = expr_stack[i];
2741 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
2743 /* Gimplify the low bound and element type size and put them into
2744 the ARRAY_REF. If these values are set, they have already been
2745 gimplified. */
2746 if (TREE_OPERAND (t, 2) == NULL_TREE)
2748 tree low = unshare_expr (array_ref_low_bound (t));
2749 if (!is_gimple_min_invariant (low))
2751 TREE_OPERAND (t, 2) = low;
2752 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
2753 post_p, is_gimple_reg,
2754 fb_rvalue);
2755 ret = MIN (ret, tret);
2758 else
2760 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
2761 is_gimple_reg, fb_rvalue);
2762 ret = MIN (ret, tret);
2765 if (TREE_OPERAND (t, 3) == NULL_TREE)
2767 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
2768 tree elmt_size = unshare_expr (array_ref_element_size (t));
2769 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
2771 /* Divide the element size by the alignment of the element
2772 type (above). */
2773 elmt_size
2774 = size_binop_loc (loc, EXACT_DIV_EXPR, elmt_size, factor);
2776 if (!is_gimple_min_invariant (elmt_size))
2778 TREE_OPERAND (t, 3) = elmt_size;
2779 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
2780 post_p, is_gimple_reg,
2781 fb_rvalue);
2782 ret = MIN (ret, tret);
2785 else
2787 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
2788 is_gimple_reg, fb_rvalue);
2789 ret = MIN (ret, tret);
2792 else if (TREE_CODE (t) == COMPONENT_REF)
2794 /* Set the field offset into T and gimplify it. */
2795 if (TREE_OPERAND (t, 2) == NULL_TREE)
2797 tree offset = unshare_expr (component_ref_field_offset (t));
2798 tree field = TREE_OPERAND (t, 1);
2799 tree factor
2800 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
2802 /* Divide the offset by its alignment. */
2803 offset = size_binop_loc (loc, EXACT_DIV_EXPR, offset, factor);
2805 if (!is_gimple_min_invariant (offset))
2807 TREE_OPERAND (t, 2) = offset;
2808 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
2809 post_p, is_gimple_reg,
2810 fb_rvalue);
2811 ret = MIN (ret, tret);
2814 else
2816 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
2817 is_gimple_reg, fb_rvalue);
2818 ret = MIN (ret, tret);
2823 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
2824 so as to match the min_lval predicate. Failure to do so may result
2825 in the creation of large aggregate temporaries. */
2826 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
2827 fallback | fb_lvalue);
2828 ret = MIN (ret, tret);
2830 /* And finally, the indices and operands of ARRAY_REF. During this
2831 loop we also remove any useless conversions. */
2832 for (; expr_stack.length () > 0; )
2834 tree t = expr_stack.pop ();
2836 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
2838 /* Gimplify the dimension. */
2839 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
2841 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
2842 is_gimple_val, fb_rvalue);
2843 ret = MIN (ret, tret);
2847 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
2849 /* The innermost expression P may have originally had
2850 TREE_SIDE_EFFECTS set which would have caused all the outer
2851 expressions in *EXPR_P leading to P to also have had
2852 TREE_SIDE_EFFECTS set. */
2853 recalculate_side_effects (t);
2856 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
2857 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
2859 canonicalize_component_ref (expr_p);
2862 expr_stack.release ();
2864 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
2866 return ret;
2869 /* Gimplify the self modifying expression pointed to by EXPR_P
2870 (++, --, +=, -=).
2872 PRE_P points to the list where side effects that must happen before
2873 *EXPR_P should be stored.
2875 POST_P points to the list where side effects that must happen after
2876 *EXPR_P should be stored.
2878 WANT_VALUE is nonzero iff we want to use the value of this expression
2879 in another expression.
2881 ARITH_TYPE is the type the computation should be performed in. */
2883 enum gimplify_status
2884 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
2885 bool want_value, tree arith_type)
2887 enum tree_code code;
2888 tree lhs, lvalue, rhs, t1;
2889 gimple_seq post = NULL, *orig_post_p = post_p;
2890 bool postfix;
2891 enum tree_code arith_code;
2892 enum gimplify_status ret;
2893 location_t loc = EXPR_LOCATION (*expr_p);
2895 code = TREE_CODE (*expr_p);
2897 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
2898 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
2900 /* Prefix or postfix? */
2901 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
2902 /* Faster to treat as prefix if result is not used. */
2903 postfix = want_value;
2904 else
2905 postfix = false;
2907 /* For postfix, make sure the inner expression's post side effects
2908 are executed after side effects from this expression. */
2909 if (postfix)
2910 post_p = &post;
2912 /* Add or subtract? */
2913 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
2914 arith_code = PLUS_EXPR;
2915 else
2916 arith_code = MINUS_EXPR;
2918 /* Gimplify the LHS into a GIMPLE lvalue. */
2919 lvalue = TREE_OPERAND (*expr_p, 0);
2920 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
2921 if (ret == GS_ERROR)
2922 return ret;
2924 /* Extract the operands to the arithmetic operation. */
2925 lhs = lvalue;
2926 rhs = TREE_OPERAND (*expr_p, 1);
2928 /* For postfix operator, we evaluate the LHS to an rvalue and then use
2929 that as the result value and in the postqueue operation. */
2930 if (postfix)
2932 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
2933 if (ret == GS_ERROR)
2934 return ret;
2936 lhs = get_initialized_tmp_var (lhs, pre_p, NULL);
2939 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
2940 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
2942 rhs = convert_to_ptrofftype_loc (loc, rhs);
2943 if (arith_code == MINUS_EXPR)
2944 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
2945 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
2947 else
2948 t1 = fold_convert (TREE_TYPE (*expr_p),
2949 fold_build2 (arith_code, arith_type,
2950 fold_convert (arith_type, lhs),
2951 fold_convert (arith_type, rhs)));
2953 if (postfix)
2955 gimplify_assign (lvalue, t1, pre_p);
2956 gimplify_seq_add_seq (orig_post_p, post);
2957 *expr_p = lhs;
2958 return GS_ALL_DONE;
2960 else
2962 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
2963 return GS_OK;
2967 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
2969 static void
2970 maybe_with_size_expr (tree *expr_p)
2972 tree expr = *expr_p;
2973 tree type = TREE_TYPE (expr);
2974 tree size;
2976 /* If we've already wrapped this or the type is error_mark_node, we can't do
2977 anything. */
2978 if (TREE_CODE (expr) == WITH_SIZE_EXPR
2979 || type == error_mark_node)
2980 return;
2982 /* If the size isn't known or is a constant, we have nothing to do. */
2983 size = TYPE_SIZE_UNIT (type);
2984 if (!size || TREE_CODE (size) == INTEGER_CST)
2985 return;
2987 /* Otherwise, make a WITH_SIZE_EXPR. */
2988 size = unshare_expr (size);
2989 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
2990 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
2993 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
2994 Store any side-effects in PRE_P. CALL_LOCATION is the location of
2995 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
2996 gimplified to an SSA name. */
2998 enum gimplify_status
2999 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3000 bool allow_ssa)
3002 bool (*test) (tree);
3003 fallback_t fb;
3005 /* In general, we allow lvalues for function arguments to avoid
3006 extra overhead of copying large aggregates out of even larger
3007 aggregates into temporaries only to copy the temporaries to
3008 the argument list. Make optimizers happy by pulling out to
3009 temporaries those types that fit in registers. */
3010 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3011 test = is_gimple_val, fb = fb_rvalue;
3012 else
3014 test = is_gimple_lvalue, fb = fb_either;
3015 /* Also strip a TARGET_EXPR that would force an extra copy. */
3016 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3018 tree init = TARGET_EXPR_INITIAL (*arg_p);
3019 if (init
3020 && !VOID_TYPE_P (TREE_TYPE (init)))
3021 *arg_p = init;
3025 /* If this is a variable sized type, we must remember the size. */
3026 maybe_with_size_expr (arg_p);
3028 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3029 /* Make sure arguments have the same location as the function call
3030 itself. */
3031 protected_set_expr_location (*arg_p, call_location);
3033 /* There is a sequence point before a function call. Side effects in
3034 the argument list must occur before the actual call. So, when
3035 gimplifying arguments, force gimplify_expr to use an internal
3036 post queue which is then appended to the end of PRE_P. */
3037 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3040 /* Don't fold inside offloading or taskreg regions: it can break code by
3041 adding decl references that weren't in the source. We'll do it during
3042 omplower pass instead. */
3044 static bool
3045 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3047 struct gimplify_omp_ctx *ctx;
3048 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3049 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3050 return false;
3051 return fold_stmt (gsi);
3054 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3055 WANT_VALUE is true if the result of the call is desired. */
3057 static enum gimplify_status
3058 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3060 tree fndecl, parms, p, fnptrtype;
3061 enum gimplify_status ret;
3062 int i, nargs;
3063 gcall *call;
3064 bool builtin_va_start_p = false;
3065 location_t loc = EXPR_LOCATION (*expr_p);
3067 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3069 /* For reliable diagnostics during inlining, it is necessary that
3070 every call_expr be annotated with file and line. */
3071 if (! EXPR_HAS_LOCATION (*expr_p))
3072 SET_EXPR_LOCATION (*expr_p, input_location);
3074 /* Gimplify internal functions created in the FEs. */
3075 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3077 if (want_value)
3078 return GS_ALL_DONE;
3080 nargs = call_expr_nargs (*expr_p);
3081 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3082 auto_vec<tree> vargs (nargs);
3084 for (i = 0; i < nargs; i++)
3086 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3087 EXPR_LOCATION (*expr_p));
3088 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3090 gimple *call = gimple_build_call_internal_vec (ifn, vargs);
3091 gimplify_seq_add_stmt (pre_p, call);
3092 return GS_ALL_DONE;
3095 /* This may be a call to a builtin function.
3097 Builtin function calls may be transformed into different
3098 (and more efficient) builtin function calls under certain
3099 circumstances. Unfortunately, gimplification can muck things
3100 up enough that the builtin expanders are not aware that certain
3101 transformations are still valid.
3103 So we attempt transformation/gimplification of the call before
3104 we gimplify the CALL_EXPR. At this time we do not manage to
3105 transform all calls in the same manner as the expanders do, but
3106 we do transform most of them. */
3107 fndecl = get_callee_fndecl (*expr_p);
3108 if (fndecl
3109 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL)
3110 switch (DECL_FUNCTION_CODE (fndecl))
3112 case BUILT_IN_ALLOCA:
3113 case BUILT_IN_ALLOCA_WITH_ALIGN:
3114 /* If the call has been built for a variable-sized object, then we
3115 want to restore the stack level when the enclosing BIND_EXPR is
3116 exited to reclaim the allocated space; otherwise, we precisely
3117 need to do the opposite and preserve the latest stack level. */
3118 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3119 gimplify_ctxp->save_stack = true;
3120 else
3121 gimplify_ctxp->keep_stack = true;
3122 break;
3124 case BUILT_IN_VA_START:
3126 builtin_va_start_p = TRUE;
3127 if (call_expr_nargs (*expr_p) < 2)
3129 error ("too few arguments to function %<va_start%>");
3130 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3131 return GS_OK;
3134 if (fold_builtin_next_arg (*expr_p, true))
3136 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3137 return GS_OK;
3139 break;
3142 default:
3145 if (fndecl && DECL_BUILT_IN (fndecl))
3147 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3148 if (new_tree && new_tree != *expr_p)
3150 /* There was a transformation of this call which computes the
3151 same value, but in a more efficient way. Return and try
3152 again. */
3153 *expr_p = new_tree;
3154 return GS_OK;
3158 /* Remember the original function pointer type. */
3159 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3161 /* There is a sequence point before the call, so any side effects in
3162 the calling expression must occur before the actual call. Force
3163 gimplify_expr to use an internal post queue. */
3164 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3165 is_gimple_call_addr, fb_rvalue);
3167 nargs = call_expr_nargs (*expr_p);
3169 /* Get argument types for verification. */
3170 fndecl = get_callee_fndecl (*expr_p);
3171 parms = NULL_TREE;
3172 if (fndecl)
3173 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3174 else
3175 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3177 if (fndecl && DECL_ARGUMENTS (fndecl))
3178 p = DECL_ARGUMENTS (fndecl);
3179 else if (parms)
3180 p = parms;
3181 else
3182 p = NULL_TREE;
3183 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3186 /* If the last argument is __builtin_va_arg_pack () and it is not
3187 passed as a named argument, decrease the number of CALL_EXPR
3188 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3189 if (!p
3190 && i < nargs
3191 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3193 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3194 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3196 if (last_arg_fndecl
3197 && TREE_CODE (last_arg_fndecl) == FUNCTION_DECL
3198 && DECL_BUILT_IN_CLASS (last_arg_fndecl) == BUILT_IN_NORMAL
3199 && DECL_FUNCTION_CODE (last_arg_fndecl) == BUILT_IN_VA_ARG_PACK)
3201 tree call = *expr_p;
3203 --nargs;
3204 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
3205 CALL_EXPR_FN (call),
3206 nargs, CALL_EXPR_ARGP (call));
3208 /* Copy all CALL_EXPR flags, location and block, except
3209 CALL_EXPR_VA_ARG_PACK flag. */
3210 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
3211 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
3212 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
3213 = CALL_EXPR_RETURN_SLOT_OPT (call);
3214 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
3215 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
3217 /* Set CALL_EXPR_VA_ARG_PACK. */
3218 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
3222 /* If the call returns twice then after building the CFG the call
3223 argument computations will no longer dominate the call because
3224 we add an abnormal incoming edge to the call. So do not use SSA
3225 vars there. */
3226 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
3228 /* Gimplify the function arguments. */
3229 if (nargs > 0)
3231 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
3232 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
3233 PUSH_ARGS_REVERSED ? i-- : i++)
3235 enum gimplify_status t;
3237 /* Avoid gimplifying the second argument to va_start, which needs to
3238 be the plain PARM_DECL. */
3239 if ((i != 1) || !builtin_va_start_p)
3241 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3242 EXPR_LOCATION (*expr_p), ! returns_twice);
3244 if (t == GS_ERROR)
3245 ret = GS_ERROR;
3250 /* Gimplify the static chain. */
3251 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
3253 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
3254 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
3255 else
3257 enum gimplify_status t;
3258 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
3259 EXPR_LOCATION (*expr_p), ! returns_twice);
3260 if (t == GS_ERROR)
3261 ret = GS_ERROR;
3265 /* Verify the function result. */
3266 if (want_value && fndecl
3267 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
3269 error_at (loc, "using result of function returning %<void%>");
3270 ret = GS_ERROR;
3273 /* Try this again in case gimplification exposed something. */
3274 if (ret != GS_ERROR)
3276 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3278 if (new_tree && new_tree != *expr_p)
3280 /* There was a transformation of this call which computes the
3281 same value, but in a more efficient way. Return and try
3282 again. */
3283 *expr_p = new_tree;
3284 return GS_OK;
3287 else
3289 *expr_p = error_mark_node;
3290 return GS_ERROR;
3293 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
3294 decl. This allows us to eliminate redundant or useless
3295 calls to "const" functions. */
3296 if (TREE_CODE (*expr_p) == CALL_EXPR)
3298 int flags = call_expr_flags (*expr_p);
3299 if (flags & (ECF_CONST | ECF_PURE)
3300 /* An infinite loop is considered a side effect. */
3301 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
3302 TREE_SIDE_EFFECTS (*expr_p) = 0;
3305 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
3306 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
3307 form and delegate the creation of a GIMPLE_CALL to
3308 gimplify_modify_expr. This is always possible because when
3309 WANT_VALUE is true, the caller wants the result of this call into
3310 a temporary, which means that we will emit an INIT_EXPR in
3311 internal_get_tmp_var which will then be handled by
3312 gimplify_modify_expr. */
3313 if (!want_value)
3315 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
3316 have to do is replicate it as a GIMPLE_CALL tuple. */
3317 gimple_stmt_iterator gsi;
3318 call = gimple_build_call_from_tree (*expr_p);
3319 gimple_call_set_fntype (call, TREE_TYPE (fnptrtype));
3320 notice_special_calls (call);
3321 gimplify_seq_add_stmt (pre_p, call);
3322 gsi = gsi_last (*pre_p);
3323 maybe_fold_stmt (&gsi);
3324 *expr_p = NULL_TREE;
3326 else
3327 /* Remember the original function type. */
3328 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
3329 CALL_EXPR_FN (*expr_p));
3331 return ret;
3334 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
3335 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
3337 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
3338 condition is true or false, respectively. If null, we should generate
3339 our own to skip over the evaluation of this specific expression.
3341 LOCUS is the source location of the COND_EXPR.
3343 This function is the tree equivalent of do_jump.
3345 shortcut_cond_r should only be called by shortcut_cond_expr. */
3347 static tree
3348 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
3349 location_t locus)
3351 tree local_label = NULL_TREE;
3352 tree t, expr = NULL;
3354 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
3355 retain the shortcut semantics. Just insert the gotos here;
3356 shortcut_cond_expr will append the real blocks later. */
3357 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3359 location_t new_locus;
3361 /* Turn if (a && b) into
3363 if (a); else goto no;
3364 if (b) goto yes; else goto no;
3365 (no:) */
3367 if (false_label_p == NULL)
3368 false_label_p = &local_label;
3370 /* Keep the original source location on the first 'if'. */
3371 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
3372 append_to_statement_list (t, &expr);
3374 /* Set the source location of the && on the second 'if'. */
3375 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
3376 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3377 new_locus);
3378 append_to_statement_list (t, &expr);
3380 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3382 location_t new_locus;
3384 /* Turn if (a || b) into
3386 if (a) goto yes;
3387 if (b) goto yes; else goto no;
3388 (yes:) */
3390 if (true_label_p == NULL)
3391 true_label_p = &local_label;
3393 /* Keep the original source location on the first 'if'. */
3394 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
3395 append_to_statement_list (t, &expr);
3397 /* Set the source location of the || on the second 'if'. */
3398 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
3399 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3400 new_locus);
3401 append_to_statement_list (t, &expr);
3403 else if (TREE_CODE (pred) == COND_EXPR
3404 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
3405 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
3407 location_t new_locus;
3409 /* As long as we're messing with gotos, turn if (a ? b : c) into
3410 if (a)
3411 if (b) goto yes; else goto no;
3412 else
3413 if (c) goto yes; else goto no;
3415 Don't do this if one of the arms has void type, which can happen
3416 in C++ when the arm is throw. */
3418 /* Keep the original source location on the first 'if'. Set the source
3419 location of the ? on the second 'if'. */
3420 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
3421 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
3422 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
3423 false_label_p, locus),
3424 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
3425 false_label_p, new_locus));
3427 else
3429 expr = build3 (COND_EXPR, void_type_node, pred,
3430 build_and_jump (true_label_p),
3431 build_and_jump (false_label_p));
3432 SET_EXPR_LOCATION (expr, locus);
3435 if (local_label)
3437 t = build1 (LABEL_EXPR, void_type_node, local_label);
3438 append_to_statement_list (t, &expr);
3441 return expr;
3444 /* Given a conditional expression EXPR with short-circuit boolean
3445 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
3446 predicate apart into the equivalent sequence of conditionals. */
3448 static tree
3449 shortcut_cond_expr (tree expr)
3451 tree pred = TREE_OPERAND (expr, 0);
3452 tree then_ = TREE_OPERAND (expr, 1);
3453 tree else_ = TREE_OPERAND (expr, 2);
3454 tree true_label, false_label, end_label, t;
3455 tree *true_label_p;
3456 tree *false_label_p;
3457 bool emit_end, emit_false, jump_over_else;
3458 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
3459 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
3461 /* First do simple transformations. */
3462 if (!else_se)
3464 /* If there is no 'else', turn
3465 if (a && b) then c
3466 into
3467 if (a) if (b) then c. */
3468 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3470 /* Keep the original source location on the first 'if'. */
3471 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3472 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3473 /* Set the source location of the && on the second 'if'. */
3474 if (EXPR_HAS_LOCATION (pred))
3475 SET_EXPR_LOCATION (expr, EXPR_LOCATION (pred));
3476 then_ = shortcut_cond_expr (expr);
3477 then_se = then_ && TREE_SIDE_EFFECTS (then_);
3478 pred = TREE_OPERAND (pred, 0);
3479 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
3480 SET_EXPR_LOCATION (expr, locus);
3484 if (!then_se)
3486 /* If there is no 'then', turn
3487 if (a || b); else d
3488 into
3489 if (a); else if (b); else d. */
3490 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3492 /* Keep the original source location on the first 'if'. */
3493 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3494 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3495 /* Set the source location of the || on the second 'if'. */
3496 if (EXPR_HAS_LOCATION (pred))
3497 SET_EXPR_LOCATION (expr, EXPR_LOCATION (pred));
3498 else_ = shortcut_cond_expr (expr);
3499 else_se = else_ && TREE_SIDE_EFFECTS (else_);
3500 pred = TREE_OPERAND (pred, 0);
3501 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
3502 SET_EXPR_LOCATION (expr, locus);
3506 /* If we're done, great. */
3507 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
3508 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
3509 return expr;
3511 /* Otherwise we need to mess with gotos. Change
3512 if (a) c; else d;
3514 if (a); else goto no;
3515 c; goto end;
3516 no: d; end:
3517 and recursively gimplify the condition. */
3519 true_label = false_label = end_label = NULL_TREE;
3521 /* If our arms just jump somewhere, hijack those labels so we don't
3522 generate jumps to jumps. */
3524 if (then_
3525 && TREE_CODE (then_) == GOTO_EXPR
3526 && TREE_CODE (GOTO_DESTINATION (then_)) == LABEL_DECL)
3528 true_label = GOTO_DESTINATION (then_);
3529 then_ = NULL;
3530 then_se = false;
3533 if (else_
3534 && TREE_CODE (else_) == GOTO_EXPR
3535 && TREE_CODE (GOTO_DESTINATION (else_)) == LABEL_DECL)
3537 false_label = GOTO_DESTINATION (else_);
3538 else_ = NULL;
3539 else_se = false;
3542 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
3543 if (true_label)
3544 true_label_p = &true_label;
3545 else
3546 true_label_p = NULL;
3548 /* The 'else' branch also needs a label if it contains interesting code. */
3549 if (false_label || else_se)
3550 false_label_p = &false_label;
3551 else
3552 false_label_p = NULL;
3554 /* If there was nothing else in our arms, just forward the label(s). */
3555 if (!then_se && !else_se)
3556 return shortcut_cond_r (pred, true_label_p, false_label_p,
3557 EXPR_LOC_OR_LOC (expr, input_location));
3559 /* If our last subexpression already has a terminal label, reuse it. */
3560 if (else_se)
3561 t = expr_last (else_);
3562 else if (then_se)
3563 t = expr_last (then_);
3564 else
3565 t = NULL;
3566 if (t && TREE_CODE (t) == LABEL_EXPR)
3567 end_label = LABEL_EXPR_LABEL (t);
3569 /* If we don't care about jumping to the 'else' branch, jump to the end
3570 if the condition is false. */
3571 if (!false_label_p)
3572 false_label_p = &end_label;
3574 /* We only want to emit these labels if we aren't hijacking them. */
3575 emit_end = (end_label == NULL_TREE);
3576 emit_false = (false_label == NULL_TREE);
3578 /* We only emit the jump over the else clause if we have to--if the
3579 then clause may fall through. Otherwise we can wind up with a
3580 useless jump and a useless label at the end of gimplified code,
3581 which will cause us to think that this conditional as a whole
3582 falls through even if it doesn't. If we then inline a function
3583 which ends with such a condition, that can cause us to issue an
3584 inappropriate warning about control reaching the end of a
3585 non-void function. */
3586 jump_over_else = block_may_fallthru (then_);
3588 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
3589 EXPR_LOC_OR_LOC (expr, input_location));
3591 expr = NULL;
3592 append_to_statement_list (pred, &expr);
3594 append_to_statement_list (then_, &expr);
3595 if (else_se)
3597 if (jump_over_else)
3599 tree last = expr_last (expr);
3600 t = build_and_jump (&end_label);
3601 if (EXPR_HAS_LOCATION (last))
3602 SET_EXPR_LOCATION (t, EXPR_LOCATION (last));
3603 append_to_statement_list (t, &expr);
3605 if (emit_false)
3607 t = build1 (LABEL_EXPR, void_type_node, false_label);
3608 append_to_statement_list (t, &expr);
3610 append_to_statement_list (else_, &expr);
3612 if (emit_end && end_label)
3614 t = build1 (LABEL_EXPR, void_type_node, end_label);
3615 append_to_statement_list (t, &expr);
3618 return expr;
3621 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
3623 tree
3624 gimple_boolify (tree expr)
3626 tree type = TREE_TYPE (expr);
3627 location_t loc = EXPR_LOCATION (expr);
3629 if (TREE_CODE (expr) == NE_EXPR
3630 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
3631 && integer_zerop (TREE_OPERAND (expr, 1)))
3633 tree call = TREE_OPERAND (expr, 0);
3634 tree fn = get_callee_fndecl (call);
3636 /* For __builtin_expect ((long) (x), y) recurse into x as well
3637 if x is truth_value_p. */
3638 if (fn
3639 && DECL_BUILT_IN_CLASS (fn) == BUILT_IN_NORMAL
3640 && DECL_FUNCTION_CODE (fn) == BUILT_IN_EXPECT
3641 && call_expr_nargs (call) == 2)
3643 tree arg = CALL_EXPR_ARG (call, 0);
3644 if (arg)
3646 if (TREE_CODE (arg) == NOP_EXPR
3647 && TREE_TYPE (arg) == TREE_TYPE (call))
3648 arg = TREE_OPERAND (arg, 0);
3649 if (truth_value_p (TREE_CODE (arg)))
3651 arg = gimple_boolify (arg);
3652 CALL_EXPR_ARG (call, 0)
3653 = fold_convert_loc (loc, TREE_TYPE (call), arg);
3659 switch (TREE_CODE (expr))
3661 case TRUTH_AND_EXPR:
3662 case TRUTH_OR_EXPR:
3663 case TRUTH_XOR_EXPR:
3664 case TRUTH_ANDIF_EXPR:
3665 case TRUTH_ORIF_EXPR:
3666 /* Also boolify the arguments of truth exprs. */
3667 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
3668 /* FALLTHRU */
3670 case TRUTH_NOT_EXPR:
3671 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3673 /* These expressions always produce boolean results. */
3674 if (TREE_CODE (type) != BOOLEAN_TYPE)
3675 TREE_TYPE (expr) = boolean_type_node;
3676 return expr;
3678 case ANNOTATE_EXPR:
3679 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
3681 case annot_expr_ivdep_kind:
3682 case annot_expr_no_vector_kind:
3683 case annot_expr_vector_kind:
3684 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3685 if (TREE_CODE (type) != BOOLEAN_TYPE)
3686 TREE_TYPE (expr) = boolean_type_node;
3687 return expr;
3688 default:
3689 gcc_unreachable ();
3692 default:
3693 if (COMPARISON_CLASS_P (expr))
3695 /* There expressions always prduce boolean results. */
3696 if (TREE_CODE (type) != BOOLEAN_TYPE)
3697 TREE_TYPE (expr) = boolean_type_node;
3698 return expr;
3700 /* Other expressions that get here must have boolean values, but
3701 might need to be converted to the appropriate mode. */
3702 if (TREE_CODE (type) == BOOLEAN_TYPE)
3703 return expr;
3704 return fold_convert_loc (loc, boolean_type_node, expr);
3708 /* Given a conditional expression *EXPR_P without side effects, gimplify
3709 its operands. New statements are inserted to PRE_P. */
3711 static enum gimplify_status
3712 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
3714 tree expr = *expr_p, cond;
3715 enum gimplify_status ret, tret;
3716 enum tree_code code;
3718 cond = gimple_boolify (COND_EXPR_COND (expr));
3720 /* We need to handle && and || specially, as their gimplification
3721 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
3722 code = TREE_CODE (cond);
3723 if (code == TRUTH_ANDIF_EXPR)
3724 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
3725 else if (code == TRUTH_ORIF_EXPR)
3726 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
3727 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_condexpr, fb_rvalue);
3728 COND_EXPR_COND (*expr_p) = cond;
3730 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
3731 is_gimple_val, fb_rvalue);
3732 ret = MIN (ret, tret);
3733 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
3734 is_gimple_val, fb_rvalue);
3736 return MIN (ret, tret);
3739 /* Return true if evaluating EXPR could trap.
3740 EXPR is GENERIC, while tree_could_trap_p can be called
3741 only on GIMPLE. */
3743 static bool
3744 generic_expr_could_trap_p (tree expr)
3746 unsigned i, n;
3748 if (!expr || is_gimple_val (expr))
3749 return false;
3751 if (!EXPR_P (expr) || tree_could_trap_p (expr))
3752 return true;
3754 n = TREE_OPERAND_LENGTH (expr);
3755 for (i = 0; i < n; i++)
3756 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
3757 return true;
3759 return false;
3762 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
3763 into
3765 if (p) if (p)
3766 t1 = a; a;
3767 else or else
3768 t1 = b; b;
3771 The second form is used when *EXPR_P is of type void.
3773 PRE_P points to the list where side effects that must happen before
3774 *EXPR_P should be stored. */
3776 static enum gimplify_status
3777 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
3779 tree expr = *expr_p;
3780 tree type = TREE_TYPE (expr);
3781 location_t loc = EXPR_LOCATION (expr);
3782 tree tmp, arm1, arm2;
3783 enum gimplify_status ret;
3784 tree label_true, label_false, label_cont;
3785 bool have_then_clause_p, have_else_clause_p;
3786 gcond *cond_stmt;
3787 enum tree_code pred_code;
3788 gimple_seq seq = NULL;
3790 /* If this COND_EXPR has a value, copy the values into a temporary within
3791 the arms. */
3792 if (!VOID_TYPE_P (type))
3794 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
3795 tree result;
3797 /* If either an rvalue is ok or we do not require an lvalue, create the
3798 temporary. But we cannot do that if the type is addressable. */
3799 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
3800 && !TREE_ADDRESSABLE (type))
3802 if (gimplify_ctxp->allow_rhs_cond_expr
3803 /* If either branch has side effects or could trap, it can't be
3804 evaluated unconditionally. */
3805 && !TREE_SIDE_EFFECTS (then_)
3806 && !generic_expr_could_trap_p (then_)
3807 && !TREE_SIDE_EFFECTS (else_)
3808 && !generic_expr_could_trap_p (else_))
3809 return gimplify_pure_cond_expr (expr_p, pre_p);
3811 tmp = create_tmp_var (type, "iftmp");
3812 result = tmp;
3815 /* Otherwise, only create and copy references to the values. */
3816 else
3818 type = build_pointer_type (type);
3820 if (!VOID_TYPE_P (TREE_TYPE (then_)))
3821 then_ = build_fold_addr_expr_loc (loc, then_);
3823 if (!VOID_TYPE_P (TREE_TYPE (else_)))
3824 else_ = build_fold_addr_expr_loc (loc, else_);
3826 expr
3827 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
3829 tmp = create_tmp_var (type, "iftmp");
3830 result = build_simple_mem_ref_loc (loc, tmp);
3833 /* Build the new then clause, `tmp = then_;'. But don't build the
3834 assignment if the value is void; in C++ it can be if it's a throw. */
3835 if (!VOID_TYPE_P (TREE_TYPE (then_)))
3836 TREE_OPERAND (expr, 1) = build2 (MODIFY_EXPR, type, tmp, then_);
3838 /* Similarly, build the new else clause, `tmp = else_;'. */
3839 if (!VOID_TYPE_P (TREE_TYPE (else_)))
3840 TREE_OPERAND (expr, 2) = build2 (MODIFY_EXPR, type, tmp, else_);
3842 TREE_TYPE (expr) = void_type_node;
3843 recalculate_side_effects (expr);
3845 /* Move the COND_EXPR to the prequeue. */
3846 gimplify_stmt (&expr, pre_p);
3848 *expr_p = result;
3849 return GS_ALL_DONE;
3852 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
3853 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
3854 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
3855 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
3857 /* Make sure the condition has BOOLEAN_TYPE. */
3858 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3860 /* Break apart && and || conditions. */
3861 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
3862 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
3864 expr = shortcut_cond_expr (expr);
3866 if (expr != *expr_p)
3868 *expr_p = expr;
3870 /* We can't rely on gimplify_expr to re-gimplify the expanded
3871 form properly, as cleanups might cause the target labels to be
3872 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
3873 set up a conditional context. */
3874 gimple_push_condition ();
3875 gimplify_stmt (expr_p, &seq);
3876 gimple_pop_condition (pre_p);
3877 gimple_seq_add_seq (pre_p, seq);
3879 return GS_ALL_DONE;
3883 /* Now do the normal gimplification. */
3885 /* Gimplify condition. */
3886 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL, is_gimple_condexpr,
3887 fb_rvalue);
3888 if (ret == GS_ERROR)
3889 return GS_ERROR;
3890 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
3892 gimple_push_condition ();
3894 have_then_clause_p = have_else_clause_p = false;
3895 if (TREE_OPERAND (expr, 1) != NULL
3896 && TREE_CODE (TREE_OPERAND (expr, 1)) == GOTO_EXPR
3897 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr, 1))) == LABEL_DECL
3898 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr, 1)))
3899 == current_function_decl)
3900 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3901 have different locations, otherwise we end up with incorrect
3902 location information on the branches. */
3903 && (optimize
3904 || !EXPR_HAS_LOCATION (expr)
3905 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr, 1))
3906 || EXPR_LOCATION (expr) == EXPR_LOCATION (TREE_OPERAND (expr, 1))))
3908 label_true = GOTO_DESTINATION (TREE_OPERAND (expr, 1));
3909 have_then_clause_p = true;
3911 else
3912 label_true = create_artificial_label (UNKNOWN_LOCATION);
3913 if (TREE_OPERAND (expr, 2) != NULL
3914 && TREE_CODE (TREE_OPERAND (expr, 2)) == GOTO_EXPR
3915 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr, 2))) == LABEL_DECL
3916 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr, 2)))
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, 2))
3924 || EXPR_LOCATION (expr) == EXPR_LOCATION (TREE_OPERAND (expr, 2))))
3926 label_false = GOTO_DESTINATION (TREE_OPERAND (expr, 2));
3927 have_else_clause_p = true;
3929 else
3930 label_false = create_artificial_label (UNKNOWN_LOCATION);
3932 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
3933 &arm2);
3934 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
3935 label_false);
3936 gimple_set_no_warning (cond_stmt, TREE_NO_WARNING (COND_EXPR_COND (expr)));
3937 gimplify_seq_add_stmt (&seq, cond_stmt);
3938 gimple_stmt_iterator gsi = gsi_last (seq);
3939 maybe_fold_stmt (&gsi);
3941 label_cont = NULL_TREE;
3942 if (!have_then_clause_p)
3944 /* For if (...) {} else { code; } put label_true after
3945 the else block. */
3946 if (TREE_OPERAND (expr, 1) == NULL_TREE
3947 && !have_else_clause_p
3948 && TREE_OPERAND (expr, 2) != NULL_TREE)
3949 label_cont = label_true;
3950 else
3952 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
3953 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
3954 /* For if (...) { code; } else {} or
3955 if (...) { code; } else goto label; or
3956 if (...) { code; return; } else { ... }
3957 label_cont isn't needed. */
3958 if (!have_else_clause_p
3959 && TREE_OPERAND (expr, 2) != NULL_TREE
3960 && gimple_seq_may_fallthru (seq))
3962 gimple *g;
3963 label_cont = create_artificial_label (UNKNOWN_LOCATION);
3965 g = gimple_build_goto (label_cont);
3967 /* GIMPLE_COND's are very low level; they have embedded
3968 gotos. This particular embedded goto should not be marked
3969 with the location of the original COND_EXPR, as it would
3970 correspond to the COND_EXPR's condition, not the ELSE or the
3971 THEN arms. To avoid marking it with the wrong location, flag
3972 it as "no location". */
3973 gimple_set_do_not_emit_location (g);
3975 gimplify_seq_add_stmt (&seq, g);
3979 if (!have_else_clause_p)
3981 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
3982 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
3984 if (label_cont)
3985 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
3987 gimple_pop_condition (pre_p);
3988 gimple_seq_add_seq (pre_p, seq);
3990 if (ret == GS_ERROR)
3991 ; /* Do nothing. */
3992 else if (have_then_clause_p || have_else_clause_p)
3993 ret = GS_ALL_DONE;
3994 else
3996 /* Both arms are empty; replace the COND_EXPR with its predicate. */
3997 expr = TREE_OPERAND (expr, 0);
3998 gimplify_stmt (&expr, pre_p);
4001 *expr_p = NULL;
4002 return ret;
4005 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4006 to be marked addressable.
4008 We cannot rely on such an expression being directly markable if a temporary
4009 has been created by the gimplification. In this case, we create another
4010 temporary and initialize it with a copy, which will become a store after we
4011 mark it addressable. This can happen if the front-end passed us something
4012 that it could not mark addressable yet, like a Fortran pass-by-reference
4013 parameter (int) floatvar. */
4015 static void
4016 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4018 while (handled_component_p (*expr_p))
4019 expr_p = &TREE_OPERAND (*expr_p, 0);
4020 if (is_gimple_reg (*expr_p))
4022 /* Do not allow an SSA name as the temporary. */
4023 tree var = get_initialized_tmp_var (*expr_p, seq_p, NULL, false);
4024 DECL_GIMPLE_REG_P (var) = 0;
4025 *expr_p = var;
4029 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4030 a call to __builtin_memcpy. */
4032 static enum gimplify_status
4033 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4034 gimple_seq *seq_p)
4036 tree t, to, to_ptr, from, from_ptr;
4037 gcall *gs;
4038 location_t loc = EXPR_LOCATION (*expr_p);
4040 to = TREE_OPERAND (*expr_p, 0);
4041 from = TREE_OPERAND (*expr_p, 1);
4043 /* Mark the RHS addressable. Beware that it may not be possible to do so
4044 directly if a temporary has been created by the gimplification. */
4045 prepare_gimple_addressable (&from, seq_p);
4047 mark_addressable (from);
4048 from_ptr = build_fold_addr_expr_loc (loc, from);
4049 gimplify_arg (&from_ptr, seq_p, loc);
4051 mark_addressable (to);
4052 to_ptr = build_fold_addr_expr_loc (loc, to);
4053 gimplify_arg (&to_ptr, seq_p, loc);
4055 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4057 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4059 if (want_value)
4061 /* tmp = memcpy() */
4062 t = create_tmp_var (TREE_TYPE (to_ptr));
4063 gimple_call_set_lhs (gs, t);
4064 gimplify_seq_add_stmt (seq_p, gs);
4066 *expr_p = build_simple_mem_ref (t);
4067 return GS_ALL_DONE;
4070 gimplify_seq_add_stmt (seq_p, gs);
4071 *expr_p = NULL;
4072 return GS_ALL_DONE;
4075 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4076 a call to __builtin_memset. In this case we know that the RHS is
4077 a CONSTRUCTOR with an empty element list. */
4079 static enum gimplify_status
4080 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4081 gimple_seq *seq_p)
4083 tree t, from, to, to_ptr;
4084 gcall *gs;
4085 location_t loc = EXPR_LOCATION (*expr_p);
4087 /* Assert our assumptions, to abort instead of producing wrong code
4088 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4089 not be immediately exposed. */
4090 from = TREE_OPERAND (*expr_p, 1);
4091 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4092 from = TREE_OPERAND (from, 0);
4094 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4095 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4097 /* Now proceed. */
4098 to = TREE_OPERAND (*expr_p, 0);
4100 to_ptr = build_fold_addr_expr_loc (loc, to);
4101 gimplify_arg (&to_ptr, seq_p, loc);
4102 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4104 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4106 if (want_value)
4108 /* tmp = memset() */
4109 t = create_tmp_var (TREE_TYPE (to_ptr));
4110 gimple_call_set_lhs (gs, t);
4111 gimplify_seq_add_stmt (seq_p, gs);
4113 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4114 return GS_ALL_DONE;
4117 gimplify_seq_add_stmt (seq_p, gs);
4118 *expr_p = NULL;
4119 return GS_ALL_DONE;
4122 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4123 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4124 assignment. Return non-null if we detect a potential overlap. */
4126 struct gimplify_init_ctor_preeval_data
4128 /* The base decl of the lhs object. May be NULL, in which case we
4129 have to assume the lhs is indirect. */
4130 tree lhs_base_decl;
4132 /* The alias set of the lhs object. */
4133 alias_set_type lhs_alias_set;
4136 static tree
4137 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4139 struct gimplify_init_ctor_preeval_data *data
4140 = (struct gimplify_init_ctor_preeval_data *) xdata;
4141 tree t = *tp;
4143 /* If we find the base object, obviously we have overlap. */
4144 if (data->lhs_base_decl == t)
4145 return t;
4147 /* If the constructor component is indirect, determine if we have a
4148 potential overlap with the lhs. The only bits of information we
4149 have to go on at this point are addressability and alias sets. */
4150 if ((INDIRECT_REF_P (t)
4151 || TREE_CODE (t) == MEM_REF)
4152 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4153 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
4154 return t;
4156 /* If the constructor component is a call, determine if it can hide a
4157 potential overlap with the lhs through an INDIRECT_REF like above.
4158 ??? Ugh - this is completely broken. In fact this whole analysis
4159 doesn't look conservative. */
4160 if (TREE_CODE (t) == CALL_EXPR)
4162 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
4164 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
4165 if (POINTER_TYPE_P (TREE_VALUE (type))
4166 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4167 && alias_sets_conflict_p (data->lhs_alias_set,
4168 get_alias_set
4169 (TREE_TYPE (TREE_VALUE (type)))))
4170 return t;
4173 if (IS_TYPE_OR_DECL_P (t))
4174 *walk_subtrees = 0;
4175 return NULL;
4178 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
4179 force values that overlap with the lhs (as described by *DATA)
4180 into temporaries. */
4182 static void
4183 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4184 struct gimplify_init_ctor_preeval_data *data)
4186 enum gimplify_status one;
4188 /* If the value is constant, then there's nothing to pre-evaluate. */
4189 if (TREE_CONSTANT (*expr_p))
4191 /* Ensure it does not have side effects, it might contain a reference to
4192 the object we're initializing. */
4193 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
4194 return;
4197 /* If the type has non-trivial constructors, we can't pre-evaluate. */
4198 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
4199 return;
4201 /* Recurse for nested constructors. */
4202 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
4204 unsigned HOST_WIDE_INT ix;
4205 constructor_elt *ce;
4206 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
4208 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
4209 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
4211 return;
4214 /* If this is a variable sized type, we must remember the size. */
4215 maybe_with_size_expr (expr_p);
4217 /* Gimplify the constructor element to something appropriate for the rhs
4218 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
4219 the gimplifier will consider this a store to memory. Doing this
4220 gimplification now means that we won't have to deal with complicated
4221 language-specific trees, nor trees like SAVE_EXPR that can induce
4222 exponential search behavior. */
4223 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
4224 if (one == GS_ERROR)
4226 *expr_p = NULL;
4227 return;
4230 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
4231 with the lhs, since "a = { .x=a }" doesn't make sense. This will
4232 always be true for all scalars, since is_gimple_mem_rhs insists on a
4233 temporary variable for them. */
4234 if (DECL_P (*expr_p))
4235 return;
4237 /* If this is of variable size, we have no choice but to assume it doesn't
4238 overlap since we can't make a temporary for it. */
4239 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
4240 return;
4242 /* Otherwise, we must search for overlap ... */
4243 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
4244 return;
4246 /* ... and if found, force the value into a temporary. */
4247 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
4250 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
4251 a RANGE_EXPR in a CONSTRUCTOR for an array.
4253 var = lower;
4254 loop_entry:
4255 object[var] = value;
4256 if (var == upper)
4257 goto loop_exit;
4258 var = var + 1;
4259 goto loop_entry;
4260 loop_exit:
4262 We increment var _after_ the loop exit check because we might otherwise
4263 fail if upper == TYPE_MAX_VALUE (type for upper).
4265 Note that we never have to deal with SAVE_EXPRs here, because this has
4266 already been taken care of for us, in gimplify_init_ctor_preeval(). */
4268 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
4269 gimple_seq *, bool);
4271 static void
4272 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
4273 tree value, tree array_elt_type,
4274 gimple_seq *pre_p, bool cleared)
4276 tree loop_entry_label, loop_exit_label, fall_thru_label;
4277 tree var, var_type, cref, tmp;
4279 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
4280 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
4281 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
4283 /* Create and initialize the index variable. */
4284 var_type = TREE_TYPE (upper);
4285 var = create_tmp_var (var_type);
4286 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
4288 /* Add the loop entry label. */
4289 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
4291 /* Build the reference. */
4292 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4293 var, NULL_TREE, NULL_TREE);
4295 /* If we are a constructor, just call gimplify_init_ctor_eval to do
4296 the store. Otherwise just assign value to the reference. */
4298 if (TREE_CODE (value) == CONSTRUCTOR)
4299 /* NB we might have to call ourself recursively through
4300 gimplify_init_ctor_eval if the value is a constructor. */
4301 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4302 pre_p, cleared);
4303 else
4304 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
4306 /* We exit the loop when the index var is equal to the upper bound. */
4307 gimplify_seq_add_stmt (pre_p,
4308 gimple_build_cond (EQ_EXPR, var, upper,
4309 loop_exit_label, fall_thru_label));
4311 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
4313 /* Otherwise, increment the index var... */
4314 tmp = build2 (PLUS_EXPR, var_type, var,
4315 fold_convert (var_type, integer_one_node));
4316 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
4318 /* ...and jump back to the loop entry. */
4319 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
4321 /* Add the loop exit label. */
4322 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
4325 /* Return true if FDECL is accessing a field that is zero sized. */
4327 static bool
4328 zero_sized_field_decl (const_tree fdecl)
4330 if (TREE_CODE (fdecl) == FIELD_DECL && DECL_SIZE (fdecl)
4331 && integer_zerop (DECL_SIZE (fdecl)))
4332 return true;
4333 return false;
4336 /* Return true if TYPE is zero sized. */
4338 static bool
4339 zero_sized_type (const_tree type)
4341 if (AGGREGATE_TYPE_P (type) && TYPE_SIZE (type)
4342 && integer_zerop (TYPE_SIZE (type)))
4343 return true;
4344 return false;
4347 /* A subroutine of gimplify_init_constructor. Generate individual
4348 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
4349 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
4350 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
4351 zeroed first. */
4353 static void
4354 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
4355 gimple_seq *pre_p, bool cleared)
4357 tree array_elt_type = NULL;
4358 unsigned HOST_WIDE_INT ix;
4359 tree purpose, value;
4361 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
4362 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
4364 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
4366 tree cref;
4368 /* NULL values are created above for gimplification errors. */
4369 if (value == NULL)
4370 continue;
4372 if (cleared && initializer_zerop (value))
4373 continue;
4375 /* ??? Here's to hoping the front end fills in all of the indices,
4376 so we don't have to figure out what's missing ourselves. */
4377 gcc_assert (purpose);
4379 /* Skip zero-sized fields, unless value has side-effects. This can
4380 happen with calls to functions returning a zero-sized type, which
4381 we shouldn't discard. As a number of downstream passes don't
4382 expect sets of zero-sized fields, we rely on the gimplification of
4383 the MODIFY_EXPR we make below to drop the assignment statement. */
4384 if (! TREE_SIDE_EFFECTS (value) && zero_sized_field_decl (purpose))
4385 continue;
4387 /* If we have a RANGE_EXPR, we have to build a loop to assign the
4388 whole range. */
4389 if (TREE_CODE (purpose) == RANGE_EXPR)
4391 tree lower = TREE_OPERAND (purpose, 0);
4392 tree upper = TREE_OPERAND (purpose, 1);
4394 /* If the lower bound is equal to upper, just treat it as if
4395 upper was the index. */
4396 if (simple_cst_equal (lower, upper))
4397 purpose = upper;
4398 else
4400 gimplify_init_ctor_eval_range (object, lower, upper, value,
4401 array_elt_type, pre_p, cleared);
4402 continue;
4406 if (array_elt_type)
4408 /* Do not use bitsizetype for ARRAY_REF indices. */
4409 if (TYPE_DOMAIN (TREE_TYPE (object)))
4410 purpose
4411 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
4412 purpose);
4413 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4414 purpose, NULL_TREE, NULL_TREE);
4416 else
4418 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
4419 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
4420 unshare_expr (object), purpose, NULL_TREE);
4423 if (TREE_CODE (value) == CONSTRUCTOR
4424 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
4425 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4426 pre_p, cleared);
4427 else
4429 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
4430 gimplify_and_add (init, pre_p);
4431 ggc_free (init);
4436 /* Return the appropriate RHS predicate for this LHS. */
4438 gimple_predicate
4439 rhs_predicate_for (tree lhs)
4441 if (is_gimple_reg (lhs))
4442 return is_gimple_reg_rhs_or_call;
4443 else
4444 return is_gimple_mem_rhs_or_call;
4447 /* Return the initial guess for an appropriate RHS predicate for this LHS,
4448 before the LHS has been gimplified. */
4450 static gimple_predicate
4451 initial_rhs_predicate_for (tree lhs)
4453 if (is_gimple_reg_type (TREE_TYPE (lhs)))
4454 return is_gimple_reg_rhs_or_call;
4455 else
4456 return is_gimple_mem_rhs_or_call;
4459 /* Gimplify a C99 compound literal expression. This just means adding
4460 the DECL_EXPR before the current statement and using its anonymous
4461 decl instead. */
4463 static enum gimplify_status
4464 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
4465 bool (*gimple_test_f) (tree),
4466 fallback_t fallback)
4468 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
4469 tree decl = DECL_EXPR_DECL (decl_s);
4470 tree init = DECL_INITIAL (decl);
4471 /* Mark the decl as addressable if the compound literal
4472 expression is addressable now, otherwise it is marked too late
4473 after we gimplify the initialization expression. */
4474 if (TREE_ADDRESSABLE (*expr_p))
4475 TREE_ADDRESSABLE (decl) = 1;
4476 /* Otherwise, if we don't need an lvalue and have a literal directly
4477 substitute it. Check if it matches the gimple predicate, as
4478 otherwise we'd generate a new temporary, and we can as well just
4479 use the decl we already have. */
4480 else if (!TREE_ADDRESSABLE (decl)
4481 && init
4482 && (fallback & fb_lvalue) == 0
4483 && gimple_test_f (init))
4485 *expr_p = init;
4486 return GS_OK;
4489 /* Preliminarily mark non-addressed complex variables as eligible
4490 for promotion to gimple registers. We'll transform their uses
4491 as we find them. */
4492 if ((TREE_CODE (TREE_TYPE (decl)) == COMPLEX_TYPE
4493 || TREE_CODE (TREE_TYPE (decl)) == VECTOR_TYPE)
4494 && !TREE_THIS_VOLATILE (decl)
4495 && !needs_to_live_in_memory (decl))
4496 DECL_GIMPLE_REG_P (decl) = 1;
4498 /* If the decl is not addressable, then it is being used in some
4499 expression or on the right hand side of a statement, and it can
4500 be put into a readonly data section. */
4501 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
4502 TREE_READONLY (decl) = 1;
4504 /* This decl isn't mentioned in the enclosing block, so add it to the
4505 list of temps. FIXME it seems a bit of a kludge to say that
4506 anonymous artificial vars aren't pushed, but everything else is. */
4507 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
4508 gimple_add_tmp_var (decl);
4510 gimplify_and_add (decl_s, pre_p);
4511 *expr_p = decl;
4512 return GS_OK;
4515 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
4516 return a new CONSTRUCTOR if something changed. */
4518 static tree
4519 optimize_compound_literals_in_ctor (tree orig_ctor)
4521 tree ctor = orig_ctor;
4522 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
4523 unsigned int idx, num = vec_safe_length (elts);
4525 for (idx = 0; idx < num; idx++)
4527 tree value = (*elts)[idx].value;
4528 tree newval = value;
4529 if (TREE_CODE (value) == CONSTRUCTOR)
4530 newval = optimize_compound_literals_in_ctor (value);
4531 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
4533 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
4534 tree decl = DECL_EXPR_DECL (decl_s);
4535 tree init = DECL_INITIAL (decl);
4537 if (!TREE_ADDRESSABLE (value)
4538 && !TREE_ADDRESSABLE (decl)
4539 && init
4540 && TREE_CODE (init) == CONSTRUCTOR)
4541 newval = optimize_compound_literals_in_ctor (init);
4543 if (newval == value)
4544 continue;
4546 if (ctor == orig_ctor)
4548 ctor = copy_node (orig_ctor);
4549 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
4550 elts = CONSTRUCTOR_ELTS (ctor);
4552 (*elts)[idx].value = newval;
4554 return ctor;
4557 /* A subroutine of gimplify_modify_expr. Break out elements of a
4558 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
4560 Note that we still need to clear any elements that don't have explicit
4561 initializers, so if not all elements are initialized we keep the
4562 original MODIFY_EXPR, we just remove all of the constructor elements.
4564 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
4565 GS_ERROR if we would have to create a temporary when gimplifying
4566 this constructor. Otherwise, return GS_OK.
4568 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
4570 static enum gimplify_status
4571 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4572 bool want_value, bool notify_temp_creation)
4574 tree object, ctor, type;
4575 enum gimplify_status ret;
4576 vec<constructor_elt, va_gc> *elts;
4578 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
4580 if (!notify_temp_creation)
4582 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
4583 is_gimple_lvalue, fb_lvalue);
4584 if (ret == GS_ERROR)
4585 return ret;
4588 object = TREE_OPERAND (*expr_p, 0);
4589 ctor = TREE_OPERAND (*expr_p, 1)
4590 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
4591 type = TREE_TYPE (ctor);
4592 elts = CONSTRUCTOR_ELTS (ctor);
4593 ret = GS_ALL_DONE;
4595 switch (TREE_CODE (type))
4597 case RECORD_TYPE:
4598 case UNION_TYPE:
4599 case QUAL_UNION_TYPE:
4600 case ARRAY_TYPE:
4602 struct gimplify_init_ctor_preeval_data preeval_data;
4603 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
4604 bool cleared, complete_p, valid_const_initializer;
4606 /* Aggregate types must lower constructors to initialization of
4607 individual elements. The exception is that a CONSTRUCTOR node
4608 with no elements indicates zero-initialization of the whole. */
4609 if (vec_safe_is_empty (elts))
4611 if (notify_temp_creation)
4612 return GS_OK;
4613 break;
4616 /* Fetch information about the constructor to direct later processing.
4617 We might want to make static versions of it in various cases, and
4618 can only do so if it known to be a valid constant initializer. */
4619 valid_const_initializer
4620 = categorize_ctor_elements (ctor, &num_nonzero_elements,
4621 &num_ctor_elements, &complete_p);
4623 /* If a const aggregate variable is being initialized, then it
4624 should never be a lose to promote the variable to be static. */
4625 if (valid_const_initializer
4626 && num_nonzero_elements > 1
4627 && TREE_READONLY (object)
4628 && VAR_P (object)
4629 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object)))
4631 if (notify_temp_creation)
4632 return GS_ERROR;
4633 DECL_INITIAL (object) = ctor;
4634 TREE_STATIC (object) = 1;
4635 if (!DECL_NAME (object))
4636 DECL_NAME (object) = create_tmp_var_name ("C");
4637 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
4639 /* ??? C++ doesn't automatically append a .<number> to the
4640 assembler name, and even when it does, it looks at FE private
4641 data structures to figure out what that number should be,
4642 which are not set for this variable. I suppose this is
4643 important for local statics for inline functions, which aren't
4644 "local" in the object file sense. So in order to get a unique
4645 TU-local symbol, we must invoke the lhd version now. */
4646 lhd_set_decl_assembler_name (object);
4648 *expr_p = NULL_TREE;
4649 break;
4652 /* If there are "lots" of initialized elements, even discounting
4653 those that are not address constants (and thus *must* be
4654 computed at runtime), then partition the constructor into
4655 constant and non-constant parts. Block copy the constant
4656 parts in, then generate code for the non-constant parts. */
4657 /* TODO. There's code in cp/typeck.c to do this. */
4659 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
4660 /* store_constructor will ignore the clearing of variable-sized
4661 objects. Initializers for such objects must explicitly set
4662 every field that needs to be set. */
4663 cleared = false;
4664 else if (!complete_p && !CONSTRUCTOR_NO_CLEARING (ctor))
4665 /* If the constructor isn't complete, clear the whole object
4666 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
4668 ??? This ought not to be needed. For any element not present
4669 in the initializer, we should simply set them to zero. Except
4670 we'd need to *find* the elements that are not present, and that
4671 requires trickery to avoid quadratic compile-time behavior in
4672 large cases or excessive memory use in small cases. */
4673 cleared = true;
4674 else if (num_ctor_elements - num_nonzero_elements
4675 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
4676 && num_nonzero_elements < num_ctor_elements / 4)
4677 /* If there are "lots" of zeros, it's more efficient to clear
4678 the memory and then set the nonzero elements. */
4679 cleared = true;
4680 else
4681 cleared = false;
4683 /* If there are "lots" of initialized elements, and all of them
4684 are valid address constants, then the entire initializer can
4685 be dropped to memory, and then memcpy'd out. Don't do this
4686 for sparse arrays, though, as it's more efficient to follow
4687 the standard CONSTRUCTOR behavior of memset followed by
4688 individual element initialization. Also don't do this for small
4689 all-zero initializers (which aren't big enough to merit
4690 clearing), and don't try to make bitwise copies of
4691 TREE_ADDRESSABLE types.
4693 We cannot apply such transformation when compiling chkp static
4694 initializer because creation of initializer image in the memory
4695 will require static initialization of bounds for it. It should
4696 result in another gimplification of similar initializer and we
4697 may fall into infinite loop. */
4698 if (valid_const_initializer
4699 && !(cleared || num_nonzero_elements == 0)
4700 && !TREE_ADDRESSABLE (type)
4701 && (!current_function_decl
4702 || !lookup_attribute ("chkp ctor",
4703 DECL_ATTRIBUTES (current_function_decl))))
4705 HOST_WIDE_INT size = int_size_in_bytes (type);
4706 unsigned int align;
4708 /* ??? We can still get unbounded array types, at least
4709 from the C++ front end. This seems wrong, but attempt
4710 to work around it for now. */
4711 if (size < 0)
4713 size = int_size_in_bytes (TREE_TYPE (object));
4714 if (size >= 0)
4715 TREE_TYPE (ctor) = type = TREE_TYPE (object);
4718 /* Find the maximum alignment we can assume for the object. */
4719 /* ??? Make use of DECL_OFFSET_ALIGN. */
4720 if (DECL_P (object))
4721 align = DECL_ALIGN (object);
4722 else
4723 align = TYPE_ALIGN (type);
4725 /* Do a block move either if the size is so small as to make
4726 each individual move a sub-unit move on average, or if it
4727 is so large as to make individual moves inefficient. */
4728 if (size > 0
4729 && num_nonzero_elements > 1
4730 && (size < num_nonzero_elements
4731 || !can_move_by_pieces (size, align)))
4733 if (notify_temp_creation)
4734 return GS_ERROR;
4736 walk_tree (&ctor, force_labels_r, NULL, NULL);
4737 ctor = tree_output_constant_def (ctor);
4738 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
4739 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
4740 TREE_OPERAND (*expr_p, 1) = ctor;
4742 /* This is no longer an assignment of a CONSTRUCTOR, but
4743 we still may have processing to do on the LHS. So
4744 pretend we didn't do anything here to let that happen. */
4745 return GS_UNHANDLED;
4749 /* If the target is volatile, we have non-zero elements and more than
4750 one field to assign, initialize the target from a temporary. */
4751 if (TREE_THIS_VOLATILE (object)
4752 && !TREE_ADDRESSABLE (type)
4753 && num_nonzero_elements > 0
4754 && vec_safe_length (elts) > 1)
4756 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
4757 TREE_OPERAND (*expr_p, 0) = temp;
4758 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
4759 *expr_p,
4760 build2 (MODIFY_EXPR, void_type_node,
4761 object, temp));
4762 return GS_OK;
4765 if (notify_temp_creation)
4766 return GS_OK;
4768 /* If there are nonzero elements and if needed, pre-evaluate to capture
4769 elements overlapping with the lhs into temporaries. We must do this
4770 before clearing to fetch the values before they are zeroed-out. */
4771 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
4773 preeval_data.lhs_base_decl = get_base_address (object);
4774 if (!DECL_P (preeval_data.lhs_base_decl))
4775 preeval_data.lhs_base_decl = NULL;
4776 preeval_data.lhs_alias_set = get_alias_set (object);
4778 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
4779 pre_p, post_p, &preeval_data);
4782 bool ctor_has_side_effects_p
4783 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
4785 if (cleared)
4787 /* Zap the CONSTRUCTOR element list, which simplifies this case.
4788 Note that we still have to gimplify, in order to handle the
4789 case of variable sized types. Avoid shared tree structures. */
4790 CONSTRUCTOR_ELTS (ctor) = NULL;
4791 TREE_SIDE_EFFECTS (ctor) = 0;
4792 object = unshare_expr (object);
4793 gimplify_stmt (expr_p, pre_p);
4796 /* If we have not block cleared the object, or if there are nonzero
4797 elements in the constructor, or if the constructor has side effects,
4798 add assignments to the individual scalar fields of the object. */
4799 if (!cleared
4800 || num_nonzero_elements > 0
4801 || ctor_has_side_effects_p)
4802 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
4804 *expr_p = NULL_TREE;
4806 break;
4808 case COMPLEX_TYPE:
4810 tree r, i;
4812 if (notify_temp_creation)
4813 return GS_OK;
4815 /* Extract the real and imaginary parts out of the ctor. */
4816 gcc_assert (elts->length () == 2);
4817 r = (*elts)[0].value;
4818 i = (*elts)[1].value;
4819 if (r == NULL || i == NULL)
4821 tree zero = build_zero_cst (TREE_TYPE (type));
4822 if (r == NULL)
4823 r = zero;
4824 if (i == NULL)
4825 i = zero;
4828 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
4829 represent creation of a complex value. */
4830 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
4832 ctor = build_complex (type, r, i);
4833 TREE_OPERAND (*expr_p, 1) = ctor;
4835 else
4837 ctor = build2 (COMPLEX_EXPR, type, r, i);
4838 TREE_OPERAND (*expr_p, 1) = ctor;
4839 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
4840 pre_p,
4841 post_p,
4842 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
4843 fb_rvalue);
4846 break;
4848 case VECTOR_TYPE:
4850 unsigned HOST_WIDE_INT ix;
4851 constructor_elt *ce;
4853 if (notify_temp_creation)
4854 return GS_OK;
4856 /* Go ahead and simplify constant constructors to VECTOR_CST. */
4857 if (TREE_CONSTANT (ctor))
4859 bool constant_p = true;
4860 tree value;
4862 /* Even when ctor is constant, it might contain non-*_CST
4863 elements, such as addresses or trapping values like
4864 1.0/0.0 - 1.0/0.0. Such expressions don't belong
4865 in VECTOR_CST nodes. */
4866 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
4867 if (!CONSTANT_CLASS_P (value))
4869 constant_p = false;
4870 break;
4873 if (constant_p)
4875 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
4876 break;
4879 TREE_CONSTANT (ctor) = 0;
4882 /* Vector types use CONSTRUCTOR all the way through gimple
4883 compilation as a general initializer. */
4884 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
4886 enum gimplify_status tret;
4887 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
4888 fb_rvalue);
4889 if (tret == GS_ERROR)
4890 ret = GS_ERROR;
4891 else if (TREE_STATIC (ctor)
4892 && !initializer_constant_valid_p (ce->value,
4893 TREE_TYPE (ce->value)))
4894 TREE_STATIC (ctor) = 0;
4896 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
4897 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
4899 break;
4901 default:
4902 /* So how did we get a CONSTRUCTOR for a scalar type? */
4903 gcc_unreachable ();
4906 if (ret == GS_ERROR)
4907 return GS_ERROR;
4908 /* If we have gimplified both sides of the initializer but have
4909 not emitted an assignment, do so now. */
4910 if (*expr_p)
4912 tree lhs = TREE_OPERAND (*expr_p, 0);
4913 tree rhs = TREE_OPERAND (*expr_p, 1);
4914 if (want_value && object == lhs)
4915 lhs = unshare_expr (lhs);
4916 gassign *init = gimple_build_assign (lhs, rhs);
4917 gimplify_seq_add_stmt (pre_p, init);
4919 if (want_value)
4921 *expr_p = object;
4922 return GS_OK;
4924 else
4926 *expr_p = NULL;
4927 return GS_ALL_DONE;
4931 /* Given a pointer value OP0, return a simplified version of an
4932 indirection through OP0, or NULL_TREE if no simplification is
4933 possible. This may only be applied to a rhs of an expression.
4934 Note that the resulting type may be different from the type pointed
4935 to in the sense that it is still compatible from the langhooks
4936 point of view. */
4938 static tree
4939 gimple_fold_indirect_ref_rhs (tree t)
4941 return gimple_fold_indirect_ref (t);
4944 /* Subroutine of gimplify_modify_expr to do simplifications of
4945 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
4946 something changes. */
4948 static enum gimplify_status
4949 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
4950 gimple_seq *pre_p, gimple_seq *post_p,
4951 bool want_value)
4953 enum gimplify_status ret = GS_UNHANDLED;
4954 bool changed;
4958 changed = false;
4959 switch (TREE_CODE (*from_p))
4961 case VAR_DECL:
4962 /* If we're assigning from a read-only variable initialized with
4963 a constructor, do the direct assignment from the constructor,
4964 but only if neither source nor target are volatile since this
4965 latter assignment might end up being done on a per-field basis. */
4966 if (DECL_INITIAL (*from_p)
4967 && TREE_READONLY (*from_p)
4968 && !TREE_THIS_VOLATILE (*from_p)
4969 && !TREE_THIS_VOLATILE (*to_p)
4970 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR)
4972 tree old_from = *from_p;
4973 enum gimplify_status subret;
4975 /* Move the constructor into the RHS. */
4976 *from_p = unshare_expr (DECL_INITIAL (*from_p));
4978 /* Let's see if gimplify_init_constructor will need to put
4979 it in memory. */
4980 subret = gimplify_init_constructor (expr_p, NULL, NULL,
4981 false, true);
4982 if (subret == GS_ERROR)
4984 /* If so, revert the change. */
4985 *from_p = old_from;
4987 else
4989 ret = GS_OK;
4990 changed = true;
4993 break;
4994 case INDIRECT_REF:
4996 /* If we have code like
4998 *(const A*)(A*)&x
5000 where the type of "x" is a (possibly cv-qualified variant
5001 of "A"), treat the entire expression as identical to "x".
5002 This kind of code arises in C++ when an object is bound
5003 to a const reference, and if "x" is a TARGET_EXPR we want
5004 to take advantage of the optimization below. */
5005 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5006 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
5007 if (t)
5009 if (TREE_THIS_VOLATILE (t) != volatile_p)
5011 if (DECL_P (t))
5012 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5013 build_fold_addr_expr (t));
5014 if (REFERENCE_CLASS_P (t))
5015 TREE_THIS_VOLATILE (t) = volatile_p;
5017 *from_p = t;
5018 ret = GS_OK;
5019 changed = true;
5021 break;
5024 case TARGET_EXPR:
5026 /* If we are initializing something from a TARGET_EXPR, strip the
5027 TARGET_EXPR and initialize it directly, if possible. This can't
5028 be done if the initializer is void, since that implies that the
5029 temporary is set in some non-trivial way.
5031 ??? What about code that pulls out the temp and uses it
5032 elsewhere? I think that such code never uses the TARGET_EXPR as
5033 an initializer. If I'm wrong, we'll die because the temp won't
5034 have any RTL. In that case, I guess we'll need to replace
5035 references somehow. */
5036 tree init = TARGET_EXPR_INITIAL (*from_p);
5038 if (init
5039 && !VOID_TYPE_P (TREE_TYPE (init)))
5041 *from_p = init;
5042 ret = GS_OK;
5043 changed = true;
5046 break;
5048 case COMPOUND_EXPR:
5049 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5050 caught. */
5051 gimplify_compound_expr (from_p, pre_p, true);
5052 ret = GS_OK;
5053 changed = true;
5054 break;
5056 case CONSTRUCTOR:
5057 /* If we already made some changes, let the front end have a
5058 crack at this before we break it down. */
5059 if (ret != GS_UNHANDLED)
5060 break;
5061 /* If we're initializing from a CONSTRUCTOR, break this into
5062 individual MODIFY_EXPRs. */
5063 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5064 false);
5066 case COND_EXPR:
5067 /* If we're assigning to a non-register type, push the assignment
5068 down into the branches. This is mandatory for ADDRESSABLE types,
5069 since we cannot generate temporaries for such, but it saves a
5070 copy in other cases as well. */
5071 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5073 /* This code should mirror the code in gimplify_cond_expr. */
5074 enum tree_code code = TREE_CODE (*expr_p);
5075 tree cond = *from_p;
5076 tree result = *to_p;
5078 ret = gimplify_expr (&result, pre_p, post_p,
5079 is_gimple_lvalue, fb_lvalue);
5080 if (ret != GS_ERROR)
5081 ret = GS_OK;
5083 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
5084 TREE_OPERAND (cond, 1)
5085 = build2 (code, void_type_node, result,
5086 TREE_OPERAND (cond, 1));
5087 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5088 TREE_OPERAND (cond, 2)
5089 = build2 (code, void_type_node, unshare_expr (result),
5090 TREE_OPERAND (cond, 2));
5092 TREE_TYPE (cond) = void_type_node;
5093 recalculate_side_effects (cond);
5095 if (want_value)
5097 gimplify_and_add (cond, pre_p);
5098 *expr_p = unshare_expr (result);
5100 else
5101 *expr_p = cond;
5102 return ret;
5104 break;
5106 case CALL_EXPR:
5107 /* For calls that return in memory, give *to_p as the CALL_EXPR's
5108 return slot so that we don't generate a temporary. */
5109 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
5110 && aggregate_value_p (*from_p, *from_p))
5112 bool use_target;
5114 if (!(rhs_predicate_for (*to_p))(*from_p))
5115 /* If we need a temporary, *to_p isn't accurate. */
5116 use_target = false;
5117 /* It's OK to use the return slot directly unless it's an NRV. */
5118 else if (TREE_CODE (*to_p) == RESULT_DECL
5119 && DECL_NAME (*to_p) == NULL_TREE
5120 && needs_to_live_in_memory (*to_p))
5121 use_target = true;
5122 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
5123 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
5124 /* Don't force regs into memory. */
5125 use_target = false;
5126 else if (TREE_CODE (*expr_p) == INIT_EXPR)
5127 /* It's OK to use the target directly if it's being
5128 initialized. */
5129 use_target = true;
5130 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
5131 != INTEGER_CST)
5132 /* Always use the target and thus RSO for variable-sized types.
5133 GIMPLE cannot deal with a variable-sized assignment
5134 embedded in a call statement. */
5135 use_target = true;
5136 else if (TREE_CODE (*to_p) != SSA_NAME
5137 && (!is_gimple_variable (*to_p)
5138 || needs_to_live_in_memory (*to_p)))
5139 /* Don't use the original target if it's already addressable;
5140 if its address escapes, and the called function uses the
5141 NRV optimization, a conforming program could see *to_p
5142 change before the called function returns; see c++/19317.
5143 When optimizing, the return_slot pass marks more functions
5144 as safe after we have escape info. */
5145 use_target = false;
5146 else
5147 use_target = true;
5149 if (use_target)
5151 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
5152 mark_addressable (*to_p);
5155 break;
5157 case WITH_SIZE_EXPR:
5158 /* Likewise for calls that return an aggregate of non-constant size,
5159 since we would not be able to generate a temporary at all. */
5160 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
5162 *from_p = TREE_OPERAND (*from_p, 0);
5163 /* We don't change ret in this case because the
5164 WITH_SIZE_EXPR might have been added in
5165 gimplify_modify_expr, so returning GS_OK would lead to an
5166 infinite loop. */
5167 changed = true;
5169 break;
5171 /* If we're initializing from a container, push the initialization
5172 inside it. */
5173 case CLEANUP_POINT_EXPR:
5174 case BIND_EXPR:
5175 case STATEMENT_LIST:
5177 tree wrap = *from_p;
5178 tree t;
5180 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
5181 fb_lvalue);
5182 if (ret != GS_ERROR)
5183 ret = GS_OK;
5185 t = voidify_wrapper_expr (wrap, *expr_p);
5186 gcc_assert (t == *expr_p);
5188 if (want_value)
5190 gimplify_and_add (wrap, pre_p);
5191 *expr_p = unshare_expr (*to_p);
5193 else
5194 *expr_p = wrap;
5195 return GS_OK;
5198 case COMPOUND_LITERAL_EXPR:
5200 tree complit = TREE_OPERAND (*expr_p, 1);
5201 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
5202 tree decl = DECL_EXPR_DECL (decl_s);
5203 tree init = DECL_INITIAL (decl);
5205 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
5206 into struct T x = { 0, 1, 2 } if the address of the
5207 compound literal has never been taken. */
5208 if (!TREE_ADDRESSABLE (complit)
5209 && !TREE_ADDRESSABLE (decl)
5210 && init)
5212 *expr_p = copy_node (*expr_p);
5213 TREE_OPERAND (*expr_p, 1) = init;
5214 return GS_OK;
5218 default:
5219 break;
5222 while (changed);
5224 return ret;
5228 /* Return true if T looks like a valid GIMPLE statement. */
5230 static bool
5231 is_gimple_stmt (tree t)
5233 const enum tree_code code = TREE_CODE (t);
5235 switch (code)
5237 case NOP_EXPR:
5238 /* The only valid NOP_EXPR is the empty statement. */
5239 return IS_EMPTY_STMT (t);
5241 case BIND_EXPR:
5242 case COND_EXPR:
5243 /* These are only valid if they're void. */
5244 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
5246 case SWITCH_EXPR:
5247 case GOTO_EXPR:
5248 case RETURN_EXPR:
5249 case LABEL_EXPR:
5250 case CASE_LABEL_EXPR:
5251 case TRY_CATCH_EXPR:
5252 case TRY_FINALLY_EXPR:
5253 case EH_FILTER_EXPR:
5254 case CATCH_EXPR:
5255 case ASM_EXPR:
5256 case STATEMENT_LIST:
5257 case OACC_PARALLEL:
5258 case OACC_KERNELS:
5259 case OACC_DATA:
5260 case OACC_HOST_DATA:
5261 case OACC_DECLARE:
5262 case OACC_UPDATE:
5263 case OACC_ENTER_DATA:
5264 case OACC_EXIT_DATA:
5265 case OACC_CACHE:
5266 case OMP_PARALLEL:
5267 case OMP_FOR:
5268 case OMP_SIMD:
5269 case CILK_SIMD:
5270 case OMP_DISTRIBUTE:
5271 case OACC_LOOP:
5272 case OMP_SECTIONS:
5273 case OMP_SECTION:
5274 case OMP_SINGLE:
5275 case OMP_MASTER:
5276 case OMP_TASKGROUP:
5277 case OMP_ORDERED:
5278 case OMP_CRITICAL:
5279 case OMP_TASK:
5280 case OMP_TARGET:
5281 case OMP_TARGET_DATA:
5282 case OMP_TARGET_UPDATE:
5283 case OMP_TARGET_ENTER_DATA:
5284 case OMP_TARGET_EXIT_DATA:
5285 case OMP_TASKLOOP:
5286 case OMP_TEAMS:
5287 /* These are always void. */
5288 return true;
5290 case CALL_EXPR:
5291 case MODIFY_EXPR:
5292 case PREDICT_EXPR:
5293 /* These are valid regardless of their type. */
5294 return true;
5296 default:
5297 return false;
5302 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
5303 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
5304 DECL_GIMPLE_REG_P set.
5306 IMPORTANT NOTE: This promotion is performed by introducing a load of the
5307 other, unmodified part of the complex object just before the total store.
5308 As a consequence, if the object is still uninitialized, an undefined value
5309 will be loaded into a register, which may result in a spurious exception
5310 if the register is floating-point and the value happens to be a signaling
5311 NaN for example. Then the fully-fledged complex operations lowering pass
5312 followed by a DCE pass are necessary in order to fix things up. */
5314 static enum gimplify_status
5315 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
5316 bool want_value)
5318 enum tree_code code, ocode;
5319 tree lhs, rhs, new_rhs, other, realpart, imagpart;
5321 lhs = TREE_OPERAND (*expr_p, 0);
5322 rhs = TREE_OPERAND (*expr_p, 1);
5323 code = TREE_CODE (lhs);
5324 lhs = TREE_OPERAND (lhs, 0);
5326 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
5327 other = build1 (ocode, TREE_TYPE (rhs), lhs);
5328 TREE_NO_WARNING (other) = 1;
5329 other = get_formal_tmp_var (other, pre_p);
5331 realpart = code == REALPART_EXPR ? rhs : other;
5332 imagpart = code == REALPART_EXPR ? other : rhs;
5334 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
5335 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
5336 else
5337 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
5339 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
5340 *expr_p = (want_value) ? rhs : NULL_TREE;
5342 return GS_ALL_DONE;
5345 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
5347 modify_expr
5348 : varname '=' rhs
5349 | '*' ID '=' rhs
5351 PRE_P points to the list where side effects that must happen before
5352 *EXPR_P should be stored.
5354 POST_P points to the list where side effects that must happen after
5355 *EXPR_P should be stored.
5357 WANT_VALUE is nonzero iff we want to use the value of this expression
5358 in another expression. */
5360 static enum gimplify_status
5361 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5362 bool want_value)
5364 tree *from_p = &TREE_OPERAND (*expr_p, 1);
5365 tree *to_p = &TREE_OPERAND (*expr_p, 0);
5366 enum gimplify_status ret = GS_UNHANDLED;
5367 gimple *assign;
5368 location_t loc = EXPR_LOCATION (*expr_p);
5369 gimple_stmt_iterator gsi;
5371 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
5372 || TREE_CODE (*expr_p) == INIT_EXPR);
5374 /* Trying to simplify a clobber using normal logic doesn't work,
5375 so handle it here. */
5376 if (TREE_CLOBBER_P (*from_p))
5378 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5379 if (ret == GS_ERROR)
5380 return ret;
5381 gcc_assert (!want_value
5382 && (VAR_P (*to_p) || TREE_CODE (*to_p) == MEM_REF));
5383 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
5384 *expr_p = NULL;
5385 return GS_ALL_DONE;
5388 /* Insert pointer conversions required by the middle-end that are not
5389 required by the frontend. This fixes middle-end type checking for
5390 for example gcc.dg/redecl-6.c. */
5391 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
5393 STRIP_USELESS_TYPE_CONVERSION (*from_p);
5394 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
5395 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
5398 /* See if any simplifications can be done based on what the RHS is. */
5399 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5400 want_value);
5401 if (ret != GS_UNHANDLED)
5402 return ret;
5404 /* For zero sized types only gimplify the left hand side and right hand
5405 side as statements and throw away the assignment. Do this after
5406 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
5407 types properly. */
5408 if (zero_sized_type (TREE_TYPE (*from_p)) && !want_value)
5410 gimplify_stmt (from_p, pre_p);
5411 gimplify_stmt (to_p, pre_p);
5412 *expr_p = NULL_TREE;
5413 return GS_ALL_DONE;
5416 /* If the value being copied is of variable width, compute the length
5417 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
5418 before gimplifying any of the operands so that we can resolve any
5419 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
5420 the size of the expression to be copied, not of the destination, so
5421 that is what we must do here. */
5422 maybe_with_size_expr (from_p);
5424 /* As a special case, we have to temporarily allow for assignments
5425 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
5426 a toplevel statement, when gimplifying the GENERIC expression
5427 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
5428 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
5430 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
5431 prevent gimplify_expr from trying to create a new temporary for
5432 foo's LHS, we tell it that it should only gimplify until it
5433 reaches the CALL_EXPR. On return from gimplify_expr, the newly
5434 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
5435 and all we need to do here is set 'a' to be its LHS. */
5437 /* Gimplify the RHS first for C++17 and bug 71104. */
5438 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
5439 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
5440 if (ret == GS_ERROR)
5441 return ret;
5443 /* Then gimplify the LHS. */
5444 /* If we gimplified the RHS to a CALL_EXPR and that call may return
5445 twice we have to make sure to gimplify into non-SSA as otherwise
5446 the abnormal edge added later will make those defs not dominate
5447 their uses.
5448 ??? Technically this applies only to the registers used in the
5449 resulting non-register *TO_P. */
5450 bool saved_into_ssa = gimplify_ctxp->into_ssa;
5451 if (saved_into_ssa
5452 && TREE_CODE (*from_p) == CALL_EXPR
5453 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
5454 gimplify_ctxp->into_ssa = false;
5455 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5456 gimplify_ctxp->into_ssa = saved_into_ssa;
5457 if (ret == GS_ERROR)
5458 return ret;
5460 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
5461 guess for the predicate was wrong. */
5462 gimple_predicate final_pred = rhs_predicate_for (*to_p);
5463 if (final_pred != initial_pred)
5465 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
5466 if (ret == GS_ERROR)
5467 return ret;
5470 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
5471 size as argument to the call. */
5472 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5474 tree call = TREE_OPERAND (*from_p, 0);
5475 tree vlasize = TREE_OPERAND (*from_p, 1);
5477 if (TREE_CODE (call) == CALL_EXPR
5478 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
5480 int nargs = call_expr_nargs (call);
5481 tree type = TREE_TYPE (call);
5482 tree ap = CALL_EXPR_ARG (call, 0);
5483 tree tag = CALL_EXPR_ARG (call, 1);
5484 tree aptag = CALL_EXPR_ARG (call, 2);
5485 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
5486 IFN_VA_ARG, type,
5487 nargs + 1, ap, tag,
5488 aptag, vlasize);
5489 TREE_OPERAND (*from_p, 0) = newcall;
5493 /* Now see if the above changed *from_p to something we handle specially. */
5494 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5495 want_value);
5496 if (ret != GS_UNHANDLED)
5497 return ret;
5499 /* If we've got a variable sized assignment between two lvalues (i.e. does
5500 not involve a call), then we can make things a bit more straightforward
5501 by converting the assignment to memcpy or memset. */
5502 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5504 tree from = TREE_OPERAND (*from_p, 0);
5505 tree size = TREE_OPERAND (*from_p, 1);
5507 if (TREE_CODE (from) == CONSTRUCTOR)
5508 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
5510 if (is_gimple_addressable (from))
5512 *from_p = from;
5513 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
5514 pre_p);
5518 /* Transform partial stores to non-addressable complex variables into
5519 total stores. This allows us to use real instead of virtual operands
5520 for these variables, which improves optimization. */
5521 if ((TREE_CODE (*to_p) == REALPART_EXPR
5522 || TREE_CODE (*to_p) == IMAGPART_EXPR)
5523 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
5524 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
5526 /* Try to alleviate the effects of the gimplification creating artificial
5527 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
5528 make sure not to create DECL_DEBUG_EXPR links across functions. */
5529 if (!gimplify_ctxp->into_ssa
5530 && VAR_P (*from_p)
5531 && DECL_IGNORED_P (*from_p)
5532 && DECL_P (*to_p)
5533 && !DECL_IGNORED_P (*to_p)
5534 && decl_function_context (*to_p) == current_function_decl)
5536 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
5537 DECL_NAME (*from_p)
5538 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
5539 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
5540 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
5543 if (want_value && TREE_THIS_VOLATILE (*to_p))
5544 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
5546 if (TREE_CODE (*from_p) == CALL_EXPR)
5548 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
5549 instead of a GIMPLE_ASSIGN. */
5550 gcall *call_stmt;
5551 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
5553 /* Gimplify internal functions created in the FEs. */
5554 int nargs = call_expr_nargs (*from_p), i;
5555 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
5556 auto_vec<tree> vargs (nargs);
5558 for (i = 0; i < nargs; i++)
5560 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
5561 EXPR_LOCATION (*from_p));
5562 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
5564 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
5565 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
5567 else
5569 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
5570 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
5571 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
5572 tree fndecl = get_callee_fndecl (*from_p);
5573 if (fndecl
5574 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL
5575 && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_EXPECT
5576 && call_expr_nargs (*from_p) == 3)
5577 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
5578 CALL_EXPR_ARG (*from_p, 0),
5579 CALL_EXPR_ARG (*from_p, 1),
5580 CALL_EXPR_ARG (*from_p, 2));
5581 else
5583 call_stmt = gimple_build_call_from_tree (*from_p);
5584 gimple_call_set_fntype (call_stmt, TREE_TYPE (fnptrtype));
5587 notice_special_calls (call_stmt);
5588 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
5589 gimple_call_set_lhs (call_stmt, *to_p);
5590 else if (TREE_CODE (*to_p) == SSA_NAME)
5591 /* The above is somewhat premature, avoid ICEing later for a
5592 SSA name w/o a definition. We may have uses in the GIMPLE IL.
5593 ??? This doesn't make it a default-def. */
5594 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
5595 assign = call_stmt;
5597 else
5599 assign = gimple_build_assign (*to_p, *from_p);
5600 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
5601 if (COMPARISON_CLASS_P (*from_p))
5602 gimple_set_no_warning (assign, TREE_NO_WARNING (*from_p));
5605 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
5607 /* We should have got an SSA name from the start. */
5608 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
5609 || ! gimple_in_ssa_p (cfun));
5612 gimplify_seq_add_stmt (pre_p, assign);
5613 gsi = gsi_last (*pre_p);
5614 maybe_fold_stmt (&gsi);
5616 if (want_value)
5618 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
5619 return GS_OK;
5621 else
5622 *expr_p = NULL;
5624 return GS_ALL_DONE;
5627 /* Gimplify a comparison between two variable-sized objects. Do this
5628 with a call to BUILT_IN_MEMCMP. */
5630 static enum gimplify_status
5631 gimplify_variable_sized_compare (tree *expr_p)
5633 location_t loc = EXPR_LOCATION (*expr_p);
5634 tree op0 = TREE_OPERAND (*expr_p, 0);
5635 tree op1 = TREE_OPERAND (*expr_p, 1);
5636 tree t, arg, dest, src, expr;
5638 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
5639 arg = unshare_expr (arg);
5640 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
5641 src = build_fold_addr_expr_loc (loc, op1);
5642 dest = build_fold_addr_expr_loc (loc, op0);
5643 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
5644 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
5646 expr
5647 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
5648 SET_EXPR_LOCATION (expr, loc);
5649 *expr_p = expr;
5651 return GS_OK;
5654 /* Gimplify a comparison between two aggregate objects of integral scalar
5655 mode as a comparison between the bitwise equivalent scalar values. */
5657 static enum gimplify_status
5658 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
5660 location_t loc = EXPR_LOCATION (*expr_p);
5661 tree op0 = TREE_OPERAND (*expr_p, 0);
5662 tree op1 = TREE_OPERAND (*expr_p, 1);
5664 tree type = TREE_TYPE (op0);
5665 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
5667 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
5668 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
5670 *expr_p
5671 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
5673 return GS_OK;
5676 /* Gimplify an expression sequence. This function gimplifies each
5677 expression and rewrites the original expression with the last
5678 expression of the sequence in GIMPLE form.
5680 PRE_P points to the list where the side effects for all the
5681 expressions in the sequence will be emitted.
5683 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
5685 static enum gimplify_status
5686 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
5688 tree t = *expr_p;
5692 tree *sub_p = &TREE_OPERAND (t, 0);
5694 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
5695 gimplify_compound_expr (sub_p, pre_p, false);
5696 else
5697 gimplify_stmt (sub_p, pre_p);
5699 t = TREE_OPERAND (t, 1);
5701 while (TREE_CODE (t) == COMPOUND_EXPR);
5703 *expr_p = t;
5704 if (want_value)
5705 return GS_OK;
5706 else
5708 gimplify_stmt (expr_p, pre_p);
5709 return GS_ALL_DONE;
5713 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
5714 gimplify. After gimplification, EXPR_P will point to a new temporary
5715 that holds the original value of the SAVE_EXPR node.
5717 PRE_P points to the list where side effects that must happen before
5718 *EXPR_P should be stored. */
5720 static enum gimplify_status
5721 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5723 enum gimplify_status ret = GS_ALL_DONE;
5724 tree val;
5726 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
5727 val = TREE_OPERAND (*expr_p, 0);
5729 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
5730 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
5732 /* The operand may be a void-valued expression such as SAVE_EXPRs
5733 generated by the Java frontend for class initialization. It is
5734 being executed only for its side-effects. */
5735 if (TREE_TYPE (val) == void_type_node)
5737 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5738 is_gimple_stmt, fb_none);
5739 val = NULL;
5741 else
5742 /* The temporary may not be an SSA name as later abnormal and EH
5743 control flow may invalidate use/def domination. */
5744 val = get_initialized_tmp_var (val, pre_p, post_p, false);
5746 TREE_OPERAND (*expr_p, 0) = val;
5747 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
5750 *expr_p = val;
5752 return ret;
5755 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
5757 unary_expr
5758 : ...
5759 | '&' varname
5762 PRE_P points to the list where side effects that must happen before
5763 *EXPR_P should be stored.
5765 POST_P points to the list where side effects that must happen after
5766 *EXPR_P should be stored. */
5768 static enum gimplify_status
5769 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5771 tree expr = *expr_p;
5772 tree op0 = TREE_OPERAND (expr, 0);
5773 enum gimplify_status ret;
5774 location_t loc = EXPR_LOCATION (*expr_p);
5776 switch (TREE_CODE (op0))
5778 case INDIRECT_REF:
5779 do_indirect_ref:
5780 /* Check if we are dealing with an expression of the form '&*ptr'.
5781 While the front end folds away '&*ptr' into 'ptr', these
5782 expressions may be generated internally by the compiler (e.g.,
5783 builtins like __builtin_va_end). */
5784 /* Caution: the silent array decomposition semantics we allow for
5785 ADDR_EXPR means we can't always discard the pair. */
5786 /* Gimplification of the ADDR_EXPR operand may drop
5787 cv-qualification conversions, so make sure we add them if
5788 needed. */
5790 tree op00 = TREE_OPERAND (op0, 0);
5791 tree t_expr = TREE_TYPE (expr);
5792 tree t_op00 = TREE_TYPE (op00);
5794 if (!useless_type_conversion_p (t_expr, t_op00))
5795 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
5796 *expr_p = op00;
5797 ret = GS_OK;
5799 break;
5801 case VIEW_CONVERT_EXPR:
5802 /* Take the address of our operand and then convert it to the type of
5803 this ADDR_EXPR.
5805 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
5806 all clear. The impact of this transformation is even less clear. */
5808 /* If the operand is a useless conversion, look through it. Doing so
5809 guarantees that the ADDR_EXPR and its operand will remain of the
5810 same type. */
5811 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
5812 op0 = TREE_OPERAND (op0, 0);
5814 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
5815 build_fold_addr_expr_loc (loc,
5816 TREE_OPERAND (op0, 0)));
5817 ret = GS_OK;
5818 break;
5820 case MEM_REF:
5821 if (integer_zerop (TREE_OPERAND (op0, 1)))
5822 goto do_indirect_ref;
5824 /* fall through */
5826 default:
5827 /* If we see a call to a declared builtin or see its address
5828 being taken (we can unify those cases here) then we can mark
5829 the builtin for implicit generation by GCC. */
5830 if (TREE_CODE (op0) == FUNCTION_DECL
5831 && DECL_BUILT_IN_CLASS (op0) == BUILT_IN_NORMAL
5832 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
5833 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
5835 /* We use fb_either here because the C frontend sometimes takes
5836 the address of a call that returns a struct; see
5837 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
5838 the implied temporary explicit. */
5840 /* Make the operand addressable. */
5841 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
5842 is_gimple_addressable, fb_either);
5843 if (ret == GS_ERROR)
5844 break;
5846 /* Then mark it. Beware that it may not be possible to do so directly
5847 if a temporary has been created by the gimplification. */
5848 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
5850 op0 = TREE_OPERAND (expr, 0);
5852 /* For various reasons, the gimplification of the expression
5853 may have made a new INDIRECT_REF. */
5854 if (TREE_CODE (op0) == INDIRECT_REF)
5855 goto do_indirect_ref;
5857 mark_addressable (TREE_OPERAND (expr, 0));
5859 /* The FEs may end up building ADDR_EXPRs early on a decl with
5860 an incomplete type. Re-build ADDR_EXPRs in canonical form
5861 here. */
5862 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
5863 *expr_p = build_fold_addr_expr (op0);
5865 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
5866 recompute_tree_invariant_for_addr_expr (*expr_p);
5868 /* If we re-built the ADDR_EXPR add a conversion to the original type
5869 if required. */
5870 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
5871 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
5873 break;
5876 return ret;
5879 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
5880 value; output operands should be a gimple lvalue. */
5882 static enum gimplify_status
5883 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5885 tree expr;
5886 int noutputs;
5887 const char **oconstraints;
5888 int i;
5889 tree link;
5890 const char *constraint;
5891 bool allows_mem, allows_reg, is_inout;
5892 enum gimplify_status ret, tret;
5893 gasm *stmt;
5894 vec<tree, va_gc> *inputs;
5895 vec<tree, va_gc> *outputs;
5896 vec<tree, va_gc> *clobbers;
5897 vec<tree, va_gc> *labels;
5898 tree link_next;
5900 expr = *expr_p;
5901 noutputs = list_length (ASM_OUTPUTS (expr));
5902 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
5904 inputs = NULL;
5905 outputs = NULL;
5906 clobbers = NULL;
5907 labels = NULL;
5909 ret = GS_ALL_DONE;
5910 link_next = NULL_TREE;
5911 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
5913 bool ok;
5914 size_t constraint_len;
5916 link_next = TREE_CHAIN (link);
5918 oconstraints[i]
5919 = constraint
5920 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
5921 constraint_len = strlen (constraint);
5922 if (constraint_len == 0)
5923 continue;
5925 ok = parse_output_constraint (&constraint, i, 0, 0,
5926 &allows_mem, &allows_reg, &is_inout);
5927 if (!ok)
5929 ret = GS_ERROR;
5930 is_inout = false;
5933 if (!allows_reg && allows_mem)
5934 mark_addressable (TREE_VALUE (link));
5936 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5937 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
5938 fb_lvalue | fb_mayfail);
5939 if (tret == GS_ERROR)
5941 error ("invalid lvalue in asm output %d", i);
5942 ret = tret;
5945 /* If the constraint does not allow memory make sure we gimplify
5946 it to a register if it is not already but its base is. This
5947 happens for complex and vector components. */
5948 if (!allows_mem)
5950 tree op = TREE_VALUE (link);
5951 if (! is_gimple_val (op)
5952 && is_gimple_reg_type (TREE_TYPE (op))
5953 && is_gimple_reg (get_base_address (op)))
5955 tree tem = create_tmp_reg (TREE_TYPE (op));
5956 tree ass;
5957 if (is_inout)
5959 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
5960 tem, unshare_expr (op));
5961 gimplify_and_add (ass, pre_p);
5963 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
5964 gimplify_and_add (ass, post_p);
5966 TREE_VALUE (link) = tem;
5967 tret = GS_OK;
5971 vec_safe_push (outputs, link);
5972 TREE_CHAIN (link) = NULL_TREE;
5974 if (is_inout)
5976 /* An input/output operand. To give the optimizers more
5977 flexibility, split it into separate input and output
5978 operands. */
5979 tree input;
5980 /* Buffer big enough to format a 32-bit UINT_MAX into. */
5981 char buf[11];
5983 /* Turn the in/out constraint into an output constraint. */
5984 char *p = xstrdup (constraint);
5985 p[0] = '=';
5986 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
5988 /* And add a matching input constraint. */
5989 if (allows_reg)
5991 sprintf (buf, "%u", i);
5993 /* If there are multiple alternatives in the constraint,
5994 handle each of them individually. Those that allow register
5995 will be replaced with operand number, the others will stay
5996 unchanged. */
5997 if (strchr (p, ',') != NULL)
5999 size_t len = 0, buflen = strlen (buf);
6000 char *beg, *end, *str, *dst;
6002 for (beg = p + 1;;)
6004 end = strchr (beg, ',');
6005 if (end == NULL)
6006 end = strchr (beg, '\0');
6007 if ((size_t) (end - beg) < buflen)
6008 len += buflen + 1;
6009 else
6010 len += end - beg + 1;
6011 if (*end)
6012 beg = end + 1;
6013 else
6014 break;
6017 str = (char *) alloca (len);
6018 for (beg = p + 1, dst = str;;)
6020 const char *tem;
6021 bool mem_p, reg_p, inout_p;
6023 end = strchr (beg, ',');
6024 if (end)
6025 *end = '\0';
6026 beg[-1] = '=';
6027 tem = beg - 1;
6028 parse_output_constraint (&tem, i, 0, 0,
6029 &mem_p, &reg_p, &inout_p);
6030 if (dst != str)
6031 *dst++ = ',';
6032 if (reg_p)
6034 memcpy (dst, buf, buflen);
6035 dst += buflen;
6037 else
6039 if (end)
6040 len = end - beg;
6041 else
6042 len = strlen (beg);
6043 memcpy (dst, beg, len);
6044 dst += len;
6046 if (end)
6047 beg = end + 1;
6048 else
6049 break;
6051 *dst = '\0';
6052 input = build_string (dst - str, str);
6054 else
6055 input = build_string (strlen (buf), buf);
6057 else
6058 input = build_string (constraint_len - 1, constraint + 1);
6060 free (p);
6062 input = build_tree_list (build_tree_list (NULL_TREE, input),
6063 unshare_expr (TREE_VALUE (link)));
6064 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
6068 link_next = NULL_TREE;
6069 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
6071 link_next = TREE_CHAIN (link);
6072 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6073 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
6074 oconstraints, &allows_mem, &allows_reg);
6076 /* If we can't make copies, we can only accept memory. */
6077 if (TREE_ADDRESSABLE (TREE_TYPE (TREE_VALUE (link))))
6079 if (allows_mem)
6080 allows_reg = 0;
6081 else
6083 error ("impossible constraint in %<asm%>");
6084 error ("non-memory input %d must stay in memory", i);
6085 return GS_ERROR;
6089 /* If the operand is a memory input, it should be an lvalue. */
6090 if (!allows_reg && allows_mem)
6092 tree inputv = TREE_VALUE (link);
6093 STRIP_NOPS (inputv);
6094 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
6095 || TREE_CODE (inputv) == PREINCREMENT_EXPR
6096 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
6097 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
6098 || TREE_CODE (inputv) == MODIFY_EXPR)
6099 TREE_VALUE (link) = error_mark_node;
6100 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6101 is_gimple_lvalue, fb_lvalue | fb_mayfail);
6102 if (tret != GS_ERROR)
6104 /* Unlike output operands, memory inputs are not guaranteed
6105 to be lvalues by the FE, and while the expressions are
6106 marked addressable there, if it is e.g. a statement
6107 expression, temporaries in it might not end up being
6108 addressable. They might be already used in the IL and thus
6109 it is too late to make them addressable now though. */
6110 tree x = TREE_VALUE (link);
6111 while (handled_component_p (x))
6112 x = TREE_OPERAND (x, 0);
6113 if (TREE_CODE (x) == MEM_REF
6114 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
6115 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
6116 if ((VAR_P (x)
6117 || TREE_CODE (x) == PARM_DECL
6118 || TREE_CODE (x) == RESULT_DECL)
6119 && !TREE_ADDRESSABLE (x)
6120 && is_gimple_reg (x))
6122 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
6123 input_location), 0,
6124 "memory input %d is not directly addressable",
6126 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
6129 mark_addressable (TREE_VALUE (link));
6130 if (tret == GS_ERROR)
6132 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
6133 "memory input %d is not directly addressable", i);
6134 ret = tret;
6137 else
6139 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6140 is_gimple_asm_val, fb_rvalue);
6141 if (tret == GS_ERROR)
6142 ret = tret;
6145 TREE_CHAIN (link) = NULL_TREE;
6146 vec_safe_push (inputs, link);
6149 link_next = NULL_TREE;
6150 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
6152 link_next = TREE_CHAIN (link);
6153 TREE_CHAIN (link) = NULL_TREE;
6154 vec_safe_push (clobbers, link);
6157 link_next = NULL_TREE;
6158 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
6160 link_next = TREE_CHAIN (link);
6161 TREE_CHAIN (link) = NULL_TREE;
6162 vec_safe_push (labels, link);
6165 /* Do not add ASMs with errors to the gimple IL stream. */
6166 if (ret != GS_ERROR)
6168 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
6169 inputs, outputs, clobbers, labels);
6171 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
6172 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
6174 gimplify_seq_add_stmt (pre_p, stmt);
6177 return ret;
6180 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
6181 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
6182 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
6183 return to this function.
6185 FIXME should we complexify the prequeue handling instead? Or use flags
6186 for all the cleanups and let the optimizer tighten them up? The current
6187 code seems pretty fragile; it will break on a cleanup within any
6188 non-conditional nesting. But any such nesting would be broken, anyway;
6189 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
6190 and continues out of it. We can do that at the RTL level, though, so
6191 having an optimizer to tighten up try/finally regions would be a Good
6192 Thing. */
6194 static enum gimplify_status
6195 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
6197 gimple_stmt_iterator iter;
6198 gimple_seq body_sequence = NULL;
6200 tree temp = voidify_wrapper_expr (*expr_p, NULL);
6202 /* We only care about the number of conditions between the innermost
6203 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
6204 any cleanups collected outside the CLEANUP_POINT_EXPR. */
6205 int old_conds = gimplify_ctxp->conditions;
6206 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
6207 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
6208 gimplify_ctxp->conditions = 0;
6209 gimplify_ctxp->conditional_cleanups = NULL;
6210 gimplify_ctxp->in_cleanup_point_expr = true;
6212 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
6214 gimplify_ctxp->conditions = old_conds;
6215 gimplify_ctxp->conditional_cleanups = old_cleanups;
6216 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
6218 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
6220 gimple *wce = gsi_stmt (iter);
6222 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
6224 if (gsi_one_before_end_p (iter))
6226 /* Note that gsi_insert_seq_before and gsi_remove do not
6227 scan operands, unlike some other sequence mutators. */
6228 if (!gimple_wce_cleanup_eh_only (wce))
6229 gsi_insert_seq_before_without_update (&iter,
6230 gimple_wce_cleanup (wce),
6231 GSI_SAME_STMT);
6232 gsi_remove (&iter, true);
6233 break;
6235 else
6237 gtry *gtry;
6238 gimple_seq seq;
6239 enum gimple_try_flags kind;
6241 if (gimple_wce_cleanup_eh_only (wce))
6242 kind = GIMPLE_TRY_CATCH;
6243 else
6244 kind = GIMPLE_TRY_FINALLY;
6245 seq = gsi_split_seq_after (iter);
6247 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
6248 /* Do not use gsi_replace here, as it may scan operands.
6249 We want to do a simple structural modification only. */
6250 gsi_set_stmt (&iter, gtry);
6251 iter = gsi_start (gtry->eval);
6254 else
6255 gsi_next (&iter);
6258 gimplify_seq_add_seq (pre_p, body_sequence);
6259 if (temp)
6261 *expr_p = temp;
6262 return GS_OK;
6264 else
6266 *expr_p = NULL;
6267 return GS_ALL_DONE;
6271 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
6272 is the cleanup action required. EH_ONLY is true if the cleanup should
6273 only be executed if an exception is thrown, not on normal exit. */
6275 static void
6276 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p)
6278 gimple *wce;
6279 gimple_seq cleanup_stmts = NULL;
6281 /* Errors can result in improperly nested cleanups. Which results in
6282 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
6283 if (seen_error ())
6284 return;
6286 if (gimple_conditional_context ())
6288 /* If we're in a conditional context, this is more complex. We only
6289 want to run the cleanup if we actually ran the initialization that
6290 necessitates it, but we want to run it after the end of the
6291 conditional context. So we wrap the try/finally around the
6292 condition and use a flag to determine whether or not to actually
6293 run the destructor. Thus
6295 test ? f(A()) : 0
6297 becomes (approximately)
6299 flag = 0;
6300 try {
6301 if (test) { A::A(temp); flag = 1; val = f(temp); }
6302 else { val = 0; }
6303 } finally {
6304 if (flag) A::~A(temp);
6308 tree flag = create_tmp_var (boolean_type_node, "cleanup");
6309 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
6310 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
6312 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
6313 gimplify_stmt (&cleanup, &cleanup_stmts);
6314 wce = gimple_build_wce (cleanup_stmts);
6316 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
6317 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6318 gimplify_seq_add_stmt (pre_p, ftrue);
6320 /* Because of this manipulation, and the EH edges that jump
6321 threading cannot redirect, the temporary (VAR) will appear
6322 to be used uninitialized. Don't warn. */
6323 TREE_NO_WARNING (var) = 1;
6325 else
6327 gimplify_stmt (&cleanup, &cleanup_stmts);
6328 wce = gimple_build_wce (cleanup_stmts);
6329 gimple_wce_set_cleanup_eh_only (wce, eh_only);
6330 gimplify_seq_add_stmt (pre_p, wce);
6334 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
6336 static enum gimplify_status
6337 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6339 tree targ = *expr_p;
6340 tree temp = TARGET_EXPR_SLOT (targ);
6341 tree init = TARGET_EXPR_INITIAL (targ);
6342 enum gimplify_status ret;
6344 bool unpoison_empty_seq = false;
6345 gimple_stmt_iterator unpoison_it;
6347 if (init)
6349 tree cleanup = NULL_TREE;
6351 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
6352 to the temps list. Handle also variable length TARGET_EXPRs. */
6353 if (TREE_CODE (DECL_SIZE (temp)) != INTEGER_CST)
6355 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
6356 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
6357 gimplify_vla_decl (temp, pre_p);
6359 else
6361 /* Save location where we need to place unpoisoning. It's possible
6362 that a variable will be converted to needs_to_live_in_memory. */
6363 unpoison_it = gsi_last (*pre_p);
6364 unpoison_empty_seq = gsi_end_p (unpoison_it);
6366 gimple_add_tmp_var (temp);
6369 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
6370 expression is supposed to initialize the slot. */
6371 if (VOID_TYPE_P (TREE_TYPE (init)))
6372 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6373 else
6375 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
6376 init = init_expr;
6377 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6378 init = NULL;
6379 ggc_free (init_expr);
6381 if (ret == GS_ERROR)
6383 /* PR c++/28266 Make sure this is expanded only once. */
6384 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6385 return GS_ERROR;
6387 if (init)
6388 gimplify_and_add (init, pre_p);
6390 /* If needed, push the cleanup for the temp. */
6391 if (TARGET_EXPR_CLEANUP (targ))
6393 if (CLEANUP_EH_ONLY (targ))
6394 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
6395 CLEANUP_EH_ONLY (targ), pre_p);
6396 else
6397 cleanup = TARGET_EXPR_CLEANUP (targ);
6400 /* Add a clobber for the temporary going out of scope, like
6401 gimplify_bind_expr. */
6402 if (gimplify_ctxp->in_cleanup_point_expr
6403 && needs_to_live_in_memory (temp))
6405 if (flag_stack_reuse == SR_ALL)
6407 tree clobber = build_constructor (TREE_TYPE (temp),
6408 NULL);
6409 TREE_THIS_VOLATILE (clobber) = true;
6410 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
6411 if (cleanup)
6412 cleanup = build2 (COMPOUND_EXPR, void_type_node, cleanup,
6413 clobber);
6414 else
6415 cleanup = clobber;
6417 if (asan_poisoned_variables && dbg_cnt (asan_use_after_scope))
6419 tree asan_cleanup = build_asan_poison_call_expr (temp);
6420 if (asan_cleanup)
6422 if (unpoison_empty_seq)
6423 unpoison_it = gsi_start (*pre_p);
6425 asan_poison_variable (temp, false, &unpoison_it,
6426 unpoison_empty_seq);
6427 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
6431 if (cleanup)
6432 gimple_push_cleanup (temp, cleanup, false, pre_p);
6434 /* Only expand this once. */
6435 TREE_OPERAND (targ, 3) = init;
6436 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6438 else
6439 /* We should have expanded this before. */
6440 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
6442 *expr_p = temp;
6443 return GS_OK;
6446 /* Gimplification of expression trees. */
6448 /* Gimplify an expression which appears at statement context. The
6449 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
6450 NULL, a new sequence is allocated.
6452 Return true if we actually added a statement to the queue. */
6454 bool
6455 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
6457 gimple_seq_node last;
6459 last = gimple_seq_last (*seq_p);
6460 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
6461 return last != gimple_seq_last (*seq_p);
6464 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
6465 to CTX. If entries already exist, force them to be some flavor of private.
6466 If there is no enclosing parallel, do nothing. */
6468 void
6469 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
6471 splay_tree_node n;
6473 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
6474 return;
6478 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6479 if (n != NULL)
6481 if (n->value & GOVD_SHARED)
6482 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
6483 else if (n->value & GOVD_MAP)
6484 n->value |= GOVD_MAP_TO_ONLY;
6485 else
6486 return;
6488 else if ((ctx->region_type & ORT_TARGET) != 0)
6490 if (ctx->target_map_scalars_firstprivate)
6491 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
6492 else
6493 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
6495 else if (ctx->region_type != ORT_WORKSHARE
6496 && ctx->region_type != ORT_SIMD
6497 && ctx->region_type != ORT_ACC
6498 && !(ctx->region_type & ORT_TARGET_DATA))
6499 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
6501 ctx = ctx->outer_context;
6503 while (ctx);
6506 /* Similarly for each of the type sizes of TYPE. */
6508 static void
6509 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
6511 if (type == NULL || type == error_mark_node)
6512 return;
6513 type = TYPE_MAIN_VARIANT (type);
6515 if (ctx->privatized_types->add (type))
6516 return;
6518 switch (TREE_CODE (type))
6520 case INTEGER_TYPE:
6521 case ENUMERAL_TYPE:
6522 case BOOLEAN_TYPE:
6523 case REAL_TYPE:
6524 case FIXED_POINT_TYPE:
6525 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
6526 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
6527 break;
6529 case ARRAY_TYPE:
6530 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
6531 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
6532 break;
6534 case RECORD_TYPE:
6535 case UNION_TYPE:
6536 case QUAL_UNION_TYPE:
6538 tree field;
6539 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
6540 if (TREE_CODE (field) == FIELD_DECL)
6542 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
6543 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
6546 break;
6548 case POINTER_TYPE:
6549 case REFERENCE_TYPE:
6550 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
6551 break;
6553 default:
6554 break;
6557 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
6558 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
6559 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
6562 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
6564 static void
6565 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
6567 splay_tree_node n;
6568 unsigned int nflags;
6569 tree t;
6571 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
6572 return;
6574 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
6575 there are constructors involved somewhere. */
6576 if (TREE_ADDRESSABLE (TREE_TYPE (decl))
6577 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
6578 flags |= GOVD_SEEN;
6580 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6581 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
6583 /* We shouldn't be re-adding the decl with the same data
6584 sharing class. */
6585 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
6586 nflags = n->value | flags;
6587 /* The only combination of data sharing classes we should see is
6588 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
6589 reduction variables to be used in data sharing clauses. */
6590 gcc_assert ((ctx->region_type & ORT_ACC) != 0
6591 || ((nflags & GOVD_DATA_SHARE_CLASS)
6592 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
6593 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
6594 n->value = nflags;
6595 return;
6598 /* When adding a variable-sized variable, we have to handle all sorts
6599 of additional bits of data: the pointer replacement variable, and
6600 the parameters of the type. */
6601 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
6603 /* Add the pointer replacement variable as PRIVATE if the variable
6604 replacement is private, else FIRSTPRIVATE since we'll need the
6605 address of the original variable either for SHARED, or for the
6606 copy into or out of the context. */
6607 if (!(flags & GOVD_LOCAL))
6609 if (flags & GOVD_MAP)
6610 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
6611 else if (flags & GOVD_PRIVATE)
6612 nflags = GOVD_PRIVATE;
6613 else if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
6614 && (flags & GOVD_FIRSTPRIVATE))
6615 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
6616 else
6617 nflags = GOVD_FIRSTPRIVATE;
6618 nflags |= flags & GOVD_SEEN;
6619 t = DECL_VALUE_EXPR (decl);
6620 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
6621 t = TREE_OPERAND (t, 0);
6622 gcc_assert (DECL_P (t));
6623 omp_add_variable (ctx, t, nflags);
6626 /* Add all of the variable and type parameters (which should have
6627 been gimplified to a formal temporary) as FIRSTPRIVATE. */
6628 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
6629 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
6630 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
6632 /* The variable-sized variable itself is never SHARED, only some form
6633 of PRIVATE. The sharing would take place via the pointer variable
6634 which we remapped above. */
6635 if (flags & GOVD_SHARED)
6636 flags = GOVD_PRIVATE | GOVD_DEBUG_PRIVATE
6637 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
6639 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
6640 alloca statement we generate for the variable, so make sure it
6641 is available. This isn't automatically needed for the SHARED
6642 case, since we won't be allocating local storage then.
6643 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
6644 in this case omp_notice_variable will be called later
6645 on when it is gimplified. */
6646 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
6647 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
6648 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
6650 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
6651 && lang_hooks.decls.omp_privatize_by_reference (decl))
6653 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
6655 /* Similar to the direct variable sized case above, we'll need the
6656 size of references being privatized. */
6657 if ((flags & GOVD_SHARED) == 0)
6659 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
6660 if (DECL_P (t))
6661 omp_notice_variable (ctx, t, true);
6665 if (n != NULL)
6666 n->value |= flags;
6667 else
6668 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
6670 /* For reductions clauses in OpenACC loop directives, by default create a
6671 copy clause on the enclosing parallel construct for carrying back the
6672 results. */
6673 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
6675 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
6676 while (outer_ctx)
6678 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
6679 if (n != NULL)
6681 /* Ignore local variables and explicitly declared clauses. */
6682 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
6683 break;
6684 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
6686 /* According to the OpenACC spec, such a reduction variable
6687 should already have a copy map on a kernels construct,
6688 verify that here. */
6689 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
6690 && (n->value & GOVD_MAP));
6692 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
6694 /* Remove firstprivate and make it a copy map. */
6695 n->value &= ~GOVD_FIRSTPRIVATE;
6696 n->value |= GOVD_MAP;
6699 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
6701 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
6702 GOVD_MAP | GOVD_SEEN);
6703 break;
6705 outer_ctx = outer_ctx->outer_context;
6710 /* Notice a threadprivate variable DECL used in OMP context CTX.
6711 This just prints out diagnostics about threadprivate variable uses
6712 in untied tasks. If DECL2 is non-NULL, prevent this warning
6713 on that variable. */
6715 static bool
6716 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
6717 tree decl2)
6719 splay_tree_node n;
6720 struct gimplify_omp_ctx *octx;
6722 for (octx = ctx; octx; octx = octx->outer_context)
6723 if ((octx->region_type & ORT_TARGET) != 0)
6725 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
6726 if (n == NULL)
6728 error ("threadprivate variable %qE used in target region",
6729 DECL_NAME (decl));
6730 error_at (octx->location, "enclosing target region");
6731 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
6733 if (decl2)
6734 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
6737 if (ctx->region_type != ORT_UNTIED_TASK)
6738 return false;
6739 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6740 if (n == NULL)
6742 error ("threadprivate variable %qE used in untied task",
6743 DECL_NAME (decl));
6744 error_at (ctx->location, "enclosing task");
6745 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
6747 if (decl2)
6748 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
6749 return false;
6752 /* Return true if global var DECL is device resident. */
6754 static bool
6755 device_resident_p (tree decl)
6757 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
6759 if (!attr)
6760 return false;
6762 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
6764 tree c = TREE_VALUE (t);
6765 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
6766 return true;
6769 return false;
6772 /* Determine outer default flags for DECL mentioned in an OMP region
6773 but not declared in an enclosing clause.
6775 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
6776 remapped firstprivate instead of shared. To some extent this is
6777 addressed in omp_firstprivatize_type_sizes, but not
6778 effectively. */
6780 static unsigned
6781 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
6782 bool in_code, unsigned flags)
6784 enum omp_clause_default_kind default_kind = ctx->default_kind;
6785 enum omp_clause_default_kind kind;
6787 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
6788 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
6789 default_kind = kind;
6791 switch (default_kind)
6793 case OMP_CLAUSE_DEFAULT_NONE:
6795 const char *rtype;
6797 if (ctx->region_type & ORT_PARALLEL)
6798 rtype = "parallel";
6799 else if (ctx->region_type & ORT_TASK)
6800 rtype = "task";
6801 else if (ctx->region_type & ORT_TEAMS)
6802 rtype = "teams";
6803 else
6804 gcc_unreachable ();
6806 error ("%qE not specified in enclosing %s",
6807 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
6808 error_at (ctx->location, "enclosing %s", rtype);
6810 /* FALLTHRU */
6811 case OMP_CLAUSE_DEFAULT_SHARED:
6812 flags |= GOVD_SHARED;
6813 break;
6814 case OMP_CLAUSE_DEFAULT_PRIVATE:
6815 flags |= GOVD_PRIVATE;
6816 break;
6817 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
6818 flags |= GOVD_FIRSTPRIVATE;
6819 break;
6820 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
6821 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
6822 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
6823 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
6825 omp_notice_variable (octx, decl, in_code);
6826 for (; octx; octx = octx->outer_context)
6828 splay_tree_node n2;
6830 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
6831 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
6832 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
6833 continue;
6834 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
6836 flags |= GOVD_FIRSTPRIVATE;
6837 goto found_outer;
6839 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
6841 flags |= GOVD_SHARED;
6842 goto found_outer;
6847 if (TREE_CODE (decl) == PARM_DECL
6848 || (!is_global_var (decl)
6849 && DECL_CONTEXT (decl) == current_function_decl))
6850 flags |= GOVD_FIRSTPRIVATE;
6851 else
6852 flags |= GOVD_SHARED;
6853 found_outer:
6854 break;
6856 default:
6857 gcc_unreachable ();
6860 return flags;
6864 /* Determine outer default flags for DECL mentioned in an OACC region
6865 but not declared in an enclosing clause. */
6867 static unsigned
6868 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
6870 const char *rkind;
6871 bool on_device = false;
6872 tree type = TREE_TYPE (decl);
6874 if (lang_hooks.decls.omp_privatize_by_reference (decl))
6875 type = TREE_TYPE (type);
6877 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
6878 && is_global_var (decl)
6879 && device_resident_p (decl))
6881 on_device = true;
6882 flags |= GOVD_MAP_TO_ONLY;
6885 switch (ctx->region_type)
6887 default:
6888 gcc_unreachable ();
6890 case ORT_ACC_KERNELS:
6891 /* Scalars are default 'copy' under kernels, non-scalars are default
6892 'present_or_copy'. */
6893 flags |= GOVD_MAP;
6894 if (!AGGREGATE_TYPE_P (type))
6895 flags |= GOVD_MAP_FORCE;
6897 rkind = "kernels";
6898 break;
6900 case ORT_ACC_PARALLEL:
6902 if (on_device || AGGREGATE_TYPE_P (type))
6903 /* Aggregates default to 'present_or_copy'. */
6904 flags |= GOVD_MAP;
6905 else
6906 /* Scalars default to 'firstprivate'. */
6907 flags |= GOVD_FIRSTPRIVATE;
6908 rkind = "parallel";
6910 break;
6913 if (DECL_ARTIFICIAL (decl))
6914 ; /* We can get compiler-generated decls, and should not complain
6915 about them. */
6916 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_NONE)
6918 error ("%qE not specified in enclosing OpenACC %qs construct",
6919 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rkind);
6920 inform (ctx->location, "enclosing OpenACC %qs construct", rkind);
6922 else
6923 gcc_checking_assert (ctx->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
6925 return flags;
6928 /* Record the fact that DECL was used within the OMP context CTX.
6929 IN_CODE is true when real code uses DECL, and false when we should
6930 merely emit default(none) errors. Return true if DECL is going to
6931 be remapped and thus DECL shouldn't be gimplified into its
6932 DECL_VALUE_EXPR (if any). */
6934 static bool
6935 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
6937 splay_tree_node n;
6938 unsigned flags = in_code ? GOVD_SEEN : 0;
6939 bool ret = false, shared;
6941 if (error_operand_p (decl))
6942 return false;
6944 if (ctx->region_type == ORT_NONE)
6945 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
6947 if (is_global_var (decl))
6949 /* Threadprivate variables are predetermined. */
6950 if (DECL_THREAD_LOCAL_P (decl))
6951 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
6953 if (DECL_HAS_VALUE_EXPR_P (decl))
6955 tree value = get_base_address (DECL_VALUE_EXPR (decl));
6957 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
6958 return omp_notice_threadprivate_variable (ctx, decl, value);
6961 if (gimplify_omp_ctxp->outer_context == NULL
6962 && VAR_P (decl)
6963 && oacc_get_fn_attrib (current_function_decl))
6965 location_t loc = DECL_SOURCE_LOCATION (decl);
6967 if (lookup_attribute ("omp declare target link",
6968 DECL_ATTRIBUTES (decl)))
6970 error_at (loc,
6971 "%qE with %<link%> clause used in %<routine%> function",
6972 DECL_NAME (decl));
6973 return false;
6975 else if (!lookup_attribute ("omp declare target",
6976 DECL_ATTRIBUTES (decl)))
6978 error_at (loc,
6979 "%qE requires a %<declare%> directive for use "
6980 "in a %<routine%> function", DECL_NAME (decl));
6981 return false;
6986 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6987 if ((ctx->region_type & ORT_TARGET) != 0)
6989 ret = lang_hooks.decls.omp_disregard_value_expr (decl, true);
6990 if (n == NULL)
6992 unsigned nflags = flags;
6993 if (ctx->target_map_pointers_as_0len_arrays
6994 || ctx->target_map_scalars_firstprivate)
6996 bool is_declare_target = false;
6997 bool is_scalar = false;
6998 if (is_global_var (decl)
6999 && varpool_node::get_create (decl)->offloadable)
7001 struct gimplify_omp_ctx *octx;
7002 for (octx = ctx->outer_context;
7003 octx; octx = octx->outer_context)
7005 n = splay_tree_lookup (octx->variables,
7006 (splay_tree_key)decl);
7007 if (n
7008 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
7009 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7010 break;
7012 is_declare_target = octx == NULL;
7014 if (!is_declare_target && ctx->target_map_scalars_firstprivate)
7015 is_scalar = lang_hooks.decls.omp_scalar_p (decl);
7016 if (is_declare_target)
7018 else if (ctx->target_map_pointers_as_0len_arrays
7019 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
7020 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
7021 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
7022 == POINTER_TYPE)))
7023 nflags |= GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
7024 else if (is_scalar)
7025 nflags |= GOVD_FIRSTPRIVATE;
7028 struct gimplify_omp_ctx *octx = ctx->outer_context;
7029 if ((ctx->region_type & ORT_ACC) && octx)
7031 /* Look in outer OpenACC contexts, to see if there's a
7032 data attribute for this variable. */
7033 omp_notice_variable (octx, decl, in_code);
7035 for (; octx; octx = octx->outer_context)
7037 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
7038 break;
7039 splay_tree_node n2
7040 = splay_tree_lookup (octx->variables,
7041 (splay_tree_key) decl);
7042 if (n2)
7044 if (octx->region_type == ORT_ACC_HOST_DATA)
7045 error ("variable %qE declared in enclosing "
7046 "%<host_data%> region", DECL_NAME (decl));
7047 nflags |= GOVD_MAP;
7048 if (octx->region_type == ORT_ACC_DATA
7049 && (n2->value & GOVD_MAP_0LEN_ARRAY))
7050 nflags |= GOVD_MAP_0LEN_ARRAY;
7051 goto found_outer;
7057 tree type = TREE_TYPE (decl);
7059 if (nflags == flags
7060 && gimplify_omp_ctxp->target_firstprivatize_array_bases
7061 && lang_hooks.decls.omp_privatize_by_reference (decl))
7062 type = TREE_TYPE (type);
7063 if (nflags == flags
7064 && !lang_hooks.types.omp_mappable_type (type))
7066 error ("%qD referenced in target region does not have "
7067 "a mappable type", decl);
7068 nflags |= GOVD_MAP | GOVD_EXPLICIT;
7070 else if (nflags == flags)
7072 if ((ctx->region_type & ORT_ACC) != 0)
7073 nflags = oacc_default_clause (ctx, decl, flags);
7074 else
7075 nflags |= GOVD_MAP;
7078 found_outer:
7079 omp_add_variable (ctx, decl, nflags);
7081 else
7083 /* If nothing changed, there's nothing left to do. */
7084 if ((n->value & flags) == flags)
7085 return ret;
7086 flags |= n->value;
7087 n->value = flags;
7089 goto do_outer;
7092 if (n == NULL)
7094 if (ctx->region_type == ORT_WORKSHARE
7095 || ctx->region_type == ORT_SIMD
7096 || ctx->region_type == ORT_ACC
7097 || (ctx->region_type & ORT_TARGET_DATA) != 0)
7098 goto do_outer;
7100 flags = omp_default_clause (ctx, decl, in_code, flags);
7102 if ((flags & GOVD_PRIVATE)
7103 && lang_hooks.decls.omp_private_outer_ref (decl))
7104 flags |= GOVD_PRIVATE_OUTER_REF;
7106 omp_add_variable (ctx, decl, flags);
7108 shared = (flags & GOVD_SHARED) != 0;
7109 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7110 goto do_outer;
7113 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
7114 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
7115 && DECL_SIZE (decl))
7117 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7119 splay_tree_node n2;
7120 tree t = DECL_VALUE_EXPR (decl);
7121 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7122 t = TREE_OPERAND (t, 0);
7123 gcc_assert (DECL_P (t));
7124 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7125 n2->value |= GOVD_SEEN;
7127 else if (lang_hooks.decls.omp_privatize_by_reference (decl)
7128 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
7129 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
7130 != INTEGER_CST))
7132 splay_tree_node n2;
7133 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7134 gcc_assert (DECL_P (t));
7135 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7136 if (n2)
7137 n2->value |= GOVD_SEEN;
7141 shared = ((flags | n->value) & GOVD_SHARED) != 0;
7142 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7144 /* If nothing changed, there's nothing left to do. */
7145 if ((n->value & flags) == flags)
7146 return ret;
7147 flags |= n->value;
7148 n->value = flags;
7150 do_outer:
7151 /* If the variable is private in the current context, then we don't
7152 need to propagate anything to an outer context. */
7153 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
7154 return ret;
7155 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7156 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7157 return ret;
7158 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
7159 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7160 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7161 return ret;
7162 if (ctx->outer_context
7163 && omp_notice_variable (ctx->outer_context, decl, in_code))
7164 return true;
7165 return ret;
7168 /* Verify that DECL is private within CTX. If there's specific information
7169 to the contrary in the innermost scope, generate an error. */
7171 static bool
7172 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
7174 splay_tree_node n;
7176 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7177 if (n != NULL)
7179 if (n->value & GOVD_SHARED)
7181 if (ctx == gimplify_omp_ctxp)
7183 if (simd)
7184 error ("iteration variable %qE is predetermined linear",
7185 DECL_NAME (decl));
7186 else
7187 error ("iteration variable %qE should be private",
7188 DECL_NAME (decl));
7189 n->value = GOVD_PRIVATE;
7190 return true;
7192 else
7193 return false;
7195 else if ((n->value & GOVD_EXPLICIT) != 0
7196 && (ctx == gimplify_omp_ctxp
7197 || (ctx->region_type == ORT_COMBINED_PARALLEL
7198 && gimplify_omp_ctxp->outer_context == ctx)))
7200 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
7201 error ("iteration variable %qE should not be firstprivate",
7202 DECL_NAME (decl));
7203 else if ((n->value & GOVD_REDUCTION) != 0)
7204 error ("iteration variable %qE should not be reduction",
7205 DECL_NAME (decl));
7206 else if (simd == 0 && (n->value & GOVD_LINEAR) != 0)
7207 error ("iteration variable %qE should not be linear",
7208 DECL_NAME (decl));
7209 else if (simd == 1 && (n->value & GOVD_LASTPRIVATE) != 0)
7210 error ("iteration variable %qE should not be lastprivate",
7211 DECL_NAME (decl));
7212 else if (simd && (n->value & GOVD_PRIVATE) != 0)
7213 error ("iteration variable %qE should not be private",
7214 DECL_NAME (decl));
7215 else if (simd == 2 && (n->value & GOVD_LINEAR) != 0)
7216 error ("iteration variable %qE is predetermined linear",
7217 DECL_NAME (decl));
7219 return (ctx == gimplify_omp_ctxp
7220 || (ctx->region_type == ORT_COMBINED_PARALLEL
7221 && gimplify_omp_ctxp->outer_context == ctx));
7224 if (ctx->region_type != ORT_WORKSHARE
7225 && ctx->region_type != ORT_SIMD
7226 && ctx->region_type != ORT_ACC)
7227 return false;
7228 else if (ctx->outer_context)
7229 return omp_is_private (ctx->outer_context, decl, simd);
7230 return false;
7233 /* Return true if DECL is private within a parallel region
7234 that binds to the current construct's context or in parallel
7235 region's REDUCTION clause. */
7237 static bool
7238 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
7240 splay_tree_node n;
7244 ctx = ctx->outer_context;
7245 if (ctx == NULL)
7247 if (is_global_var (decl))
7248 return false;
7250 /* References might be private, but might be shared too,
7251 when checking for copyprivate, assume they might be
7252 private, otherwise assume they might be shared. */
7253 if (copyprivate)
7254 return true;
7256 if (lang_hooks.decls.omp_privatize_by_reference (decl))
7257 return false;
7259 /* Treat C++ privatized non-static data members outside
7260 of the privatization the same. */
7261 if (omp_member_access_dummy_var (decl))
7262 return false;
7264 return true;
7267 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
7269 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7270 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
7271 continue;
7273 if (n != NULL)
7275 if ((n->value & GOVD_LOCAL) != 0
7276 && omp_member_access_dummy_var (decl))
7277 return false;
7278 return (n->value & GOVD_SHARED) == 0;
7281 while (ctx->region_type == ORT_WORKSHARE
7282 || ctx->region_type == ORT_SIMD
7283 || ctx->region_type == ORT_ACC);
7284 return false;
7287 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
7289 static tree
7290 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
7292 tree t = *tp;
7294 /* If this node has been visited, unmark it and keep looking. */
7295 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
7296 return t;
7298 if (IS_TYPE_OR_DECL_P (t))
7299 *walk_subtrees = 0;
7300 return NULL_TREE;
7303 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
7304 and previous omp contexts. */
7306 static void
7307 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
7308 enum omp_region_type region_type,
7309 enum tree_code code)
7311 struct gimplify_omp_ctx *ctx, *outer_ctx;
7312 tree c;
7313 hash_map<tree, tree> *struct_map_to_clause = NULL;
7314 tree *prev_list_p = NULL;
7316 ctx = new_omp_context (region_type);
7317 outer_ctx = ctx->outer_context;
7318 if (code == OMP_TARGET)
7320 if (!lang_GNU_Fortran ())
7321 ctx->target_map_pointers_as_0len_arrays = true;
7322 ctx->target_map_scalars_firstprivate = true;
7324 if (!lang_GNU_Fortran ())
7325 switch (code)
7327 case OMP_TARGET:
7328 case OMP_TARGET_DATA:
7329 case OMP_TARGET_ENTER_DATA:
7330 case OMP_TARGET_EXIT_DATA:
7331 case OACC_HOST_DATA:
7332 ctx->target_firstprivatize_array_bases = true;
7333 default:
7334 break;
7337 while ((c = *list_p) != NULL)
7339 bool remove = false;
7340 bool notice_outer = true;
7341 const char *check_non_private = NULL;
7342 unsigned int flags;
7343 tree decl;
7345 switch (OMP_CLAUSE_CODE (c))
7347 case OMP_CLAUSE_PRIVATE:
7348 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
7349 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
7351 flags |= GOVD_PRIVATE_OUTER_REF;
7352 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
7354 else
7355 notice_outer = false;
7356 goto do_add;
7357 case OMP_CLAUSE_SHARED:
7358 flags = GOVD_SHARED | GOVD_EXPLICIT;
7359 goto do_add;
7360 case OMP_CLAUSE_FIRSTPRIVATE:
7361 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
7362 check_non_private = "firstprivate";
7363 goto do_add;
7364 case OMP_CLAUSE_LASTPRIVATE:
7365 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
7366 check_non_private = "lastprivate";
7367 decl = OMP_CLAUSE_DECL (c);
7368 if (error_operand_p (decl))
7369 goto do_add;
7370 else if (outer_ctx
7371 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
7372 || outer_ctx->region_type == ORT_COMBINED_TEAMS)
7373 && splay_tree_lookup (outer_ctx->variables,
7374 (splay_tree_key) decl) == NULL)
7376 omp_add_variable (outer_ctx, decl, GOVD_SHARED | GOVD_SEEN);
7377 if (outer_ctx->outer_context)
7378 omp_notice_variable (outer_ctx->outer_context, decl, true);
7380 else if (outer_ctx
7381 && (outer_ctx->region_type & ORT_TASK) != 0
7382 && outer_ctx->combined_loop
7383 && splay_tree_lookup (outer_ctx->variables,
7384 (splay_tree_key) decl) == NULL)
7386 omp_add_variable (outer_ctx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
7387 if (outer_ctx->outer_context)
7388 omp_notice_variable (outer_ctx->outer_context, decl, true);
7390 else if (outer_ctx
7391 && (outer_ctx->region_type == ORT_WORKSHARE
7392 || outer_ctx->region_type == ORT_ACC)
7393 && outer_ctx->combined_loop
7394 && splay_tree_lookup (outer_ctx->variables,
7395 (splay_tree_key) decl) == NULL
7396 && !omp_check_private (outer_ctx, decl, false))
7398 omp_add_variable (outer_ctx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
7399 if (outer_ctx->outer_context
7400 && (outer_ctx->outer_context->region_type
7401 == ORT_COMBINED_PARALLEL)
7402 && splay_tree_lookup (outer_ctx->outer_context->variables,
7403 (splay_tree_key) decl) == NULL)
7405 struct gimplify_omp_ctx *octx = outer_ctx->outer_context;
7406 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
7407 if (octx->outer_context)
7409 octx = octx->outer_context;
7410 if (octx->region_type == ORT_WORKSHARE
7411 && octx->combined_loop
7412 && splay_tree_lookup (octx->variables,
7413 (splay_tree_key) decl) == NULL
7414 && !omp_check_private (octx, decl, false))
7416 omp_add_variable (octx, decl,
7417 GOVD_LASTPRIVATE | GOVD_SEEN);
7418 octx = octx->outer_context;
7419 if (octx
7420 && octx->region_type == ORT_COMBINED_TEAMS
7421 && (splay_tree_lookup (octx->variables,
7422 (splay_tree_key) decl)
7423 == NULL))
7425 omp_add_variable (octx, decl,
7426 GOVD_SHARED | GOVD_SEEN);
7427 octx = octx->outer_context;
7430 if (octx)
7431 omp_notice_variable (octx, decl, true);
7434 else if (outer_ctx->outer_context)
7435 omp_notice_variable (outer_ctx->outer_context, decl, true);
7437 goto do_add;
7438 case OMP_CLAUSE_REDUCTION:
7439 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
7440 /* OpenACC permits reductions on private variables. */
7441 if (!(region_type & ORT_ACC))
7442 check_non_private = "reduction";
7443 decl = OMP_CLAUSE_DECL (c);
7444 if (TREE_CODE (decl) == MEM_REF)
7446 tree type = TREE_TYPE (decl);
7447 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
7448 NULL, is_gimple_val, fb_rvalue, false)
7449 == GS_ERROR)
7451 remove = true;
7452 break;
7454 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
7455 if (DECL_P (v))
7457 omp_firstprivatize_variable (ctx, v);
7458 omp_notice_variable (ctx, v, true);
7460 decl = TREE_OPERAND (decl, 0);
7461 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
7463 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
7464 NULL, is_gimple_val, fb_rvalue, false)
7465 == GS_ERROR)
7467 remove = true;
7468 break;
7470 v = TREE_OPERAND (decl, 1);
7471 if (DECL_P (v))
7473 omp_firstprivatize_variable (ctx, v);
7474 omp_notice_variable (ctx, v, true);
7476 decl = TREE_OPERAND (decl, 0);
7478 if (TREE_CODE (decl) == ADDR_EXPR
7479 || TREE_CODE (decl) == INDIRECT_REF)
7480 decl = TREE_OPERAND (decl, 0);
7482 goto do_add_decl;
7483 case OMP_CLAUSE_LINEAR:
7484 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
7485 is_gimple_val, fb_rvalue) == GS_ERROR)
7487 remove = true;
7488 break;
7490 else
7492 if (code == OMP_SIMD
7493 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
7495 struct gimplify_omp_ctx *octx = outer_ctx;
7496 if (octx
7497 && octx->region_type == ORT_WORKSHARE
7498 && octx->combined_loop
7499 && !octx->distribute)
7501 if (octx->outer_context
7502 && (octx->outer_context->region_type
7503 == ORT_COMBINED_PARALLEL))
7504 octx = octx->outer_context->outer_context;
7505 else
7506 octx = octx->outer_context;
7508 if (octx
7509 && octx->region_type == ORT_WORKSHARE
7510 && octx->combined_loop
7511 && octx->distribute)
7513 error_at (OMP_CLAUSE_LOCATION (c),
7514 "%<linear%> clause for variable other than "
7515 "loop iterator specified on construct "
7516 "combined with %<distribute%>");
7517 remove = true;
7518 break;
7521 /* For combined #pragma omp parallel for simd, need to put
7522 lastprivate and perhaps firstprivate too on the
7523 parallel. Similarly for #pragma omp for simd. */
7524 struct gimplify_omp_ctx *octx = outer_ctx;
7525 decl = NULL_TREE;
7528 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
7529 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
7530 break;
7531 decl = OMP_CLAUSE_DECL (c);
7532 if (error_operand_p (decl))
7534 decl = NULL_TREE;
7535 break;
7537 flags = GOVD_SEEN;
7538 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
7539 flags |= GOVD_FIRSTPRIVATE;
7540 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
7541 flags |= GOVD_LASTPRIVATE;
7542 if (octx
7543 && octx->region_type == ORT_WORKSHARE
7544 && octx->combined_loop)
7546 if (octx->outer_context
7547 && (octx->outer_context->region_type
7548 == ORT_COMBINED_PARALLEL))
7549 octx = octx->outer_context;
7550 else if (omp_check_private (octx, decl, false))
7551 break;
7553 else if (octx
7554 && (octx->region_type & ORT_TASK) != 0
7555 && octx->combined_loop)
7557 else if (octx
7558 && octx->region_type == ORT_COMBINED_PARALLEL
7559 && ctx->region_type == ORT_WORKSHARE
7560 && octx == outer_ctx)
7561 flags = GOVD_SEEN | GOVD_SHARED;
7562 else if (octx
7563 && octx->region_type == ORT_COMBINED_TEAMS)
7564 flags = GOVD_SEEN | GOVD_SHARED;
7565 else if (octx
7566 && octx->region_type == ORT_COMBINED_TARGET)
7568 flags &= ~GOVD_LASTPRIVATE;
7569 if (flags == GOVD_SEEN)
7570 break;
7572 else
7573 break;
7574 splay_tree_node on
7575 = splay_tree_lookup (octx->variables,
7576 (splay_tree_key) decl);
7577 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
7579 octx = NULL;
7580 break;
7582 omp_add_variable (octx, decl, flags);
7583 if (octx->outer_context == NULL)
7584 break;
7585 octx = octx->outer_context;
7587 while (1);
7588 if (octx
7589 && decl
7590 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
7591 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
7592 omp_notice_variable (octx, decl, true);
7594 flags = GOVD_LINEAR | GOVD_EXPLICIT;
7595 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
7596 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
7598 notice_outer = false;
7599 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
7601 goto do_add;
7603 case OMP_CLAUSE_MAP:
7604 decl = OMP_CLAUSE_DECL (c);
7605 if (error_operand_p (decl))
7606 remove = true;
7607 switch (code)
7609 case OMP_TARGET:
7610 break;
7611 case OACC_DATA:
7612 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
7613 break;
7614 /* FALLTHRU */
7615 case OMP_TARGET_DATA:
7616 case OMP_TARGET_ENTER_DATA:
7617 case OMP_TARGET_EXIT_DATA:
7618 case OACC_ENTER_DATA:
7619 case OACC_EXIT_DATA:
7620 case OACC_HOST_DATA:
7621 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
7622 || (OMP_CLAUSE_MAP_KIND (c)
7623 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
7624 /* For target {,enter ,exit }data only the array slice is
7625 mapped, but not the pointer to it. */
7626 remove = true;
7627 break;
7628 default:
7629 break;
7631 if (remove)
7632 break;
7633 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
7635 struct gimplify_omp_ctx *octx;
7636 for (octx = outer_ctx; octx; octx = octx->outer_context)
7638 if (octx->region_type != ORT_ACC_HOST_DATA)
7639 break;
7640 splay_tree_node n2
7641 = splay_tree_lookup (octx->variables,
7642 (splay_tree_key) decl);
7643 if (n2)
7644 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
7645 "declared in enclosing %<host_data%> region",
7646 DECL_NAME (decl));
7649 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
7650 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
7651 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
7652 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
7653 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
7655 remove = true;
7656 break;
7658 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
7659 || (OMP_CLAUSE_MAP_KIND (c)
7660 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
7661 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
7663 OMP_CLAUSE_SIZE (c)
7664 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
7665 false);
7666 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
7667 GOVD_FIRSTPRIVATE | GOVD_SEEN);
7669 if (!DECL_P (decl))
7671 tree d = decl, *pd;
7672 if (TREE_CODE (d) == ARRAY_REF)
7674 while (TREE_CODE (d) == ARRAY_REF)
7675 d = TREE_OPERAND (d, 0);
7676 if (TREE_CODE (d) == COMPONENT_REF
7677 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
7678 decl = d;
7680 pd = &OMP_CLAUSE_DECL (c);
7681 if (d == decl
7682 && TREE_CODE (decl) == INDIRECT_REF
7683 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
7684 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
7685 == REFERENCE_TYPE))
7687 pd = &TREE_OPERAND (decl, 0);
7688 decl = TREE_OPERAND (decl, 0);
7690 if (TREE_CODE (decl) == COMPONENT_REF)
7692 while (TREE_CODE (decl) == COMPONENT_REF)
7693 decl = TREE_OPERAND (decl, 0);
7694 if (TREE_CODE (decl) == INDIRECT_REF
7695 && DECL_P (TREE_OPERAND (decl, 0))
7696 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
7697 == REFERENCE_TYPE))
7698 decl = TREE_OPERAND (decl, 0);
7700 if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue, fb_lvalue)
7701 == GS_ERROR)
7703 remove = true;
7704 break;
7706 if (DECL_P (decl))
7708 if (error_operand_p (decl))
7710 remove = true;
7711 break;
7714 tree stype = TREE_TYPE (decl);
7715 if (TREE_CODE (stype) == REFERENCE_TYPE)
7716 stype = TREE_TYPE (stype);
7717 if (TYPE_SIZE_UNIT (stype) == NULL
7718 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
7720 error_at (OMP_CLAUSE_LOCATION (c),
7721 "mapping field %qE of variable length "
7722 "structure", OMP_CLAUSE_DECL (c));
7723 remove = true;
7724 break;
7727 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
7729 /* Error recovery. */
7730 if (prev_list_p == NULL)
7732 remove = true;
7733 break;
7735 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
7737 tree ch = OMP_CLAUSE_CHAIN (*prev_list_p);
7738 if (ch == NULL_TREE || OMP_CLAUSE_CHAIN (ch) != c)
7740 remove = true;
7741 break;
7746 tree offset;
7747 HOST_WIDE_INT bitsize, bitpos;
7748 machine_mode mode;
7749 int unsignedp, reversep, volatilep = 0;
7750 tree base = OMP_CLAUSE_DECL (c);
7751 while (TREE_CODE (base) == ARRAY_REF)
7752 base = TREE_OPERAND (base, 0);
7753 if (TREE_CODE (base) == INDIRECT_REF)
7754 base = TREE_OPERAND (base, 0);
7755 base = get_inner_reference (base, &bitsize, &bitpos, &offset,
7756 &mode, &unsignedp, &reversep,
7757 &volatilep);
7758 tree orig_base = base;
7759 if ((TREE_CODE (base) == INDIRECT_REF
7760 || (TREE_CODE (base) == MEM_REF
7761 && integer_zerop (TREE_OPERAND (base, 1))))
7762 && DECL_P (TREE_OPERAND (base, 0))
7763 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0)))
7764 == REFERENCE_TYPE))
7765 base = TREE_OPERAND (base, 0);
7766 gcc_assert (base == decl
7767 && (offset == NULL_TREE
7768 || TREE_CODE (offset) == INTEGER_CST));
7770 splay_tree_node n
7771 = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7772 bool ptr = (OMP_CLAUSE_MAP_KIND (c)
7773 == GOMP_MAP_ALWAYS_POINTER);
7774 if (n == NULL || (n->value & GOVD_MAP) == 0)
7776 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7777 OMP_CLAUSE_MAP);
7778 OMP_CLAUSE_SET_MAP_KIND (l, GOMP_MAP_STRUCT);
7779 if (orig_base != base)
7780 OMP_CLAUSE_DECL (l) = unshare_expr (orig_base);
7781 else
7782 OMP_CLAUSE_DECL (l) = decl;
7783 OMP_CLAUSE_SIZE (l) = size_int (1);
7784 if (struct_map_to_clause == NULL)
7785 struct_map_to_clause = new hash_map<tree, tree>;
7786 struct_map_to_clause->put (decl, l);
7787 if (ptr)
7789 enum gomp_map_kind mkind
7790 = code == OMP_TARGET_EXIT_DATA
7791 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
7792 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7793 OMP_CLAUSE_MAP);
7794 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
7795 OMP_CLAUSE_DECL (c2)
7796 = unshare_expr (OMP_CLAUSE_DECL (c));
7797 OMP_CLAUSE_CHAIN (c2) = *prev_list_p;
7798 OMP_CLAUSE_SIZE (c2)
7799 = TYPE_SIZE_UNIT (ptr_type_node);
7800 OMP_CLAUSE_CHAIN (l) = c2;
7801 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
7803 tree c4 = OMP_CLAUSE_CHAIN (*prev_list_p);
7804 tree c3
7805 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7806 OMP_CLAUSE_MAP);
7807 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
7808 OMP_CLAUSE_DECL (c3)
7809 = unshare_expr (OMP_CLAUSE_DECL (c4));
7810 OMP_CLAUSE_SIZE (c3)
7811 = TYPE_SIZE_UNIT (ptr_type_node);
7812 OMP_CLAUSE_CHAIN (c3) = *prev_list_p;
7813 OMP_CLAUSE_CHAIN (c2) = c3;
7815 *prev_list_p = l;
7816 prev_list_p = NULL;
7818 else
7820 OMP_CLAUSE_CHAIN (l) = c;
7821 *list_p = l;
7822 list_p = &OMP_CLAUSE_CHAIN (l);
7824 if (orig_base != base && code == OMP_TARGET)
7826 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7827 OMP_CLAUSE_MAP);
7828 enum gomp_map_kind mkind
7829 = GOMP_MAP_FIRSTPRIVATE_REFERENCE;
7830 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
7831 OMP_CLAUSE_DECL (c2) = decl;
7832 OMP_CLAUSE_SIZE (c2) = size_zero_node;
7833 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
7834 OMP_CLAUSE_CHAIN (l) = c2;
7836 flags = GOVD_MAP | GOVD_EXPLICIT;
7837 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) || ptr)
7838 flags |= GOVD_SEEN;
7839 goto do_add_decl;
7841 else
7843 tree *osc = struct_map_to_clause->get (decl);
7844 tree *sc = NULL, *scp = NULL;
7845 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) || ptr)
7846 n->value |= GOVD_SEEN;
7847 offset_int o1, o2;
7848 if (offset)
7849 o1 = wi::to_offset (offset);
7850 else
7851 o1 = 0;
7852 if (bitpos)
7853 o1 = o1 + bitpos / BITS_PER_UNIT;
7854 sc = &OMP_CLAUSE_CHAIN (*osc);
7855 if (*sc != c
7856 && (OMP_CLAUSE_MAP_KIND (*sc)
7857 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
7858 sc = &OMP_CLAUSE_CHAIN (*sc);
7859 for (; *sc != c; sc = &OMP_CLAUSE_CHAIN (*sc))
7860 if (ptr && sc == prev_list_p)
7861 break;
7862 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc))
7863 != COMPONENT_REF
7864 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
7865 != INDIRECT_REF)
7866 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
7867 != ARRAY_REF))
7868 break;
7869 else
7871 tree offset2;
7872 HOST_WIDE_INT bitsize2, bitpos2;
7873 base = OMP_CLAUSE_DECL (*sc);
7874 if (TREE_CODE (base) == ARRAY_REF)
7876 while (TREE_CODE (base) == ARRAY_REF)
7877 base = TREE_OPERAND (base, 0);
7878 if (TREE_CODE (base) != COMPONENT_REF
7879 || (TREE_CODE (TREE_TYPE (base))
7880 != ARRAY_TYPE))
7881 break;
7883 else if (TREE_CODE (base) == INDIRECT_REF
7884 && (TREE_CODE (TREE_OPERAND (base, 0))
7885 == COMPONENT_REF)
7886 && (TREE_CODE (TREE_TYPE
7887 (TREE_OPERAND (base, 0)))
7888 == REFERENCE_TYPE))
7889 base = TREE_OPERAND (base, 0);
7890 base = get_inner_reference (base, &bitsize2,
7891 &bitpos2, &offset2,
7892 &mode, &unsignedp,
7893 &reversep, &volatilep);
7894 if ((TREE_CODE (base) == INDIRECT_REF
7895 || (TREE_CODE (base) == MEM_REF
7896 && integer_zerop (TREE_OPERAND (base,
7897 1))))
7898 && DECL_P (TREE_OPERAND (base, 0))
7899 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base,
7900 0)))
7901 == REFERENCE_TYPE))
7902 base = TREE_OPERAND (base, 0);
7903 if (base != decl)
7904 break;
7905 if (scp)
7906 continue;
7907 gcc_assert (offset == NULL_TREE
7908 || TREE_CODE (offset) == INTEGER_CST);
7909 tree d1 = OMP_CLAUSE_DECL (*sc);
7910 tree d2 = OMP_CLAUSE_DECL (c);
7911 while (TREE_CODE (d1) == ARRAY_REF)
7912 d1 = TREE_OPERAND (d1, 0);
7913 while (TREE_CODE (d2) == ARRAY_REF)
7914 d2 = TREE_OPERAND (d2, 0);
7915 if (TREE_CODE (d1) == INDIRECT_REF)
7916 d1 = TREE_OPERAND (d1, 0);
7917 if (TREE_CODE (d2) == INDIRECT_REF)
7918 d2 = TREE_OPERAND (d2, 0);
7919 while (TREE_CODE (d1) == COMPONENT_REF)
7920 if (TREE_CODE (d2) == COMPONENT_REF
7921 && TREE_OPERAND (d1, 1)
7922 == TREE_OPERAND (d2, 1))
7924 d1 = TREE_OPERAND (d1, 0);
7925 d2 = TREE_OPERAND (d2, 0);
7927 else
7928 break;
7929 if (d1 == d2)
7931 error_at (OMP_CLAUSE_LOCATION (c),
7932 "%qE appears more than once in map "
7933 "clauses", OMP_CLAUSE_DECL (c));
7934 remove = true;
7935 break;
7937 if (offset2)
7938 o2 = wi::to_offset (offset2);
7939 else
7940 o2 = 0;
7941 if (bitpos2)
7942 o2 = o2 + bitpos2 / BITS_PER_UNIT;
7943 if (wi::ltu_p (o1, o2)
7944 || (wi::eq_p (o1, o2) && bitpos < bitpos2))
7946 if (ptr)
7947 scp = sc;
7948 else
7949 break;
7952 if (remove)
7953 break;
7954 OMP_CLAUSE_SIZE (*osc)
7955 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc),
7956 size_one_node);
7957 if (ptr)
7959 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7960 OMP_CLAUSE_MAP);
7961 tree cl = NULL_TREE;
7962 enum gomp_map_kind mkind
7963 = code == OMP_TARGET_EXIT_DATA
7964 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
7965 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
7966 OMP_CLAUSE_DECL (c2)
7967 = unshare_expr (OMP_CLAUSE_DECL (c));
7968 OMP_CLAUSE_CHAIN (c2) = scp ? *scp : *prev_list_p;
7969 OMP_CLAUSE_SIZE (c2)
7970 = TYPE_SIZE_UNIT (ptr_type_node);
7971 cl = scp ? *prev_list_p : c2;
7972 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
7974 tree c4 = OMP_CLAUSE_CHAIN (*prev_list_p);
7975 tree c3
7976 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
7977 OMP_CLAUSE_MAP);
7978 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
7979 OMP_CLAUSE_DECL (c3)
7980 = unshare_expr (OMP_CLAUSE_DECL (c4));
7981 OMP_CLAUSE_SIZE (c3)
7982 = TYPE_SIZE_UNIT (ptr_type_node);
7983 OMP_CLAUSE_CHAIN (c3) = *prev_list_p;
7984 if (!scp)
7985 OMP_CLAUSE_CHAIN (c2) = c3;
7986 else
7987 cl = c3;
7989 if (scp)
7990 *scp = c2;
7991 if (sc == prev_list_p)
7993 *sc = cl;
7994 prev_list_p = NULL;
7996 else
7998 *prev_list_p = OMP_CLAUSE_CHAIN (c);
7999 list_p = prev_list_p;
8000 prev_list_p = NULL;
8001 OMP_CLAUSE_CHAIN (c) = *sc;
8002 *sc = cl;
8003 continue;
8006 else if (*sc != c)
8008 *list_p = OMP_CLAUSE_CHAIN (c);
8009 OMP_CLAUSE_CHAIN (c) = *sc;
8010 *sc = c;
8011 continue;
8015 if (!remove
8016 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ALWAYS_POINTER
8017 && OMP_CLAUSE_CHAIN (c)
8018 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c)) == OMP_CLAUSE_MAP
8019 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
8020 == GOMP_MAP_ALWAYS_POINTER))
8021 prev_list_p = list_p;
8022 break;
8024 flags = GOVD_MAP | GOVD_EXPLICIT;
8025 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
8026 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM)
8027 flags |= GOVD_MAP_ALWAYS_TO;
8028 goto do_add;
8030 case OMP_CLAUSE_DEPEND:
8031 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
8033 tree deps = OMP_CLAUSE_DECL (c);
8034 while (deps && TREE_CODE (deps) == TREE_LIST)
8036 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
8037 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
8038 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
8039 pre_p, NULL, is_gimple_val, fb_rvalue);
8040 deps = TREE_CHAIN (deps);
8042 break;
8044 else if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
8045 break;
8046 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8048 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8049 NULL, is_gimple_val, fb_rvalue);
8050 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8052 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8054 remove = true;
8055 break;
8057 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
8058 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8059 is_gimple_val, fb_rvalue) == GS_ERROR)
8061 remove = true;
8062 break;
8064 break;
8066 case OMP_CLAUSE_TO:
8067 case OMP_CLAUSE_FROM:
8068 case OMP_CLAUSE__CACHE_:
8069 decl = OMP_CLAUSE_DECL (c);
8070 if (error_operand_p (decl))
8072 remove = true;
8073 break;
8075 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
8076 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
8077 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
8078 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
8079 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
8081 remove = true;
8082 break;
8084 if (!DECL_P (decl))
8086 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
8087 NULL, is_gimple_lvalue, fb_lvalue)
8088 == GS_ERROR)
8090 remove = true;
8091 break;
8093 break;
8095 goto do_notice;
8097 case OMP_CLAUSE_USE_DEVICE_PTR:
8098 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
8099 goto do_add;
8100 case OMP_CLAUSE_IS_DEVICE_PTR:
8101 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
8102 goto do_add;
8104 do_add:
8105 decl = OMP_CLAUSE_DECL (c);
8106 do_add_decl:
8107 if (error_operand_p (decl))
8109 remove = true;
8110 break;
8112 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
8114 tree t = omp_member_access_dummy_var (decl);
8115 if (t)
8117 tree v = DECL_VALUE_EXPR (decl);
8118 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
8119 if (outer_ctx)
8120 omp_notice_variable (outer_ctx, t, true);
8123 if (code == OACC_DATA
8124 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
8125 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
8126 flags |= GOVD_MAP_0LEN_ARRAY;
8127 omp_add_variable (ctx, decl, flags);
8128 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
8129 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
8131 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
8132 GOVD_LOCAL | GOVD_SEEN);
8133 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
8134 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
8135 find_decl_expr,
8136 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
8137 NULL) == NULL_TREE)
8138 omp_add_variable (ctx,
8139 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
8140 GOVD_LOCAL | GOVD_SEEN);
8141 gimplify_omp_ctxp = ctx;
8142 push_gimplify_context ();
8144 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
8145 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
8147 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
8148 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
8149 pop_gimplify_context
8150 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
8151 push_gimplify_context ();
8152 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
8153 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
8154 pop_gimplify_context
8155 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
8156 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
8157 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
8159 gimplify_omp_ctxp = outer_ctx;
8161 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
8162 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
8164 gimplify_omp_ctxp = ctx;
8165 push_gimplify_context ();
8166 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
8168 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
8169 NULL, NULL);
8170 TREE_SIDE_EFFECTS (bind) = 1;
8171 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
8172 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
8174 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
8175 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
8176 pop_gimplify_context
8177 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
8178 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
8180 gimplify_omp_ctxp = outer_ctx;
8182 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
8183 && OMP_CLAUSE_LINEAR_STMT (c))
8185 gimplify_omp_ctxp = ctx;
8186 push_gimplify_context ();
8187 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
8189 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
8190 NULL, NULL);
8191 TREE_SIDE_EFFECTS (bind) = 1;
8192 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
8193 OMP_CLAUSE_LINEAR_STMT (c) = bind;
8195 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
8196 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
8197 pop_gimplify_context
8198 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
8199 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
8201 gimplify_omp_ctxp = outer_ctx;
8203 if (notice_outer)
8204 goto do_notice;
8205 break;
8207 case OMP_CLAUSE_COPYIN:
8208 case OMP_CLAUSE_COPYPRIVATE:
8209 decl = OMP_CLAUSE_DECL (c);
8210 if (error_operand_p (decl))
8212 remove = true;
8213 break;
8215 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
8216 && !remove
8217 && !omp_check_private (ctx, decl, true))
8219 remove = true;
8220 if (is_global_var (decl))
8222 if (DECL_THREAD_LOCAL_P (decl))
8223 remove = false;
8224 else if (DECL_HAS_VALUE_EXPR_P (decl))
8226 tree value = get_base_address (DECL_VALUE_EXPR (decl));
8228 if (value
8229 && DECL_P (value)
8230 && DECL_THREAD_LOCAL_P (value))
8231 remove = false;
8234 if (remove)
8235 error_at (OMP_CLAUSE_LOCATION (c),
8236 "copyprivate variable %qE is not threadprivate"
8237 " or private in outer context", DECL_NAME (decl));
8239 do_notice:
8240 if (outer_ctx)
8241 omp_notice_variable (outer_ctx, decl, true);
8242 if (check_non_private
8243 && region_type == ORT_WORKSHARE
8244 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
8245 || decl == OMP_CLAUSE_DECL (c)
8246 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
8247 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
8248 == ADDR_EXPR
8249 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
8250 == POINTER_PLUS_EXPR
8251 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
8252 (OMP_CLAUSE_DECL (c), 0), 0))
8253 == ADDR_EXPR)))))
8254 && omp_check_private (ctx, decl, false))
8256 error ("%s variable %qE is private in outer context",
8257 check_non_private, DECL_NAME (decl));
8258 remove = true;
8260 break;
8262 case OMP_CLAUSE_IF:
8263 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
8264 && OMP_CLAUSE_IF_MODIFIER (c) != code)
8266 const char *p[2];
8267 for (int i = 0; i < 2; i++)
8268 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
8270 case OMP_PARALLEL: p[i] = "parallel"; break;
8271 case OMP_TASK: p[i] = "task"; break;
8272 case OMP_TASKLOOP: p[i] = "taskloop"; break;
8273 case OMP_TARGET_DATA: p[i] = "target data"; break;
8274 case OMP_TARGET: p[i] = "target"; break;
8275 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
8276 case OMP_TARGET_ENTER_DATA:
8277 p[i] = "target enter data"; break;
8278 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
8279 default: gcc_unreachable ();
8281 error_at (OMP_CLAUSE_LOCATION (c),
8282 "expected %qs %<if%> clause modifier rather than %qs",
8283 p[0], p[1]);
8284 remove = true;
8286 /* Fall through. */
8288 case OMP_CLAUSE_FINAL:
8289 OMP_CLAUSE_OPERAND (c, 0)
8290 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
8291 /* Fall through. */
8293 case OMP_CLAUSE_SCHEDULE:
8294 case OMP_CLAUSE_NUM_THREADS:
8295 case OMP_CLAUSE_NUM_TEAMS:
8296 case OMP_CLAUSE_THREAD_LIMIT:
8297 case OMP_CLAUSE_DIST_SCHEDULE:
8298 case OMP_CLAUSE_DEVICE:
8299 case OMP_CLAUSE_PRIORITY:
8300 case OMP_CLAUSE_GRAINSIZE:
8301 case OMP_CLAUSE_NUM_TASKS:
8302 case OMP_CLAUSE_HINT:
8303 case OMP_CLAUSE__CILK_FOR_COUNT_:
8304 case OMP_CLAUSE_ASYNC:
8305 case OMP_CLAUSE_WAIT:
8306 case OMP_CLAUSE_NUM_GANGS:
8307 case OMP_CLAUSE_NUM_WORKERS:
8308 case OMP_CLAUSE_VECTOR_LENGTH:
8309 case OMP_CLAUSE_WORKER:
8310 case OMP_CLAUSE_VECTOR:
8311 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
8312 is_gimple_val, fb_rvalue) == GS_ERROR)
8313 remove = true;
8314 break;
8316 case OMP_CLAUSE_GANG:
8317 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
8318 is_gimple_val, fb_rvalue) == GS_ERROR)
8319 remove = true;
8320 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
8321 is_gimple_val, fb_rvalue) == GS_ERROR)
8322 remove = true;
8323 break;
8325 case OMP_CLAUSE_TILE:
8326 for (tree list = OMP_CLAUSE_TILE_LIST (c); !remove && list;
8327 list = TREE_CHAIN (list))
8329 if (gimplify_expr (&TREE_VALUE (list), pre_p, NULL,
8330 is_gimple_val, fb_rvalue) == GS_ERROR)
8331 remove = true;
8333 break;
8335 case OMP_CLAUSE_NOWAIT:
8336 case OMP_CLAUSE_ORDERED:
8337 case OMP_CLAUSE_UNTIED:
8338 case OMP_CLAUSE_COLLAPSE:
8339 case OMP_CLAUSE_AUTO:
8340 case OMP_CLAUSE_SEQ:
8341 case OMP_CLAUSE_INDEPENDENT:
8342 case OMP_CLAUSE_MERGEABLE:
8343 case OMP_CLAUSE_PROC_BIND:
8344 case OMP_CLAUSE_SAFELEN:
8345 case OMP_CLAUSE_SIMDLEN:
8346 case OMP_CLAUSE_NOGROUP:
8347 case OMP_CLAUSE_THREADS:
8348 case OMP_CLAUSE_SIMD:
8349 break;
8351 case OMP_CLAUSE_DEFAULTMAP:
8352 ctx->target_map_scalars_firstprivate = false;
8353 break;
8355 case OMP_CLAUSE_ALIGNED:
8356 decl = OMP_CLAUSE_DECL (c);
8357 if (error_operand_p (decl))
8359 remove = true;
8360 break;
8362 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
8363 is_gimple_val, fb_rvalue) == GS_ERROR)
8365 remove = true;
8366 break;
8368 if (!is_global_var (decl)
8369 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
8370 omp_add_variable (ctx, decl, GOVD_ALIGNED);
8371 break;
8373 case OMP_CLAUSE_DEFAULT:
8374 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
8375 break;
8377 default:
8378 gcc_unreachable ();
8381 if (code == OACC_DATA
8382 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
8383 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
8384 remove = true;
8385 if (remove)
8386 *list_p = OMP_CLAUSE_CHAIN (c);
8387 else
8388 list_p = &OMP_CLAUSE_CHAIN (c);
8391 gimplify_omp_ctxp = ctx;
8392 if (struct_map_to_clause)
8393 delete struct_map_to_clause;
8396 /* Return true if DECL is a candidate for shared to firstprivate
8397 optimization. We only consider non-addressable scalars, not
8398 too big, and not references. */
8400 static bool
8401 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
8403 if (TREE_ADDRESSABLE (decl))
8404 return false;
8405 tree type = TREE_TYPE (decl);
8406 if (!is_gimple_reg_type (type)
8407 || TREE_CODE (type) == REFERENCE_TYPE
8408 || TREE_ADDRESSABLE (type))
8409 return false;
8410 /* Don't optimize too large decls, as each thread/task will have
8411 its own. */
8412 HOST_WIDE_INT len = int_size_in_bytes (type);
8413 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
8414 return false;
8415 if (lang_hooks.decls.omp_privatize_by_reference (decl))
8416 return false;
8417 return true;
8420 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
8421 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
8422 GOVD_WRITTEN in outer contexts. */
8424 static void
8425 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
8427 for (; ctx; ctx = ctx->outer_context)
8429 splay_tree_node n = splay_tree_lookup (ctx->variables,
8430 (splay_tree_key) decl);
8431 if (n == NULL)
8432 continue;
8433 else if (n->value & GOVD_SHARED)
8435 n->value |= GOVD_WRITTEN;
8436 return;
8438 else if (n->value & GOVD_DATA_SHARE_CLASS)
8439 return;
8443 /* Helper callback for walk_gimple_seq to discover possible stores
8444 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
8445 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
8446 for those. */
8448 static tree
8449 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
8451 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
8453 *walk_subtrees = 0;
8454 if (!wi->is_lhs)
8455 return NULL_TREE;
8457 tree op = *tp;
8460 if (handled_component_p (op))
8461 op = TREE_OPERAND (op, 0);
8462 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
8463 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
8464 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
8465 else
8466 break;
8468 while (1);
8469 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
8470 return NULL_TREE;
8472 omp_mark_stores (gimplify_omp_ctxp, op);
8473 return NULL_TREE;
8476 /* Helper callback for walk_gimple_seq to discover possible stores
8477 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
8478 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
8479 for those. */
8481 static tree
8482 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
8483 bool *handled_ops_p,
8484 struct walk_stmt_info *wi)
8486 gimple *stmt = gsi_stmt (*gsi_p);
8487 switch (gimple_code (stmt))
8489 /* Don't recurse on OpenMP constructs for which
8490 gimplify_adjust_omp_clauses already handled the bodies,
8491 except handle gimple_omp_for_pre_body. */
8492 case GIMPLE_OMP_FOR:
8493 *handled_ops_p = true;
8494 if (gimple_omp_for_pre_body (stmt))
8495 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
8496 omp_find_stores_stmt, omp_find_stores_op, wi);
8497 break;
8498 case GIMPLE_OMP_PARALLEL:
8499 case GIMPLE_OMP_TASK:
8500 case GIMPLE_OMP_SECTIONS:
8501 case GIMPLE_OMP_SINGLE:
8502 case GIMPLE_OMP_TARGET:
8503 case GIMPLE_OMP_TEAMS:
8504 case GIMPLE_OMP_CRITICAL:
8505 *handled_ops_p = true;
8506 break;
8507 default:
8508 break;
8510 return NULL_TREE;
8513 struct gimplify_adjust_omp_clauses_data
8515 tree *list_p;
8516 gimple_seq *pre_p;
8519 /* For all variables that were not actually used within the context,
8520 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
8522 static int
8523 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
8525 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
8526 gimple_seq *pre_p
8527 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
8528 tree decl = (tree) n->key;
8529 unsigned flags = n->value;
8530 enum omp_clause_code code;
8531 tree clause;
8532 bool private_debug;
8534 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
8535 return 0;
8536 if ((flags & GOVD_SEEN) == 0)
8537 return 0;
8538 if (flags & GOVD_DEBUG_PRIVATE)
8540 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_PRIVATE);
8541 private_debug = true;
8543 else if (flags & GOVD_MAP)
8544 private_debug = false;
8545 else
8546 private_debug
8547 = lang_hooks.decls.omp_private_debug_clause (decl,
8548 !!(flags & GOVD_SHARED));
8549 if (private_debug)
8550 code = OMP_CLAUSE_PRIVATE;
8551 else if (flags & GOVD_MAP)
8553 code = OMP_CLAUSE_MAP;
8554 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
8555 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
8557 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
8558 return 0;
8561 else if (flags & GOVD_SHARED)
8563 if (is_global_var (decl))
8565 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
8566 while (ctx != NULL)
8568 splay_tree_node on
8569 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8570 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
8571 | GOVD_PRIVATE | GOVD_REDUCTION
8572 | GOVD_LINEAR | GOVD_MAP)) != 0)
8573 break;
8574 ctx = ctx->outer_context;
8576 if (ctx == NULL)
8577 return 0;
8579 code = OMP_CLAUSE_SHARED;
8581 else if (flags & GOVD_PRIVATE)
8582 code = OMP_CLAUSE_PRIVATE;
8583 else if (flags & GOVD_FIRSTPRIVATE)
8585 code = OMP_CLAUSE_FIRSTPRIVATE;
8586 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
8587 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
8588 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
8590 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
8591 "%<target%> construct", decl);
8592 return 0;
8595 else if (flags & GOVD_LASTPRIVATE)
8596 code = OMP_CLAUSE_LASTPRIVATE;
8597 else if (flags & GOVD_ALIGNED)
8598 return 0;
8599 else
8600 gcc_unreachable ();
8602 if (((flags & GOVD_LASTPRIVATE)
8603 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
8604 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8605 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8607 tree chain = *list_p;
8608 clause = build_omp_clause (input_location, code);
8609 OMP_CLAUSE_DECL (clause) = decl;
8610 OMP_CLAUSE_CHAIN (clause) = chain;
8611 if (private_debug)
8612 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
8613 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
8614 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
8615 else if (code == OMP_CLAUSE_SHARED
8616 && (flags & GOVD_WRITTEN) == 0
8617 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8618 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
8619 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
8620 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
8621 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
8623 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
8624 OMP_CLAUSE_DECL (nc) = decl;
8625 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
8626 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
8627 OMP_CLAUSE_DECL (clause)
8628 = build_simple_mem_ref_loc (input_location, decl);
8629 OMP_CLAUSE_DECL (clause)
8630 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
8631 build_int_cst (build_pointer_type (char_type_node), 0));
8632 OMP_CLAUSE_SIZE (clause) = size_zero_node;
8633 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8634 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
8635 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
8636 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
8637 OMP_CLAUSE_CHAIN (nc) = chain;
8638 OMP_CLAUSE_CHAIN (clause) = nc;
8639 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8640 gimplify_omp_ctxp = ctx->outer_context;
8641 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
8642 pre_p, NULL, is_gimple_val, fb_rvalue);
8643 gimplify_omp_ctxp = ctx;
8645 else if (code == OMP_CLAUSE_MAP)
8647 int kind = (flags & GOVD_MAP_TO_ONLY
8648 ? GOMP_MAP_TO
8649 : GOMP_MAP_TOFROM);
8650 if (flags & GOVD_MAP_FORCE)
8651 kind |= GOMP_MAP_FLAG_FORCE;
8652 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
8653 if (DECL_SIZE (decl)
8654 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
8656 tree decl2 = DECL_VALUE_EXPR (decl);
8657 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
8658 decl2 = TREE_OPERAND (decl2, 0);
8659 gcc_assert (DECL_P (decl2));
8660 tree mem = build_simple_mem_ref (decl2);
8661 OMP_CLAUSE_DECL (clause) = mem;
8662 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
8663 if (gimplify_omp_ctxp->outer_context)
8665 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
8666 omp_notice_variable (ctx, decl2, true);
8667 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
8669 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
8670 OMP_CLAUSE_MAP);
8671 OMP_CLAUSE_DECL (nc) = decl;
8672 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8673 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
8674 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
8675 else
8676 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
8677 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
8678 OMP_CLAUSE_CHAIN (clause) = nc;
8680 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
8681 && lang_hooks.decls.omp_privatize_by_reference (decl))
8683 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
8684 OMP_CLAUSE_SIZE (clause)
8685 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
8686 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8687 gimplify_omp_ctxp = ctx->outer_context;
8688 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
8689 pre_p, NULL, is_gimple_val, fb_rvalue);
8690 gimplify_omp_ctxp = ctx;
8691 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
8692 OMP_CLAUSE_MAP);
8693 OMP_CLAUSE_DECL (nc) = decl;
8694 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8695 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
8696 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
8697 OMP_CLAUSE_CHAIN (clause) = nc;
8699 else
8700 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
8702 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
8704 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
8705 OMP_CLAUSE_DECL (nc) = decl;
8706 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
8707 OMP_CLAUSE_CHAIN (nc) = chain;
8708 OMP_CLAUSE_CHAIN (clause) = nc;
8709 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8710 gimplify_omp_ctxp = ctx->outer_context;
8711 lang_hooks.decls.omp_finish_clause (nc, pre_p);
8712 gimplify_omp_ctxp = ctx;
8714 *list_p = clause;
8715 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8716 gimplify_omp_ctxp = ctx->outer_context;
8717 lang_hooks.decls.omp_finish_clause (clause, pre_p);
8718 if (gimplify_omp_ctxp)
8719 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
8720 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
8721 && DECL_P (OMP_CLAUSE_SIZE (clause)))
8722 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
8723 true);
8724 gimplify_omp_ctxp = ctx;
8725 return 0;
8728 static void
8729 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
8730 enum tree_code code)
8732 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8733 tree c, decl;
8735 if (body)
8737 struct gimplify_omp_ctx *octx;
8738 for (octx = ctx; octx; octx = octx->outer_context)
8739 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
8740 break;
8741 if (octx)
8743 struct walk_stmt_info wi;
8744 memset (&wi, 0, sizeof (wi));
8745 walk_gimple_seq (body, omp_find_stores_stmt,
8746 omp_find_stores_op, &wi);
8749 while ((c = *list_p) != NULL)
8751 splay_tree_node n;
8752 bool remove = false;
8754 switch (OMP_CLAUSE_CODE (c))
8756 case OMP_CLAUSE_FIRSTPRIVATE:
8757 if ((ctx->region_type & ORT_TARGET)
8758 && (ctx->region_type & ORT_ACC) == 0
8759 && TYPE_ATOMIC (strip_array_types
8760 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
8762 error_at (OMP_CLAUSE_LOCATION (c),
8763 "%<_Atomic%> %qD in %<firstprivate%> clause on "
8764 "%<target%> construct", OMP_CLAUSE_DECL (c));
8765 remove = true;
8766 break;
8768 /* FALLTHRU */
8769 case OMP_CLAUSE_PRIVATE:
8770 case OMP_CLAUSE_SHARED:
8771 case OMP_CLAUSE_LINEAR:
8772 decl = OMP_CLAUSE_DECL (c);
8773 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8774 remove = !(n->value & GOVD_SEEN);
8775 if (! remove)
8777 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
8778 if ((n->value & GOVD_DEBUG_PRIVATE)
8779 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
8781 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
8782 || ((n->value & GOVD_DATA_SHARE_CLASS)
8783 == GOVD_PRIVATE));
8784 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
8785 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
8787 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
8788 && (n->value & GOVD_WRITTEN) == 0
8789 && DECL_P (decl)
8790 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8791 OMP_CLAUSE_SHARED_READONLY (c) = 1;
8792 else if (DECL_P (decl)
8793 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
8794 && (n->value & GOVD_WRITTEN) != 1)
8795 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
8796 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
8797 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8798 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8800 break;
8802 case OMP_CLAUSE_LASTPRIVATE:
8803 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
8804 accurately reflect the presence of a FIRSTPRIVATE clause. */
8805 decl = OMP_CLAUSE_DECL (c);
8806 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8807 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
8808 = (n->value & GOVD_FIRSTPRIVATE) != 0;
8809 if (code == OMP_DISTRIBUTE
8810 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
8812 remove = true;
8813 error_at (OMP_CLAUSE_LOCATION (c),
8814 "same variable used in %<firstprivate%> and "
8815 "%<lastprivate%> clauses on %<distribute%> "
8816 "construct");
8818 if (!remove
8819 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
8820 && DECL_P (decl)
8821 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
8822 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
8823 break;
8825 case OMP_CLAUSE_ALIGNED:
8826 decl = OMP_CLAUSE_DECL (c);
8827 if (!is_global_var (decl))
8829 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8830 remove = n == NULL || !(n->value & GOVD_SEEN);
8831 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
8833 struct gimplify_omp_ctx *octx;
8834 if (n != NULL
8835 && (n->value & (GOVD_DATA_SHARE_CLASS
8836 & ~GOVD_FIRSTPRIVATE)))
8837 remove = true;
8838 else
8839 for (octx = ctx->outer_context; octx;
8840 octx = octx->outer_context)
8842 n = splay_tree_lookup (octx->variables,
8843 (splay_tree_key) decl);
8844 if (n == NULL)
8845 continue;
8846 if (n->value & GOVD_LOCAL)
8847 break;
8848 /* We have to avoid assigning a shared variable
8849 to itself when trying to add
8850 __builtin_assume_aligned. */
8851 if (n->value & GOVD_SHARED)
8853 remove = true;
8854 break;
8859 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
8861 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8862 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
8863 remove = true;
8865 break;
8867 case OMP_CLAUSE_MAP:
8868 if (code == OMP_TARGET_EXIT_DATA
8869 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
8871 remove = true;
8872 break;
8874 decl = OMP_CLAUSE_DECL (c);
8875 /* Data clauses associated with acc parallel reductions must be
8876 compatible with present_or_copy. Warn and adjust the clause
8877 if that is not the case. */
8878 if (ctx->region_type == ORT_ACC_PARALLEL)
8880 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
8881 n = NULL;
8883 if (DECL_P (t))
8884 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
8886 if (n && (n->value & GOVD_REDUCTION))
8888 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
8890 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
8891 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
8892 && kind != GOMP_MAP_FORCE_PRESENT
8893 && kind != GOMP_MAP_POINTER)
8895 warning_at (OMP_CLAUSE_LOCATION (c), 0,
8896 "incompatible data clause with reduction "
8897 "on %qE; promoting to present_or_copy",
8898 DECL_NAME (t));
8899 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
8903 if (!DECL_P (decl))
8905 if ((ctx->region_type & ORT_TARGET) != 0
8906 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
8908 if (TREE_CODE (decl) == INDIRECT_REF
8909 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
8910 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
8911 == REFERENCE_TYPE))
8912 decl = TREE_OPERAND (decl, 0);
8913 if (TREE_CODE (decl) == COMPONENT_REF)
8915 while (TREE_CODE (decl) == COMPONENT_REF)
8916 decl = TREE_OPERAND (decl, 0);
8917 if (DECL_P (decl))
8919 n = splay_tree_lookup (ctx->variables,
8920 (splay_tree_key) decl);
8921 if (!(n->value & GOVD_SEEN))
8922 remove = true;
8926 break;
8928 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8929 if ((ctx->region_type & ORT_TARGET) != 0
8930 && !(n->value & GOVD_SEEN)
8931 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
8932 && !lookup_attribute ("omp declare target link",
8933 DECL_ATTRIBUTES (decl)))
8935 remove = true;
8936 /* For struct element mapping, if struct is never referenced
8937 in target block and none of the mapping has always modifier,
8938 remove all the struct element mappings, which immediately
8939 follow the GOMP_MAP_STRUCT map clause. */
8940 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
8942 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
8943 while (cnt--)
8944 OMP_CLAUSE_CHAIN (c)
8945 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
8948 else if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
8949 && code == OMP_TARGET_EXIT_DATA)
8950 remove = true;
8951 else if (DECL_SIZE (decl)
8952 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
8953 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
8954 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
8955 && (OMP_CLAUSE_MAP_KIND (c)
8956 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
8958 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
8959 for these, TREE_CODE (DECL_SIZE (decl)) will always be
8960 INTEGER_CST. */
8961 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
8963 tree decl2 = DECL_VALUE_EXPR (decl);
8964 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
8965 decl2 = TREE_OPERAND (decl2, 0);
8966 gcc_assert (DECL_P (decl2));
8967 tree mem = build_simple_mem_ref (decl2);
8968 OMP_CLAUSE_DECL (c) = mem;
8969 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
8970 if (ctx->outer_context)
8972 omp_notice_variable (ctx->outer_context, decl2, true);
8973 omp_notice_variable (ctx->outer_context,
8974 OMP_CLAUSE_SIZE (c), true);
8976 if (((ctx->region_type & ORT_TARGET) != 0
8977 || !ctx->target_firstprivatize_array_bases)
8978 && ((n->value & GOVD_SEEN) == 0
8979 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
8981 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
8982 OMP_CLAUSE_MAP);
8983 OMP_CLAUSE_DECL (nc) = decl;
8984 OMP_CLAUSE_SIZE (nc) = size_zero_node;
8985 if (ctx->target_firstprivatize_array_bases)
8986 OMP_CLAUSE_SET_MAP_KIND (nc,
8987 GOMP_MAP_FIRSTPRIVATE_POINTER);
8988 else
8989 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
8990 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
8991 OMP_CLAUSE_CHAIN (c) = nc;
8992 c = nc;
8995 else
8997 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
8998 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
8999 gcc_assert ((n->value & GOVD_SEEN) == 0
9000 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
9001 == 0));
9003 break;
9005 case OMP_CLAUSE_TO:
9006 case OMP_CLAUSE_FROM:
9007 case OMP_CLAUSE__CACHE_:
9008 decl = OMP_CLAUSE_DECL (c);
9009 if (!DECL_P (decl))
9010 break;
9011 if (DECL_SIZE (decl)
9012 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
9014 tree decl2 = DECL_VALUE_EXPR (decl);
9015 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
9016 decl2 = TREE_OPERAND (decl2, 0);
9017 gcc_assert (DECL_P (decl2));
9018 tree mem = build_simple_mem_ref (decl2);
9019 OMP_CLAUSE_DECL (c) = mem;
9020 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
9021 if (ctx->outer_context)
9023 omp_notice_variable (ctx->outer_context, decl2, true);
9024 omp_notice_variable (ctx->outer_context,
9025 OMP_CLAUSE_SIZE (c), true);
9028 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9029 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
9030 break;
9032 case OMP_CLAUSE_REDUCTION:
9033 decl = OMP_CLAUSE_DECL (c);
9034 /* OpenACC reductions need a present_or_copy data clause.
9035 Add one if necessary. Error is the reduction is private. */
9036 if (ctx->region_type == ORT_ACC_PARALLEL)
9038 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
9039 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
9040 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
9041 "reduction on %qE", DECL_NAME (decl));
9042 else if ((n->value & GOVD_MAP) == 0)
9044 tree next = OMP_CLAUSE_CHAIN (c);
9045 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
9046 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
9047 OMP_CLAUSE_DECL (nc) = decl;
9048 OMP_CLAUSE_CHAIN (c) = nc;
9049 lang_hooks.decls.omp_finish_clause (nc, pre_p);
9050 while (1)
9052 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
9053 if (OMP_CLAUSE_CHAIN (nc) == NULL)
9054 break;
9055 nc = OMP_CLAUSE_CHAIN (nc);
9057 OMP_CLAUSE_CHAIN (nc) = next;
9058 n->value |= GOVD_MAP;
9061 if (DECL_P (decl)
9062 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
9063 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
9064 break;
9065 case OMP_CLAUSE_COPYIN:
9066 case OMP_CLAUSE_COPYPRIVATE:
9067 case OMP_CLAUSE_IF:
9068 case OMP_CLAUSE_NUM_THREADS:
9069 case OMP_CLAUSE_NUM_TEAMS:
9070 case OMP_CLAUSE_THREAD_LIMIT:
9071 case OMP_CLAUSE_DIST_SCHEDULE:
9072 case OMP_CLAUSE_DEVICE:
9073 case OMP_CLAUSE_SCHEDULE:
9074 case OMP_CLAUSE_NOWAIT:
9075 case OMP_CLAUSE_ORDERED:
9076 case OMP_CLAUSE_DEFAULT:
9077 case OMP_CLAUSE_UNTIED:
9078 case OMP_CLAUSE_COLLAPSE:
9079 case OMP_CLAUSE_FINAL:
9080 case OMP_CLAUSE_MERGEABLE:
9081 case OMP_CLAUSE_PROC_BIND:
9082 case OMP_CLAUSE_SAFELEN:
9083 case OMP_CLAUSE_SIMDLEN:
9084 case OMP_CLAUSE_DEPEND:
9085 case OMP_CLAUSE_PRIORITY:
9086 case OMP_CLAUSE_GRAINSIZE:
9087 case OMP_CLAUSE_NUM_TASKS:
9088 case OMP_CLAUSE_NOGROUP:
9089 case OMP_CLAUSE_THREADS:
9090 case OMP_CLAUSE_SIMD:
9091 case OMP_CLAUSE_HINT:
9092 case OMP_CLAUSE_DEFAULTMAP:
9093 case OMP_CLAUSE_USE_DEVICE_PTR:
9094 case OMP_CLAUSE_IS_DEVICE_PTR:
9095 case OMP_CLAUSE__CILK_FOR_COUNT_:
9096 case OMP_CLAUSE_ASYNC:
9097 case OMP_CLAUSE_WAIT:
9098 case OMP_CLAUSE_INDEPENDENT:
9099 case OMP_CLAUSE_NUM_GANGS:
9100 case OMP_CLAUSE_NUM_WORKERS:
9101 case OMP_CLAUSE_VECTOR_LENGTH:
9102 case OMP_CLAUSE_GANG:
9103 case OMP_CLAUSE_WORKER:
9104 case OMP_CLAUSE_VECTOR:
9105 case OMP_CLAUSE_AUTO:
9106 case OMP_CLAUSE_SEQ:
9107 break;
9109 case OMP_CLAUSE_TILE:
9110 /* We're not yet making use of the information provided by OpenACC
9111 tile clauses. Discard these here, to simplify later middle end
9112 processing. */
9113 remove = true;
9114 break;
9116 default:
9117 gcc_unreachable ();
9120 if (remove)
9121 *list_p = OMP_CLAUSE_CHAIN (c);
9122 else
9123 list_p = &OMP_CLAUSE_CHAIN (c);
9126 /* Add in any implicit data sharing. */
9127 struct gimplify_adjust_omp_clauses_data data;
9128 data.list_p = list_p;
9129 data.pre_p = pre_p;
9130 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
9132 gimplify_omp_ctxp = ctx->outer_context;
9133 delete_omp_context (ctx);
9136 /* Gimplify OACC_CACHE. */
9138 static void
9139 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
9141 tree expr = *expr_p;
9143 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
9144 OACC_CACHE);
9145 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
9146 OACC_CACHE);
9148 /* TODO: Do something sensible with this information. */
9150 *expr_p = NULL_TREE;
9153 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
9154 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
9155 kind. The entry kind will replace the one in CLAUSE, while the exit
9156 kind will be used in a new omp_clause and returned to the caller. */
9158 static tree
9159 gimplify_oacc_declare_1 (tree clause)
9161 HOST_WIDE_INT kind, new_op;
9162 bool ret = false;
9163 tree c = NULL;
9165 kind = OMP_CLAUSE_MAP_KIND (clause);
9167 switch (kind)
9169 case GOMP_MAP_ALLOC:
9170 case GOMP_MAP_FORCE_ALLOC:
9171 case GOMP_MAP_FORCE_TO:
9172 new_op = GOMP_MAP_DELETE;
9173 ret = true;
9174 break;
9176 case GOMP_MAP_FORCE_FROM:
9177 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
9178 new_op = GOMP_MAP_FORCE_FROM;
9179 ret = true;
9180 break;
9182 case GOMP_MAP_FORCE_TOFROM:
9183 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_TO);
9184 new_op = GOMP_MAP_FORCE_FROM;
9185 ret = true;
9186 break;
9188 case GOMP_MAP_FROM:
9189 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
9190 new_op = GOMP_MAP_FROM;
9191 ret = true;
9192 break;
9194 case GOMP_MAP_TOFROM:
9195 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
9196 new_op = GOMP_MAP_FROM;
9197 ret = true;
9198 break;
9200 case GOMP_MAP_DEVICE_RESIDENT:
9201 case GOMP_MAP_FORCE_DEVICEPTR:
9202 case GOMP_MAP_FORCE_PRESENT:
9203 case GOMP_MAP_LINK:
9204 case GOMP_MAP_POINTER:
9205 case GOMP_MAP_TO:
9206 break;
9208 default:
9209 gcc_unreachable ();
9210 break;
9213 if (ret)
9215 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
9216 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
9217 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
9220 return c;
9223 /* Gimplify OACC_DECLARE. */
9225 static void
9226 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
9228 tree expr = *expr_p;
9229 gomp_target *stmt;
9230 tree clauses, t;
9232 clauses = OACC_DECLARE_CLAUSES (expr);
9234 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
9236 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
9238 tree decl = OMP_CLAUSE_DECL (t);
9240 if (TREE_CODE (decl) == MEM_REF)
9241 continue;
9243 if (VAR_P (decl)
9244 && !is_global_var (decl)
9245 && DECL_CONTEXT (decl) == current_function_decl)
9247 tree c = gimplify_oacc_declare_1 (t);
9248 if (c)
9250 if (oacc_declare_returns == NULL)
9251 oacc_declare_returns = new hash_map<tree, tree>;
9253 oacc_declare_returns->put (decl, c);
9257 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
9260 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
9261 clauses);
9263 gimplify_seq_add_stmt (pre_p, stmt);
9265 *expr_p = NULL_TREE;
9268 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
9269 gimplification of the body, as well as scanning the body for used
9270 variables. We need to do this scan now, because variable-sized
9271 decls will be decomposed during gimplification. */
9273 static void
9274 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
9276 tree expr = *expr_p;
9277 gimple *g;
9278 gimple_seq body = NULL;
9280 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
9281 OMP_PARALLEL_COMBINED (expr)
9282 ? ORT_COMBINED_PARALLEL
9283 : ORT_PARALLEL, OMP_PARALLEL);
9285 push_gimplify_context ();
9287 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
9288 if (gimple_code (g) == GIMPLE_BIND)
9289 pop_gimplify_context (g);
9290 else
9291 pop_gimplify_context (NULL);
9293 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
9294 OMP_PARALLEL);
9296 g = gimple_build_omp_parallel (body,
9297 OMP_PARALLEL_CLAUSES (expr),
9298 NULL_TREE, NULL_TREE);
9299 if (OMP_PARALLEL_COMBINED (expr))
9300 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
9301 gimplify_seq_add_stmt (pre_p, g);
9302 *expr_p = NULL_TREE;
9305 /* Gimplify the contents of an OMP_TASK statement. This involves
9306 gimplification of the body, as well as scanning the body for used
9307 variables. We need to do this scan now, because variable-sized
9308 decls will be decomposed during gimplification. */
9310 static void
9311 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
9313 tree expr = *expr_p;
9314 gimple *g;
9315 gimple_seq body = NULL;
9317 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
9318 omp_find_clause (OMP_TASK_CLAUSES (expr),
9319 OMP_CLAUSE_UNTIED)
9320 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
9322 push_gimplify_context ();
9324 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
9325 if (gimple_code (g) == GIMPLE_BIND)
9326 pop_gimplify_context (g);
9327 else
9328 pop_gimplify_context (NULL);
9330 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
9331 OMP_TASK);
9333 g = gimple_build_omp_task (body,
9334 OMP_TASK_CLAUSES (expr),
9335 NULL_TREE, NULL_TREE,
9336 NULL_TREE, NULL_TREE, NULL_TREE);
9337 gimplify_seq_add_stmt (pre_p, g);
9338 *expr_p = NULL_TREE;
9341 /* Helper function of gimplify_omp_for, find OMP_FOR resp. OMP_SIMD
9342 with non-NULL OMP_FOR_INIT. */
9344 static tree
9345 find_combined_omp_for (tree *tp, int *walk_subtrees, void *)
9347 *walk_subtrees = 0;
9348 switch (TREE_CODE (*tp))
9350 case OMP_FOR:
9351 *walk_subtrees = 1;
9352 /* FALLTHRU */
9353 case OMP_SIMD:
9354 if (OMP_FOR_INIT (*tp) != NULL_TREE)
9355 return *tp;
9356 break;
9357 case BIND_EXPR:
9358 case STATEMENT_LIST:
9359 case OMP_PARALLEL:
9360 *walk_subtrees = 1;
9361 break;
9362 default:
9363 break;
9365 return NULL_TREE;
9368 /* Gimplify the gross structure of an OMP_FOR statement. */
9370 static enum gimplify_status
9371 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
9373 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
9374 enum gimplify_status ret = GS_ALL_DONE;
9375 enum gimplify_status tret;
9376 gomp_for *gfor;
9377 gimple_seq for_body, for_pre_body;
9378 int i;
9379 bitmap has_decl_expr = NULL;
9380 enum omp_region_type ort = ORT_WORKSHARE;
9382 orig_for_stmt = for_stmt = *expr_p;
9384 switch (TREE_CODE (for_stmt))
9386 case OMP_FOR:
9387 case CILK_FOR:
9388 case OMP_DISTRIBUTE:
9389 break;
9390 case OACC_LOOP:
9391 ort = ORT_ACC;
9392 break;
9393 case OMP_TASKLOOP:
9394 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
9395 ort = ORT_UNTIED_TASK;
9396 else
9397 ort = ORT_TASK;
9398 break;
9399 case OMP_SIMD:
9400 case CILK_SIMD:
9401 ort = ORT_SIMD;
9402 break;
9403 default:
9404 gcc_unreachable ();
9407 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
9408 clause for the IV. */
9409 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9411 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
9412 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
9413 decl = TREE_OPERAND (t, 0);
9414 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
9415 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
9416 && OMP_CLAUSE_DECL (c) == decl)
9418 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
9419 break;
9423 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
9425 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
9426 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
9427 find_combined_omp_for, NULL, NULL);
9428 if (inner_for_stmt == NULL_TREE)
9430 gcc_assert (seen_error ());
9431 *expr_p = NULL_TREE;
9432 return GS_ERROR;
9436 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
9437 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
9438 TREE_CODE (for_stmt));
9440 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
9441 gimplify_omp_ctxp->distribute = true;
9443 /* Handle OMP_FOR_INIT. */
9444 for_pre_body = NULL;
9445 if (ort == ORT_SIMD && OMP_FOR_PRE_BODY (for_stmt))
9447 has_decl_expr = BITMAP_ALLOC (NULL);
9448 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
9449 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
9450 == VAR_DECL)
9452 t = OMP_FOR_PRE_BODY (for_stmt);
9453 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
9455 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
9457 tree_stmt_iterator si;
9458 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
9459 tsi_next (&si))
9461 t = tsi_stmt (si);
9462 if (TREE_CODE (t) == DECL_EXPR
9463 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
9464 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
9468 if (OMP_FOR_PRE_BODY (for_stmt))
9470 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
9471 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
9472 else
9474 struct gimplify_omp_ctx ctx;
9475 memset (&ctx, 0, sizeof (ctx));
9476 ctx.region_type = ORT_NONE;
9477 gimplify_omp_ctxp = &ctx;
9478 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
9479 gimplify_omp_ctxp = NULL;
9482 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
9484 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
9485 for_stmt = inner_for_stmt;
9487 /* For taskloop, need to gimplify the start, end and step before the
9488 taskloop, outside of the taskloop omp context. */
9489 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
9491 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
9493 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
9494 if (!is_gimple_constant (TREE_OPERAND (t, 1)))
9496 TREE_OPERAND (t, 1)
9497 = get_initialized_tmp_var (TREE_OPERAND (t, 1),
9498 pre_p, NULL, false);
9499 tree c = build_omp_clause (input_location,
9500 OMP_CLAUSE_FIRSTPRIVATE);
9501 OMP_CLAUSE_DECL (c) = TREE_OPERAND (t, 1);
9502 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9503 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9506 /* Handle OMP_FOR_COND. */
9507 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
9508 if (!is_gimple_constant (TREE_OPERAND (t, 1)))
9510 TREE_OPERAND (t, 1)
9511 = get_initialized_tmp_var (TREE_OPERAND (t, 1),
9512 gimple_seq_empty_p (for_pre_body)
9513 ? pre_p : &for_pre_body, NULL,
9514 false);
9515 tree c = build_omp_clause (input_location,
9516 OMP_CLAUSE_FIRSTPRIVATE);
9517 OMP_CLAUSE_DECL (c) = TREE_OPERAND (t, 1);
9518 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9519 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9522 /* Handle OMP_FOR_INCR. */
9523 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
9524 if (TREE_CODE (t) == MODIFY_EXPR)
9526 decl = TREE_OPERAND (t, 0);
9527 t = TREE_OPERAND (t, 1);
9528 tree *tp = &TREE_OPERAND (t, 1);
9529 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
9530 tp = &TREE_OPERAND (t, 0);
9532 if (!is_gimple_constant (*tp))
9534 gimple_seq *seq = gimple_seq_empty_p (for_pre_body)
9535 ? pre_p : &for_pre_body;
9536 *tp = get_initialized_tmp_var (*tp, seq, NULL, false);
9537 tree c = build_omp_clause (input_location,
9538 OMP_CLAUSE_FIRSTPRIVATE);
9539 OMP_CLAUSE_DECL (c) = *tp;
9540 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
9541 OMP_FOR_CLAUSES (orig_for_stmt) = c;
9546 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
9547 OMP_TASKLOOP);
9550 if (orig_for_stmt != for_stmt)
9551 gimplify_omp_ctxp->combined_loop = true;
9553 for_body = NULL;
9554 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9555 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
9556 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9557 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
9559 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
9560 bool is_doacross = false;
9561 if (c && OMP_CLAUSE_ORDERED_EXPR (c))
9563 is_doacross = true;
9564 gimplify_omp_ctxp->loop_iter_var.create (TREE_VEC_LENGTH
9565 (OMP_FOR_INIT (for_stmt))
9566 * 2);
9568 int collapse = 1;
9569 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
9570 if (c)
9571 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
9572 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
9574 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
9575 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
9576 decl = TREE_OPERAND (t, 0);
9577 gcc_assert (DECL_P (decl));
9578 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
9579 || POINTER_TYPE_P (TREE_TYPE (decl)));
9580 if (is_doacross)
9582 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
9583 gimplify_omp_ctxp->loop_iter_var.quick_push
9584 (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i));
9585 else
9586 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
9587 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
9590 /* Make sure the iteration variable is private. */
9591 tree c = NULL_TREE;
9592 tree c2 = NULL_TREE;
9593 if (orig_for_stmt != for_stmt)
9594 /* Do this only on innermost construct for combined ones. */;
9595 else if (ort == ORT_SIMD)
9597 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
9598 (splay_tree_key) decl);
9599 omp_is_private (gimplify_omp_ctxp, decl,
9600 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
9601 != 1));
9602 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
9603 omp_notice_variable (gimplify_omp_ctxp, decl, true);
9604 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9606 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
9607 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
9608 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
9609 if (has_decl_expr
9610 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
9612 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
9613 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9615 struct gimplify_omp_ctx *outer
9616 = gimplify_omp_ctxp->outer_context;
9617 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9619 if (outer->region_type == ORT_WORKSHARE
9620 && outer->combined_loop)
9622 n = splay_tree_lookup (outer->variables,
9623 (splay_tree_key)decl);
9624 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
9626 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
9627 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9629 else
9631 struct gimplify_omp_ctx *octx = outer->outer_context;
9632 if (octx
9633 && octx->region_type == ORT_COMBINED_PARALLEL
9634 && octx->outer_context
9635 && (octx->outer_context->region_type
9636 == ORT_WORKSHARE)
9637 && octx->outer_context->combined_loop)
9639 octx = octx->outer_context;
9640 n = splay_tree_lookup (octx->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;
9652 OMP_CLAUSE_DECL (c) = decl;
9653 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
9654 OMP_FOR_CLAUSES (for_stmt) = c;
9655 omp_add_variable (gimplify_omp_ctxp, decl, flags);
9656 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9658 if (outer->region_type == ORT_WORKSHARE
9659 && outer->combined_loop)
9661 if (outer->outer_context
9662 && (outer->outer_context->region_type
9663 == ORT_COMBINED_PARALLEL))
9664 outer = outer->outer_context;
9665 else if (omp_check_private (outer, decl, false))
9666 outer = NULL;
9668 else if (((outer->region_type & ORT_TASK) != 0)
9669 && outer->combined_loop
9670 && !omp_check_private (gimplify_omp_ctxp,
9671 decl, false))
9673 else if (outer->region_type != ORT_COMBINED_PARALLEL)
9675 omp_notice_variable (outer, decl, true);
9676 outer = NULL;
9678 if (outer)
9680 n = splay_tree_lookup (outer->variables,
9681 (splay_tree_key)decl);
9682 if (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9684 omp_add_variable (outer, decl,
9685 GOVD_LASTPRIVATE | GOVD_SEEN);
9686 if (outer->region_type == ORT_COMBINED_PARALLEL
9687 && outer->outer_context
9688 && (outer->outer_context->region_type
9689 == ORT_WORKSHARE)
9690 && outer->outer_context->combined_loop)
9692 outer = outer->outer_context;
9693 n = splay_tree_lookup (outer->variables,
9694 (splay_tree_key)decl);
9695 if (omp_check_private (outer, decl, false))
9696 outer = NULL;
9697 else if (n == NULL
9698 || ((n->value & GOVD_DATA_SHARE_CLASS)
9699 == 0))
9700 omp_add_variable (outer, decl,
9701 GOVD_LASTPRIVATE
9702 | GOVD_SEEN);
9703 else
9704 outer = NULL;
9706 if (outer && outer->outer_context
9707 && (outer->outer_context->region_type
9708 == ORT_COMBINED_TEAMS))
9710 outer = outer->outer_context;
9711 n = splay_tree_lookup (outer->variables,
9712 (splay_tree_key)decl);
9713 if (n == NULL
9714 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9715 omp_add_variable (outer, decl,
9716 GOVD_SHARED | GOVD_SEEN);
9717 else
9718 outer = NULL;
9720 if (outer && outer->outer_context)
9721 omp_notice_variable (outer->outer_context, decl,
9722 true);
9727 else
9729 bool lastprivate
9730 = (!has_decl_expr
9731 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
9732 struct gimplify_omp_ctx *outer
9733 = gimplify_omp_ctxp->outer_context;
9734 if (outer && lastprivate)
9736 if (outer->region_type == ORT_WORKSHARE
9737 && outer->combined_loop)
9739 n = splay_tree_lookup (outer->variables,
9740 (splay_tree_key)decl);
9741 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
9743 lastprivate = false;
9744 outer = NULL;
9746 else if (outer->outer_context
9747 && (outer->outer_context->region_type
9748 == ORT_COMBINED_PARALLEL))
9749 outer = outer->outer_context;
9750 else if (omp_check_private (outer, decl, false))
9751 outer = NULL;
9753 else if (((outer->region_type & ORT_TASK) != 0)
9754 && outer->combined_loop
9755 && !omp_check_private (gimplify_omp_ctxp,
9756 decl, false))
9758 else if (outer->region_type != ORT_COMBINED_PARALLEL)
9760 omp_notice_variable (outer, decl, true);
9761 outer = NULL;
9763 if (outer)
9765 n = splay_tree_lookup (outer->variables,
9766 (splay_tree_key)decl);
9767 if (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9769 omp_add_variable (outer, decl,
9770 GOVD_LASTPRIVATE | GOVD_SEEN);
9771 if (outer->region_type == ORT_COMBINED_PARALLEL
9772 && outer->outer_context
9773 && (outer->outer_context->region_type
9774 == ORT_WORKSHARE)
9775 && outer->outer_context->combined_loop)
9777 outer = outer->outer_context;
9778 n = splay_tree_lookup (outer->variables,
9779 (splay_tree_key)decl);
9780 if (omp_check_private (outer, decl, false))
9781 outer = NULL;
9782 else if (n == NULL
9783 || ((n->value & GOVD_DATA_SHARE_CLASS)
9784 == 0))
9785 omp_add_variable (outer, decl,
9786 GOVD_LASTPRIVATE
9787 | GOVD_SEEN);
9788 else
9789 outer = NULL;
9791 if (outer && outer->outer_context
9792 && (outer->outer_context->region_type
9793 == ORT_COMBINED_TEAMS))
9795 outer = outer->outer_context;
9796 n = splay_tree_lookup (outer->variables,
9797 (splay_tree_key)decl);
9798 if (n == NULL
9799 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
9800 omp_add_variable (outer, decl,
9801 GOVD_SHARED | GOVD_SEEN);
9802 else
9803 outer = NULL;
9805 if (outer && outer->outer_context)
9806 omp_notice_variable (outer->outer_context, decl,
9807 true);
9812 c = build_omp_clause (input_location,
9813 lastprivate ? OMP_CLAUSE_LASTPRIVATE
9814 : OMP_CLAUSE_PRIVATE);
9815 OMP_CLAUSE_DECL (c) = decl;
9816 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
9817 OMP_FOR_CLAUSES (for_stmt) = c;
9818 omp_add_variable (gimplify_omp_ctxp, decl,
9819 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
9820 | GOVD_EXPLICIT | GOVD_SEEN);
9821 c = NULL_TREE;
9824 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
9825 omp_notice_variable (gimplify_omp_ctxp, decl, true);
9826 else
9827 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
9829 /* If DECL is not a gimple register, create a temporary variable to act
9830 as an iteration counter. This is valid, since DECL cannot be
9831 modified in the body of the loop. Similarly for any iteration vars
9832 in simd with collapse > 1 where the iterator vars must be
9833 lastprivate. */
9834 if (orig_for_stmt != for_stmt)
9835 var = decl;
9836 else if (!is_gimple_reg (decl)
9837 || (ort == ORT_SIMD
9838 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1))
9840 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
9841 /* Make sure omp_add_variable is not called on it prematurely.
9842 We call it ourselves a few lines later. */
9843 gimplify_omp_ctxp = NULL;
9844 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
9845 gimplify_omp_ctxp = ctx;
9846 TREE_OPERAND (t, 0) = var;
9848 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
9850 if (ort == ORT_SIMD
9851 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
9853 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
9854 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
9855 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
9856 OMP_CLAUSE_DECL (c2) = var;
9857 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
9858 OMP_FOR_CLAUSES (for_stmt) = c2;
9859 omp_add_variable (gimplify_omp_ctxp, var,
9860 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
9861 if (c == NULL_TREE)
9863 c = c2;
9864 c2 = NULL_TREE;
9867 else
9868 omp_add_variable (gimplify_omp_ctxp, var,
9869 GOVD_PRIVATE | GOVD_SEEN);
9871 else
9872 var = decl;
9874 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
9875 is_gimple_val, fb_rvalue, false);
9876 ret = MIN (ret, tret);
9877 if (ret == GS_ERROR)
9878 return ret;
9880 /* Handle OMP_FOR_COND. */
9881 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
9882 gcc_assert (COMPARISON_CLASS_P (t));
9883 gcc_assert (TREE_OPERAND (t, 0) == decl);
9885 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
9886 is_gimple_val, fb_rvalue, false);
9887 ret = MIN (ret, tret);
9889 /* Handle OMP_FOR_INCR. */
9890 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
9891 switch (TREE_CODE (t))
9893 case PREINCREMENT_EXPR:
9894 case POSTINCREMENT_EXPR:
9896 tree decl = TREE_OPERAND (t, 0);
9897 /* c_omp_for_incr_canonicalize_ptr() should have been
9898 called to massage things appropriately. */
9899 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
9901 if (orig_for_stmt != for_stmt)
9902 break;
9903 t = build_int_cst (TREE_TYPE (decl), 1);
9904 if (c)
9905 OMP_CLAUSE_LINEAR_STEP (c) = t;
9906 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
9907 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
9908 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
9909 break;
9912 case PREDECREMENT_EXPR:
9913 case POSTDECREMENT_EXPR:
9914 /* c_omp_for_incr_canonicalize_ptr() should have been
9915 called to massage things appropriately. */
9916 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
9917 if (orig_for_stmt != for_stmt)
9918 break;
9919 t = build_int_cst (TREE_TYPE (decl), -1);
9920 if (c)
9921 OMP_CLAUSE_LINEAR_STEP (c) = t;
9922 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
9923 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
9924 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
9925 break;
9927 case MODIFY_EXPR:
9928 gcc_assert (TREE_OPERAND (t, 0) == decl);
9929 TREE_OPERAND (t, 0) = var;
9931 t = TREE_OPERAND (t, 1);
9932 switch (TREE_CODE (t))
9934 case PLUS_EXPR:
9935 if (TREE_OPERAND (t, 1) == decl)
9937 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
9938 TREE_OPERAND (t, 0) = var;
9939 break;
9942 /* Fallthru. */
9943 case MINUS_EXPR:
9944 case POINTER_PLUS_EXPR:
9945 gcc_assert (TREE_OPERAND (t, 0) == decl);
9946 TREE_OPERAND (t, 0) = var;
9947 break;
9948 default:
9949 gcc_unreachable ();
9952 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
9953 is_gimple_val, fb_rvalue, false);
9954 ret = MIN (ret, tret);
9955 if (c)
9957 tree step = TREE_OPERAND (t, 1);
9958 tree stept = TREE_TYPE (decl);
9959 if (POINTER_TYPE_P (stept))
9960 stept = sizetype;
9961 step = fold_convert (stept, step);
9962 if (TREE_CODE (t) == MINUS_EXPR)
9963 step = fold_build1 (NEGATE_EXPR, stept, step);
9964 OMP_CLAUSE_LINEAR_STEP (c) = step;
9965 if (step != TREE_OPERAND (t, 1))
9967 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
9968 &for_pre_body, NULL,
9969 is_gimple_val, fb_rvalue, false);
9970 ret = MIN (ret, tret);
9973 break;
9975 default:
9976 gcc_unreachable ();
9979 if (c2)
9981 gcc_assert (c);
9982 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
9985 if ((var != decl || collapse > 1) && orig_for_stmt == for_stmt)
9987 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
9988 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
9989 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
9990 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
9991 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
9992 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
9993 && OMP_CLAUSE_DECL (c) == decl)
9995 if (is_doacross && (collapse == 1 || i >= collapse))
9996 t = var;
9997 else
9999 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10000 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
10001 gcc_assert (TREE_OPERAND (t, 0) == var);
10002 t = TREE_OPERAND (t, 1);
10003 gcc_assert (TREE_CODE (t) == PLUS_EXPR
10004 || TREE_CODE (t) == MINUS_EXPR
10005 || TREE_CODE (t) == POINTER_PLUS_EXPR);
10006 gcc_assert (TREE_OPERAND (t, 0) == var);
10007 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
10008 is_doacross ? var : decl,
10009 TREE_OPERAND (t, 1));
10011 gimple_seq *seq;
10012 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
10013 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
10014 else
10015 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
10016 gimplify_assign (decl, t, seq);
10021 BITMAP_FREE (has_decl_expr);
10023 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10025 push_gimplify_context ();
10026 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
10028 OMP_FOR_BODY (orig_for_stmt)
10029 = build3 (BIND_EXPR, void_type_node, NULL,
10030 OMP_FOR_BODY (orig_for_stmt), NULL);
10031 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
10035 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
10036 &for_body);
10038 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10040 if (gimple_code (g) == GIMPLE_BIND)
10041 pop_gimplify_context (g);
10042 else
10043 pop_gimplify_context (NULL);
10046 if (orig_for_stmt != for_stmt)
10047 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
10049 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
10050 decl = TREE_OPERAND (t, 0);
10051 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10052 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10053 gimplify_omp_ctxp = ctx->outer_context;
10054 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
10055 gimplify_omp_ctxp = ctx;
10056 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
10057 TREE_OPERAND (t, 0) = var;
10058 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10059 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
10060 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
10063 gimplify_adjust_omp_clauses (pre_p, for_body,
10064 &OMP_FOR_CLAUSES (orig_for_stmt),
10065 TREE_CODE (orig_for_stmt));
10067 int kind;
10068 switch (TREE_CODE (orig_for_stmt))
10070 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
10071 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
10072 case CILK_SIMD: kind = GF_OMP_FOR_KIND_CILKSIMD; break;
10073 case CILK_FOR: kind = GF_OMP_FOR_KIND_CILKFOR; break;
10074 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
10075 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
10076 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
10077 default:
10078 gcc_unreachable ();
10080 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
10081 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
10082 for_pre_body);
10083 if (orig_for_stmt != for_stmt)
10084 gimple_omp_for_set_combined_p (gfor, true);
10085 if (gimplify_omp_ctxp
10086 && (gimplify_omp_ctxp->combined_loop
10087 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
10088 && gimplify_omp_ctxp->outer_context
10089 && gimplify_omp_ctxp->outer_context->combined_loop)))
10091 gimple_omp_for_set_combined_into_p (gfor, true);
10092 if (gimplify_omp_ctxp->combined_loop)
10093 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
10094 else
10095 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
10098 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
10100 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
10101 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
10102 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
10103 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
10104 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
10105 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
10106 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
10107 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
10110 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
10111 constructs with GIMPLE_OMP_TASK sandwiched in between them.
10112 The outer taskloop stands for computing the number of iterations,
10113 counts for collapsed loops and holding taskloop specific clauses.
10114 The task construct stands for the effect of data sharing on the
10115 explicit task it creates and the inner taskloop stands for expansion
10116 of the static loop inside of the explicit task construct. */
10117 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
10119 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
10120 tree task_clauses = NULL_TREE;
10121 tree c = *gfor_clauses_ptr;
10122 tree *gtask_clauses_ptr = &task_clauses;
10123 tree outer_for_clauses = NULL_TREE;
10124 tree *gforo_clauses_ptr = &outer_for_clauses;
10125 for (; c; c = OMP_CLAUSE_CHAIN (c))
10126 switch (OMP_CLAUSE_CODE (c))
10128 /* These clauses are allowed on task, move them there. */
10129 case OMP_CLAUSE_SHARED:
10130 case OMP_CLAUSE_FIRSTPRIVATE:
10131 case OMP_CLAUSE_DEFAULT:
10132 case OMP_CLAUSE_IF:
10133 case OMP_CLAUSE_UNTIED:
10134 case OMP_CLAUSE_FINAL:
10135 case OMP_CLAUSE_MERGEABLE:
10136 case OMP_CLAUSE_PRIORITY:
10137 *gtask_clauses_ptr = c;
10138 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10139 break;
10140 case OMP_CLAUSE_PRIVATE:
10141 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
10143 /* We want private on outer for and firstprivate
10144 on task. */
10145 *gtask_clauses_ptr
10146 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10147 OMP_CLAUSE_FIRSTPRIVATE);
10148 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10149 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL);
10150 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10151 *gforo_clauses_ptr = c;
10152 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10154 else
10156 *gtask_clauses_ptr = c;
10157 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10159 break;
10160 /* These clauses go into outer taskloop clauses. */
10161 case OMP_CLAUSE_GRAINSIZE:
10162 case OMP_CLAUSE_NUM_TASKS:
10163 case OMP_CLAUSE_NOGROUP:
10164 *gforo_clauses_ptr = c;
10165 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10166 break;
10167 /* Taskloop clause we duplicate on both taskloops. */
10168 case OMP_CLAUSE_COLLAPSE:
10169 *gfor_clauses_ptr = c;
10170 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10171 *gforo_clauses_ptr = copy_node (c);
10172 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
10173 break;
10174 /* For lastprivate, keep the clause on inner taskloop, and add
10175 a shared clause on task. If the same decl is also firstprivate,
10176 add also firstprivate clause on the inner taskloop. */
10177 case OMP_CLAUSE_LASTPRIVATE:
10178 if (OMP_CLAUSE_LASTPRIVATE_TASKLOOP_IV (c))
10180 /* For taskloop C++ lastprivate IVs, we want:
10181 1) private on outer taskloop
10182 2) firstprivate and shared on task
10183 3) lastprivate on inner taskloop */
10184 *gtask_clauses_ptr
10185 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10186 OMP_CLAUSE_FIRSTPRIVATE);
10187 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10188 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL);
10189 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10190 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
10191 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10192 OMP_CLAUSE_PRIVATE);
10193 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
10194 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
10195 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
10196 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
10198 *gfor_clauses_ptr = c;
10199 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
10200 *gtask_clauses_ptr
10201 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
10202 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
10203 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
10204 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
10205 gtask_clauses_ptr
10206 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
10207 break;
10208 default:
10209 gcc_unreachable ();
10211 *gfor_clauses_ptr = NULL_TREE;
10212 *gtask_clauses_ptr = NULL_TREE;
10213 *gforo_clauses_ptr = NULL_TREE;
10214 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
10215 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
10216 NULL_TREE, NULL_TREE, NULL_TREE);
10217 gimple_omp_task_set_taskloop_p (g, true);
10218 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
10219 gomp_for *gforo
10220 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
10221 gimple_omp_for_collapse (gfor),
10222 gimple_omp_for_pre_body (gfor));
10223 gimple_omp_for_set_pre_body (gfor, NULL);
10224 gimple_omp_for_set_combined_p (gforo, true);
10225 gimple_omp_for_set_combined_into_p (gfor, true);
10226 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
10228 t = unshare_expr (gimple_omp_for_index (gfor, i));
10229 gimple_omp_for_set_index (gforo, i, t);
10230 t = unshare_expr (gimple_omp_for_initial (gfor, i));
10231 gimple_omp_for_set_initial (gforo, i, t);
10232 gimple_omp_for_set_cond (gforo, i,
10233 gimple_omp_for_cond (gfor, i));
10234 t = unshare_expr (gimple_omp_for_final (gfor, i));
10235 gimple_omp_for_set_final (gforo, i, t);
10236 t = unshare_expr (gimple_omp_for_incr (gfor, i));
10237 gimple_omp_for_set_incr (gforo, i, t);
10239 gimplify_seq_add_stmt (pre_p, gforo);
10241 else
10242 gimplify_seq_add_stmt (pre_p, gfor);
10243 if (ret != GS_ALL_DONE)
10244 return GS_ERROR;
10245 *expr_p = NULL_TREE;
10246 return GS_ALL_DONE;
10249 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
10250 of OMP_TARGET's body. */
10252 static tree
10253 find_omp_teams (tree *tp, int *walk_subtrees, void *)
10255 *walk_subtrees = 0;
10256 switch (TREE_CODE (*tp))
10258 case OMP_TEAMS:
10259 return *tp;
10260 case BIND_EXPR:
10261 case STATEMENT_LIST:
10262 *walk_subtrees = 1;
10263 break;
10264 default:
10265 break;
10267 return NULL_TREE;
10270 /* Helper function of optimize_target_teams, determine if the expression
10271 can be computed safely before the target construct on the host. */
10273 static tree
10274 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
10276 splay_tree_node n;
10278 if (TYPE_P (*tp))
10280 *walk_subtrees = 0;
10281 return NULL_TREE;
10283 switch (TREE_CODE (*tp))
10285 case VAR_DECL:
10286 case PARM_DECL:
10287 case RESULT_DECL:
10288 *walk_subtrees = 0;
10289 if (error_operand_p (*tp)
10290 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
10291 || DECL_HAS_VALUE_EXPR_P (*tp)
10292 || DECL_THREAD_LOCAL_P (*tp)
10293 || TREE_SIDE_EFFECTS (*tp)
10294 || TREE_THIS_VOLATILE (*tp))
10295 return *tp;
10296 if (is_global_var (*tp)
10297 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
10298 || lookup_attribute ("omp declare target link",
10299 DECL_ATTRIBUTES (*tp))))
10300 return *tp;
10301 if (VAR_P (*tp)
10302 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
10303 && !is_global_var (*tp)
10304 && decl_function_context (*tp) == current_function_decl)
10305 return *tp;
10306 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
10307 (splay_tree_key) *tp);
10308 if (n == NULL)
10310 if (gimplify_omp_ctxp->target_map_scalars_firstprivate)
10311 return NULL_TREE;
10312 return *tp;
10314 else if (n->value & GOVD_LOCAL)
10315 return *tp;
10316 else if (n->value & GOVD_FIRSTPRIVATE)
10317 return NULL_TREE;
10318 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
10319 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
10320 return NULL_TREE;
10321 return *tp;
10322 case INTEGER_CST:
10323 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
10324 return *tp;
10325 return NULL_TREE;
10326 case TARGET_EXPR:
10327 if (TARGET_EXPR_INITIAL (*tp)
10328 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
10329 return *tp;
10330 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
10331 walk_subtrees, NULL);
10332 /* Allow some reasonable subset of integral arithmetics. */
10333 case PLUS_EXPR:
10334 case MINUS_EXPR:
10335 case MULT_EXPR:
10336 case TRUNC_DIV_EXPR:
10337 case CEIL_DIV_EXPR:
10338 case FLOOR_DIV_EXPR:
10339 case ROUND_DIV_EXPR:
10340 case TRUNC_MOD_EXPR:
10341 case CEIL_MOD_EXPR:
10342 case FLOOR_MOD_EXPR:
10343 case ROUND_MOD_EXPR:
10344 case RDIV_EXPR:
10345 case EXACT_DIV_EXPR:
10346 case MIN_EXPR:
10347 case MAX_EXPR:
10348 case LSHIFT_EXPR:
10349 case RSHIFT_EXPR:
10350 case BIT_IOR_EXPR:
10351 case BIT_XOR_EXPR:
10352 case BIT_AND_EXPR:
10353 case NEGATE_EXPR:
10354 case ABS_EXPR:
10355 case BIT_NOT_EXPR:
10356 case NON_LVALUE_EXPR:
10357 CASE_CONVERT:
10358 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
10359 return *tp;
10360 return NULL_TREE;
10361 /* And disallow anything else, except for comparisons. */
10362 default:
10363 if (COMPARISON_CLASS_P (*tp))
10364 return NULL_TREE;
10365 return *tp;
10369 /* Try to determine if the num_teams and/or thread_limit expressions
10370 can have their values determined already before entering the
10371 target construct.
10372 INTEGER_CSTs trivially are,
10373 integral decls that are firstprivate (explicitly or implicitly)
10374 or explicitly map(always, to:) or map(always, tofrom:) on the target
10375 region too, and expressions involving simple arithmetics on those
10376 too, function calls are not ok, dereferencing something neither etc.
10377 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
10378 EXPR based on what we find:
10379 0 stands for clause not specified at all, use implementation default
10380 -1 stands for value that can't be determined easily before entering
10381 the target construct.
10382 If teams construct is not present at all, use 1 for num_teams
10383 and 0 for thread_limit (only one team is involved, and the thread
10384 limit is implementation defined. */
10386 static void
10387 optimize_target_teams (tree target, gimple_seq *pre_p)
10389 tree body = OMP_BODY (target);
10390 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
10391 tree num_teams = integer_zero_node;
10392 tree thread_limit = integer_zero_node;
10393 location_t num_teams_loc = EXPR_LOCATION (target);
10394 location_t thread_limit_loc = EXPR_LOCATION (target);
10395 tree c, *p, expr;
10396 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
10398 if (teams == NULL_TREE)
10399 num_teams = integer_one_node;
10400 else
10401 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
10403 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
10405 p = &num_teams;
10406 num_teams_loc = OMP_CLAUSE_LOCATION (c);
10408 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
10410 p = &thread_limit;
10411 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
10413 else
10414 continue;
10415 expr = OMP_CLAUSE_OPERAND (c, 0);
10416 if (TREE_CODE (expr) == INTEGER_CST)
10418 *p = expr;
10419 continue;
10421 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
10423 *p = integer_minus_one_node;
10424 continue;
10426 *p = expr;
10427 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
10428 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
10429 == GS_ERROR)
10431 gimplify_omp_ctxp = target_ctx;
10432 *p = integer_minus_one_node;
10433 continue;
10435 gimplify_omp_ctxp = target_ctx;
10436 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
10437 OMP_CLAUSE_OPERAND (c, 0) = *p;
10439 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
10440 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
10441 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
10442 OMP_TARGET_CLAUSES (target) = c;
10443 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
10444 OMP_CLAUSE_NUM_TEAMS_EXPR (c) = num_teams;
10445 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
10446 OMP_TARGET_CLAUSES (target) = c;
10449 /* Gimplify the gross structure of several OMP constructs. */
10451 static void
10452 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
10454 tree expr = *expr_p;
10455 gimple *stmt;
10456 gimple_seq body = NULL;
10457 enum omp_region_type ort;
10459 switch (TREE_CODE (expr))
10461 case OMP_SECTIONS:
10462 case OMP_SINGLE:
10463 ort = ORT_WORKSHARE;
10464 break;
10465 case OMP_TARGET:
10466 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
10467 break;
10468 case OACC_KERNELS:
10469 ort = ORT_ACC_KERNELS;
10470 break;
10471 case OACC_PARALLEL:
10472 ort = ORT_ACC_PARALLEL;
10473 break;
10474 case OACC_DATA:
10475 ort = ORT_ACC_DATA;
10476 break;
10477 case OMP_TARGET_DATA:
10478 ort = ORT_TARGET_DATA;
10479 break;
10480 case OMP_TEAMS:
10481 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
10482 break;
10483 case OACC_HOST_DATA:
10484 ort = ORT_ACC_HOST_DATA;
10485 break;
10486 default:
10487 gcc_unreachable ();
10489 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
10490 TREE_CODE (expr));
10491 if (TREE_CODE (expr) == OMP_TARGET)
10492 optimize_target_teams (expr, pre_p);
10493 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0)
10495 push_gimplify_context ();
10496 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
10497 if (gimple_code (g) == GIMPLE_BIND)
10498 pop_gimplify_context (g);
10499 else
10500 pop_gimplify_context (NULL);
10501 if ((ort & ORT_TARGET_DATA) != 0)
10503 enum built_in_function end_ix;
10504 switch (TREE_CODE (expr))
10506 case OACC_DATA:
10507 case OACC_HOST_DATA:
10508 end_ix = BUILT_IN_GOACC_DATA_END;
10509 break;
10510 case OMP_TARGET_DATA:
10511 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
10512 break;
10513 default:
10514 gcc_unreachable ();
10516 tree fn = builtin_decl_explicit (end_ix);
10517 g = gimple_build_call (fn, 0);
10518 gimple_seq cleanup = NULL;
10519 gimple_seq_add_stmt (&cleanup, g);
10520 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
10521 body = NULL;
10522 gimple_seq_add_stmt (&body, g);
10525 else
10526 gimplify_and_add (OMP_BODY (expr), &body);
10527 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
10528 TREE_CODE (expr));
10530 switch (TREE_CODE (expr))
10532 case OACC_DATA:
10533 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
10534 OMP_CLAUSES (expr));
10535 break;
10536 case OACC_KERNELS:
10537 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
10538 OMP_CLAUSES (expr));
10539 break;
10540 case OACC_HOST_DATA:
10541 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
10542 OMP_CLAUSES (expr));
10543 break;
10544 case OACC_PARALLEL:
10545 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
10546 OMP_CLAUSES (expr));
10547 break;
10548 case OMP_SECTIONS:
10549 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
10550 break;
10551 case OMP_SINGLE:
10552 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
10553 break;
10554 case OMP_TARGET:
10555 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
10556 OMP_CLAUSES (expr));
10557 break;
10558 case OMP_TARGET_DATA:
10559 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
10560 OMP_CLAUSES (expr));
10561 break;
10562 case OMP_TEAMS:
10563 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
10564 break;
10565 default:
10566 gcc_unreachable ();
10569 gimplify_seq_add_stmt (pre_p, stmt);
10570 *expr_p = NULL_TREE;
10573 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
10574 target update constructs. */
10576 static void
10577 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
10579 tree expr = *expr_p;
10580 int kind;
10581 gomp_target *stmt;
10582 enum omp_region_type ort = ORT_WORKSHARE;
10584 switch (TREE_CODE (expr))
10586 case OACC_ENTER_DATA:
10587 case OACC_EXIT_DATA:
10588 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
10589 ort = ORT_ACC;
10590 break;
10591 case OACC_UPDATE:
10592 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
10593 ort = ORT_ACC;
10594 break;
10595 case OMP_TARGET_UPDATE:
10596 kind = GF_OMP_TARGET_KIND_UPDATE;
10597 break;
10598 case OMP_TARGET_ENTER_DATA:
10599 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
10600 break;
10601 case OMP_TARGET_EXIT_DATA:
10602 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
10603 break;
10604 default:
10605 gcc_unreachable ();
10607 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
10608 ort, TREE_CODE (expr));
10609 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
10610 TREE_CODE (expr));
10611 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
10613 gimplify_seq_add_stmt (pre_p, stmt);
10614 *expr_p = NULL_TREE;
10617 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
10618 stabilized the lhs of the atomic operation as *ADDR. Return true if
10619 EXPR is this stabilized form. */
10621 static bool
10622 goa_lhs_expr_p (tree expr, tree addr)
10624 /* Also include casts to other type variants. The C front end is fond
10625 of adding these for e.g. volatile variables. This is like
10626 STRIP_TYPE_NOPS but includes the main variant lookup. */
10627 STRIP_USELESS_TYPE_CONVERSION (expr);
10629 if (TREE_CODE (expr) == INDIRECT_REF)
10631 expr = TREE_OPERAND (expr, 0);
10632 while (expr != addr
10633 && (CONVERT_EXPR_P (expr)
10634 || TREE_CODE (expr) == NON_LVALUE_EXPR)
10635 && TREE_CODE (expr) == TREE_CODE (addr)
10636 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
10638 expr = TREE_OPERAND (expr, 0);
10639 addr = TREE_OPERAND (addr, 0);
10641 if (expr == addr)
10642 return true;
10643 return (TREE_CODE (addr) == ADDR_EXPR
10644 && TREE_CODE (expr) == ADDR_EXPR
10645 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
10647 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
10648 return true;
10649 return false;
10652 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
10653 expression does not involve the lhs, evaluate it into a temporary.
10654 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
10655 or -1 if an error was encountered. */
10657 static int
10658 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
10659 tree lhs_var)
10661 tree expr = *expr_p;
10662 int saw_lhs;
10664 if (goa_lhs_expr_p (expr, lhs_addr))
10666 *expr_p = lhs_var;
10667 return 1;
10669 if (is_gimple_val (expr))
10670 return 0;
10672 saw_lhs = 0;
10673 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
10675 case tcc_binary:
10676 case tcc_comparison:
10677 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
10678 lhs_var);
10679 /* FALLTHRU */
10680 case tcc_unary:
10681 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
10682 lhs_var);
10683 break;
10684 case tcc_expression:
10685 switch (TREE_CODE (expr))
10687 case TRUTH_ANDIF_EXPR:
10688 case TRUTH_ORIF_EXPR:
10689 case TRUTH_AND_EXPR:
10690 case TRUTH_OR_EXPR:
10691 case TRUTH_XOR_EXPR:
10692 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
10693 lhs_addr, lhs_var);
10694 /* FALLTHRU */
10695 case TRUTH_NOT_EXPR:
10696 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
10697 lhs_addr, lhs_var);
10698 break;
10699 case COMPOUND_EXPR:
10700 /* Break out any preevaluations from cp_build_modify_expr. */
10701 for (; TREE_CODE (expr) == COMPOUND_EXPR;
10702 expr = TREE_OPERAND (expr, 1))
10703 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
10704 *expr_p = expr;
10705 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var);
10706 default:
10707 break;
10709 break;
10710 default:
10711 break;
10714 if (saw_lhs == 0)
10716 enum gimplify_status gs;
10717 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
10718 if (gs != GS_ALL_DONE)
10719 saw_lhs = -1;
10722 return saw_lhs;
10725 /* Gimplify an OMP_ATOMIC statement. */
10727 static enum gimplify_status
10728 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
10730 tree addr = TREE_OPERAND (*expr_p, 0);
10731 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
10732 ? NULL : TREE_OPERAND (*expr_p, 1);
10733 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
10734 tree tmp_load;
10735 gomp_atomic_load *loadstmt;
10736 gomp_atomic_store *storestmt;
10738 tmp_load = create_tmp_reg (type);
10739 if (rhs && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load) < 0)
10740 return GS_ERROR;
10742 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
10743 != GS_ALL_DONE)
10744 return GS_ERROR;
10746 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr);
10747 gimplify_seq_add_stmt (pre_p, loadstmt);
10748 if (rhs && gimplify_expr (&rhs, pre_p, NULL, is_gimple_val, fb_rvalue)
10749 != GS_ALL_DONE)
10750 return GS_ERROR;
10752 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
10753 rhs = tmp_load;
10754 storestmt = gimple_build_omp_atomic_store (rhs);
10755 gimplify_seq_add_stmt (pre_p, storestmt);
10756 if (OMP_ATOMIC_SEQ_CST (*expr_p))
10758 gimple_omp_atomic_set_seq_cst (loadstmt);
10759 gimple_omp_atomic_set_seq_cst (storestmt);
10761 switch (TREE_CODE (*expr_p))
10763 case OMP_ATOMIC_READ:
10764 case OMP_ATOMIC_CAPTURE_OLD:
10765 *expr_p = tmp_load;
10766 gimple_omp_atomic_set_need_value (loadstmt);
10767 break;
10768 case OMP_ATOMIC_CAPTURE_NEW:
10769 *expr_p = rhs;
10770 gimple_omp_atomic_set_need_value (storestmt);
10771 break;
10772 default:
10773 *expr_p = NULL;
10774 break;
10777 return GS_ALL_DONE;
10780 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
10781 body, and adding some EH bits. */
10783 static enum gimplify_status
10784 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
10786 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
10787 gimple *body_stmt;
10788 gtransaction *trans_stmt;
10789 gimple_seq body = NULL;
10790 int subcode = 0;
10792 /* Wrap the transaction body in a BIND_EXPR so we have a context
10793 where to put decls for OMP. */
10794 if (TREE_CODE (tbody) != BIND_EXPR)
10796 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
10797 TREE_SIDE_EFFECTS (bind) = 1;
10798 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
10799 TRANSACTION_EXPR_BODY (expr) = bind;
10802 push_gimplify_context ();
10803 temp = voidify_wrapper_expr (*expr_p, NULL);
10805 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
10806 pop_gimplify_context (body_stmt);
10808 trans_stmt = gimple_build_transaction (body);
10809 if (TRANSACTION_EXPR_OUTER (expr))
10810 subcode = GTMA_IS_OUTER;
10811 else if (TRANSACTION_EXPR_RELAXED (expr))
10812 subcode = GTMA_IS_RELAXED;
10813 gimple_transaction_set_subcode (trans_stmt, subcode);
10815 gimplify_seq_add_stmt (pre_p, trans_stmt);
10817 if (temp)
10819 *expr_p = temp;
10820 return GS_OK;
10823 *expr_p = NULL_TREE;
10824 return GS_ALL_DONE;
10827 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
10828 is the OMP_BODY of the original EXPR (which has already been
10829 gimplified so it's not present in the EXPR).
10831 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
10833 static gimple *
10834 gimplify_omp_ordered (tree expr, gimple_seq body)
10836 tree c, decls;
10837 int failures = 0;
10838 unsigned int i;
10839 tree source_c = NULL_TREE;
10840 tree sink_c = NULL_TREE;
10842 if (gimplify_omp_ctxp)
10844 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
10845 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10846 && gimplify_omp_ctxp->loop_iter_var.is_empty ()
10847 && (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK
10848 || OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE))
10850 error_at (OMP_CLAUSE_LOCATION (c),
10851 "%<ordered%> construct with %<depend%> clause must be "
10852 "closely nested inside a loop with %<ordered%> clause "
10853 "with a parameter");
10854 failures++;
10856 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10857 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
10859 bool fail = false;
10860 for (decls = OMP_CLAUSE_DECL (c), i = 0;
10861 decls && TREE_CODE (decls) == TREE_LIST;
10862 decls = TREE_CHAIN (decls), ++i)
10863 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
10864 continue;
10865 else if (TREE_VALUE (decls)
10866 != gimplify_omp_ctxp->loop_iter_var[2 * i])
10868 error_at (OMP_CLAUSE_LOCATION (c),
10869 "variable %qE is not an iteration "
10870 "of outermost loop %d, expected %qE",
10871 TREE_VALUE (decls), i + 1,
10872 gimplify_omp_ctxp->loop_iter_var[2 * i]);
10873 fail = true;
10874 failures++;
10876 else
10877 TREE_VALUE (decls)
10878 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
10879 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
10881 error_at (OMP_CLAUSE_LOCATION (c),
10882 "number of variables in %<depend(sink)%> "
10883 "clause does not match number of "
10884 "iteration variables");
10885 failures++;
10887 sink_c = c;
10889 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
10890 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
10892 if (source_c)
10894 error_at (OMP_CLAUSE_LOCATION (c),
10895 "more than one %<depend(source)%> clause on an "
10896 "%<ordered%> construct");
10897 failures++;
10899 else
10900 source_c = c;
10903 if (source_c && sink_c)
10905 error_at (OMP_CLAUSE_LOCATION (source_c),
10906 "%<depend(source)%> clause specified together with "
10907 "%<depend(sink:)%> clauses on the same construct");
10908 failures++;
10911 if (failures)
10912 return gimple_build_nop ();
10913 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
10916 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
10917 expression produces a value to be used as an operand inside a GIMPLE
10918 statement, the value will be stored back in *EXPR_P. This value will
10919 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
10920 an SSA_NAME. The corresponding sequence of GIMPLE statements is
10921 emitted in PRE_P and POST_P.
10923 Additionally, this process may overwrite parts of the input
10924 expression during gimplification. Ideally, it should be
10925 possible to do non-destructive gimplification.
10927 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
10928 the expression needs to evaluate to a value to be used as
10929 an operand in a GIMPLE statement, this value will be stored in
10930 *EXPR_P on exit. This happens when the caller specifies one
10931 of fb_lvalue or fb_rvalue fallback flags.
10933 PRE_P will contain the sequence of GIMPLE statements corresponding
10934 to the evaluation of EXPR and all the side-effects that must
10935 be executed before the main expression. On exit, the last
10936 statement of PRE_P is the core statement being gimplified. For
10937 instance, when gimplifying 'if (++a)' the last statement in
10938 PRE_P will be 'if (t.1)' where t.1 is the result of
10939 pre-incrementing 'a'.
10941 POST_P will contain the sequence of GIMPLE statements corresponding
10942 to the evaluation of all the side-effects that must be executed
10943 after the main expression. If this is NULL, the post
10944 side-effects are stored at the end of PRE_P.
10946 The reason why the output is split in two is to handle post
10947 side-effects explicitly. In some cases, an expression may have
10948 inner and outer post side-effects which need to be emitted in
10949 an order different from the one given by the recursive
10950 traversal. For instance, for the expression (*p--)++ the post
10951 side-effects of '--' must actually occur *after* the post
10952 side-effects of '++'. However, gimplification will first visit
10953 the inner expression, so if a separate POST sequence was not
10954 used, the resulting sequence would be:
10956 1 t.1 = *p
10957 2 p = p - 1
10958 3 t.2 = t.1 + 1
10959 4 *p = t.2
10961 However, the post-decrement operation in line #2 must not be
10962 evaluated until after the store to *p at line #4, so the
10963 correct sequence should be:
10965 1 t.1 = *p
10966 2 t.2 = t.1 + 1
10967 3 *p = t.2
10968 4 p = p - 1
10970 So, by specifying a separate post queue, it is possible
10971 to emit the post side-effects in the correct order.
10972 If POST_P is NULL, an internal queue will be used. Before
10973 returning to the caller, the sequence POST_P is appended to
10974 the main output sequence PRE_P.
10976 GIMPLE_TEST_F points to a function that takes a tree T and
10977 returns nonzero if T is in the GIMPLE form requested by the
10978 caller. The GIMPLE predicates are in gimple.c.
10980 FALLBACK tells the function what sort of a temporary we want if
10981 gimplification cannot produce an expression that complies with
10982 GIMPLE_TEST_F.
10984 fb_none means that no temporary should be generated
10985 fb_rvalue means that an rvalue is OK to generate
10986 fb_lvalue means that an lvalue is OK to generate
10987 fb_either means that either is OK, but an lvalue is preferable.
10988 fb_mayfail means that gimplification may fail (in which case
10989 GS_ERROR will be returned)
10991 The return value is either GS_ERROR or GS_ALL_DONE, since this
10992 function iterates until EXPR is completely gimplified or an error
10993 occurs. */
10995 enum gimplify_status
10996 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
10997 bool (*gimple_test_f) (tree), fallback_t fallback)
10999 tree tmp;
11000 gimple_seq internal_pre = NULL;
11001 gimple_seq internal_post = NULL;
11002 tree save_expr;
11003 bool is_statement;
11004 location_t saved_location;
11005 enum gimplify_status ret;
11006 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
11007 tree label;
11009 save_expr = *expr_p;
11010 if (save_expr == NULL_TREE)
11011 return GS_ALL_DONE;
11013 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
11014 is_statement = gimple_test_f == is_gimple_stmt;
11015 if (is_statement)
11016 gcc_assert (pre_p);
11018 /* Consistency checks. */
11019 if (gimple_test_f == is_gimple_reg)
11020 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
11021 else if (gimple_test_f == is_gimple_val
11022 || gimple_test_f == is_gimple_call_addr
11023 || gimple_test_f == is_gimple_condexpr
11024 || gimple_test_f == is_gimple_mem_rhs
11025 || gimple_test_f == is_gimple_mem_rhs_or_call
11026 || gimple_test_f == is_gimple_reg_rhs
11027 || gimple_test_f == is_gimple_reg_rhs_or_call
11028 || gimple_test_f == is_gimple_asm_val
11029 || gimple_test_f == is_gimple_mem_ref_addr)
11030 gcc_assert (fallback & fb_rvalue);
11031 else if (gimple_test_f == is_gimple_min_lval
11032 || gimple_test_f == is_gimple_lvalue)
11033 gcc_assert (fallback & fb_lvalue);
11034 else if (gimple_test_f == is_gimple_addressable)
11035 gcc_assert (fallback & fb_either);
11036 else if (gimple_test_f == is_gimple_stmt)
11037 gcc_assert (fallback == fb_none);
11038 else
11040 /* We should have recognized the GIMPLE_TEST_F predicate to
11041 know what kind of fallback to use in case a temporary is
11042 needed to hold the value or address of *EXPR_P. */
11043 gcc_unreachable ();
11046 /* We used to check the predicate here and return immediately if it
11047 succeeds. This is wrong; the design is for gimplification to be
11048 idempotent, and for the predicates to only test for valid forms, not
11049 whether they are fully simplified. */
11050 if (pre_p == NULL)
11051 pre_p = &internal_pre;
11053 if (post_p == NULL)
11054 post_p = &internal_post;
11056 /* Remember the last statements added to PRE_P and POST_P. Every
11057 new statement added by the gimplification helpers needs to be
11058 annotated with location information. To centralize the
11059 responsibility, we remember the last statement that had been
11060 added to both queues before gimplifying *EXPR_P. If
11061 gimplification produces new statements in PRE_P and POST_P, those
11062 statements will be annotated with the same location information
11063 as *EXPR_P. */
11064 pre_last_gsi = gsi_last (*pre_p);
11065 post_last_gsi = gsi_last (*post_p);
11067 saved_location = input_location;
11068 if (save_expr != error_mark_node
11069 && EXPR_HAS_LOCATION (*expr_p))
11070 input_location = EXPR_LOCATION (*expr_p);
11072 /* Loop over the specific gimplifiers until the toplevel node
11073 remains the same. */
11076 /* Strip away as many useless type conversions as possible
11077 at the toplevel. */
11078 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
11080 /* Remember the expr. */
11081 save_expr = *expr_p;
11083 /* Die, die, die, my darling. */
11084 if (save_expr == error_mark_node
11085 || (TREE_TYPE (save_expr)
11086 && TREE_TYPE (save_expr) == error_mark_node))
11088 ret = GS_ERROR;
11089 break;
11092 /* Do any language-specific gimplification. */
11093 ret = ((enum gimplify_status)
11094 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
11095 if (ret == GS_OK)
11097 if (*expr_p == NULL_TREE)
11098 break;
11099 if (*expr_p != save_expr)
11100 continue;
11102 else if (ret != GS_UNHANDLED)
11103 break;
11105 /* Make sure that all the cases set 'ret' appropriately. */
11106 ret = GS_UNHANDLED;
11107 switch (TREE_CODE (*expr_p))
11109 /* First deal with the special cases. */
11111 case POSTINCREMENT_EXPR:
11112 case POSTDECREMENT_EXPR:
11113 case PREINCREMENT_EXPR:
11114 case PREDECREMENT_EXPR:
11115 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
11116 fallback != fb_none,
11117 TREE_TYPE (*expr_p));
11118 break;
11120 case VIEW_CONVERT_EXPR:
11121 if (is_gimple_reg_type (TREE_TYPE (*expr_p))
11122 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
11124 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11125 post_p, is_gimple_val, fb_rvalue);
11126 recalculate_side_effects (*expr_p);
11127 break;
11129 /* Fallthru. */
11131 case ARRAY_REF:
11132 case ARRAY_RANGE_REF:
11133 case REALPART_EXPR:
11134 case IMAGPART_EXPR:
11135 case COMPONENT_REF:
11136 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
11137 fallback ? fallback : fb_rvalue);
11138 break;
11140 case COND_EXPR:
11141 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
11143 /* C99 code may assign to an array in a structure value of a
11144 conditional expression, and this has undefined behavior
11145 only on execution, so create a temporary if an lvalue is
11146 required. */
11147 if (fallback == fb_lvalue)
11149 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11150 mark_addressable (*expr_p);
11151 ret = GS_OK;
11153 break;
11155 case CALL_EXPR:
11156 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
11158 /* C99 code may assign to an array in a structure returned
11159 from a function, and this has undefined behavior only on
11160 execution, so create a temporary if an lvalue is
11161 required. */
11162 if (fallback == fb_lvalue)
11164 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11165 mark_addressable (*expr_p);
11166 ret = GS_OK;
11168 break;
11170 case TREE_LIST:
11171 gcc_unreachable ();
11173 case COMPOUND_EXPR:
11174 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
11175 break;
11177 case COMPOUND_LITERAL_EXPR:
11178 ret = gimplify_compound_literal_expr (expr_p, pre_p,
11179 gimple_test_f, fallback);
11180 break;
11182 case MODIFY_EXPR:
11183 case INIT_EXPR:
11184 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
11185 fallback != fb_none);
11186 break;
11188 case TRUTH_ANDIF_EXPR:
11189 case TRUTH_ORIF_EXPR:
11191 /* Preserve the original type of the expression and the
11192 source location of the outer expression. */
11193 tree org_type = TREE_TYPE (*expr_p);
11194 *expr_p = gimple_boolify (*expr_p);
11195 *expr_p = build3_loc (input_location, COND_EXPR,
11196 org_type, *expr_p,
11197 fold_convert_loc
11198 (input_location,
11199 org_type, boolean_true_node),
11200 fold_convert_loc
11201 (input_location,
11202 org_type, boolean_false_node));
11203 ret = GS_OK;
11204 break;
11207 case TRUTH_NOT_EXPR:
11209 tree type = TREE_TYPE (*expr_p);
11210 /* The parsers are careful to generate TRUTH_NOT_EXPR
11211 only with operands that are always zero or one.
11212 We do not fold here but handle the only interesting case
11213 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
11214 *expr_p = gimple_boolify (*expr_p);
11215 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
11216 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
11217 TREE_TYPE (*expr_p),
11218 TREE_OPERAND (*expr_p, 0));
11219 else
11220 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
11221 TREE_TYPE (*expr_p),
11222 TREE_OPERAND (*expr_p, 0),
11223 build_int_cst (TREE_TYPE (*expr_p), 1));
11224 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
11225 *expr_p = fold_convert_loc (input_location, type, *expr_p);
11226 ret = GS_OK;
11227 break;
11230 case ADDR_EXPR:
11231 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
11232 break;
11234 case ANNOTATE_EXPR:
11236 tree cond = TREE_OPERAND (*expr_p, 0);
11237 tree kind = TREE_OPERAND (*expr_p, 1);
11238 tree type = TREE_TYPE (cond);
11239 if (!INTEGRAL_TYPE_P (type))
11241 *expr_p = cond;
11242 ret = GS_OK;
11243 break;
11245 tree tmp = create_tmp_var (type);
11246 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
11247 gcall *call
11248 = gimple_build_call_internal (IFN_ANNOTATE, 2, cond, kind);
11249 gimple_call_set_lhs (call, tmp);
11250 gimplify_seq_add_stmt (pre_p, call);
11251 *expr_p = tmp;
11252 ret = GS_ALL_DONE;
11253 break;
11256 case VA_ARG_EXPR:
11257 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
11258 break;
11260 CASE_CONVERT:
11261 if (IS_EMPTY_STMT (*expr_p))
11263 ret = GS_ALL_DONE;
11264 break;
11267 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
11268 || fallback == fb_none)
11270 /* Just strip a conversion to void (or in void context) and
11271 try again. */
11272 *expr_p = TREE_OPERAND (*expr_p, 0);
11273 ret = GS_OK;
11274 break;
11277 ret = gimplify_conversion (expr_p);
11278 if (ret == GS_ERROR)
11279 break;
11280 if (*expr_p != save_expr)
11281 break;
11282 /* FALLTHRU */
11284 case FIX_TRUNC_EXPR:
11285 /* unary_expr: ... | '(' cast ')' val | ... */
11286 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11287 is_gimple_val, fb_rvalue);
11288 recalculate_side_effects (*expr_p);
11289 break;
11291 case INDIRECT_REF:
11293 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
11294 bool notrap = TREE_THIS_NOTRAP (*expr_p);
11295 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
11297 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
11298 if (*expr_p != save_expr)
11300 ret = GS_OK;
11301 break;
11304 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11305 is_gimple_reg, fb_rvalue);
11306 if (ret == GS_ERROR)
11307 break;
11309 recalculate_side_effects (*expr_p);
11310 *expr_p = fold_build2_loc (input_location, MEM_REF,
11311 TREE_TYPE (*expr_p),
11312 TREE_OPERAND (*expr_p, 0),
11313 build_int_cst (saved_ptr_type, 0));
11314 TREE_THIS_VOLATILE (*expr_p) = volatilep;
11315 TREE_THIS_NOTRAP (*expr_p) = notrap;
11316 ret = GS_OK;
11317 break;
11320 /* We arrive here through the various re-gimplifcation paths. */
11321 case MEM_REF:
11322 /* First try re-folding the whole thing. */
11323 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
11324 TREE_OPERAND (*expr_p, 0),
11325 TREE_OPERAND (*expr_p, 1));
11326 if (tmp)
11328 REF_REVERSE_STORAGE_ORDER (tmp)
11329 = REF_REVERSE_STORAGE_ORDER (*expr_p);
11330 *expr_p = tmp;
11331 recalculate_side_effects (*expr_p);
11332 ret = GS_OK;
11333 break;
11335 /* Avoid re-gimplifying the address operand if it is already
11336 in suitable form. Re-gimplifying would mark the address
11337 operand addressable. Always gimplify when not in SSA form
11338 as we still may have to gimplify decls with value-exprs. */
11339 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
11340 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
11342 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11343 is_gimple_mem_ref_addr, fb_rvalue);
11344 if (ret == GS_ERROR)
11345 break;
11347 recalculate_side_effects (*expr_p);
11348 ret = GS_ALL_DONE;
11349 break;
11351 /* Constants need not be gimplified. */
11352 case INTEGER_CST:
11353 case REAL_CST:
11354 case FIXED_CST:
11355 case STRING_CST:
11356 case COMPLEX_CST:
11357 case VECTOR_CST:
11358 /* Drop the overflow flag on constants, we do not want
11359 that in the GIMPLE IL. */
11360 if (TREE_OVERFLOW_P (*expr_p))
11361 *expr_p = drop_tree_overflow (*expr_p);
11362 ret = GS_ALL_DONE;
11363 break;
11365 case CONST_DECL:
11366 /* If we require an lvalue, such as for ADDR_EXPR, retain the
11367 CONST_DECL node. Otherwise the decl is replaceable by its
11368 value. */
11369 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
11370 if (fallback & fb_lvalue)
11371 ret = GS_ALL_DONE;
11372 else
11374 *expr_p = DECL_INITIAL (*expr_p);
11375 ret = GS_OK;
11377 break;
11379 case DECL_EXPR:
11380 ret = gimplify_decl_expr (expr_p, pre_p);
11381 break;
11383 case BIND_EXPR:
11384 ret = gimplify_bind_expr (expr_p, pre_p);
11385 break;
11387 case LOOP_EXPR:
11388 ret = gimplify_loop_expr (expr_p, pre_p);
11389 break;
11391 case SWITCH_EXPR:
11392 ret = gimplify_switch_expr (expr_p, pre_p);
11393 break;
11395 case EXIT_EXPR:
11396 ret = gimplify_exit_expr (expr_p);
11397 break;
11399 case GOTO_EXPR:
11400 /* If the target is not LABEL, then it is a computed jump
11401 and the target needs to be gimplified. */
11402 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
11404 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
11405 NULL, is_gimple_val, fb_rvalue);
11406 if (ret == GS_ERROR)
11407 break;
11409 gimplify_seq_add_stmt (pre_p,
11410 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
11411 ret = GS_ALL_DONE;
11412 break;
11414 case PREDICT_EXPR:
11415 gimplify_seq_add_stmt (pre_p,
11416 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
11417 PREDICT_EXPR_OUTCOME (*expr_p)));
11418 ret = GS_ALL_DONE;
11419 break;
11421 case LABEL_EXPR:
11422 ret = gimplify_label_expr (expr_p, pre_p);
11423 label = LABEL_EXPR_LABEL (*expr_p);
11424 gcc_assert (decl_function_context (label) == current_function_decl);
11426 /* If the label is used in a goto statement, or address of the label
11427 is taken, we need to unpoison all variables that were seen so far.
11428 Doing so would prevent us from reporting a false positives. */
11429 if (asan_poisoned_variables
11430 && asan_used_labels != NULL
11431 && asan_used_labels->contains (label))
11432 asan_poison_variables (asan_poisoned_variables, false, pre_p);
11433 break;
11435 case CASE_LABEL_EXPR:
11436 ret = gimplify_case_label_expr (expr_p, pre_p);
11438 if (gimplify_ctxp->live_switch_vars)
11439 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
11440 pre_p);
11441 break;
11443 case RETURN_EXPR:
11444 ret = gimplify_return_expr (*expr_p, pre_p);
11445 break;
11447 case CONSTRUCTOR:
11448 /* Don't reduce this in place; let gimplify_init_constructor work its
11449 magic. Buf if we're just elaborating this for side effects, just
11450 gimplify any element that has side-effects. */
11451 if (fallback == fb_none)
11453 unsigned HOST_WIDE_INT ix;
11454 tree val;
11455 tree temp = NULL_TREE;
11456 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
11457 if (TREE_SIDE_EFFECTS (val))
11458 append_to_statement_list (val, &temp);
11460 *expr_p = temp;
11461 ret = temp ? GS_OK : GS_ALL_DONE;
11463 /* C99 code may assign to an array in a constructed
11464 structure or union, and this has undefined behavior only
11465 on execution, so create a temporary if an lvalue is
11466 required. */
11467 else if (fallback == fb_lvalue)
11469 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
11470 mark_addressable (*expr_p);
11471 ret = GS_OK;
11473 else
11474 ret = GS_ALL_DONE;
11475 break;
11477 /* The following are special cases that are not handled by the
11478 original GIMPLE grammar. */
11480 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
11481 eliminated. */
11482 case SAVE_EXPR:
11483 ret = gimplify_save_expr (expr_p, pre_p, post_p);
11484 break;
11486 case BIT_FIELD_REF:
11487 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11488 post_p, is_gimple_lvalue, fb_either);
11489 recalculate_side_effects (*expr_p);
11490 break;
11492 case TARGET_MEM_REF:
11494 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
11496 if (TMR_BASE (*expr_p))
11497 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
11498 post_p, is_gimple_mem_ref_addr, fb_either);
11499 if (TMR_INDEX (*expr_p))
11500 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
11501 post_p, is_gimple_val, fb_rvalue);
11502 if (TMR_INDEX2 (*expr_p))
11503 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
11504 post_p, is_gimple_val, fb_rvalue);
11505 /* TMR_STEP and TMR_OFFSET are always integer constants. */
11506 ret = MIN (r0, r1);
11508 break;
11510 case NON_LVALUE_EXPR:
11511 /* This should have been stripped above. */
11512 gcc_unreachable ();
11514 case ASM_EXPR:
11515 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
11516 break;
11518 case TRY_FINALLY_EXPR:
11519 case TRY_CATCH_EXPR:
11521 gimple_seq eval, cleanup;
11522 gtry *try_;
11524 /* Calls to destructors are generated automatically in FINALLY/CATCH
11525 block. They should have location as UNKNOWN_LOCATION. However,
11526 gimplify_call_expr will reset these call stmts to input_location
11527 if it finds stmt's location is unknown. To prevent resetting for
11528 destructors, we set the input_location to unknown.
11529 Note that this only affects the destructor calls in FINALLY/CATCH
11530 block, and will automatically reset to its original value by the
11531 end of gimplify_expr. */
11532 input_location = UNKNOWN_LOCATION;
11533 eval = cleanup = NULL;
11534 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
11535 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
11536 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
11537 if (gimple_seq_empty_p (cleanup))
11539 gimple_seq_add_seq (pre_p, eval);
11540 ret = GS_ALL_DONE;
11541 break;
11543 try_ = gimple_build_try (eval, cleanup,
11544 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
11545 ? GIMPLE_TRY_FINALLY
11546 : GIMPLE_TRY_CATCH);
11547 if (EXPR_HAS_LOCATION (save_expr))
11548 gimple_set_location (try_, EXPR_LOCATION (save_expr));
11549 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
11550 gimple_set_location (try_, saved_location);
11551 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
11552 gimple_try_set_catch_is_cleanup (try_,
11553 TRY_CATCH_IS_CLEANUP (*expr_p));
11554 gimplify_seq_add_stmt (pre_p, try_);
11555 ret = GS_ALL_DONE;
11556 break;
11559 case CLEANUP_POINT_EXPR:
11560 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
11561 break;
11563 case TARGET_EXPR:
11564 ret = gimplify_target_expr (expr_p, pre_p, post_p);
11565 break;
11567 case CATCH_EXPR:
11569 gimple *c;
11570 gimple_seq handler = NULL;
11571 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
11572 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
11573 gimplify_seq_add_stmt (pre_p, c);
11574 ret = GS_ALL_DONE;
11575 break;
11578 case EH_FILTER_EXPR:
11580 gimple *ehf;
11581 gimple_seq failure = NULL;
11583 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
11584 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
11585 gimple_set_no_warning (ehf, TREE_NO_WARNING (*expr_p));
11586 gimplify_seq_add_stmt (pre_p, ehf);
11587 ret = GS_ALL_DONE;
11588 break;
11591 case OBJ_TYPE_REF:
11593 enum gimplify_status r0, r1;
11594 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
11595 post_p, is_gimple_val, fb_rvalue);
11596 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
11597 post_p, is_gimple_val, fb_rvalue);
11598 TREE_SIDE_EFFECTS (*expr_p) = 0;
11599 ret = MIN (r0, r1);
11601 break;
11603 case LABEL_DECL:
11604 /* We get here when taking the address of a label. We mark
11605 the label as "forced"; meaning it can never be removed and
11606 it is a potential target for any computed goto. */
11607 FORCED_LABEL (*expr_p) = 1;
11608 ret = GS_ALL_DONE;
11609 break;
11611 case STATEMENT_LIST:
11612 ret = gimplify_statement_list (expr_p, pre_p);
11613 break;
11615 case WITH_SIZE_EXPR:
11617 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11618 post_p == &internal_post ? NULL : post_p,
11619 gimple_test_f, fallback);
11620 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
11621 is_gimple_val, fb_rvalue);
11622 ret = GS_ALL_DONE;
11624 break;
11626 case VAR_DECL:
11627 case PARM_DECL:
11628 ret = gimplify_var_or_parm_decl (expr_p);
11629 break;
11631 case RESULT_DECL:
11632 /* When within an OMP context, notice uses of variables. */
11633 if (gimplify_omp_ctxp)
11634 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
11635 ret = GS_ALL_DONE;
11636 break;
11638 case SSA_NAME:
11639 /* Allow callbacks into the gimplifier during optimization. */
11640 ret = GS_ALL_DONE;
11641 break;
11643 case OMP_PARALLEL:
11644 gimplify_omp_parallel (expr_p, pre_p);
11645 ret = GS_ALL_DONE;
11646 break;
11648 case OMP_TASK:
11649 gimplify_omp_task (expr_p, pre_p);
11650 ret = GS_ALL_DONE;
11651 break;
11653 case OMP_FOR:
11654 case OMP_SIMD:
11655 case CILK_SIMD:
11656 case CILK_FOR:
11657 case OMP_DISTRIBUTE:
11658 case OMP_TASKLOOP:
11659 case OACC_LOOP:
11660 ret = gimplify_omp_for (expr_p, pre_p);
11661 break;
11663 case OACC_CACHE:
11664 gimplify_oacc_cache (expr_p, pre_p);
11665 ret = GS_ALL_DONE;
11666 break;
11668 case OACC_DECLARE:
11669 gimplify_oacc_declare (expr_p, pre_p);
11670 ret = GS_ALL_DONE;
11671 break;
11673 case OACC_HOST_DATA:
11674 case OACC_DATA:
11675 case OACC_KERNELS:
11676 case OACC_PARALLEL:
11677 case OMP_SECTIONS:
11678 case OMP_SINGLE:
11679 case OMP_TARGET:
11680 case OMP_TARGET_DATA:
11681 case OMP_TEAMS:
11682 gimplify_omp_workshare (expr_p, pre_p);
11683 ret = GS_ALL_DONE;
11684 break;
11686 case OACC_ENTER_DATA:
11687 case OACC_EXIT_DATA:
11688 case OACC_UPDATE:
11689 case OMP_TARGET_UPDATE:
11690 case OMP_TARGET_ENTER_DATA:
11691 case OMP_TARGET_EXIT_DATA:
11692 gimplify_omp_target_update (expr_p, pre_p);
11693 ret = GS_ALL_DONE;
11694 break;
11696 case OMP_SECTION:
11697 case OMP_MASTER:
11698 case OMP_TASKGROUP:
11699 case OMP_ORDERED:
11700 case OMP_CRITICAL:
11702 gimple_seq body = NULL;
11703 gimple *g;
11705 gimplify_and_add (OMP_BODY (*expr_p), &body);
11706 switch (TREE_CODE (*expr_p))
11708 case OMP_SECTION:
11709 g = gimple_build_omp_section (body);
11710 break;
11711 case OMP_MASTER:
11712 g = gimple_build_omp_master (body);
11713 break;
11714 case OMP_TASKGROUP:
11716 gimple_seq cleanup = NULL;
11717 tree fn
11718 = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
11719 g = gimple_build_call (fn, 0);
11720 gimple_seq_add_stmt (&cleanup, g);
11721 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
11722 body = NULL;
11723 gimple_seq_add_stmt (&body, g);
11724 g = gimple_build_omp_taskgroup (body);
11726 break;
11727 case OMP_ORDERED:
11728 g = gimplify_omp_ordered (*expr_p, body);
11729 break;
11730 case OMP_CRITICAL:
11731 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
11732 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
11733 gimplify_adjust_omp_clauses (pre_p, body,
11734 &OMP_CRITICAL_CLAUSES (*expr_p),
11735 OMP_CRITICAL);
11736 g = gimple_build_omp_critical (body,
11737 OMP_CRITICAL_NAME (*expr_p),
11738 OMP_CRITICAL_CLAUSES (*expr_p));
11739 break;
11740 default:
11741 gcc_unreachable ();
11743 gimplify_seq_add_stmt (pre_p, g);
11744 ret = GS_ALL_DONE;
11745 break;
11748 case OMP_ATOMIC:
11749 case OMP_ATOMIC_READ:
11750 case OMP_ATOMIC_CAPTURE_OLD:
11751 case OMP_ATOMIC_CAPTURE_NEW:
11752 ret = gimplify_omp_atomic (expr_p, pre_p);
11753 break;
11755 case TRANSACTION_EXPR:
11756 ret = gimplify_transaction (expr_p, pre_p);
11757 break;
11759 case TRUTH_AND_EXPR:
11760 case TRUTH_OR_EXPR:
11761 case TRUTH_XOR_EXPR:
11763 tree orig_type = TREE_TYPE (*expr_p);
11764 tree new_type, xop0, xop1;
11765 *expr_p = gimple_boolify (*expr_p);
11766 new_type = TREE_TYPE (*expr_p);
11767 if (!useless_type_conversion_p (orig_type, new_type))
11769 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
11770 ret = GS_OK;
11771 break;
11774 /* Boolified binary truth expressions are semantically equivalent
11775 to bitwise binary expressions. Canonicalize them to the
11776 bitwise variant. */
11777 switch (TREE_CODE (*expr_p))
11779 case TRUTH_AND_EXPR:
11780 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
11781 break;
11782 case TRUTH_OR_EXPR:
11783 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
11784 break;
11785 case TRUTH_XOR_EXPR:
11786 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
11787 break;
11788 default:
11789 break;
11791 /* Now make sure that operands have compatible type to
11792 expression's new_type. */
11793 xop0 = TREE_OPERAND (*expr_p, 0);
11794 xop1 = TREE_OPERAND (*expr_p, 1);
11795 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
11796 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
11797 new_type,
11798 xop0);
11799 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
11800 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
11801 new_type,
11802 xop1);
11803 /* Continue classified as tcc_binary. */
11804 goto expr_2;
11807 case VEC_COND_EXPR:
11809 enum gimplify_status r0, r1, r2;
11811 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11812 post_p, is_gimple_condexpr, fb_rvalue);
11813 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11814 post_p, is_gimple_val, fb_rvalue);
11815 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
11816 post_p, is_gimple_val, fb_rvalue);
11818 ret = MIN (MIN (r0, r1), r2);
11819 recalculate_side_effects (*expr_p);
11821 break;
11823 case FMA_EXPR:
11824 case VEC_PERM_EXPR:
11825 /* Classified as tcc_expression. */
11826 goto expr_3;
11828 case BIT_INSERT_EXPR:
11829 /* Argument 3 is a constant. */
11830 goto expr_2;
11832 case POINTER_PLUS_EXPR:
11834 enum gimplify_status r0, r1;
11835 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11836 post_p, is_gimple_val, fb_rvalue);
11837 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11838 post_p, is_gimple_val, fb_rvalue);
11839 recalculate_side_effects (*expr_p);
11840 ret = MIN (r0, r1);
11841 break;
11844 case CILK_SYNC_STMT:
11846 if (!fn_contains_cilk_spawn_p (cfun))
11848 error_at (EXPR_LOCATION (*expr_p),
11849 "expected %<_Cilk_spawn%> before %<_Cilk_sync%>");
11850 ret = GS_ERROR;
11852 else
11854 gimplify_cilk_sync (expr_p, pre_p);
11855 ret = GS_ALL_DONE;
11857 break;
11860 default:
11861 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
11863 case tcc_comparison:
11864 /* Handle comparison of objects of non scalar mode aggregates
11865 with a call to memcmp. It would be nice to only have to do
11866 this for variable-sized objects, but then we'd have to allow
11867 the same nest of reference nodes we allow for MODIFY_EXPR and
11868 that's too complex.
11870 Compare scalar mode aggregates as scalar mode values. Using
11871 memcmp for them would be very inefficient at best, and is
11872 plain wrong if bitfields are involved. */
11874 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
11876 /* Vector comparisons need no boolification. */
11877 if (TREE_CODE (type) == VECTOR_TYPE)
11878 goto expr_2;
11879 else if (!AGGREGATE_TYPE_P (type))
11881 tree org_type = TREE_TYPE (*expr_p);
11882 *expr_p = gimple_boolify (*expr_p);
11883 if (!useless_type_conversion_p (org_type,
11884 TREE_TYPE (*expr_p)))
11886 *expr_p = fold_convert_loc (input_location,
11887 org_type, *expr_p);
11888 ret = GS_OK;
11890 else
11891 goto expr_2;
11893 else if (TYPE_MODE (type) != BLKmode)
11894 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
11895 else
11896 ret = gimplify_variable_sized_compare (expr_p);
11898 break;
11901 /* If *EXPR_P does not need to be special-cased, handle it
11902 according to its class. */
11903 case tcc_unary:
11904 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11905 post_p, is_gimple_val, fb_rvalue);
11906 break;
11908 case tcc_binary:
11909 expr_2:
11911 enum gimplify_status r0, r1;
11913 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11914 post_p, is_gimple_val, fb_rvalue);
11915 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11916 post_p, is_gimple_val, fb_rvalue);
11918 ret = MIN (r0, r1);
11919 break;
11922 expr_3:
11924 enum gimplify_status r0, r1, r2;
11926 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
11927 post_p, is_gimple_val, fb_rvalue);
11928 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
11929 post_p, is_gimple_val, fb_rvalue);
11930 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
11931 post_p, is_gimple_val, fb_rvalue);
11933 ret = MIN (MIN (r0, r1), r2);
11934 break;
11937 case tcc_declaration:
11938 case tcc_constant:
11939 ret = GS_ALL_DONE;
11940 goto dont_recalculate;
11942 default:
11943 gcc_unreachable ();
11946 recalculate_side_effects (*expr_p);
11948 dont_recalculate:
11949 break;
11952 gcc_assert (*expr_p || ret != GS_OK);
11954 while (ret == GS_OK);
11956 /* If we encountered an error_mark somewhere nested inside, either
11957 stub out the statement or propagate the error back out. */
11958 if (ret == GS_ERROR)
11960 if (is_statement)
11961 *expr_p = NULL;
11962 goto out;
11965 /* This was only valid as a return value from the langhook, which
11966 we handled. Make sure it doesn't escape from any other context. */
11967 gcc_assert (ret != GS_UNHANDLED);
11969 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
11971 /* We aren't looking for a value, and we don't have a valid
11972 statement. If it doesn't have side-effects, throw it away. */
11973 if (!TREE_SIDE_EFFECTS (*expr_p))
11974 *expr_p = NULL;
11975 else if (!TREE_THIS_VOLATILE (*expr_p))
11977 /* This is probably a _REF that contains something nested that
11978 has side effects. Recurse through the operands to find it. */
11979 enum tree_code code = TREE_CODE (*expr_p);
11981 switch (code)
11983 case COMPONENT_REF:
11984 case REALPART_EXPR:
11985 case IMAGPART_EXPR:
11986 case VIEW_CONVERT_EXPR:
11987 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11988 gimple_test_f, fallback);
11989 break;
11991 case ARRAY_REF:
11992 case ARRAY_RANGE_REF:
11993 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
11994 gimple_test_f, fallback);
11995 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
11996 gimple_test_f, fallback);
11997 break;
11999 default:
12000 /* Anything else with side-effects must be converted to
12001 a valid statement before we get here. */
12002 gcc_unreachable ();
12005 *expr_p = NULL;
12007 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
12008 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
12010 /* Historically, the compiler has treated a bare reference
12011 to a non-BLKmode volatile lvalue as forcing a load. */
12012 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
12014 /* Normally, we do not want to create a temporary for a
12015 TREE_ADDRESSABLE type because such a type should not be
12016 copied by bitwise-assignment. However, we make an
12017 exception here, as all we are doing here is ensuring that
12018 we read the bytes that make up the type. We use
12019 create_tmp_var_raw because create_tmp_var will abort when
12020 given a TREE_ADDRESSABLE type. */
12021 tree tmp = create_tmp_var_raw (type, "vol");
12022 gimple_add_tmp_var (tmp);
12023 gimplify_assign (tmp, *expr_p, pre_p);
12024 *expr_p = NULL;
12026 else
12027 /* We can't do anything useful with a volatile reference to
12028 an incomplete type, so just throw it away. Likewise for
12029 a BLKmode type, since any implicit inner load should
12030 already have been turned into an explicit one by the
12031 gimplification process. */
12032 *expr_p = NULL;
12035 /* If we are gimplifying at the statement level, we're done. Tack
12036 everything together and return. */
12037 if (fallback == fb_none || is_statement)
12039 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
12040 it out for GC to reclaim it. */
12041 *expr_p = NULL_TREE;
12043 if (!gimple_seq_empty_p (internal_pre)
12044 || !gimple_seq_empty_p (internal_post))
12046 gimplify_seq_add_seq (&internal_pre, internal_post);
12047 gimplify_seq_add_seq (pre_p, internal_pre);
12050 /* The result of gimplifying *EXPR_P is going to be the last few
12051 statements in *PRE_P and *POST_P. Add location information
12052 to all the statements that were added by the gimplification
12053 helpers. */
12054 if (!gimple_seq_empty_p (*pre_p))
12055 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
12057 if (!gimple_seq_empty_p (*post_p))
12058 annotate_all_with_location_after (*post_p, post_last_gsi,
12059 input_location);
12061 goto out;
12064 #ifdef ENABLE_GIMPLE_CHECKING
12065 if (*expr_p)
12067 enum tree_code code = TREE_CODE (*expr_p);
12068 /* These expressions should already be in gimple IR form. */
12069 gcc_assert (code != MODIFY_EXPR
12070 && code != ASM_EXPR
12071 && code != BIND_EXPR
12072 && code != CATCH_EXPR
12073 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
12074 && code != EH_FILTER_EXPR
12075 && code != GOTO_EXPR
12076 && code != LABEL_EXPR
12077 && code != LOOP_EXPR
12078 && code != SWITCH_EXPR
12079 && code != TRY_FINALLY_EXPR
12080 && code != OACC_PARALLEL
12081 && code != OACC_KERNELS
12082 && code != OACC_DATA
12083 && code != OACC_HOST_DATA
12084 && code != OACC_DECLARE
12085 && code != OACC_UPDATE
12086 && code != OACC_ENTER_DATA
12087 && code != OACC_EXIT_DATA
12088 && code != OACC_CACHE
12089 && code != OMP_CRITICAL
12090 && code != OMP_FOR
12091 && code != OACC_LOOP
12092 && code != OMP_MASTER
12093 && code != OMP_TASKGROUP
12094 && code != OMP_ORDERED
12095 && code != OMP_PARALLEL
12096 && code != OMP_SECTIONS
12097 && code != OMP_SECTION
12098 && code != OMP_SINGLE);
12100 #endif
12102 /* Otherwise we're gimplifying a subexpression, so the resulting
12103 value is interesting. If it's a valid operand that matches
12104 GIMPLE_TEST_F, we're done. Unless we are handling some
12105 post-effects internally; if that's the case, we need to copy into
12106 a temporary before adding the post-effects to POST_P. */
12107 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
12108 goto out;
12110 /* Otherwise, we need to create a new temporary for the gimplified
12111 expression. */
12113 /* We can't return an lvalue if we have an internal postqueue. The
12114 object the lvalue refers to would (probably) be modified by the
12115 postqueue; we need to copy the value out first, which means an
12116 rvalue. */
12117 if ((fallback & fb_lvalue)
12118 && gimple_seq_empty_p (internal_post)
12119 && is_gimple_addressable (*expr_p))
12121 /* An lvalue will do. Take the address of the expression, store it
12122 in a temporary, and replace the expression with an INDIRECT_REF of
12123 that temporary. */
12124 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
12125 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
12126 *expr_p = build_simple_mem_ref (tmp);
12128 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
12130 /* An rvalue will do. Assign the gimplified expression into a
12131 new temporary TMP and replace the original expression with
12132 TMP. First, make sure that the expression has a type so that
12133 it can be assigned into a temporary. */
12134 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
12135 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
12137 else
12139 #ifdef ENABLE_GIMPLE_CHECKING
12140 if (!(fallback & fb_mayfail))
12142 fprintf (stderr, "gimplification failed:\n");
12143 print_generic_expr (stderr, *expr_p, 0);
12144 debug_tree (*expr_p);
12145 internal_error ("gimplification failed");
12147 #endif
12148 gcc_assert (fallback & fb_mayfail);
12150 /* If this is an asm statement, and the user asked for the
12151 impossible, don't die. Fail and let gimplify_asm_expr
12152 issue an error. */
12153 ret = GS_ERROR;
12154 goto out;
12157 /* Make sure the temporary matches our predicate. */
12158 gcc_assert ((*gimple_test_f) (*expr_p));
12160 if (!gimple_seq_empty_p (internal_post))
12162 annotate_all_with_location (internal_post, input_location);
12163 gimplify_seq_add_seq (pre_p, internal_post);
12166 out:
12167 input_location = saved_location;
12168 return ret;
12171 /* Like gimplify_expr but make sure the gimplified result is not itself
12172 a SSA name (but a decl if it were). Temporaries required by
12173 evaluating *EXPR_P may be still SSA names. */
12175 static enum gimplify_status
12176 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
12177 bool (*gimple_test_f) (tree), fallback_t fallback,
12178 bool allow_ssa)
12180 bool was_ssa_name_p = TREE_CODE (*expr_p) == SSA_NAME;
12181 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
12182 gimple_test_f, fallback);
12183 if (! allow_ssa
12184 && TREE_CODE (*expr_p) == SSA_NAME)
12186 tree name = *expr_p;
12187 if (was_ssa_name_p)
12188 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
12189 else
12191 /* Avoid the extra copy if possible. */
12192 *expr_p = create_tmp_reg (TREE_TYPE (name));
12193 gimple_set_lhs (SSA_NAME_DEF_STMT (name), *expr_p);
12194 release_ssa_name (name);
12197 return ret;
12200 /* Look through TYPE for variable-sized objects and gimplify each such
12201 size that we find. Add to LIST_P any statements generated. */
12203 void
12204 gimplify_type_sizes (tree type, gimple_seq *list_p)
12206 tree field, t;
12208 if (type == NULL || type == error_mark_node)
12209 return;
12211 /* We first do the main variant, then copy into any other variants. */
12212 type = TYPE_MAIN_VARIANT (type);
12214 /* Avoid infinite recursion. */
12215 if (TYPE_SIZES_GIMPLIFIED (type))
12216 return;
12218 TYPE_SIZES_GIMPLIFIED (type) = 1;
12220 switch (TREE_CODE (type))
12222 case INTEGER_TYPE:
12223 case ENUMERAL_TYPE:
12224 case BOOLEAN_TYPE:
12225 case REAL_TYPE:
12226 case FIXED_POINT_TYPE:
12227 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
12228 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
12230 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
12232 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
12233 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
12235 break;
12237 case ARRAY_TYPE:
12238 /* These types may not have declarations, so handle them here. */
12239 gimplify_type_sizes (TREE_TYPE (type), list_p);
12240 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
12241 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
12242 with assigned stack slots, for -O1+ -g they should be tracked
12243 by VTA. */
12244 if (!(TYPE_NAME (type)
12245 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
12246 && DECL_IGNORED_P (TYPE_NAME (type)))
12247 && TYPE_DOMAIN (type)
12248 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
12250 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
12251 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
12252 DECL_IGNORED_P (t) = 0;
12253 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
12254 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
12255 DECL_IGNORED_P (t) = 0;
12257 break;
12259 case RECORD_TYPE:
12260 case UNION_TYPE:
12261 case QUAL_UNION_TYPE:
12262 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
12263 if (TREE_CODE (field) == FIELD_DECL)
12265 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
12266 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
12267 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
12268 gimplify_type_sizes (TREE_TYPE (field), list_p);
12270 break;
12272 case POINTER_TYPE:
12273 case REFERENCE_TYPE:
12274 /* We used to recurse on the pointed-to type here, which turned out to
12275 be incorrect because its definition might refer to variables not
12276 yet initialized at this point if a forward declaration is involved.
12278 It was actually useful for anonymous pointed-to types to ensure
12279 that the sizes evaluation dominates every possible later use of the
12280 values. Restricting to such types here would be safe since there
12281 is no possible forward declaration around, but would introduce an
12282 undesirable middle-end semantic to anonymity. We then defer to
12283 front-ends the responsibility of ensuring that the sizes are
12284 evaluated both early and late enough, e.g. by attaching artificial
12285 type declarations to the tree. */
12286 break;
12288 default:
12289 break;
12292 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
12293 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
12295 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
12297 TYPE_SIZE (t) = TYPE_SIZE (type);
12298 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
12299 TYPE_SIZES_GIMPLIFIED (t) = 1;
12303 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
12304 a size or position, has had all of its SAVE_EXPRs evaluated.
12305 We add any required statements to *STMT_P. */
12307 void
12308 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
12310 tree expr = *expr_p;
12312 /* We don't do anything if the value isn't there, is constant, or contains
12313 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
12314 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
12315 will want to replace it with a new variable, but that will cause problems
12316 if this type is from outside the function. It's OK to have that here. */
12317 if (is_gimple_sizepos (expr))
12318 return;
12320 *expr_p = unshare_expr (expr);
12322 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
12323 if the def vanishes. */
12324 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
12327 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
12328 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
12329 is true, also gimplify the parameters. */
12331 gbind *
12332 gimplify_body (tree fndecl, bool do_parms)
12334 location_t saved_location = input_location;
12335 gimple_seq parm_stmts, seq;
12336 gimple *outer_stmt;
12337 gbind *outer_bind;
12338 struct cgraph_node *cgn;
12340 timevar_push (TV_TREE_GIMPLIFY);
12342 init_tree_ssa (cfun);
12344 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
12345 gimplification. */
12346 default_rtl_profile ();
12348 gcc_assert (gimplify_ctxp == NULL);
12349 push_gimplify_context (true);
12351 if (flag_openacc || flag_openmp)
12353 gcc_assert (gimplify_omp_ctxp == NULL);
12354 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
12355 gimplify_omp_ctxp = new_omp_context (ORT_TARGET);
12358 /* Unshare most shared trees in the body and in that of any nested functions.
12359 It would seem we don't have to do this for nested functions because
12360 they are supposed to be output and then the outer function gimplified
12361 first, but the g++ front end doesn't always do it that way. */
12362 unshare_body (fndecl);
12363 unvisit_body (fndecl);
12365 cgn = cgraph_node::get (fndecl);
12366 if (cgn && cgn->origin)
12367 nonlocal_vlas = new hash_set<tree>;
12369 /* Make sure input_location isn't set to something weird. */
12370 input_location = DECL_SOURCE_LOCATION (fndecl);
12372 /* Resolve callee-copies. This has to be done before processing
12373 the body so that DECL_VALUE_EXPR gets processed correctly. */
12374 parm_stmts = do_parms ? gimplify_parameters () : NULL;
12376 /* Gimplify the function's body. */
12377 seq = NULL;
12378 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
12379 outer_stmt = gimple_seq_first_stmt (seq);
12380 if (!outer_stmt)
12382 outer_stmt = gimple_build_nop ();
12383 gimplify_seq_add_stmt (&seq, outer_stmt);
12386 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
12387 not the case, wrap everything in a GIMPLE_BIND to make it so. */
12388 if (gimple_code (outer_stmt) == GIMPLE_BIND
12389 && gimple_seq_first (seq) == gimple_seq_last (seq))
12390 outer_bind = as_a <gbind *> (outer_stmt);
12391 else
12392 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
12394 DECL_SAVED_TREE (fndecl) = NULL_TREE;
12396 /* If we had callee-copies statements, insert them at the beginning
12397 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
12398 if (!gimple_seq_empty_p (parm_stmts))
12400 tree parm;
12402 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
12403 gimple_bind_set_body (outer_bind, parm_stmts);
12405 for (parm = DECL_ARGUMENTS (current_function_decl);
12406 parm; parm = DECL_CHAIN (parm))
12407 if (DECL_HAS_VALUE_EXPR_P (parm))
12409 DECL_HAS_VALUE_EXPR_P (parm) = 0;
12410 DECL_IGNORED_P (parm) = 0;
12414 if (nonlocal_vlas)
12416 if (nonlocal_vla_vars)
12418 /* tree-nested.c may later on call declare_vars (..., true);
12419 which relies on BLOCK_VARS chain to be the tail of the
12420 gimple_bind_vars chain. Ensure we don't violate that
12421 assumption. */
12422 if (gimple_bind_block (outer_bind)
12423 == DECL_INITIAL (current_function_decl))
12424 declare_vars (nonlocal_vla_vars, outer_bind, true);
12425 else
12426 BLOCK_VARS (DECL_INITIAL (current_function_decl))
12427 = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl)),
12428 nonlocal_vla_vars);
12429 nonlocal_vla_vars = NULL_TREE;
12431 delete nonlocal_vlas;
12432 nonlocal_vlas = NULL;
12435 if ((flag_openacc || flag_openmp || flag_openmp_simd)
12436 && gimplify_omp_ctxp)
12438 delete_omp_context (gimplify_omp_ctxp);
12439 gimplify_omp_ctxp = NULL;
12442 pop_gimplify_context (outer_bind);
12443 gcc_assert (gimplify_ctxp == NULL);
12445 if (flag_checking && !seen_error ())
12446 verify_gimple_in_seq (gimple_bind_body (outer_bind));
12448 timevar_pop (TV_TREE_GIMPLIFY);
12449 input_location = saved_location;
12451 return outer_bind;
12454 typedef char *char_p; /* For DEF_VEC_P. */
12456 /* Return whether we should exclude FNDECL from instrumentation. */
12458 static bool
12459 flag_instrument_functions_exclude_p (tree fndecl)
12461 vec<char_p> *v;
12463 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
12464 if (v && v->length () > 0)
12466 const char *name;
12467 int i;
12468 char *s;
12470 name = lang_hooks.decl_printable_name (fndecl, 0);
12471 FOR_EACH_VEC_ELT (*v, i, s)
12472 if (strstr (name, s) != NULL)
12473 return true;
12476 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
12477 if (v && v->length () > 0)
12479 const char *name;
12480 int i;
12481 char *s;
12483 name = DECL_SOURCE_FILE (fndecl);
12484 FOR_EACH_VEC_ELT (*v, i, s)
12485 if (strstr (name, s) != NULL)
12486 return true;
12489 return false;
12492 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
12493 node for the function we want to gimplify.
12495 Return the sequence of GIMPLE statements corresponding to the body
12496 of FNDECL. */
12498 void
12499 gimplify_function_tree (tree fndecl)
12501 tree parm, ret;
12502 gimple_seq seq;
12503 gbind *bind;
12505 gcc_assert (!gimple_body (fndecl));
12507 if (DECL_STRUCT_FUNCTION (fndecl))
12508 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
12509 else
12510 push_struct_function (fndecl);
12512 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
12513 if necessary. */
12514 cfun->curr_properties |= PROP_gimple_lva;
12516 for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = DECL_CHAIN (parm))
12518 /* Preliminarily mark non-addressed complex variables as eligible
12519 for promotion to gimple registers. We'll transform their uses
12520 as we find them. */
12521 if ((TREE_CODE (TREE_TYPE (parm)) == COMPLEX_TYPE
12522 || TREE_CODE (TREE_TYPE (parm)) == VECTOR_TYPE)
12523 && !TREE_THIS_VOLATILE (parm)
12524 && !needs_to_live_in_memory (parm))
12525 DECL_GIMPLE_REG_P (parm) = 1;
12528 ret = DECL_RESULT (fndecl);
12529 if ((TREE_CODE (TREE_TYPE (ret)) == COMPLEX_TYPE
12530 || TREE_CODE (TREE_TYPE (ret)) == VECTOR_TYPE)
12531 && !needs_to_live_in_memory (ret))
12532 DECL_GIMPLE_REG_P (ret) = 1;
12534 if (asan_sanitize_use_after_scope () && !asan_no_sanitize_address_p ())
12535 asan_poisoned_variables = new hash_set<tree> ();
12536 bind = gimplify_body (fndecl, true);
12537 if (asan_poisoned_variables)
12539 delete asan_poisoned_variables;
12540 asan_poisoned_variables = NULL;
12543 /* The tree body of the function is no longer needed, replace it
12544 with the new GIMPLE body. */
12545 seq = NULL;
12546 gimple_seq_add_stmt (&seq, bind);
12547 gimple_set_body (fndecl, seq);
12549 /* If we're instrumenting function entry/exit, then prepend the call to
12550 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
12551 catch the exit hook. */
12552 /* ??? Add some way to ignore exceptions for this TFE. */
12553 if (flag_instrument_function_entry_exit
12554 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
12555 /* Do not instrument extern inline functions. */
12556 && !(DECL_DECLARED_INLINE_P (fndecl)
12557 && DECL_EXTERNAL (fndecl)
12558 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
12559 && !flag_instrument_functions_exclude_p (fndecl))
12561 tree x;
12562 gbind *new_bind;
12563 gimple *tf;
12564 gimple_seq cleanup = NULL, body = NULL;
12565 tree tmp_var;
12566 gcall *call;
12568 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
12569 call = gimple_build_call (x, 1, integer_zero_node);
12570 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
12571 gimple_call_set_lhs (call, tmp_var);
12572 gimplify_seq_add_stmt (&cleanup, call);
12573 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
12574 call = gimple_build_call (x, 2,
12575 build_fold_addr_expr (current_function_decl),
12576 tmp_var);
12577 gimplify_seq_add_stmt (&cleanup, call);
12578 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
12580 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
12581 call = gimple_build_call (x, 1, integer_zero_node);
12582 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
12583 gimple_call_set_lhs (call, tmp_var);
12584 gimplify_seq_add_stmt (&body, call);
12585 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
12586 call = gimple_build_call (x, 2,
12587 build_fold_addr_expr (current_function_decl),
12588 tmp_var);
12589 gimplify_seq_add_stmt (&body, call);
12590 gimplify_seq_add_stmt (&body, tf);
12591 new_bind = gimple_build_bind (NULL, body, NULL);
12593 /* Replace the current function body with the body
12594 wrapped in the try/finally TF. */
12595 seq = NULL;
12596 gimple_seq_add_stmt (&seq, new_bind);
12597 gimple_set_body (fndecl, seq);
12598 bind = new_bind;
12601 if ((flag_sanitize & SANITIZE_THREAD) != 0
12602 && !lookup_attribute ("no_sanitize_thread", DECL_ATTRIBUTES (fndecl)))
12604 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
12605 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
12606 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
12607 /* Replace the current function body with the body
12608 wrapped in the try/finally TF. */
12609 seq = NULL;
12610 gimple_seq_add_stmt (&seq, new_bind);
12611 gimple_set_body (fndecl, seq);
12614 DECL_SAVED_TREE (fndecl) = NULL_TREE;
12615 cfun->curr_properties |= PROP_gimple_any;
12617 pop_cfun ();
12619 dump_function (TDI_generic, fndecl);
12622 /* Return a dummy expression of type TYPE in order to keep going after an
12623 error. */
12625 static tree
12626 dummy_object (tree type)
12628 tree t = build_int_cst (build_pointer_type (type), 0);
12629 return build2 (MEM_REF, type, t, t);
12632 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
12633 builtin function, but a very special sort of operator. */
12635 enum gimplify_status
12636 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
12637 gimple_seq *post_p ATTRIBUTE_UNUSED)
12639 tree promoted_type, have_va_type;
12640 tree valist = TREE_OPERAND (*expr_p, 0);
12641 tree type = TREE_TYPE (*expr_p);
12642 tree t, tag, aptag;
12643 location_t loc = EXPR_LOCATION (*expr_p);
12645 /* Verify that valist is of the proper type. */
12646 have_va_type = TREE_TYPE (valist);
12647 if (have_va_type == error_mark_node)
12648 return GS_ERROR;
12649 have_va_type = targetm.canonical_va_list_type (have_va_type);
12650 if (have_va_type == NULL_TREE
12651 && POINTER_TYPE_P (TREE_TYPE (valist)))
12652 /* Handle 'Case 1: Not an array type' from c-common.c/build_va_arg. */
12653 have_va_type
12654 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
12655 gcc_assert (have_va_type != NULL_TREE);
12657 /* Generate a diagnostic for requesting data of a type that cannot
12658 be passed through `...' due to type promotion at the call site. */
12659 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
12660 != type)
12662 static bool gave_help;
12663 bool warned;
12664 /* Use the expansion point to handle cases such as passing bool (defined
12665 in a system header) through `...'. */
12666 source_location xloc
12667 = expansion_point_location_if_in_system_header (loc);
12669 /* Unfortunately, this is merely undefined, rather than a constraint
12670 violation, so we cannot make this an error. If this call is never
12671 executed, the program is still strictly conforming. */
12672 warned = warning_at (xloc, 0,
12673 "%qT is promoted to %qT when passed through %<...%>",
12674 type, promoted_type);
12675 if (!gave_help && warned)
12677 gave_help = true;
12678 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
12679 promoted_type, type);
12682 /* We can, however, treat "undefined" any way we please.
12683 Call abort to encourage the user to fix the program. */
12684 if (warned)
12685 inform (xloc, "if this code is reached, the program will abort");
12686 /* Before the abort, allow the evaluation of the va_list
12687 expression to exit or longjmp. */
12688 gimplify_and_add (valist, pre_p);
12689 t = build_call_expr_loc (loc,
12690 builtin_decl_implicit (BUILT_IN_TRAP), 0);
12691 gimplify_and_add (t, pre_p);
12693 /* This is dead code, but go ahead and finish so that the
12694 mode of the result comes out right. */
12695 *expr_p = dummy_object (type);
12696 return GS_ALL_DONE;
12699 tag = build_int_cst (build_pointer_type (type), 0);
12700 aptag = build_int_cst (TREE_TYPE (valist), 0);
12702 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
12703 valist, tag, aptag);
12705 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
12706 needs to be expanded. */
12707 cfun->curr_properties &= ~PROP_gimple_lva;
12709 return GS_OK;
12712 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
12714 DST/SRC are the destination and source respectively. You can pass
12715 ungimplified trees in DST or SRC, in which case they will be
12716 converted to a gimple operand if necessary.
12718 This function returns the newly created GIMPLE_ASSIGN tuple. */
12720 gimple *
12721 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
12723 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
12724 gimplify_and_add (t, seq_p);
12725 ggc_free (t);
12726 return gimple_seq_last_stmt (*seq_p);
12729 inline hashval_t
12730 gimplify_hasher::hash (const elt_t *p)
12732 tree t = p->val;
12733 return iterative_hash_expr (t, 0);
12736 inline bool
12737 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
12739 tree t1 = p1->val;
12740 tree t2 = p2->val;
12741 enum tree_code code = TREE_CODE (t1);
12743 if (TREE_CODE (t2) != code
12744 || TREE_TYPE (t1) != TREE_TYPE (t2))
12745 return false;
12747 if (!operand_equal_p (t1, t2, 0))
12748 return false;
12750 /* Only allow them to compare equal if they also hash equal; otherwise
12751 results are nondeterminate, and we fail bootstrap comparison. */
12752 gcc_checking_assert (hash (p1) == hash (p2));
12754 return true;