2015-06-11 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / gimplify.c
blob39911a142c77454e39ff29df52a9d4734611d4f6
1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2015 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 "input.h"
27 #include "alias.h"
28 #include "symtab.h"
29 #include "options.h"
30 #include "tree.h"
31 #include "fold-const.h"
32 #include "tm.h"
33 #include "hard-reg-set.h"
34 #include "function.h"
35 #include "rtl.h"
36 #include "flags.h"
37 #include "insn-config.h"
38 #include "expmed.h"
39 #include "dojump.h"
40 #include "explow.h"
41 #include "calls.h"
42 #include "emit-rtl.h"
43 #include "varasm.h"
44 #include "stmt.h"
45 #include "expr.h"
46 #include "predict.h"
47 #include "basic-block.h"
48 #include "tree-ssa-alias.h"
49 #include "internal-fn.h"
50 #include "gimple-fold.h"
51 #include "tree-eh.h"
52 #include "gimple-expr.h"
53 #include "is-a.h"
54 #include "gimple.h"
55 #include "gimplify.h"
56 #include "gimple-iterator.h"
57 #include "stringpool.h"
58 #include "stor-layout.h"
59 #include "print-tree.h"
60 #include "tree-iterator.h"
61 #include "tree-inline.h"
62 #include "tree-pretty-print.h"
63 #include "langhooks.h"
64 #include "bitmap.h"
65 #include "gimple-ssa.h"
66 #include "plugin-api.h"
67 #include "ipa-ref.h"
68 #include "cgraph.h"
69 #include "tree-cfg.h"
70 #include "tree-ssanames.h"
71 #include "tree-ssa.h"
72 #include "diagnostic-core.h"
73 #include "target.h"
74 #include "splay-tree.h"
75 #include "omp-low.h"
76 #include "gimple-low.h"
77 #include "cilk.h"
78 #include "gomp-constants.h"
79 #include "tree-dump.h"
81 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
82 #include "tree-pass.h" /* FIXME: only for PROP_gimple_any */
83 #include "builtins.h"
85 enum gimplify_omp_var_data
87 GOVD_SEEN = 1,
88 GOVD_EXPLICIT = 2,
89 GOVD_SHARED = 4,
90 GOVD_PRIVATE = 8,
91 GOVD_FIRSTPRIVATE = 16,
92 GOVD_LASTPRIVATE = 32,
93 GOVD_REDUCTION = 64,
94 GOVD_LOCAL = 128,
95 GOVD_MAP = 256,
96 GOVD_DEBUG_PRIVATE = 512,
97 GOVD_PRIVATE_OUTER_REF = 1024,
98 GOVD_LINEAR = 2048,
99 GOVD_ALIGNED = 4096,
101 /* Flag for GOVD_MAP: don't copy back. */
102 GOVD_MAP_TO_ONLY = 8192,
104 /* Flag for GOVD_LINEAR or GOVD_LASTPRIVATE: no outer reference. */
105 GOVD_LINEAR_LASTPRIVATE_NO_OUTER = 16384,
107 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
108 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
109 | GOVD_LOCAL)
113 enum omp_region_type
115 ORT_WORKSHARE = 0,
116 ORT_SIMD = 1,
117 ORT_PARALLEL = 2,
118 ORT_COMBINED_PARALLEL = 3,
119 ORT_TASK = 4,
120 ORT_UNTIED_TASK = 5,
121 ORT_TEAMS = 8,
122 ORT_COMBINED_TEAMS = 9,
123 /* Data region. */
124 ORT_TARGET_DATA = 16,
125 /* Data region with offloading. */
126 ORT_TARGET = 32
129 /* Gimplify hashtable helper. */
131 struct gimplify_hasher : typed_free_remove <elt_t>
133 typedef elt_t *value_type;
134 typedef elt_t *compare_type;
135 static inline hashval_t hash (const elt_t *);
136 static inline bool equal (const elt_t *, const elt_t *);
139 struct gimplify_ctx
141 struct gimplify_ctx *prev_context;
143 vec<gbind *> bind_expr_stack;
144 tree temps;
145 gimple_seq conditional_cleanups;
146 tree exit_label;
147 tree return_temp;
149 vec<tree> case_labels;
150 /* The formal temporary table. Should this be persistent? */
151 hash_table<gimplify_hasher> *temp_htab;
153 int conditions;
154 bool save_stack;
155 bool into_ssa;
156 bool allow_rhs_cond_expr;
157 bool in_cleanup_point_expr;
160 struct gimplify_omp_ctx
162 struct gimplify_omp_ctx *outer_context;
163 splay_tree variables;
164 hash_set<tree> *privatized_types;
165 location_t location;
166 enum omp_clause_default_kind default_kind;
167 enum omp_region_type region_type;
168 bool combined_loop;
169 bool distribute;
172 static struct gimplify_ctx *gimplify_ctxp;
173 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
175 /* Forward declaration. */
176 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
178 /* Shorter alias name for the above function for use in gimplify.c
179 only. */
181 static inline void
182 gimplify_seq_add_stmt (gimple_seq *seq_p, gimple gs)
184 gimple_seq_add_stmt_without_update (seq_p, gs);
187 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
188 NULL, a new sequence is allocated. This function is
189 similar to gimple_seq_add_seq, but does not scan the operands.
190 During gimplification, we need to manipulate statement sequences
191 before the def/use vectors have been constructed. */
193 static void
194 gimplify_seq_add_seq (gimple_seq *dst_p, gimple_seq src)
196 gimple_stmt_iterator si;
198 if (src == NULL)
199 return;
201 si = gsi_last (*dst_p);
202 gsi_insert_seq_after_without_update (&si, src, GSI_NEW_STMT);
206 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
207 and popping gimplify contexts. */
209 static struct gimplify_ctx *ctx_pool = NULL;
211 /* Return a gimplify context struct from the pool. */
213 static inline struct gimplify_ctx *
214 ctx_alloc (void)
216 struct gimplify_ctx * c = ctx_pool;
218 if (c)
219 ctx_pool = c->prev_context;
220 else
221 c = XNEW (struct gimplify_ctx);
223 memset (c, '\0', sizeof (*c));
224 return c;
227 /* Put gimplify context C back into the pool. */
229 static inline void
230 ctx_free (struct gimplify_ctx *c)
232 c->prev_context = ctx_pool;
233 ctx_pool = c;
236 /* Free allocated ctx stack memory. */
238 void
239 free_gimplify_stack (void)
241 struct gimplify_ctx *c;
243 while ((c = ctx_pool))
245 ctx_pool = c->prev_context;
246 free (c);
251 /* Set up a context for the gimplifier. */
253 void
254 push_gimplify_context (bool in_ssa, bool rhs_cond_ok)
256 struct gimplify_ctx *c = ctx_alloc ();
258 c->prev_context = gimplify_ctxp;
259 gimplify_ctxp = c;
260 gimplify_ctxp->into_ssa = in_ssa;
261 gimplify_ctxp->allow_rhs_cond_expr = rhs_cond_ok;
264 /* Tear down a context for the gimplifier. If BODY is non-null, then
265 put the temporaries into the outer BIND_EXPR. Otherwise, put them
266 in the local_decls.
268 BODY is not a sequence, but the first tuple in a sequence. */
270 void
271 pop_gimplify_context (gimple body)
273 struct gimplify_ctx *c = gimplify_ctxp;
275 gcc_assert (c
276 && (!c->bind_expr_stack.exists ()
277 || c->bind_expr_stack.is_empty ()));
278 c->bind_expr_stack.release ();
279 gimplify_ctxp = c->prev_context;
281 if (body)
282 declare_vars (c->temps, body, false);
283 else
284 record_vars (c->temps);
286 delete c->temp_htab;
287 c->temp_htab = NULL;
288 ctx_free (c);
291 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
293 static void
294 gimple_push_bind_expr (gbind *bind_stmt)
296 gimplify_ctxp->bind_expr_stack.reserve (8);
297 gimplify_ctxp->bind_expr_stack.safe_push (bind_stmt);
300 /* Pop the first element off the stack of bindings. */
302 static void
303 gimple_pop_bind_expr (void)
305 gimplify_ctxp->bind_expr_stack.pop ();
308 /* Return the first element of the stack of bindings. */
310 gbind *
311 gimple_current_bind_expr (void)
313 return gimplify_ctxp->bind_expr_stack.last ();
316 /* Return the stack of bindings created during gimplification. */
318 vec<gbind *>
319 gimple_bind_expr_stack (void)
321 return gimplify_ctxp->bind_expr_stack;
324 /* Return true iff there is a COND_EXPR between us and the innermost
325 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
327 static bool
328 gimple_conditional_context (void)
330 return gimplify_ctxp->conditions > 0;
333 /* Note that we've entered a COND_EXPR. */
335 static void
336 gimple_push_condition (void)
338 #ifdef ENABLE_GIMPLE_CHECKING
339 if (gimplify_ctxp->conditions == 0)
340 gcc_assert (gimple_seq_empty_p (gimplify_ctxp->conditional_cleanups));
341 #endif
342 ++(gimplify_ctxp->conditions);
345 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
346 now, add any conditional cleanups we've seen to the prequeue. */
348 static void
349 gimple_pop_condition (gimple_seq *pre_p)
351 int conds = --(gimplify_ctxp->conditions);
353 gcc_assert (conds >= 0);
354 if (conds == 0)
356 gimplify_seq_add_seq (pre_p, gimplify_ctxp->conditional_cleanups);
357 gimplify_ctxp->conditional_cleanups = NULL;
361 /* A stable comparison routine for use with splay trees and DECLs. */
363 static int
364 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
366 tree a = (tree) xa;
367 tree b = (tree) xb;
369 return DECL_UID (a) - DECL_UID (b);
372 /* Create a new omp construct that deals with variable remapping. */
374 static struct gimplify_omp_ctx *
375 new_omp_context (enum omp_region_type region_type)
377 struct gimplify_omp_ctx *c;
379 c = XCNEW (struct gimplify_omp_ctx);
380 c->outer_context = gimplify_omp_ctxp;
381 c->variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
382 c->privatized_types = new hash_set<tree>;
383 c->location = input_location;
384 c->region_type = region_type;
385 if ((region_type & ORT_TASK) == 0)
386 c->default_kind = OMP_CLAUSE_DEFAULT_SHARED;
387 else
388 c->default_kind = OMP_CLAUSE_DEFAULT_UNSPECIFIED;
390 return c;
393 /* Destroy an omp construct that deals with variable remapping. */
395 static void
396 delete_omp_context (struct gimplify_omp_ctx *c)
398 splay_tree_delete (c->variables);
399 delete c->privatized_types;
400 XDELETE (c);
403 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
404 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
406 /* Both gimplify the statement T and append it to *SEQ_P. This function
407 behaves exactly as gimplify_stmt, but you don't have to pass T as a
408 reference. */
410 void
411 gimplify_and_add (tree t, gimple_seq *seq_p)
413 gimplify_stmt (&t, seq_p);
416 /* Gimplify statement T into sequence *SEQ_P, and return the first
417 tuple in the sequence of generated tuples for this statement.
418 Return NULL if gimplifying T produced no tuples. */
420 static gimple
421 gimplify_and_return_first (tree t, gimple_seq *seq_p)
423 gimple_stmt_iterator last = gsi_last (*seq_p);
425 gimplify_and_add (t, seq_p);
427 if (!gsi_end_p (last))
429 gsi_next (&last);
430 return gsi_stmt (last);
432 else
433 return gimple_seq_first_stmt (*seq_p);
436 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
437 LHS, or for a call argument. */
439 static bool
440 is_gimple_mem_rhs (tree t)
442 /* If we're dealing with a renamable type, either source or dest must be
443 a renamed variable. */
444 if (is_gimple_reg_type (TREE_TYPE (t)))
445 return is_gimple_val (t);
446 else
447 return is_gimple_val (t) || is_gimple_lvalue (t);
450 /* Return true if T is a CALL_EXPR or an expression that can be
451 assigned to a temporary. Note that this predicate should only be
452 used during gimplification. See the rationale for this in
453 gimplify_modify_expr. */
455 static bool
456 is_gimple_reg_rhs_or_call (tree t)
458 return (get_gimple_rhs_class (TREE_CODE (t)) != GIMPLE_INVALID_RHS
459 || TREE_CODE (t) == CALL_EXPR);
462 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
463 this predicate should only be used during gimplification. See the
464 rationale for this in gimplify_modify_expr. */
466 static bool
467 is_gimple_mem_rhs_or_call (tree t)
469 /* If we're dealing with a renamable type, either source or dest must be
470 a renamed variable. */
471 if (is_gimple_reg_type (TREE_TYPE (t)))
472 return is_gimple_val (t);
473 else
474 return (is_gimple_val (t) || is_gimple_lvalue (t)
475 || TREE_CODE (t) == CALL_EXPR);
478 /* Create a temporary with a name derived from VAL. Subroutine of
479 lookup_tmp_var; nobody else should call this function. */
481 static inline tree
482 create_tmp_from_val (tree val)
484 /* Drop all qualifiers and address-space information from the value type. */
485 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (val));
486 tree var = create_tmp_var (type, get_name (val));
487 if (TREE_CODE (TREE_TYPE (var)) == COMPLEX_TYPE
488 || TREE_CODE (TREE_TYPE (var)) == VECTOR_TYPE)
489 DECL_GIMPLE_REG_P (var) = 1;
490 return var;
493 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
494 an existing expression temporary. */
496 static tree
497 lookup_tmp_var (tree val, bool is_formal)
499 tree ret;
501 /* If not optimizing, never really reuse a temporary. local-alloc
502 won't allocate any variable that is used in more than one basic
503 block, which means it will go into memory, causing much extra
504 work in reload and final and poorer code generation, outweighing
505 the extra memory allocation here. */
506 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
507 ret = create_tmp_from_val (val);
508 else
510 elt_t elt, *elt_p;
511 elt_t **slot;
513 elt.val = val;
514 if (!gimplify_ctxp->temp_htab)
515 gimplify_ctxp->temp_htab = new hash_table<gimplify_hasher> (1000);
516 slot = gimplify_ctxp->temp_htab->find_slot (&elt, INSERT);
517 if (*slot == NULL)
519 elt_p = XNEW (elt_t);
520 elt_p->val = val;
521 elt_p->temp = ret = create_tmp_from_val (val);
522 *slot = elt_p;
524 else
526 elt_p = *slot;
527 ret = elt_p->temp;
531 return ret;
534 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
536 static tree
537 internal_get_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
538 bool is_formal)
540 tree t, mod;
542 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
543 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
544 gimplify_expr (&val, pre_p, post_p, is_gimple_reg_rhs_or_call,
545 fb_rvalue);
547 if (gimplify_ctxp->into_ssa
548 && is_gimple_reg_type (TREE_TYPE (val)))
549 t = make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val)));
550 else
551 t = lookup_tmp_var (val, is_formal);
553 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
555 SET_EXPR_LOCATION (mod, EXPR_LOC_OR_LOC (val, input_location));
557 /* gimplify_modify_expr might want to reduce this further. */
558 gimplify_and_add (mod, pre_p);
559 ggc_free (mod);
561 return t;
564 /* Return a formal temporary variable initialized with VAL. PRE_P is as
565 in gimplify_expr. Only use this function if:
567 1) The value of the unfactored expression represented by VAL will not
568 change between the initialization and use of the temporary, and
569 2) The temporary will not be otherwise modified.
571 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
572 and #2 means it is inappropriate for && temps.
574 For other cases, use get_initialized_tmp_var instead. */
576 tree
577 get_formal_tmp_var (tree val, gimple_seq *pre_p)
579 return internal_get_tmp_var (val, pre_p, NULL, true);
582 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
583 are as in gimplify_expr. */
585 tree
586 get_initialized_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p)
588 return internal_get_tmp_var (val, pre_p, post_p, false);
591 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
592 generate debug info for them; otherwise don't. */
594 void
595 declare_vars (tree vars, gimple gs, bool debug_info)
597 tree last = vars;
598 if (last)
600 tree temps, block;
602 gbind *scope = as_a <gbind *> (gs);
604 temps = nreverse (last);
606 block = gimple_bind_block (scope);
607 gcc_assert (!block || TREE_CODE (block) == BLOCK);
608 if (!block || !debug_info)
610 DECL_CHAIN (last) = gimple_bind_vars (scope);
611 gimple_bind_set_vars (scope, temps);
613 else
615 /* We need to attach the nodes both to the BIND_EXPR and to its
616 associated BLOCK for debugging purposes. The key point here
617 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
618 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
619 if (BLOCK_VARS (block))
620 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
621 else
623 gimple_bind_set_vars (scope,
624 chainon (gimple_bind_vars (scope), temps));
625 BLOCK_VARS (block) = temps;
631 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
632 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
633 no such upper bound can be obtained. */
635 static void
636 force_constant_size (tree var)
638 /* The only attempt we make is by querying the maximum size of objects
639 of the variable's type. */
641 HOST_WIDE_INT max_size;
643 gcc_assert (TREE_CODE (var) == VAR_DECL);
645 max_size = max_int_size_in_bytes (TREE_TYPE (var));
647 gcc_assert (max_size >= 0);
649 DECL_SIZE_UNIT (var)
650 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
651 DECL_SIZE (var)
652 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
655 /* Push the temporary variable TMP into the current binding. */
657 void
658 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
660 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
662 /* Later processing assumes that the object size is constant, which might
663 not be true at this point. Force the use of a constant upper bound in
664 this case. */
665 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp)))
666 force_constant_size (tmp);
668 DECL_CONTEXT (tmp) = fn->decl;
669 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
671 record_vars_into (tmp, fn->decl);
674 /* Push the temporary variable TMP into the current binding. */
676 void
677 gimple_add_tmp_var (tree tmp)
679 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
681 /* Later processing assumes that the object size is constant, which might
682 not be true at this point. Force the use of a constant upper bound in
683 this case. */
684 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp)))
685 force_constant_size (tmp);
687 DECL_CONTEXT (tmp) = current_function_decl;
688 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
690 if (gimplify_ctxp)
692 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
693 gimplify_ctxp->temps = tmp;
695 /* Mark temporaries local within the nearest enclosing parallel. */
696 if (gimplify_omp_ctxp)
698 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
699 while (ctx
700 && (ctx->region_type == ORT_WORKSHARE
701 || ctx->region_type == ORT_SIMD))
702 ctx = ctx->outer_context;
703 if (ctx)
704 omp_add_variable (ctx, tmp, GOVD_LOCAL | GOVD_SEEN);
707 else if (cfun)
708 record_vars (tmp);
709 else
711 gimple_seq body_seq;
713 /* This case is for nested functions. We need to expose the locals
714 they create. */
715 body_seq = gimple_body (current_function_decl);
716 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
722 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
723 nodes that are referenced more than once in GENERIC functions. This is
724 necessary because gimplification (translation into GIMPLE) is performed
725 by modifying tree nodes in-place, so gimplication of a shared node in a
726 first context could generate an invalid GIMPLE form in a second context.
728 This is achieved with a simple mark/copy/unmark algorithm that walks the
729 GENERIC representation top-down, marks nodes with TREE_VISITED the first
730 time it encounters them, duplicates them if they already have TREE_VISITED
731 set, and finally removes the TREE_VISITED marks it has set.
733 The algorithm works only at the function level, i.e. it generates a GENERIC
734 representation of a function with no nodes shared within the function when
735 passed a GENERIC function (except for nodes that are allowed to be shared).
737 At the global level, it is also necessary to unshare tree nodes that are
738 referenced in more than one function, for the same aforementioned reason.
739 This requires some cooperation from the front-end. There are 2 strategies:
741 1. Manual unsharing. The front-end needs to call unshare_expr on every
742 expression that might end up being shared across functions.
744 2. Deep unsharing. This is an extension of regular unsharing. Instead
745 of calling unshare_expr on expressions that might be shared across
746 functions, the front-end pre-marks them with TREE_VISITED. This will
747 ensure that they are unshared on the first reference within functions
748 when the regular unsharing algorithm runs. The counterpart is that
749 this algorithm must look deeper than for manual unsharing, which is
750 specified by LANG_HOOKS_DEEP_UNSHARING.
752 If there are only few specific cases of node sharing across functions, it is
753 probably easier for a front-end to unshare the expressions manually. On the
754 contrary, if the expressions generated at the global level are as widespread
755 as expressions generated within functions, deep unsharing is very likely the
756 way to go. */
758 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
759 These nodes model computations that must be done once. If we were to
760 unshare something like SAVE_EXPR(i++), the gimplification process would
761 create wrong code. However, if DATA is non-null, it must hold a pointer
762 set that is used to unshare the subtrees of these nodes. */
764 static tree
765 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
767 tree t = *tp;
768 enum tree_code code = TREE_CODE (t);
770 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
771 copy their subtrees if we can make sure to do it only once. */
772 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
774 if (data && !((hash_set<tree> *)data)->add (t))
776 else
777 *walk_subtrees = 0;
780 /* Stop at types, decls, constants like copy_tree_r. */
781 else if (TREE_CODE_CLASS (code) == tcc_type
782 || TREE_CODE_CLASS (code) == tcc_declaration
783 || TREE_CODE_CLASS (code) == tcc_constant
784 /* We can't do anything sensible with a BLOCK used as an
785 expression, but we also can't just die when we see it
786 because of non-expression uses. So we avert our eyes
787 and cross our fingers. Silly Java. */
788 || code == BLOCK)
789 *walk_subtrees = 0;
791 /* Cope with the statement expression extension. */
792 else if (code == STATEMENT_LIST)
795 /* Leave the bulk of the work to copy_tree_r itself. */
796 else
797 copy_tree_r (tp, walk_subtrees, NULL);
799 return NULL_TREE;
802 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
803 If *TP has been visited already, then *TP is deeply copied by calling
804 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
806 static tree
807 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
809 tree t = *tp;
810 enum tree_code code = TREE_CODE (t);
812 /* Skip types, decls, and constants. But we do want to look at their
813 types and the bounds of types. Mark them as visited so we properly
814 unmark their subtrees on the unmark pass. If we've already seen them,
815 don't look down further. */
816 if (TREE_CODE_CLASS (code) == tcc_type
817 || TREE_CODE_CLASS (code) == tcc_declaration
818 || TREE_CODE_CLASS (code) == tcc_constant)
820 if (TREE_VISITED (t))
821 *walk_subtrees = 0;
822 else
823 TREE_VISITED (t) = 1;
826 /* If this node has been visited already, unshare it and don't look
827 any deeper. */
828 else if (TREE_VISITED (t))
830 walk_tree (tp, mostly_copy_tree_r, data, NULL);
831 *walk_subtrees = 0;
834 /* Otherwise, mark the node as visited and keep looking. */
835 else
836 TREE_VISITED (t) = 1;
838 return NULL_TREE;
841 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
842 copy_if_shared_r callback unmodified. */
844 static inline void
845 copy_if_shared (tree *tp, void *data)
847 walk_tree (tp, copy_if_shared_r, data, NULL);
850 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
851 any nested functions. */
853 static void
854 unshare_body (tree fndecl)
856 struct cgraph_node *cgn = cgraph_node::get (fndecl);
857 /* If the language requires deep unsharing, we need a pointer set to make
858 sure we don't repeatedly unshare subtrees of unshareable nodes. */
859 hash_set<tree> *visited
860 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
862 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
863 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
864 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
866 delete visited;
868 if (cgn)
869 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
870 unshare_body (cgn->decl);
873 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
874 Subtrees are walked until the first unvisited node is encountered. */
876 static tree
877 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
879 tree t = *tp;
881 /* If this node has been visited, unmark it and keep looking. */
882 if (TREE_VISITED (t))
883 TREE_VISITED (t) = 0;
885 /* Otherwise, don't look any deeper. */
886 else
887 *walk_subtrees = 0;
889 return NULL_TREE;
892 /* Unmark the visited trees rooted at *TP. */
894 static inline void
895 unmark_visited (tree *tp)
897 walk_tree (tp, unmark_visited_r, NULL, NULL);
900 /* Likewise, but mark all trees as not visited. */
902 static void
903 unvisit_body (tree fndecl)
905 struct cgraph_node *cgn = cgraph_node::get (fndecl);
907 unmark_visited (&DECL_SAVED_TREE (fndecl));
908 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
909 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
911 if (cgn)
912 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
913 unvisit_body (cgn->decl);
916 /* Unconditionally make an unshared copy of EXPR. This is used when using
917 stored expressions which span multiple functions, such as BINFO_VTABLE,
918 as the normal unsharing process can't tell that they're shared. */
920 tree
921 unshare_expr (tree expr)
923 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
924 return expr;
927 /* Worker for unshare_expr_without_location. */
929 static tree
930 prune_expr_location (tree *tp, int *walk_subtrees, void *)
932 if (EXPR_P (*tp))
933 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
934 else
935 *walk_subtrees = 0;
936 return NULL_TREE;
939 /* Similar to unshare_expr but also prune all expression locations
940 from EXPR. */
942 tree
943 unshare_expr_without_location (tree expr)
945 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
946 if (EXPR_P (expr))
947 walk_tree (&expr, prune_expr_location, NULL, NULL);
948 return expr;
951 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
952 contain statements and have a value. Assign its value to a temporary
953 and give it void_type_node. Return the temporary, or NULL_TREE if
954 WRAPPER was already void. */
956 tree
957 voidify_wrapper_expr (tree wrapper, tree temp)
959 tree type = TREE_TYPE (wrapper);
960 if (type && !VOID_TYPE_P (type))
962 tree *p;
964 /* Set p to point to the body of the wrapper. Loop until we find
965 something that isn't a wrapper. */
966 for (p = &wrapper; p && *p; )
968 switch (TREE_CODE (*p))
970 case BIND_EXPR:
971 TREE_SIDE_EFFECTS (*p) = 1;
972 TREE_TYPE (*p) = void_type_node;
973 /* For a BIND_EXPR, the body is operand 1. */
974 p = &BIND_EXPR_BODY (*p);
975 break;
977 case CLEANUP_POINT_EXPR:
978 case TRY_FINALLY_EXPR:
979 case TRY_CATCH_EXPR:
980 TREE_SIDE_EFFECTS (*p) = 1;
981 TREE_TYPE (*p) = void_type_node;
982 p = &TREE_OPERAND (*p, 0);
983 break;
985 case STATEMENT_LIST:
987 tree_stmt_iterator i = tsi_last (*p);
988 TREE_SIDE_EFFECTS (*p) = 1;
989 TREE_TYPE (*p) = void_type_node;
990 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
992 break;
994 case COMPOUND_EXPR:
995 /* Advance to the last statement. Set all container types to
996 void. */
997 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
999 TREE_SIDE_EFFECTS (*p) = 1;
1000 TREE_TYPE (*p) = void_type_node;
1002 break;
1004 case TRANSACTION_EXPR:
1005 TREE_SIDE_EFFECTS (*p) = 1;
1006 TREE_TYPE (*p) = void_type_node;
1007 p = &TRANSACTION_EXPR_BODY (*p);
1008 break;
1010 default:
1011 /* Assume that any tree upon which voidify_wrapper_expr is
1012 directly called is a wrapper, and that its body is op0. */
1013 if (p == &wrapper)
1015 TREE_SIDE_EFFECTS (*p) = 1;
1016 TREE_TYPE (*p) = void_type_node;
1017 p = &TREE_OPERAND (*p, 0);
1018 break;
1020 goto out;
1024 out:
1025 if (p == NULL || IS_EMPTY_STMT (*p))
1026 temp = NULL_TREE;
1027 else if (temp)
1029 /* The wrapper is on the RHS of an assignment that we're pushing
1030 down. */
1031 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1032 || TREE_CODE (temp) == MODIFY_EXPR);
1033 TREE_OPERAND (temp, 1) = *p;
1034 *p = temp;
1036 else
1038 temp = create_tmp_var (type, "retval");
1039 *p = build2 (INIT_EXPR, type, temp, *p);
1042 return temp;
1045 return NULL_TREE;
1048 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1049 a temporary through which they communicate. */
1051 static void
1052 build_stack_save_restore (gcall **save, gcall **restore)
1054 tree tmp_var;
1056 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1057 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1058 gimple_call_set_lhs (*save, tmp_var);
1060 *restore
1061 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1062 1, tmp_var);
1065 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1067 static enum gimplify_status
1068 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1070 tree bind_expr = *expr_p;
1071 bool old_save_stack = gimplify_ctxp->save_stack;
1072 tree t;
1073 gbind *bind_stmt;
1074 gimple_seq body, cleanup;
1075 gcall *stack_save;
1076 location_t start_locus = 0, end_locus = 0;
1078 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1080 /* Mark variables seen in this bind expr. */
1081 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1083 if (TREE_CODE (t) == VAR_DECL)
1085 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1087 /* Mark variable as local. */
1088 if (ctx && !DECL_EXTERNAL (t)
1089 && (! DECL_SEEN_IN_BIND_EXPR_P (t)
1090 || splay_tree_lookup (ctx->variables,
1091 (splay_tree_key) t) == NULL))
1093 if (ctx->region_type == ORT_SIMD
1094 && TREE_ADDRESSABLE (t)
1095 && !TREE_STATIC (t))
1096 omp_add_variable (ctx, t, GOVD_PRIVATE | GOVD_SEEN);
1097 else
1098 omp_add_variable (ctx, t, GOVD_LOCAL | GOVD_SEEN);
1101 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1103 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1104 cfun->has_local_explicit_reg_vars = true;
1107 /* Preliminarily mark non-addressed complex variables as eligible
1108 for promotion to gimple registers. We'll transform their uses
1109 as we find them. */
1110 if ((TREE_CODE (TREE_TYPE (t)) == COMPLEX_TYPE
1111 || TREE_CODE (TREE_TYPE (t)) == VECTOR_TYPE)
1112 && !TREE_THIS_VOLATILE (t)
1113 && (TREE_CODE (t) == VAR_DECL && !DECL_HARD_REGISTER (t))
1114 && !needs_to_live_in_memory (t))
1115 DECL_GIMPLE_REG_P (t) = 1;
1118 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1119 BIND_EXPR_BLOCK (bind_expr));
1120 gimple_push_bind_expr (bind_stmt);
1122 gimplify_ctxp->save_stack = false;
1124 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1125 body = NULL;
1126 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1127 gimple_bind_set_body (bind_stmt, body);
1129 /* Source location wise, the cleanup code (stack_restore and clobbers)
1130 belongs to the end of the block, so propagate what we have. The
1131 stack_save operation belongs to the beginning of block, which we can
1132 infer from the bind_expr directly if the block has no explicit
1133 assignment. */
1134 if (BIND_EXPR_BLOCK (bind_expr))
1136 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1137 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1139 if (start_locus == 0)
1140 start_locus = EXPR_LOCATION (bind_expr);
1142 cleanup = NULL;
1143 stack_save = NULL;
1144 if (gimplify_ctxp->save_stack)
1146 gcall *stack_restore;
1148 /* Save stack on entry and restore it on exit. Add a try_finally
1149 block to achieve this. */
1150 build_stack_save_restore (&stack_save, &stack_restore);
1152 gimple_set_location (stack_save, start_locus);
1153 gimple_set_location (stack_restore, end_locus);
1155 gimplify_seq_add_stmt (&cleanup, stack_restore);
1158 /* Add clobbers for all variables that go out of scope. */
1159 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1161 if (TREE_CODE (t) == VAR_DECL
1162 && !is_global_var (t)
1163 && DECL_CONTEXT (t) == current_function_decl
1164 && !DECL_HARD_REGISTER (t)
1165 && !TREE_THIS_VOLATILE (t)
1166 && !DECL_HAS_VALUE_EXPR_P (t)
1167 /* Only care for variables that have to be in memory. Others
1168 will be rewritten into SSA names, hence moved to the top-level. */
1169 && !is_gimple_reg (t)
1170 && flag_stack_reuse != SR_NONE)
1172 tree clobber = build_constructor (TREE_TYPE (t), NULL);
1173 gimple clobber_stmt;
1174 TREE_THIS_VOLATILE (clobber) = 1;
1175 clobber_stmt = gimple_build_assign (t, clobber);
1176 gimple_set_location (clobber_stmt, end_locus);
1177 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1181 if (cleanup)
1183 gtry *gs;
1184 gimple_seq new_body;
1186 new_body = NULL;
1187 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1188 GIMPLE_TRY_FINALLY);
1190 if (stack_save)
1191 gimplify_seq_add_stmt (&new_body, stack_save);
1192 gimplify_seq_add_stmt (&new_body, gs);
1193 gimple_bind_set_body (bind_stmt, new_body);
1196 gimplify_ctxp->save_stack = old_save_stack;
1197 gimple_pop_bind_expr ();
1199 gimplify_seq_add_stmt (pre_p, bind_stmt);
1201 if (temp)
1203 *expr_p = temp;
1204 return GS_OK;
1207 *expr_p = NULL_TREE;
1208 return GS_ALL_DONE;
1211 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1212 GIMPLE value, it is assigned to a new temporary and the statement is
1213 re-written to return the temporary.
1215 PRE_P points to the sequence where side effects that must happen before
1216 STMT should be stored. */
1218 static enum gimplify_status
1219 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1221 greturn *ret;
1222 tree ret_expr = TREE_OPERAND (stmt, 0);
1223 tree result_decl, result;
1225 if (ret_expr == error_mark_node)
1226 return GS_ERROR;
1228 /* Implicit _Cilk_sync must be inserted right before any return statement
1229 if there is a _Cilk_spawn in the function. If the user has provided a
1230 _Cilk_sync, the optimizer should remove this duplicate one. */
1231 if (fn_contains_cilk_spawn_p (cfun))
1233 tree impl_sync = build0 (CILK_SYNC_STMT, void_type_node);
1234 gimplify_and_add (impl_sync, pre_p);
1237 if (!ret_expr
1238 || TREE_CODE (ret_expr) == RESULT_DECL
1239 || ret_expr == error_mark_node)
1241 greturn *ret = gimple_build_return (ret_expr);
1242 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1243 gimplify_seq_add_stmt (pre_p, ret);
1244 return GS_ALL_DONE;
1247 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1248 result_decl = NULL_TREE;
1249 else
1251 result_decl = TREE_OPERAND (ret_expr, 0);
1253 /* See through a return by reference. */
1254 if (TREE_CODE (result_decl) == INDIRECT_REF)
1255 result_decl = TREE_OPERAND (result_decl, 0);
1257 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1258 || TREE_CODE (ret_expr) == INIT_EXPR)
1259 && TREE_CODE (result_decl) == RESULT_DECL);
1262 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1263 Recall that aggregate_value_p is FALSE for any aggregate type that is
1264 returned in registers. If we're returning values in registers, then
1265 we don't want to extend the lifetime of the RESULT_DECL, particularly
1266 across another call. In addition, for those aggregates for which
1267 hard_function_value generates a PARALLEL, we'll die during normal
1268 expansion of structure assignments; there's special code in expand_return
1269 to handle this case that does not exist in expand_expr. */
1270 if (!result_decl)
1271 result = NULL_TREE;
1272 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1274 if (TREE_CODE (DECL_SIZE (result_decl)) != INTEGER_CST)
1276 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1277 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1278 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1279 should be effectively allocated by the caller, i.e. all calls to
1280 this function must be subject to the Return Slot Optimization. */
1281 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1282 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1284 result = result_decl;
1286 else if (gimplify_ctxp->return_temp)
1287 result = gimplify_ctxp->return_temp;
1288 else
1290 result = create_tmp_reg (TREE_TYPE (result_decl));
1292 /* ??? With complex control flow (usually involving abnormal edges),
1293 we can wind up warning about an uninitialized value for this. Due
1294 to how this variable is constructed and initialized, this is never
1295 true. Give up and never warn. */
1296 TREE_NO_WARNING (result) = 1;
1298 gimplify_ctxp->return_temp = result;
1301 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1302 Then gimplify the whole thing. */
1303 if (result != result_decl)
1304 TREE_OPERAND (ret_expr, 0) = result;
1306 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1308 ret = gimple_build_return (result);
1309 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1310 gimplify_seq_add_stmt (pre_p, ret);
1312 return GS_ALL_DONE;
1315 /* Gimplify a variable-length array DECL. */
1317 static void
1318 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1320 /* This is a variable-sized decl. Simplify its size and mark it
1321 for deferred expansion. */
1322 tree t, addr, ptr_type;
1324 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1325 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1327 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1328 if (DECL_HAS_VALUE_EXPR_P (decl))
1329 return;
1331 /* All occurrences of this decl in final gimplified code will be
1332 replaced by indirection. Setting DECL_VALUE_EXPR does two
1333 things: First, it lets the rest of the gimplifier know what
1334 replacement to use. Second, it lets the debug info know
1335 where to find the value. */
1336 ptr_type = build_pointer_type (TREE_TYPE (decl));
1337 addr = create_tmp_var (ptr_type, get_name (decl));
1338 DECL_IGNORED_P (addr) = 0;
1339 t = build_fold_indirect_ref (addr);
1340 TREE_THIS_NOTRAP (t) = 1;
1341 SET_DECL_VALUE_EXPR (decl, t);
1342 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1344 t = builtin_decl_explicit (BUILT_IN_ALLOCA_WITH_ALIGN);
1345 t = build_call_expr (t, 2, DECL_SIZE_UNIT (decl),
1346 size_int (DECL_ALIGN (decl)));
1347 /* The call has been built for a variable-sized object. */
1348 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1349 t = fold_convert (ptr_type, t);
1350 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1352 gimplify_and_add (t, seq_p);
1354 /* Indicate that we need to restore the stack level when the
1355 enclosing BIND_EXPR is exited. */
1356 gimplify_ctxp->save_stack = true;
1359 /* A helper function to be called via walk_tree. Mark all labels under *TP
1360 as being forced. To be called for DECL_INITIAL of static variables. */
1362 static tree
1363 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1365 if (TYPE_P (*tp))
1366 *walk_subtrees = 0;
1367 if (TREE_CODE (*tp) == LABEL_DECL)
1368 FORCED_LABEL (*tp) = 1;
1370 return NULL_TREE;
1373 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1374 and initialization explicit. */
1376 static enum gimplify_status
1377 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1379 tree stmt = *stmt_p;
1380 tree decl = DECL_EXPR_DECL (stmt);
1382 *stmt_p = NULL_TREE;
1384 if (TREE_TYPE (decl) == error_mark_node)
1385 return GS_ERROR;
1387 if ((TREE_CODE (decl) == TYPE_DECL
1388 || TREE_CODE (decl) == VAR_DECL)
1389 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1390 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1392 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1393 in case its size expressions contain problematic nodes like CALL_EXPR. */
1394 if (TREE_CODE (decl) == TYPE_DECL
1395 && DECL_ORIGINAL_TYPE (decl)
1396 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1397 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1399 if (TREE_CODE (decl) == VAR_DECL && !DECL_EXTERNAL (decl))
1401 tree init = DECL_INITIAL (decl);
1403 if (TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
1404 || (!TREE_STATIC (decl)
1405 && flag_stack_check == GENERIC_STACK_CHECK
1406 && compare_tree_int (DECL_SIZE_UNIT (decl),
1407 STACK_CHECK_MAX_VAR_SIZE) > 0))
1408 gimplify_vla_decl (decl, seq_p);
1410 /* Some front ends do not explicitly declare all anonymous
1411 artificial variables. We compensate here by declaring the
1412 variables, though it would be better if the front ends would
1413 explicitly declare them. */
1414 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1415 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1416 gimple_add_tmp_var (decl);
1418 if (init && init != error_mark_node)
1420 if (!TREE_STATIC (decl))
1422 DECL_INITIAL (decl) = NULL_TREE;
1423 init = build2 (INIT_EXPR, void_type_node, decl, init);
1424 gimplify_and_add (init, seq_p);
1425 ggc_free (init);
1427 else
1428 /* We must still examine initializers for static variables
1429 as they may contain a label address. */
1430 walk_tree (&init, force_labels_r, NULL, NULL);
1434 return GS_ALL_DONE;
1437 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1438 and replacing the LOOP_EXPR with goto, but if the loop contains an
1439 EXIT_EXPR, we need to append a label for it to jump to. */
1441 static enum gimplify_status
1442 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1444 tree saved_label = gimplify_ctxp->exit_label;
1445 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1447 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1449 gimplify_ctxp->exit_label = NULL_TREE;
1451 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1453 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
1455 if (gimplify_ctxp->exit_label)
1456 gimplify_seq_add_stmt (pre_p,
1457 gimple_build_label (gimplify_ctxp->exit_label));
1459 gimplify_ctxp->exit_label = saved_label;
1461 *expr_p = NULL;
1462 return GS_ALL_DONE;
1465 /* Gimplify a statement list onto a sequence. These may be created either
1466 by an enlightened front-end, or by shortcut_cond_expr. */
1468 static enum gimplify_status
1469 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
1471 tree temp = voidify_wrapper_expr (*expr_p, NULL);
1473 tree_stmt_iterator i = tsi_start (*expr_p);
1475 while (!tsi_end_p (i))
1477 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
1478 tsi_delink (&i);
1481 if (temp)
1483 *expr_p = temp;
1484 return GS_OK;
1487 return GS_ALL_DONE;
1491 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
1492 branch to. */
1494 static enum gimplify_status
1495 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
1497 tree switch_expr = *expr_p;
1498 gimple_seq switch_body_seq = NULL;
1499 enum gimplify_status ret;
1500 tree index_type = TREE_TYPE (switch_expr);
1501 if (index_type == NULL_TREE)
1502 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
1504 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
1505 fb_rvalue);
1506 if (ret == GS_ERROR || ret == GS_UNHANDLED)
1507 return ret;
1509 if (SWITCH_BODY (switch_expr))
1511 vec<tree> labels;
1512 vec<tree> saved_labels;
1513 tree default_case = NULL_TREE;
1514 gswitch *switch_stmt;
1516 /* If someone can be bothered to fill in the labels, they can
1517 be bothered to null out the body too. */
1518 gcc_assert (!SWITCH_LABELS (switch_expr));
1520 /* Save old labels, get new ones from body, then restore the old
1521 labels. Save all the things from the switch body to append after. */
1522 saved_labels = gimplify_ctxp->case_labels;
1523 gimplify_ctxp->case_labels.create (8);
1525 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
1526 labels = gimplify_ctxp->case_labels;
1527 gimplify_ctxp->case_labels = saved_labels;
1529 preprocess_case_label_vec_for_gimple (labels, index_type,
1530 &default_case);
1532 if (!default_case)
1534 glabel *new_default;
1536 default_case
1537 = build_case_label (NULL_TREE, NULL_TREE,
1538 create_artificial_label (UNKNOWN_LOCATION));
1539 new_default = gimple_build_label (CASE_LABEL (default_case));
1540 gimplify_seq_add_stmt (&switch_body_seq, new_default);
1543 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
1544 default_case, labels);
1545 gimplify_seq_add_stmt (pre_p, switch_stmt);
1546 gimplify_seq_add_seq (pre_p, switch_body_seq);
1547 labels.release ();
1549 else
1550 gcc_assert (SWITCH_LABELS (switch_expr));
1552 return GS_ALL_DONE;
1555 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
1557 static enum gimplify_status
1558 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
1560 struct gimplify_ctx *ctxp;
1561 glabel *label_stmt;
1563 /* Invalid programs can play Duff's Device type games with, for example,
1564 #pragma omp parallel. At least in the C front end, we don't
1565 detect such invalid branches until after gimplification, in the
1566 diagnose_omp_blocks pass. */
1567 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
1568 if (ctxp->case_labels.exists ())
1569 break;
1571 label_stmt = gimple_build_label (CASE_LABEL (*expr_p));
1572 ctxp->case_labels.safe_push (*expr_p);
1573 gimplify_seq_add_stmt (pre_p, label_stmt);
1575 return GS_ALL_DONE;
1578 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
1579 if necessary. */
1581 tree
1582 build_and_jump (tree *label_p)
1584 if (label_p == NULL)
1585 /* If there's nowhere to jump, just fall through. */
1586 return NULL_TREE;
1588 if (*label_p == NULL_TREE)
1590 tree label = create_artificial_label (UNKNOWN_LOCATION);
1591 *label_p = label;
1594 return build1 (GOTO_EXPR, void_type_node, *label_p);
1597 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
1598 This also involves building a label to jump to and communicating it to
1599 gimplify_loop_expr through gimplify_ctxp->exit_label. */
1601 static enum gimplify_status
1602 gimplify_exit_expr (tree *expr_p)
1604 tree cond = TREE_OPERAND (*expr_p, 0);
1605 tree expr;
1607 expr = build_and_jump (&gimplify_ctxp->exit_label);
1608 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
1609 *expr_p = expr;
1611 return GS_OK;
1614 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
1615 different from its canonical type, wrap the whole thing inside a
1616 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
1617 type.
1619 The canonical type of a COMPONENT_REF is the type of the field being
1620 referenced--unless the field is a bit-field which can be read directly
1621 in a smaller mode, in which case the canonical type is the
1622 sign-appropriate type corresponding to that mode. */
1624 static void
1625 canonicalize_component_ref (tree *expr_p)
1627 tree expr = *expr_p;
1628 tree type;
1630 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
1632 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
1633 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
1634 else
1635 type = TREE_TYPE (TREE_OPERAND (expr, 1));
1637 /* One could argue that all the stuff below is not necessary for
1638 the non-bitfield case and declare it a FE error if type
1639 adjustment would be needed. */
1640 if (TREE_TYPE (expr) != type)
1642 #ifdef ENABLE_TYPES_CHECKING
1643 tree old_type = TREE_TYPE (expr);
1644 #endif
1645 int type_quals;
1647 /* We need to preserve qualifiers and propagate them from
1648 operand 0. */
1649 type_quals = TYPE_QUALS (type)
1650 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
1651 if (TYPE_QUALS (type) != type_quals)
1652 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
1654 /* Set the type of the COMPONENT_REF to the underlying type. */
1655 TREE_TYPE (expr) = type;
1657 #ifdef ENABLE_TYPES_CHECKING
1658 /* It is now a FE error, if the conversion from the canonical
1659 type to the original expression type is not useless. */
1660 gcc_assert (useless_type_conversion_p (old_type, type));
1661 #endif
1665 /* If a NOP conversion is changing a pointer to array of foo to a pointer
1666 to foo, embed that change in the ADDR_EXPR by converting
1667 T array[U];
1668 (T *)&array
1670 &array[L]
1671 where L is the lower bound. For simplicity, only do this for constant
1672 lower bound.
1673 The constraint is that the type of &array[L] is trivially convertible
1674 to T *. */
1676 static void
1677 canonicalize_addr_expr (tree *expr_p)
1679 tree expr = *expr_p;
1680 tree addr_expr = TREE_OPERAND (expr, 0);
1681 tree datype, ddatype, pddatype;
1683 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
1684 if (!POINTER_TYPE_P (TREE_TYPE (expr))
1685 || TREE_CODE (addr_expr) != ADDR_EXPR)
1686 return;
1688 /* The addr_expr type should be a pointer to an array. */
1689 datype = TREE_TYPE (TREE_TYPE (addr_expr));
1690 if (TREE_CODE (datype) != ARRAY_TYPE)
1691 return;
1693 /* The pointer to element type shall be trivially convertible to
1694 the expression pointer type. */
1695 ddatype = TREE_TYPE (datype);
1696 pddatype = build_pointer_type (ddatype);
1697 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
1698 pddatype))
1699 return;
1701 /* The lower bound and element sizes must be constant. */
1702 if (!TYPE_SIZE_UNIT (ddatype)
1703 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
1704 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
1705 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
1706 return;
1708 /* All checks succeeded. Build a new node to merge the cast. */
1709 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
1710 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
1711 NULL_TREE, NULL_TREE);
1712 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
1714 /* We can have stripped a required restrict qualifier above. */
1715 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
1716 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
1719 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
1720 underneath as appropriate. */
1722 static enum gimplify_status
1723 gimplify_conversion (tree *expr_p)
1725 location_t loc = EXPR_LOCATION (*expr_p);
1726 gcc_assert (CONVERT_EXPR_P (*expr_p));
1728 /* Then strip away all but the outermost conversion. */
1729 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
1731 /* And remove the outermost conversion if it's useless. */
1732 if (tree_ssa_useless_type_conversion (*expr_p))
1733 *expr_p = TREE_OPERAND (*expr_p, 0);
1735 /* If we still have a conversion at the toplevel,
1736 then canonicalize some constructs. */
1737 if (CONVERT_EXPR_P (*expr_p))
1739 tree sub = TREE_OPERAND (*expr_p, 0);
1741 /* If a NOP conversion is changing the type of a COMPONENT_REF
1742 expression, then canonicalize its type now in order to expose more
1743 redundant conversions. */
1744 if (TREE_CODE (sub) == COMPONENT_REF)
1745 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
1747 /* If a NOP conversion is changing a pointer to array of foo
1748 to a pointer to foo, embed that change in the ADDR_EXPR. */
1749 else if (TREE_CODE (sub) == ADDR_EXPR)
1750 canonicalize_addr_expr (expr_p);
1753 /* If we have a conversion to a non-register type force the
1754 use of a VIEW_CONVERT_EXPR instead. */
1755 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
1756 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
1757 TREE_OPERAND (*expr_p, 0));
1759 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
1760 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
1761 TREE_SET_CODE (*expr_p, NOP_EXPR);
1763 return GS_OK;
1766 /* Nonlocal VLAs seen in the current function. */
1767 static hash_set<tree> *nonlocal_vlas;
1769 /* The VAR_DECLs created for nonlocal VLAs for debug info purposes. */
1770 static tree nonlocal_vla_vars;
1772 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
1773 DECL_VALUE_EXPR, and it's worth re-examining things. */
1775 static enum gimplify_status
1776 gimplify_var_or_parm_decl (tree *expr_p)
1778 tree decl = *expr_p;
1780 /* ??? If this is a local variable, and it has not been seen in any
1781 outer BIND_EXPR, then it's probably the result of a duplicate
1782 declaration, for which we've already issued an error. It would
1783 be really nice if the front end wouldn't leak these at all.
1784 Currently the only known culprit is C++ destructors, as seen
1785 in g++.old-deja/g++.jason/binding.C. */
1786 if (TREE_CODE (decl) == VAR_DECL
1787 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
1788 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
1789 && decl_function_context (decl) == current_function_decl)
1791 gcc_assert (seen_error ());
1792 return GS_ERROR;
1795 /* When within an OMP context, notice uses of variables. */
1796 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
1797 return GS_ALL_DONE;
1799 /* If the decl is an alias for another expression, substitute it now. */
1800 if (DECL_HAS_VALUE_EXPR_P (decl))
1802 tree value_expr = DECL_VALUE_EXPR (decl);
1804 /* For referenced nonlocal VLAs add a decl for debugging purposes
1805 to the current function. */
1806 if (TREE_CODE (decl) == VAR_DECL
1807 && TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
1808 && nonlocal_vlas != NULL
1809 && TREE_CODE (value_expr) == INDIRECT_REF
1810 && TREE_CODE (TREE_OPERAND (value_expr, 0)) == VAR_DECL
1811 && decl_function_context (decl) != current_function_decl)
1813 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1814 while (ctx
1815 && (ctx->region_type == ORT_WORKSHARE
1816 || ctx->region_type == ORT_SIMD))
1817 ctx = ctx->outer_context;
1818 if (!ctx && !nonlocal_vlas->add (decl))
1820 tree copy = copy_node (decl);
1822 lang_hooks.dup_lang_specific_decl (copy);
1823 SET_DECL_RTL (copy, 0);
1824 TREE_USED (copy) = 1;
1825 DECL_CHAIN (copy) = nonlocal_vla_vars;
1826 nonlocal_vla_vars = copy;
1827 SET_DECL_VALUE_EXPR (copy, unshare_expr (value_expr));
1828 DECL_HAS_VALUE_EXPR_P (copy) = 1;
1832 *expr_p = unshare_expr (value_expr);
1833 return GS_OK;
1836 return GS_ALL_DONE;
1839 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
1841 static void
1842 recalculate_side_effects (tree t)
1844 enum tree_code code = TREE_CODE (t);
1845 int len = TREE_OPERAND_LENGTH (t);
1846 int i;
1848 switch (TREE_CODE_CLASS (code))
1850 case tcc_expression:
1851 switch (code)
1853 case INIT_EXPR:
1854 case MODIFY_EXPR:
1855 case VA_ARG_EXPR:
1856 case PREDECREMENT_EXPR:
1857 case PREINCREMENT_EXPR:
1858 case POSTDECREMENT_EXPR:
1859 case POSTINCREMENT_EXPR:
1860 /* All of these have side-effects, no matter what their
1861 operands are. */
1862 return;
1864 default:
1865 break;
1867 /* Fall through. */
1869 case tcc_comparison: /* a comparison expression */
1870 case tcc_unary: /* a unary arithmetic expression */
1871 case tcc_binary: /* a binary arithmetic expression */
1872 case tcc_reference: /* a reference */
1873 case tcc_vl_exp: /* a function call */
1874 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
1875 for (i = 0; i < len; ++i)
1877 tree op = TREE_OPERAND (t, i);
1878 if (op && TREE_SIDE_EFFECTS (op))
1879 TREE_SIDE_EFFECTS (t) = 1;
1881 break;
1883 case tcc_constant:
1884 /* No side-effects. */
1885 return;
1887 default:
1888 gcc_unreachable ();
1892 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
1893 node *EXPR_P.
1895 compound_lval
1896 : min_lval '[' val ']'
1897 | min_lval '.' ID
1898 | compound_lval '[' val ']'
1899 | compound_lval '.' ID
1901 This is not part of the original SIMPLE definition, which separates
1902 array and member references, but it seems reasonable to handle them
1903 together. Also, this way we don't run into problems with union
1904 aliasing; gcc requires that for accesses through a union to alias, the
1905 union reference must be explicit, which was not always the case when we
1906 were splitting up array and member refs.
1908 PRE_P points to the sequence where side effects that must happen before
1909 *EXPR_P should be stored.
1911 POST_P points to the sequence where side effects that must happen after
1912 *EXPR_P should be stored. */
1914 static enum gimplify_status
1915 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
1916 fallback_t fallback)
1918 tree *p;
1919 enum gimplify_status ret = GS_ALL_DONE, tret;
1920 int i;
1921 location_t loc = EXPR_LOCATION (*expr_p);
1922 tree expr = *expr_p;
1924 /* Create a stack of the subexpressions so later we can walk them in
1925 order from inner to outer. */
1926 auto_vec<tree, 10> expr_stack;
1928 /* We can handle anything that get_inner_reference can deal with. */
1929 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
1931 restart:
1932 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
1933 if (TREE_CODE (*p) == INDIRECT_REF)
1934 *p = fold_indirect_ref_loc (loc, *p);
1936 if (handled_component_p (*p))
1938 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
1939 additional COMPONENT_REFs. */
1940 else if ((TREE_CODE (*p) == VAR_DECL || TREE_CODE (*p) == PARM_DECL)
1941 && gimplify_var_or_parm_decl (p) == GS_OK)
1942 goto restart;
1943 else
1944 break;
1946 expr_stack.safe_push (*p);
1949 gcc_assert (expr_stack.length ());
1951 /* Now EXPR_STACK is a stack of pointers to all the refs we've
1952 walked through and P points to the innermost expression.
1954 Java requires that we elaborated nodes in source order. That
1955 means we must gimplify the inner expression followed by each of
1956 the indices, in order. But we can't gimplify the inner
1957 expression until we deal with any variable bounds, sizes, or
1958 positions in order to deal with PLACEHOLDER_EXPRs.
1960 So we do this in three steps. First we deal with the annotations
1961 for any variables in the components, then we gimplify the base,
1962 then we gimplify any indices, from left to right. */
1963 for (i = expr_stack.length () - 1; i >= 0; i--)
1965 tree t = expr_stack[i];
1967 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
1969 /* Gimplify the low bound and element type size and put them into
1970 the ARRAY_REF. If these values are set, they have already been
1971 gimplified. */
1972 if (TREE_OPERAND (t, 2) == NULL_TREE)
1974 tree low = unshare_expr (array_ref_low_bound (t));
1975 if (!is_gimple_min_invariant (low))
1977 TREE_OPERAND (t, 2) = low;
1978 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
1979 post_p, is_gimple_reg,
1980 fb_rvalue);
1981 ret = MIN (ret, tret);
1984 else
1986 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1987 is_gimple_reg, fb_rvalue);
1988 ret = MIN (ret, tret);
1991 if (TREE_OPERAND (t, 3) == NULL_TREE)
1993 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
1994 tree elmt_size = unshare_expr (array_ref_element_size (t));
1995 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
1997 /* Divide the element size by the alignment of the element
1998 type (above). */
1999 elmt_size
2000 = size_binop_loc (loc, EXACT_DIV_EXPR, elmt_size, factor);
2002 if (!is_gimple_min_invariant (elmt_size))
2004 TREE_OPERAND (t, 3) = elmt_size;
2005 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
2006 post_p, is_gimple_reg,
2007 fb_rvalue);
2008 ret = MIN (ret, tret);
2011 else
2013 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
2014 is_gimple_reg, fb_rvalue);
2015 ret = MIN (ret, tret);
2018 else if (TREE_CODE (t) == COMPONENT_REF)
2020 /* Set the field offset into T and gimplify it. */
2021 if (TREE_OPERAND (t, 2) == NULL_TREE)
2023 tree offset = unshare_expr (component_ref_field_offset (t));
2024 tree field = TREE_OPERAND (t, 1);
2025 tree factor
2026 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
2028 /* Divide the offset by its alignment. */
2029 offset = size_binop_loc (loc, EXACT_DIV_EXPR, offset, factor);
2031 if (!is_gimple_min_invariant (offset))
2033 TREE_OPERAND (t, 2) = offset;
2034 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
2035 post_p, is_gimple_reg,
2036 fb_rvalue);
2037 ret = MIN (ret, tret);
2040 else
2042 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
2043 is_gimple_reg, fb_rvalue);
2044 ret = MIN (ret, tret);
2049 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
2050 so as to match the min_lval predicate. Failure to do so may result
2051 in the creation of large aggregate temporaries. */
2052 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
2053 fallback | fb_lvalue);
2054 ret = MIN (ret, tret);
2056 /* And finally, the indices and operands of ARRAY_REF. During this
2057 loop we also remove any useless conversions. */
2058 for (; expr_stack.length () > 0; )
2060 tree t = expr_stack.pop ();
2062 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
2064 /* Gimplify the dimension. */
2065 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
2067 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
2068 is_gimple_val, fb_rvalue);
2069 ret = MIN (ret, tret);
2073 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
2075 /* The innermost expression P may have originally had
2076 TREE_SIDE_EFFECTS set which would have caused all the outer
2077 expressions in *EXPR_P leading to P to also have had
2078 TREE_SIDE_EFFECTS set. */
2079 recalculate_side_effects (t);
2082 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
2083 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
2085 canonicalize_component_ref (expr_p);
2088 expr_stack.release ();
2090 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
2092 return ret;
2095 /* Gimplify the self modifying expression pointed to by EXPR_P
2096 (++, --, +=, -=).
2098 PRE_P points to the list where side effects that must happen before
2099 *EXPR_P should be stored.
2101 POST_P points to the list where side effects that must happen after
2102 *EXPR_P should be stored.
2104 WANT_VALUE is nonzero iff we want to use the value of this expression
2105 in another expression.
2107 ARITH_TYPE is the type the computation should be performed in. */
2109 enum gimplify_status
2110 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
2111 bool want_value, tree arith_type)
2113 enum tree_code code;
2114 tree lhs, lvalue, rhs, t1;
2115 gimple_seq post = NULL, *orig_post_p = post_p;
2116 bool postfix;
2117 enum tree_code arith_code;
2118 enum gimplify_status ret;
2119 location_t loc = EXPR_LOCATION (*expr_p);
2121 code = TREE_CODE (*expr_p);
2123 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
2124 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
2126 /* Prefix or postfix? */
2127 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
2128 /* Faster to treat as prefix if result is not used. */
2129 postfix = want_value;
2130 else
2131 postfix = false;
2133 /* For postfix, make sure the inner expression's post side effects
2134 are executed after side effects from this expression. */
2135 if (postfix)
2136 post_p = &post;
2138 /* Add or subtract? */
2139 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
2140 arith_code = PLUS_EXPR;
2141 else
2142 arith_code = MINUS_EXPR;
2144 /* Gimplify the LHS into a GIMPLE lvalue. */
2145 lvalue = TREE_OPERAND (*expr_p, 0);
2146 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
2147 if (ret == GS_ERROR)
2148 return ret;
2150 /* Extract the operands to the arithmetic operation. */
2151 lhs = lvalue;
2152 rhs = TREE_OPERAND (*expr_p, 1);
2154 /* For postfix operator, we evaluate the LHS to an rvalue and then use
2155 that as the result value and in the postqueue operation. */
2156 if (postfix)
2158 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
2159 if (ret == GS_ERROR)
2160 return ret;
2162 lhs = get_initialized_tmp_var (lhs, pre_p, NULL);
2165 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
2166 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
2168 rhs = convert_to_ptrofftype_loc (loc, rhs);
2169 if (arith_code == MINUS_EXPR)
2170 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
2171 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
2173 else
2174 t1 = fold_convert (TREE_TYPE (*expr_p),
2175 fold_build2 (arith_code, arith_type,
2176 fold_convert (arith_type, lhs),
2177 fold_convert (arith_type, rhs)));
2179 if (postfix)
2181 gimplify_assign (lvalue, t1, pre_p);
2182 gimplify_seq_add_seq (orig_post_p, post);
2183 *expr_p = lhs;
2184 return GS_ALL_DONE;
2186 else
2188 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
2189 return GS_OK;
2193 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
2195 static void
2196 maybe_with_size_expr (tree *expr_p)
2198 tree expr = *expr_p;
2199 tree type = TREE_TYPE (expr);
2200 tree size;
2202 /* If we've already wrapped this or the type is error_mark_node, we can't do
2203 anything. */
2204 if (TREE_CODE (expr) == WITH_SIZE_EXPR
2205 || type == error_mark_node)
2206 return;
2208 /* If the size isn't known or is a constant, we have nothing to do. */
2209 size = TYPE_SIZE_UNIT (type);
2210 if (!size || TREE_CODE (size) == INTEGER_CST)
2211 return;
2213 /* Otherwise, make a WITH_SIZE_EXPR. */
2214 size = unshare_expr (size);
2215 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
2216 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
2219 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
2220 Store any side-effects in PRE_P. CALL_LOCATION is the location of
2221 the CALL_EXPR. */
2223 enum gimplify_status
2224 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location)
2226 bool (*test) (tree);
2227 fallback_t fb;
2229 /* In general, we allow lvalues for function arguments to avoid
2230 extra overhead of copying large aggregates out of even larger
2231 aggregates into temporaries only to copy the temporaries to
2232 the argument list. Make optimizers happy by pulling out to
2233 temporaries those types that fit in registers. */
2234 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
2235 test = is_gimple_val, fb = fb_rvalue;
2236 else
2238 test = is_gimple_lvalue, fb = fb_either;
2239 /* Also strip a TARGET_EXPR that would force an extra copy. */
2240 if (TREE_CODE (*arg_p) == TARGET_EXPR)
2242 tree init = TARGET_EXPR_INITIAL (*arg_p);
2243 if (init
2244 && !VOID_TYPE_P (TREE_TYPE (init)))
2245 *arg_p = init;
2249 /* If this is a variable sized type, we must remember the size. */
2250 maybe_with_size_expr (arg_p);
2252 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
2253 /* Make sure arguments have the same location as the function call
2254 itself. */
2255 protected_set_expr_location (*arg_p, call_location);
2257 /* There is a sequence point before a function call. Side effects in
2258 the argument list must occur before the actual call. So, when
2259 gimplifying arguments, force gimplify_expr to use an internal
2260 post queue which is then appended to the end of PRE_P. */
2261 return gimplify_expr (arg_p, pre_p, NULL, test, fb);
2264 /* Don't fold inside offloading regions: it can break code by adding decl
2265 references that weren't in the source. We'll do it during omplower pass
2266 instead. */
2268 static bool
2269 maybe_fold_stmt (gimple_stmt_iterator *gsi)
2271 struct gimplify_omp_ctx *ctx;
2272 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
2273 if (ctx->region_type == ORT_TARGET)
2274 return false;
2275 return fold_stmt (gsi);
2278 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
2279 WANT_VALUE is true if the result of the call is desired. */
2281 static enum gimplify_status
2282 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
2284 tree fndecl, parms, p, fnptrtype;
2285 enum gimplify_status ret;
2286 int i, nargs;
2287 gcall *call;
2288 bool builtin_va_start_p = false;
2289 location_t loc = EXPR_LOCATION (*expr_p);
2291 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
2293 /* For reliable diagnostics during inlining, it is necessary that
2294 every call_expr be annotated with file and line. */
2295 if (! EXPR_HAS_LOCATION (*expr_p))
2296 SET_EXPR_LOCATION (*expr_p, input_location);
2298 /* Gimplify internal functions created in the FEs. */
2299 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
2301 if (want_value)
2302 return GS_ALL_DONE;
2304 nargs = call_expr_nargs (*expr_p);
2305 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
2306 auto_vec<tree> vargs (nargs);
2308 for (i = 0; i < nargs; i++)
2310 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
2311 EXPR_LOCATION (*expr_p));
2312 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
2314 gimple call = gimple_build_call_internal_vec (ifn, vargs);
2315 gimplify_seq_add_stmt (pre_p, call);
2316 return GS_ALL_DONE;
2319 /* This may be a call to a builtin function.
2321 Builtin function calls may be transformed into different
2322 (and more efficient) builtin function calls under certain
2323 circumstances. Unfortunately, gimplification can muck things
2324 up enough that the builtin expanders are not aware that certain
2325 transformations are still valid.
2327 So we attempt transformation/gimplification of the call before
2328 we gimplify the CALL_EXPR. At this time we do not manage to
2329 transform all calls in the same manner as the expanders do, but
2330 we do transform most of them. */
2331 fndecl = get_callee_fndecl (*expr_p);
2332 if (fndecl
2333 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL)
2334 switch (DECL_FUNCTION_CODE (fndecl))
2336 case BUILT_IN_VA_START:
2338 builtin_va_start_p = TRUE;
2339 if (call_expr_nargs (*expr_p) < 2)
2341 error ("too few arguments to function %<va_start%>");
2342 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
2343 return GS_OK;
2346 if (fold_builtin_next_arg (*expr_p, true))
2348 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
2349 return GS_OK;
2351 break;
2353 case BUILT_IN_LINE:
2355 *expr_p = build_int_cst (TREE_TYPE (*expr_p),
2356 LOCATION_LINE (EXPR_LOCATION (*expr_p)));
2357 return GS_OK;
2359 case BUILT_IN_FILE:
2361 const char *locfile = LOCATION_FILE (EXPR_LOCATION (*expr_p));
2362 *expr_p = build_string_literal (strlen (locfile) + 1, locfile);
2363 return GS_OK;
2365 case BUILT_IN_FUNCTION:
2367 const char *function;
2368 function = IDENTIFIER_POINTER (DECL_NAME (current_function_decl));
2369 *expr_p = build_string_literal (strlen (function) + 1, function);
2370 return GS_OK;
2372 default:
2375 if (fndecl && DECL_BUILT_IN (fndecl))
2377 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
2378 if (new_tree && new_tree != *expr_p)
2380 /* There was a transformation of this call which computes the
2381 same value, but in a more efficient way. Return and try
2382 again. */
2383 *expr_p = new_tree;
2384 return GS_OK;
2388 /* Remember the original function pointer type. */
2389 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
2391 /* There is a sequence point before the call, so any side effects in
2392 the calling expression must occur before the actual call. Force
2393 gimplify_expr to use an internal post queue. */
2394 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
2395 is_gimple_call_addr, fb_rvalue);
2397 nargs = call_expr_nargs (*expr_p);
2399 /* Get argument types for verification. */
2400 fndecl = get_callee_fndecl (*expr_p);
2401 parms = NULL_TREE;
2402 if (fndecl)
2403 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
2404 else
2405 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
2407 if (fndecl && DECL_ARGUMENTS (fndecl))
2408 p = DECL_ARGUMENTS (fndecl);
2409 else if (parms)
2410 p = parms;
2411 else
2412 p = NULL_TREE;
2413 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
2416 /* If the last argument is __builtin_va_arg_pack () and it is not
2417 passed as a named argument, decrease the number of CALL_EXPR
2418 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
2419 if (!p
2420 && i < nargs
2421 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
2423 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
2424 tree last_arg_fndecl = get_callee_fndecl (last_arg);
2426 if (last_arg_fndecl
2427 && TREE_CODE (last_arg_fndecl) == FUNCTION_DECL
2428 && DECL_BUILT_IN_CLASS (last_arg_fndecl) == BUILT_IN_NORMAL
2429 && DECL_FUNCTION_CODE (last_arg_fndecl) == BUILT_IN_VA_ARG_PACK)
2431 tree call = *expr_p;
2433 --nargs;
2434 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
2435 CALL_EXPR_FN (call),
2436 nargs, CALL_EXPR_ARGP (call));
2438 /* Copy all CALL_EXPR flags, location and block, except
2439 CALL_EXPR_VA_ARG_PACK flag. */
2440 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
2441 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
2442 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
2443 = CALL_EXPR_RETURN_SLOT_OPT (call);
2444 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
2445 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
2447 /* Set CALL_EXPR_VA_ARG_PACK. */
2448 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
2452 /* Gimplify the function arguments. */
2453 if (nargs > 0)
2455 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
2456 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
2457 PUSH_ARGS_REVERSED ? i-- : i++)
2459 enum gimplify_status t;
2461 /* Avoid gimplifying the second argument to va_start, which needs to
2462 be the plain PARM_DECL. */
2463 if ((i != 1) || !builtin_va_start_p)
2465 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
2466 EXPR_LOCATION (*expr_p));
2468 if (t == GS_ERROR)
2469 ret = GS_ERROR;
2474 /* Gimplify the static chain. */
2475 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
2477 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
2478 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
2479 else
2481 enum gimplify_status t;
2482 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
2483 EXPR_LOCATION (*expr_p));
2484 if (t == GS_ERROR)
2485 ret = GS_ERROR;
2489 /* Verify the function result. */
2490 if (want_value && fndecl
2491 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
2493 error_at (loc, "using result of function returning %<void%>");
2494 ret = GS_ERROR;
2497 /* Try this again in case gimplification exposed something. */
2498 if (ret != GS_ERROR)
2500 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
2502 if (new_tree && new_tree != *expr_p)
2504 /* There was a transformation of this call which computes the
2505 same value, but in a more efficient way. Return and try
2506 again. */
2507 *expr_p = new_tree;
2508 return GS_OK;
2511 else
2513 *expr_p = error_mark_node;
2514 return GS_ERROR;
2517 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
2518 decl. This allows us to eliminate redundant or useless
2519 calls to "const" functions. */
2520 if (TREE_CODE (*expr_p) == CALL_EXPR)
2522 int flags = call_expr_flags (*expr_p);
2523 if (flags & (ECF_CONST | ECF_PURE)
2524 /* An infinite loop is considered a side effect. */
2525 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
2526 TREE_SIDE_EFFECTS (*expr_p) = 0;
2529 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
2530 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
2531 form and delegate the creation of a GIMPLE_CALL to
2532 gimplify_modify_expr. This is always possible because when
2533 WANT_VALUE is true, the caller wants the result of this call into
2534 a temporary, which means that we will emit an INIT_EXPR in
2535 internal_get_tmp_var which will then be handled by
2536 gimplify_modify_expr. */
2537 if (!want_value)
2539 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
2540 have to do is replicate it as a GIMPLE_CALL tuple. */
2541 gimple_stmt_iterator gsi;
2542 call = gimple_build_call_from_tree (*expr_p);
2543 gimple_call_set_fntype (call, TREE_TYPE (fnptrtype));
2544 notice_special_calls (call);
2545 gimplify_seq_add_stmt (pre_p, call);
2546 gsi = gsi_last (*pre_p);
2547 maybe_fold_stmt (&gsi);
2548 *expr_p = NULL_TREE;
2550 else
2551 /* Remember the original function type. */
2552 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
2553 CALL_EXPR_FN (*expr_p));
2555 return ret;
2558 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
2559 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
2561 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
2562 condition is true or false, respectively. If null, we should generate
2563 our own to skip over the evaluation of this specific expression.
2565 LOCUS is the source location of the COND_EXPR.
2567 This function is the tree equivalent of do_jump.
2569 shortcut_cond_r should only be called by shortcut_cond_expr. */
2571 static tree
2572 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
2573 location_t locus)
2575 tree local_label = NULL_TREE;
2576 tree t, expr = NULL;
2578 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
2579 retain the shortcut semantics. Just insert the gotos here;
2580 shortcut_cond_expr will append the real blocks later. */
2581 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
2583 location_t new_locus;
2585 /* Turn if (a && b) into
2587 if (a); else goto no;
2588 if (b) goto yes; else goto no;
2589 (no:) */
2591 if (false_label_p == NULL)
2592 false_label_p = &local_label;
2594 /* Keep the original source location on the first 'if'. */
2595 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
2596 append_to_statement_list (t, &expr);
2598 /* Set the source location of the && on the second 'if'. */
2599 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
2600 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
2601 new_locus);
2602 append_to_statement_list (t, &expr);
2604 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
2606 location_t new_locus;
2608 /* Turn if (a || b) into
2610 if (a) goto yes;
2611 if (b) goto yes; else goto no;
2612 (yes:) */
2614 if (true_label_p == NULL)
2615 true_label_p = &local_label;
2617 /* Keep the original source location on the first 'if'. */
2618 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
2619 append_to_statement_list (t, &expr);
2621 /* Set the source location of the || on the second 'if'. */
2622 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
2623 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
2624 new_locus);
2625 append_to_statement_list (t, &expr);
2627 else if (TREE_CODE (pred) == COND_EXPR
2628 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
2629 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
2631 location_t new_locus;
2633 /* As long as we're messing with gotos, turn if (a ? b : c) into
2634 if (a)
2635 if (b) goto yes; else goto no;
2636 else
2637 if (c) goto yes; else goto no;
2639 Don't do this if one of the arms has void type, which can happen
2640 in C++ when the arm is throw. */
2642 /* Keep the original source location on the first 'if'. Set the source
2643 location of the ? on the second 'if'. */
2644 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
2645 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
2646 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
2647 false_label_p, locus),
2648 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
2649 false_label_p, new_locus));
2651 else
2653 expr = build3 (COND_EXPR, void_type_node, pred,
2654 build_and_jump (true_label_p),
2655 build_and_jump (false_label_p));
2656 SET_EXPR_LOCATION (expr, locus);
2659 if (local_label)
2661 t = build1 (LABEL_EXPR, void_type_node, local_label);
2662 append_to_statement_list (t, &expr);
2665 return expr;
2668 /* Given a conditional expression EXPR with short-circuit boolean
2669 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
2670 predicate apart into the equivalent sequence of conditionals. */
2672 static tree
2673 shortcut_cond_expr (tree expr)
2675 tree pred = TREE_OPERAND (expr, 0);
2676 tree then_ = TREE_OPERAND (expr, 1);
2677 tree else_ = TREE_OPERAND (expr, 2);
2678 tree true_label, false_label, end_label, t;
2679 tree *true_label_p;
2680 tree *false_label_p;
2681 bool emit_end, emit_false, jump_over_else;
2682 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
2683 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
2685 /* First do simple transformations. */
2686 if (!else_se)
2688 /* If there is no 'else', turn
2689 if (a && b) then c
2690 into
2691 if (a) if (b) then c. */
2692 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
2694 /* Keep the original source location on the first 'if'. */
2695 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
2696 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
2697 /* Set the source location of the && on the second 'if'. */
2698 if (EXPR_HAS_LOCATION (pred))
2699 SET_EXPR_LOCATION (expr, EXPR_LOCATION (pred));
2700 then_ = shortcut_cond_expr (expr);
2701 then_se = then_ && TREE_SIDE_EFFECTS (then_);
2702 pred = TREE_OPERAND (pred, 0);
2703 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
2704 SET_EXPR_LOCATION (expr, locus);
2708 if (!then_se)
2710 /* If there is no 'then', turn
2711 if (a || b); else d
2712 into
2713 if (a); else if (b); else d. */
2714 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
2716 /* Keep the original source location on the first 'if'. */
2717 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
2718 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
2719 /* Set the source location of the || on the second 'if'. */
2720 if (EXPR_HAS_LOCATION (pred))
2721 SET_EXPR_LOCATION (expr, EXPR_LOCATION (pred));
2722 else_ = shortcut_cond_expr (expr);
2723 else_se = else_ && TREE_SIDE_EFFECTS (else_);
2724 pred = TREE_OPERAND (pred, 0);
2725 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
2726 SET_EXPR_LOCATION (expr, locus);
2730 /* If we're done, great. */
2731 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
2732 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
2733 return expr;
2735 /* Otherwise we need to mess with gotos. Change
2736 if (a) c; else d;
2738 if (a); else goto no;
2739 c; goto end;
2740 no: d; end:
2741 and recursively gimplify the condition. */
2743 true_label = false_label = end_label = NULL_TREE;
2745 /* If our arms just jump somewhere, hijack those labels so we don't
2746 generate jumps to jumps. */
2748 if (then_
2749 && TREE_CODE (then_) == GOTO_EXPR
2750 && TREE_CODE (GOTO_DESTINATION (then_)) == LABEL_DECL)
2752 true_label = GOTO_DESTINATION (then_);
2753 then_ = NULL;
2754 then_se = false;
2757 if (else_
2758 && TREE_CODE (else_) == GOTO_EXPR
2759 && TREE_CODE (GOTO_DESTINATION (else_)) == LABEL_DECL)
2761 false_label = GOTO_DESTINATION (else_);
2762 else_ = NULL;
2763 else_se = false;
2766 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
2767 if (true_label)
2768 true_label_p = &true_label;
2769 else
2770 true_label_p = NULL;
2772 /* The 'else' branch also needs a label if it contains interesting code. */
2773 if (false_label || else_se)
2774 false_label_p = &false_label;
2775 else
2776 false_label_p = NULL;
2778 /* If there was nothing else in our arms, just forward the label(s). */
2779 if (!then_se && !else_se)
2780 return shortcut_cond_r (pred, true_label_p, false_label_p,
2781 EXPR_LOC_OR_LOC (expr, input_location));
2783 /* If our last subexpression already has a terminal label, reuse it. */
2784 if (else_se)
2785 t = expr_last (else_);
2786 else if (then_se)
2787 t = expr_last (then_);
2788 else
2789 t = NULL;
2790 if (t && TREE_CODE (t) == LABEL_EXPR)
2791 end_label = LABEL_EXPR_LABEL (t);
2793 /* If we don't care about jumping to the 'else' branch, jump to the end
2794 if the condition is false. */
2795 if (!false_label_p)
2796 false_label_p = &end_label;
2798 /* We only want to emit these labels if we aren't hijacking them. */
2799 emit_end = (end_label == NULL_TREE);
2800 emit_false = (false_label == NULL_TREE);
2802 /* We only emit the jump over the else clause if we have to--if the
2803 then clause may fall through. Otherwise we can wind up with a
2804 useless jump and a useless label at the end of gimplified code,
2805 which will cause us to think that this conditional as a whole
2806 falls through even if it doesn't. If we then inline a function
2807 which ends with such a condition, that can cause us to issue an
2808 inappropriate warning about control reaching the end of a
2809 non-void function. */
2810 jump_over_else = block_may_fallthru (then_);
2812 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
2813 EXPR_LOC_OR_LOC (expr, input_location));
2815 expr = NULL;
2816 append_to_statement_list (pred, &expr);
2818 append_to_statement_list (then_, &expr);
2819 if (else_se)
2821 if (jump_over_else)
2823 tree last = expr_last (expr);
2824 t = build_and_jump (&end_label);
2825 if (EXPR_HAS_LOCATION (last))
2826 SET_EXPR_LOCATION (t, EXPR_LOCATION (last));
2827 append_to_statement_list (t, &expr);
2829 if (emit_false)
2831 t = build1 (LABEL_EXPR, void_type_node, false_label);
2832 append_to_statement_list (t, &expr);
2834 append_to_statement_list (else_, &expr);
2836 if (emit_end && end_label)
2838 t = build1 (LABEL_EXPR, void_type_node, end_label);
2839 append_to_statement_list (t, &expr);
2842 return expr;
2845 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
2847 tree
2848 gimple_boolify (tree expr)
2850 tree type = TREE_TYPE (expr);
2851 location_t loc = EXPR_LOCATION (expr);
2853 if (TREE_CODE (expr) == NE_EXPR
2854 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
2855 && integer_zerop (TREE_OPERAND (expr, 1)))
2857 tree call = TREE_OPERAND (expr, 0);
2858 tree fn = get_callee_fndecl (call);
2860 /* For __builtin_expect ((long) (x), y) recurse into x as well
2861 if x is truth_value_p. */
2862 if (fn
2863 && DECL_BUILT_IN_CLASS (fn) == BUILT_IN_NORMAL
2864 && DECL_FUNCTION_CODE (fn) == BUILT_IN_EXPECT
2865 && call_expr_nargs (call) == 2)
2867 tree arg = CALL_EXPR_ARG (call, 0);
2868 if (arg)
2870 if (TREE_CODE (arg) == NOP_EXPR
2871 && TREE_TYPE (arg) == TREE_TYPE (call))
2872 arg = TREE_OPERAND (arg, 0);
2873 if (truth_value_p (TREE_CODE (arg)))
2875 arg = gimple_boolify (arg);
2876 CALL_EXPR_ARG (call, 0)
2877 = fold_convert_loc (loc, TREE_TYPE (call), arg);
2883 switch (TREE_CODE (expr))
2885 case TRUTH_AND_EXPR:
2886 case TRUTH_OR_EXPR:
2887 case TRUTH_XOR_EXPR:
2888 case TRUTH_ANDIF_EXPR:
2889 case TRUTH_ORIF_EXPR:
2890 /* Also boolify the arguments of truth exprs. */
2891 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
2892 /* FALLTHRU */
2894 case TRUTH_NOT_EXPR:
2895 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2897 /* These expressions always produce boolean results. */
2898 if (TREE_CODE (type) != BOOLEAN_TYPE)
2899 TREE_TYPE (expr) = boolean_type_node;
2900 return expr;
2902 case ANNOTATE_EXPR:
2903 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
2905 case annot_expr_ivdep_kind:
2906 case annot_expr_no_vector_kind:
2907 case annot_expr_vector_kind:
2908 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2909 if (TREE_CODE (type) != BOOLEAN_TYPE)
2910 TREE_TYPE (expr) = boolean_type_node;
2911 return expr;
2912 default:
2913 gcc_unreachable ();
2916 default:
2917 if (COMPARISON_CLASS_P (expr))
2919 /* There expressions always prduce boolean results. */
2920 if (TREE_CODE (type) != BOOLEAN_TYPE)
2921 TREE_TYPE (expr) = boolean_type_node;
2922 return expr;
2924 /* Other expressions that get here must have boolean values, but
2925 might need to be converted to the appropriate mode. */
2926 if (TREE_CODE (type) == BOOLEAN_TYPE)
2927 return expr;
2928 return fold_convert_loc (loc, boolean_type_node, expr);
2932 /* Given a conditional expression *EXPR_P without side effects, gimplify
2933 its operands. New statements are inserted to PRE_P. */
2935 static enum gimplify_status
2936 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
2938 tree expr = *expr_p, cond;
2939 enum gimplify_status ret, tret;
2940 enum tree_code code;
2942 cond = gimple_boolify (COND_EXPR_COND (expr));
2944 /* We need to handle && and || specially, as their gimplification
2945 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
2946 code = TREE_CODE (cond);
2947 if (code == TRUTH_ANDIF_EXPR)
2948 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
2949 else if (code == TRUTH_ORIF_EXPR)
2950 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
2951 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_condexpr, fb_rvalue);
2952 COND_EXPR_COND (*expr_p) = cond;
2954 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
2955 is_gimple_val, fb_rvalue);
2956 ret = MIN (ret, tret);
2957 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
2958 is_gimple_val, fb_rvalue);
2960 return MIN (ret, tret);
2963 /* Return true if evaluating EXPR could trap.
2964 EXPR is GENERIC, while tree_could_trap_p can be called
2965 only on GIMPLE. */
2967 static bool
2968 generic_expr_could_trap_p (tree expr)
2970 unsigned i, n;
2972 if (!expr || is_gimple_val (expr))
2973 return false;
2975 if (!EXPR_P (expr) || tree_could_trap_p (expr))
2976 return true;
2978 n = TREE_OPERAND_LENGTH (expr);
2979 for (i = 0; i < n; i++)
2980 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
2981 return true;
2983 return false;
2986 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
2987 into
2989 if (p) if (p)
2990 t1 = a; a;
2991 else or else
2992 t1 = b; b;
2995 The second form is used when *EXPR_P is of type void.
2997 PRE_P points to the list where side effects that must happen before
2998 *EXPR_P should be stored. */
3000 static enum gimplify_status
3001 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
3003 tree expr = *expr_p;
3004 tree type = TREE_TYPE (expr);
3005 location_t loc = EXPR_LOCATION (expr);
3006 tree tmp, arm1, arm2;
3007 enum gimplify_status ret;
3008 tree label_true, label_false, label_cont;
3009 bool have_then_clause_p, have_else_clause_p;
3010 gcond *cond_stmt;
3011 enum tree_code pred_code;
3012 gimple_seq seq = NULL;
3014 /* If this COND_EXPR has a value, copy the values into a temporary within
3015 the arms. */
3016 if (!VOID_TYPE_P (type))
3018 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
3019 tree result;
3021 /* If either an rvalue is ok or we do not require an lvalue, create the
3022 temporary. But we cannot do that if the type is addressable. */
3023 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
3024 && !TREE_ADDRESSABLE (type))
3026 if (gimplify_ctxp->allow_rhs_cond_expr
3027 /* If either branch has side effects or could trap, it can't be
3028 evaluated unconditionally. */
3029 && !TREE_SIDE_EFFECTS (then_)
3030 && !generic_expr_could_trap_p (then_)
3031 && !TREE_SIDE_EFFECTS (else_)
3032 && !generic_expr_could_trap_p (else_))
3033 return gimplify_pure_cond_expr (expr_p, pre_p);
3035 tmp = create_tmp_var (type, "iftmp");
3036 result = tmp;
3039 /* Otherwise, only create and copy references to the values. */
3040 else
3042 type = build_pointer_type (type);
3044 if (!VOID_TYPE_P (TREE_TYPE (then_)))
3045 then_ = build_fold_addr_expr_loc (loc, then_);
3047 if (!VOID_TYPE_P (TREE_TYPE (else_)))
3048 else_ = build_fold_addr_expr_loc (loc, else_);
3050 expr
3051 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
3053 tmp = create_tmp_var (type, "iftmp");
3054 result = build_simple_mem_ref_loc (loc, tmp);
3057 /* Build the new then clause, `tmp = then_;'. But don't build the
3058 assignment if the value is void; in C++ it can be if it's a throw. */
3059 if (!VOID_TYPE_P (TREE_TYPE (then_)))
3060 TREE_OPERAND (expr, 1) = build2 (MODIFY_EXPR, type, tmp, then_);
3062 /* Similarly, build the new else clause, `tmp = else_;'. */
3063 if (!VOID_TYPE_P (TREE_TYPE (else_)))
3064 TREE_OPERAND (expr, 2) = build2 (MODIFY_EXPR, type, tmp, else_);
3066 TREE_TYPE (expr) = void_type_node;
3067 recalculate_side_effects (expr);
3069 /* Move the COND_EXPR to the prequeue. */
3070 gimplify_stmt (&expr, pre_p);
3072 *expr_p = result;
3073 return GS_ALL_DONE;
3076 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
3077 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
3078 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
3079 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
3081 /* Make sure the condition has BOOLEAN_TYPE. */
3082 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3084 /* Break apart && and || conditions. */
3085 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
3086 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
3088 expr = shortcut_cond_expr (expr);
3090 if (expr != *expr_p)
3092 *expr_p = expr;
3094 /* We can't rely on gimplify_expr to re-gimplify the expanded
3095 form properly, as cleanups might cause the target labels to be
3096 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
3097 set up a conditional context. */
3098 gimple_push_condition ();
3099 gimplify_stmt (expr_p, &seq);
3100 gimple_pop_condition (pre_p);
3101 gimple_seq_add_seq (pre_p, seq);
3103 return GS_ALL_DONE;
3107 /* Now do the normal gimplification. */
3109 /* Gimplify condition. */
3110 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL, is_gimple_condexpr,
3111 fb_rvalue);
3112 if (ret == GS_ERROR)
3113 return GS_ERROR;
3114 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
3116 gimple_push_condition ();
3118 have_then_clause_p = have_else_clause_p = false;
3119 if (TREE_OPERAND (expr, 1) != NULL
3120 && TREE_CODE (TREE_OPERAND (expr, 1)) == GOTO_EXPR
3121 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr, 1))) == LABEL_DECL
3122 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr, 1)))
3123 == current_function_decl)
3124 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3125 have different locations, otherwise we end up with incorrect
3126 location information on the branches. */
3127 && (optimize
3128 || !EXPR_HAS_LOCATION (expr)
3129 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr, 1))
3130 || EXPR_LOCATION (expr) == EXPR_LOCATION (TREE_OPERAND (expr, 1))))
3132 label_true = GOTO_DESTINATION (TREE_OPERAND (expr, 1));
3133 have_then_clause_p = true;
3135 else
3136 label_true = create_artificial_label (UNKNOWN_LOCATION);
3137 if (TREE_OPERAND (expr, 2) != NULL
3138 && TREE_CODE (TREE_OPERAND (expr, 2)) == GOTO_EXPR
3139 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr, 2))) == LABEL_DECL
3140 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr, 2)))
3141 == current_function_decl)
3142 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3143 have different locations, otherwise we end up with incorrect
3144 location information on the branches. */
3145 && (optimize
3146 || !EXPR_HAS_LOCATION (expr)
3147 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr, 2))
3148 || EXPR_LOCATION (expr) == EXPR_LOCATION (TREE_OPERAND (expr, 2))))
3150 label_false = GOTO_DESTINATION (TREE_OPERAND (expr, 2));
3151 have_else_clause_p = true;
3153 else
3154 label_false = create_artificial_label (UNKNOWN_LOCATION);
3156 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
3157 &arm2);
3159 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
3160 label_false);
3162 gimplify_seq_add_stmt (&seq, cond_stmt);
3163 label_cont = NULL_TREE;
3164 if (!have_then_clause_p)
3166 /* For if (...) {} else { code; } put label_true after
3167 the else block. */
3168 if (TREE_OPERAND (expr, 1) == NULL_TREE
3169 && !have_else_clause_p
3170 && TREE_OPERAND (expr, 2) != NULL_TREE)
3171 label_cont = label_true;
3172 else
3174 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
3175 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
3176 /* For if (...) { code; } else {} or
3177 if (...) { code; } else goto label; or
3178 if (...) { code; return; } else { ... }
3179 label_cont isn't needed. */
3180 if (!have_else_clause_p
3181 && TREE_OPERAND (expr, 2) != NULL_TREE
3182 && gimple_seq_may_fallthru (seq))
3184 gimple g;
3185 label_cont = create_artificial_label (UNKNOWN_LOCATION);
3187 g = gimple_build_goto (label_cont);
3189 /* GIMPLE_COND's are very low level; they have embedded
3190 gotos. This particular embedded goto should not be marked
3191 with the location of the original COND_EXPR, as it would
3192 correspond to the COND_EXPR's condition, not the ELSE or the
3193 THEN arms. To avoid marking it with the wrong location, flag
3194 it as "no location". */
3195 gimple_set_do_not_emit_location (g);
3197 gimplify_seq_add_stmt (&seq, g);
3201 if (!have_else_clause_p)
3203 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
3204 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
3206 if (label_cont)
3207 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
3209 gimple_pop_condition (pre_p);
3210 gimple_seq_add_seq (pre_p, seq);
3212 if (ret == GS_ERROR)
3213 ; /* Do nothing. */
3214 else if (have_then_clause_p || have_else_clause_p)
3215 ret = GS_ALL_DONE;
3216 else
3218 /* Both arms are empty; replace the COND_EXPR with its predicate. */
3219 expr = TREE_OPERAND (expr, 0);
3220 gimplify_stmt (&expr, pre_p);
3223 *expr_p = NULL;
3224 return ret;
3227 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
3228 to be marked addressable.
3230 We cannot rely on such an expression being directly markable if a temporary
3231 has been created by the gimplification. In this case, we create another
3232 temporary and initialize it with a copy, which will become a store after we
3233 mark it addressable. This can happen if the front-end passed us something
3234 that it could not mark addressable yet, like a Fortran pass-by-reference
3235 parameter (int) floatvar. */
3237 static void
3238 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
3240 while (handled_component_p (*expr_p))
3241 expr_p = &TREE_OPERAND (*expr_p, 0);
3242 if (is_gimple_reg (*expr_p))
3244 tree var = get_initialized_tmp_var (*expr_p, seq_p, NULL);
3245 DECL_GIMPLE_REG_P (var) = 0;
3246 *expr_p = var;
3250 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
3251 a call to __builtin_memcpy. */
3253 static enum gimplify_status
3254 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
3255 gimple_seq *seq_p)
3257 tree t, to, to_ptr, from, from_ptr;
3258 gcall *gs;
3259 location_t loc = EXPR_LOCATION (*expr_p);
3261 to = TREE_OPERAND (*expr_p, 0);
3262 from = TREE_OPERAND (*expr_p, 1);
3264 /* Mark the RHS addressable. Beware that it may not be possible to do so
3265 directly if a temporary has been created by the gimplification. */
3266 prepare_gimple_addressable (&from, seq_p);
3268 mark_addressable (from);
3269 from_ptr = build_fold_addr_expr_loc (loc, from);
3270 gimplify_arg (&from_ptr, seq_p, loc);
3272 mark_addressable (to);
3273 to_ptr = build_fold_addr_expr_loc (loc, to);
3274 gimplify_arg (&to_ptr, seq_p, loc);
3276 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
3278 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
3280 if (want_value)
3282 /* tmp = memcpy() */
3283 t = create_tmp_var (TREE_TYPE (to_ptr));
3284 gimple_call_set_lhs (gs, t);
3285 gimplify_seq_add_stmt (seq_p, gs);
3287 *expr_p = build_simple_mem_ref (t);
3288 return GS_ALL_DONE;
3291 gimplify_seq_add_stmt (seq_p, gs);
3292 *expr_p = NULL;
3293 return GS_ALL_DONE;
3296 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
3297 a call to __builtin_memset. In this case we know that the RHS is
3298 a CONSTRUCTOR with an empty element list. */
3300 static enum gimplify_status
3301 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
3302 gimple_seq *seq_p)
3304 tree t, from, to, to_ptr;
3305 gcall *gs;
3306 location_t loc = EXPR_LOCATION (*expr_p);
3308 /* Assert our assumptions, to abort instead of producing wrong code
3309 silently if they are not met. Beware that the RHS CONSTRUCTOR might
3310 not be immediately exposed. */
3311 from = TREE_OPERAND (*expr_p, 1);
3312 if (TREE_CODE (from) == WITH_SIZE_EXPR)
3313 from = TREE_OPERAND (from, 0);
3315 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
3316 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
3318 /* Now proceed. */
3319 to = TREE_OPERAND (*expr_p, 0);
3321 to_ptr = build_fold_addr_expr_loc (loc, to);
3322 gimplify_arg (&to_ptr, seq_p, loc);
3323 t = builtin_decl_implicit (BUILT_IN_MEMSET);
3325 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
3327 if (want_value)
3329 /* tmp = memset() */
3330 t = create_tmp_var (TREE_TYPE (to_ptr));
3331 gimple_call_set_lhs (gs, t);
3332 gimplify_seq_add_stmt (seq_p, gs);
3334 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
3335 return GS_ALL_DONE;
3338 gimplify_seq_add_stmt (seq_p, gs);
3339 *expr_p = NULL;
3340 return GS_ALL_DONE;
3343 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
3344 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
3345 assignment. Return non-null if we detect a potential overlap. */
3347 struct gimplify_init_ctor_preeval_data
3349 /* The base decl of the lhs object. May be NULL, in which case we
3350 have to assume the lhs is indirect. */
3351 tree lhs_base_decl;
3353 /* The alias set of the lhs object. */
3354 alias_set_type lhs_alias_set;
3357 static tree
3358 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
3360 struct gimplify_init_ctor_preeval_data *data
3361 = (struct gimplify_init_ctor_preeval_data *) xdata;
3362 tree t = *tp;
3364 /* If we find the base object, obviously we have overlap. */
3365 if (data->lhs_base_decl == t)
3366 return t;
3368 /* If the constructor component is indirect, determine if we have a
3369 potential overlap with the lhs. The only bits of information we
3370 have to go on at this point are addressability and alias sets. */
3371 if ((INDIRECT_REF_P (t)
3372 || TREE_CODE (t) == MEM_REF)
3373 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
3374 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
3375 return t;
3377 /* If the constructor component is a call, determine if it can hide a
3378 potential overlap with the lhs through an INDIRECT_REF like above.
3379 ??? Ugh - this is completely broken. In fact this whole analysis
3380 doesn't look conservative. */
3381 if (TREE_CODE (t) == CALL_EXPR)
3383 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
3385 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
3386 if (POINTER_TYPE_P (TREE_VALUE (type))
3387 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
3388 && alias_sets_conflict_p (data->lhs_alias_set,
3389 get_alias_set
3390 (TREE_TYPE (TREE_VALUE (type)))))
3391 return t;
3394 if (IS_TYPE_OR_DECL_P (t))
3395 *walk_subtrees = 0;
3396 return NULL;
3399 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
3400 force values that overlap with the lhs (as described by *DATA)
3401 into temporaries. */
3403 static void
3404 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3405 struct gimplify_init_ctor_preeval_data *data)
3407 enum gimplify_status one;
3409 /* If the value is constant, then there's nothing to pre-evaluate. */
3410 if (TREE_CONSTANT (*expr_p))
3412 /* Ensure it does not have side effects, it might contain a reference to
3413 the object we're initializing. */
3414 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
3415 return;
3418 /* If the type has non-trivial constructors, we can't pre-evaluate. */
3419 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
3420 return;
3422 /* Recurse for nested constructors. */
3423 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
3425 unsigned HOST_WIDE_INT ix;
3426 constructor_elt *ce;
3427 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
3429 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
3430 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
3432 return;
3435 /* If this is a variable sized type, we must remember the size. */
3436 maybe_with_size_expr (expr_p);
3438 /* Gimplify the constructor element to something appropriate for the rhs
3439 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
3440 the gimplifier will consider this a store to memory. Doing this
3441 gimplification now means that we won't have to deal with complicated
3442 language-specific trees, nor trees like SAVE_EXPR that can induce
3443 exponential search behavior. */
3444 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
3445 if (one == GS_ERROR)
3447 *expr_p = NULL;
3448 return;
3451 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
3452 with the lhs, since "a = { .x=a }" doesn't make sense. This will
3453 always be true for all scalars, since is_gimple_mem_rhs insists on a
3454 temporary variable for them. */
3455 if (DECL_P (*expr_p))
3456 return;
3458 /* If this is of variable size, we have no choice but to assume it doesn't
3459 overlap since we can't make a temporary for it. */
3460 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
3461 return;
3463 /* Otherwise, we must search for overlap ... */
3464 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
3465 return;
3467 /* ... and if found, force the value into a temporary. */
3468 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
3471 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
3472 a RANGE_EXPR in a CONSTRUCTOR for an array.
3474 var = lower;
3475 loop_entry:
3476 object[var] = value;
3477 if (var == upper)
3478 goto loop_exit;
3479 var = var + 1;
3480 goto loop_entry;
3481 loop_exit:
3483 We increment var _after_ the loop exit check because we might otherwise
3484 fail if upper == TYPE_MAX_VALUE (type for upper).
3486 Note that we never have to deal with SAVE_EXPRs here, because this has
3487 already been taken care of for us, in gimplify_init_ctor_preeval(). */
3489 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
3490 gimple_seq *, bool);
3492 static void
3493 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
3494 tree value, tree array_elt_type,
3495 gimple_seq *pre_p, bool cleared)
3497 tree loop_entry_label, loop_exit_label, fall_thru_label;
3498 tree var, var_type, cref, tmp;
3500 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
3501 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
3502 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
3504 /* Create and initialize the index variable. */
3505 var_type = TREE_TYPE (upper);
3506 var = create_tmp_var (var_type);
3507 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
3509 /* Add the loop entry label. */
3510 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
3512 /* Build the reference. */
3513 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
3514 var, NULL_TREE, NULL_TREE);
3516 /* If we are a constructor, just call gimplify_init_ctor_eval to do
3517 the store. Otherwise just assign value to the reference. */
3519 if (TREE_CODE (value) == CONSTRUCTOR)
3520 /* NB we might have to call ourself recursively through
3521 gimplify_init_ctor_eval if the value is a constructor. */
3522 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
3523 pre_p, cleared);
3524 else
3525 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
3527 /* We exit the loop when the index var is equal to the upper bound. */
3528 gimplify_seq_add_stmt (pre_p,
3529 gimple_build_cond (EQ_EXPR, var, upper,
3530 loop_exit_label, fall_thru_label));
3532 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
3534 /* Otherwise, increment the index var... */
3535 tmp = build2 (PLUS_EXPR, var_type, var,
3536 fold_convert (var_type, integer_one_node));
3537 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
3539 /* ...and jump back to the loop entry. */
3540 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
3542 /* Add the loop exit label. */
3543 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
3546 /* Return true if FDECL is accessing a field that is zero sized. */
3548 static bool
3549 zero_sized_field_decl (const_tree fdecl)
3551 if (TREE_CODE (fdecl) == FIELD_DECL && DECL_SIZE (fdecl)
3552 && integer_zerop (DECL_SIZE (fdecl)))
3553 return true;
3554 return false;
3557 /* Return true if TYPE is zero sized. */
3559 static bool
3560 zero_sized_type (const_tree type)
3562 if (AGGREGATE_TYPE_P (type) && TYPE_SIZE (type)
3563 && integer_zerop (TYPE_SIZE (type)))
3564 return true;
3565 return false;
3568 /* A subroutine of gimplify_init_constructor. Generate individual
3569 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
3570 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
3571 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
3572 zeroed first. */
3574 static void
3575 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
3576 gimple_seq *pre_p, bool cleared)
3578 tree array_elt_type = NULL;
3579 unsigned HOST_WIDE_INT ix;
3580 tree purpose, value;
3582 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
3583 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
3585 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
3587 tree cref;
3589 /* NULL values are created above for gimplification errors. */
3590 if (value == NULL)
3591 continue;
3593 if (cleared && initializer_zerop (value))
3594 continue;
3596 /* ??? Here's to hoping the front end fills in all of the indices,
3597 so we don't have to figure out what's missing ourselves. */
3598 gcc_assert (purpose);
3600 /* Skip zero-sized fields, unless value has side-effects. This can
3601 happen with calls to functions returning a zero-sized type, which
3602 we shouldn't discard. As a number of downstream passes don't
3603 expect sets of zero-sized fields, we rely on the gimplification of
3604 the MODIFY_EXPR we make below to drop the assignment statement. */
3605 if (! TREE_SIDE_EFFECTS (value) && zero_sized_field_decl (purpose))
3606 continue;
3608 /* If we have a RANGE_EXPR, we have to build a loop to assign the
3609 whole range. */
3610 if (TREE_CODE (purpose) == RANGE_EXPR)
3612 tree lower = TREE_OPERAND (purpose, 0);
3613 tree upper = TREE_OPERAND (purpose, 1);
3615 /* If the lower bound is equal to upper, just treat it as if
3616 upper was the index. */
3617 if (simple_cst_equal (lower, upper))
3618 purpose = upper;
3619 else
3621 gimplify_init_ctor_eval_range (object, lower, upper, value,
3622 array_elt_type, pre_p, cleared);
3623 continue;
3627 if (array_elt_type)
3629 /* Do not use bitsizetype for ARRAY_REF indices. */
3630 if (TYPE_DOMAIN (TREE_TYPE (object)))
3631 purpose
3632 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
3633 purpose);
3634 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
3635 purpose, NULL_TREE, NULL_TREE);
3637 else
3639 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
3640 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
3641 unshare_expr (object), purpose, NULL_TREE);
3644 if (TREE_CODE (value) == CONSTRUCTOR
3645 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
3646 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
3647 pre_p, cleared);
3648 else
3650 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
3651 gimplify_and_add (init, pre_p);
3652 ggc_free (init);
3657 /* Return the appropriate RHS predicate for this LHS. */
3659 gimple_predicate
3660 rhs_predicate_for (tree lhs)
3662 if (is_gimple_reg (lhs))
3663 return is_gimple_reg_rhs_or_call;
3664 else
3665 return is_gimple_mem_rhs_or_call;
3668 /* Gimplify a C99 compound literal expression. This just means adding
3669 the DECL_EXPR before the current statement and using its anonymous
3670 decl instead. */
3672 static enum gimplify_status
3673 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
3674 bool (*gimple_test_f) (tree),
3675 fallback_t fallback)
3677 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
3678 tree decl = DECL_EXPR_DECL (decl_s);
3679 tree init = DECL_INITIAL (decl);
3680 /* Mark the decl as addressable if the compound literal
3681 expression is addressable now, otherwise it is marked too late
3682 after we gimplify the initialization expression. */
3683 if (TREE_ADDRESSABLE (*expr_p))
3684 TREE_ADDRESSABLE (decl) = 1;
3685 /* Otherwise, if we don't need an lvalue and have a literal directly
3686 substitute it. Check if it matches the gimple predicate, as
3687 otherwise we'd generate a new temporary, and we can as well just
3688 use the decl we already have. */
3689 else if (!TREE_ADDRESSABLE (decl)
3690 && init
3691 && (fallback & fb_lvalue) == 0
3692 && gimple_test_f (init))
3694 *expr_p = init;
3695 return GS_OK;
3698 /* Preliminarily mark non-addressed complex variables as eligible
3699 for promotion to gimple registers. We'll transform their uses
3700 as we find them. */
3701 if ((TREE_CODE (TREE_TYPE (decl)) == COMPLEX_TYPE
3702 || TREE_CODE (TREE_TYPE (decl)) == VECTOR_TYPE)
3703 && !TREE_THIS_VOLATILE (decl)
3704 && !needs_to_live_in_memory (decl))
3705 DECL_GIMPLE_REG_P (decl) = 1;
3707 /* If the decl is not addressable, then it is being used in some
3708 expression or on the right hand side of a statement, and it can
3709 be put into a readonly data section. */
3710 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
3711 TREE_READONLY (decl) = 1;
3713 /* This decl isn't mentioned in the enclosing block, so add it to the
3714 list of temps. FIXME it seems a bit of a kludge to say that
3715 anonymous artificial vars aren't pushed, but everything else is. */
3716 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
3717 gimple_add_tmp_var (decl);
3719 gimplify_and_add (decl_s, pre_p);
3720 *expr_p = decl;
3721 return GS_OK;
3724 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
3725 return a new CONSTRUCTOR if something changed. */
3727 static tree
3728 optimize_compound_literals_in_ctor (tree orig_ctor)
3730 tree ctor = orig_ctor;
3731 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
3732 unsigned int idx, num = vec_safe_length (elts);
3734 for (idx = 0; idx < num; idx++)
3736 tree value = (*elts)[idx].value;
3737 tree newval = value;
3738 if (TREE_CODE (value) == CONSTRUCTOR)
3739 newval = optimize_compound_literals_in_ctor (value);
3740 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
3742 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
3743 tree decl = DECL_EXPR_DECL (decl_s);
3744 tree init = DECL_INITIAL (decl);
3746 if (!TREE_ADDRESSABLE (value)
3747 && !TREE_ADDRESSABLE (decl)
3748 && init
3749 && TREE_CODE (init) == CONSTRUCTOR)
3750 newval = optimize_compound_literals_in_ctor (init);
3752 if (newval == value)
3753 continue;
3755 if (ctor == orig_ctor)
3757 ctor = copy_node (orig_ctor);
3758 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
3759 elts = CONSTRUCTOR_ELTS (ctor);
3761 (*elts)[idx].value = newval;
3763 return ctor;
3766 /* A subroutine of gimplify_modify_expr. Break out elements of a
3767 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
3769 Note that we still need to clear any elements that don't have explicit
3770 initializers, so if not all elements are initialized we keep the
3771 original MODIFY_EXPR, we just remove all of the constructor elements.
3773 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
3774 GS_ERROR if we would have to create a temporary when gimplifying
3775 this constructor. Otherwise, return GS_OK.
3777 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
3779 static enum gimplify_status
3780 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3781 bool want_value, bool notify_temp_creation)
3783 tree object, ctor, type;
3784 enum gimplify_status ret;
3785 vec<constructor_elt, va_gc> *elts;
3787 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
3789 if (!notify_temp_creation)
3791 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3792 is_gimple_lvalue, fb_lvalue);
3793 if (ret == GS_ERROR)
3794 return ret;
3797 object = TREE_OPERAND (*expr_p, 0);
3798 ctor = TREE_OPERAND (*expr_p, 1) =
3799 optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
3800 type = TREE_TYPE (ctor);
3801 elts = CONSTRUCTOR_ELTS (ctor);
3802 ret = GS_ALL_DONE;
3804 switch (TREE_CODE (type))
3806 case RECORD_TYPE:
3807 case UNION_TYPE:
3808 case QUAL_UNION_TYPE:
3809 case ARRAY_TYPE:
3811 struct gimplify_init_ctor_preeval_data preeval_data;
3812 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
3813 bool cleared, complete_p, valid_const_initializer;
3815 /* Aggregate types must lower constructors to initialization of
3816 individual elements. The exception is that a CONSTRUCTOR node
3817 with no elements indicates zero-initialization of the whole. */
3818 if (vec_safe_is_empty (elts))
3820 if (notify_temp_creation)
3821 return GS_OK;
3822 break;
3825 /* Fetch information about the constructor to direct later processing.
3826 We might want to make static versions of it in various cases, and
3827 can only do so if it known to be a valid constant initializer. */
3828 valid_const_initializer
3829 = categorize_ctor_elements (ctor, &num_nonzero_elements,
3830 &num_ctor_elements, &complete_p);
3832 /* If a const aggregate variable is being initialized, then it
3833 should never be a lose to promote the variable to be static. */
3834 if (valid_const_initializer
3835 && num_nonzero_elements > 1
3836 && TREE_READONLY (object)
3837 && TREE_CODE (object) == VAR_DECL
3838 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object)))
3840 if (notify_temp_creation)
3841 return GS_ERROR;
3842 DECL_INITIAL (object) = ctor;
3843 TREE_STATIC (object) = 1;
3844 if (!DECL_NAME (object))
3845 DECL_NAME (object) = create_tmp_var_name ("C");
3846 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
3848 /* ??? C++ doesn't automatically append a .<number> to the
3849 assembler name, and even when it does, it looks at FE private
3850 data structures to figure out what that number should be,
3851 which are not set for this variable. I suppose this is
3852 important for local statics for inline functions, which aren't
3853 "local" in the object file sense. So in order to get a unique
3854 TU-local symbol, we must invoke the lhd version now. */
3855 lhd_set_decl_assembler_name (object);
3857 *expr_p = NULL_TREE;
3858 break;
3861 /* If there are "lots" of initialized elements, even discounting
3862 those that are not address constants (and thus *must* be
3863 computed at runtime), then partition the constructor into
3864 constant and non-constant parts. Block copy the constant
3865 parts in, then generate code for the non-constant parts. */
3866 /* TODO. There's code in cp/typeck.c to do this. */
3868 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
3869 /* store_constructor will ignore the clearing of variable-sized
3870 objects. Initializers for such objects must explicitly set
3871 every field that needs to be set. */
3872 cleared = false;
3873 else if (!complete_p && !CONSTRUCTOR_NO_CLEARING (ctor))
3874 /* If the constructor isn't complete, clear the whole object
3875 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
3877 ??? This ought not to be needed. For any element not present
3878 in the initializer, we should simply set them to zero. Except
3879 we'd need to *find* the elements that are not present, and that
3880 requires trickery to avoid quadratic compile-time behavior in
3881 large cases or excessive memory use in small cases. */
3882 cleared = true;
3883 else if (num_ctor_elements - num_nonzero_elements
3884 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
3885 && num_nonzero_elements < num_ctor_elements / 4)
3886 /* If there are "lots" of zeros, it's more efficient to clear
3887 the memory and then set the nonzero elements. */
3888 cleared = true;
3889 else
3890 cleared = false;
3892 /* If there are "lots" of initialized elements, and all of them
3893 are valid address constants, then the entire initializer can
3894 be dropped to memory, and then memcpy'd out. Don't do this
3895 for sparse arrays, though, as it's more efficient to follow
3896 the standard CONSTRUCTOR behavior of memset followed by
3897 individual element initialization. Also don't do this for small
3898 all-zero initializers (which aren't big enough to merit
3899 clearing), and don't try to make bitwise copies of
3900 TREE_ADDRESSABLE types.
3902 We cannot apply such transformation when compiling chkp static
3903 initializer because creation of initializer image in the memory
3904 will require static initialization of bounds for it. It should
3905 result in another gimplification of similar initializer and we
3906 may fall into infinite loop. */
3907 if (valid_const_initializer
3908 && !(cleared || num_nonzero_elements == 0)
3909 && !TREE_ADDRESSABLE (type)
3910 && (!current_function_decl
3911 || !lookup_attribute ("chkp ctor",
3912 DECL_ATTRIBUTES (current_function_decl))))
3914 HOST_WIDE_INT size = int_size_in_bytes (type);
3915 unsigned int align;
3917 /* ??? We can still get unbounded array types, at least
3918 from the C++ front end. This seems wrong, but attempt
3919 to work around it for now. */
3920 if (size < 0)
3922 size = int_size_in_bytes (TREE_TYPE (object));
3923 if (size >= 0)
3924 TREE_TYPE (ctor) = type = TREE_TYPE (object);
3927 /* Find the maximum alignment we can assume for the object. */
3928 /* ??? Make use of DECL_OFFSET_ALIGN. */
3929 if (DECL_P (object))
3930 align = DECL_ALIGN (object);
3931 else
3932 align = TYPE_ALIGN (type);
3934 /* Do a block move either if the size is so small as to make
3935 each individual move a sub-unit move on average, or if it
3936 is so large as to make individual moves inefficient. */
3937 if (size > 0
3938 && num_nonzero_elements > 1
3939 && (size < num_nonzero_elements
3940 || !can_move_by_pieces (size, align)))
3942 if (notify_temp_creation)
3943 return GS_ERROR;
3945 walk_tree (&ctor, force_labels_r, NULL, NULL);
3946 ctor = tree_output_constant_def (ctor);
3947 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
3948 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
3949 TREE_OPERAND (*expr_p, 1) = ctor;
3951 /* This is no longer an assignment of a CONSTRUCTOR, but
3952 we still may have processing to do on the LHS. So
3953 pretend we didn't do anything here to let that happen. */
3954 return GS_UNHANDLED;
3958 /* If the target is volatile, we have non-zero elements and more than
3959 one field to assign, initialize the target from a temporary. */
3960 if (TREE_THIS_VOLATILE (object)
3961 && !TREE_ADDRESSABLE (type)
3962 && num_nonzero_elements > 0
3963 && vec_safe_length (elts) > 1)
3965 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
3966 TREE_OPERAND (*expr_p, 0) = temp;
3967 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
3968 *expr_p,
3969 build2 (MODIFY_EXPR, void_type_node,
3970 object, temp));
3971 return GS_OK;
3974 if (notify_temp_creation)
3975 return GS_OK;
3977 /* If there are nonzero elements and if needed, pre-evaluate to capture
3978 elements overlapping with the lhs into temporaries. We must do this
3979 before clearing to fetch the values before they are zeroed-out. */
3980 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
3982 preeval_data.lhs_base_decl = get_base_address (object);
3983 if (!DECL_P (preeval_data.lhs_base_decl))
3984 preeval_data.lhs_base_decl = NULL;
3985 preeval_data.lhs_alias_set = get_alias_set (object);
3987 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
3988 pre_p, post_p, &preeval_data);
3991 bool ctor_has_side_effects_p
3992 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
3994 if (cleared)
3996 /* Zap the CONSTRUCTOR element list, which simplifies this case.
3997 Note that we still have to gimplify, in order to handle the
3998 case of variable sized types. Avoid shared tree structures. */
3999 CONSTRUCTOR_ELTS (ctor) = NULL;
4000 TREE_SIDE_EFFECTS (ctor) = 0;
4001 object = unshare_expr (object);
4002 gimplify_stmt (expr_p, pre_p);
4005 /* If we have not block cleared the object, or if there are nonzero
4006 elements in the constructor, or if the constructor has side effects,
4007 add assignments to the individual scalar fields of the object. */
4008 if (!cleared
4009 || num_nonzero_elements > 0
4010 || ctor_has_side_effects_p)
4011 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
4013 *expr_p = NULL_TREE;
4015 break;
4017 case COMPLEX_TYPE:
4019 tree r, i;
4021 if (notify_temp_creation)
4022 return GS_OK;
4024 /* Extract the real and imaginary parts out of the ctor. */
4025 gcc_assert (elts->length () == 2);
4026 r = (*elts)[0].value;
4027 i = (*elts)[1].value;
4028 if (r == NULL || i == NULL)
4030 tree zero = build_zero_cst (TREE_TYPE (type));
4031 if (r == NULL)
4032 r = zero;
4033 if (i == NULL)
4034 i = zero;
4037 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
4038 represent creation of a complex value. */
4039 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
4041 ctor = build_complex (type, r, i);
4042 TREE_OPERAND (*expr_p, 1) = ctor;
4044 else
4046 ctor = build2 (COMPLEX_EXPR, type, r, i);
4047 TREE_OPERAND (*expr_p, 1) = ctor;
4048 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
4049 pre_p,
4050 post_p,
4051 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
4052 fb_rvalue);
4055 break;
4057 case VECTOR_TYPE:
4059 unsigned HOST_WIDE_INT ix;
4060 constructor_elt *ce;
4062 if (notify_temp_creation)
4063 return GS_OK;
4065 /* Go ahead and simplify constant constructors to VECTOR_CST. */
4066 if (TREE_CONSTANT (ctor))
4068 bool constant_p = true;
4069 tree value;
4071 /* Even when ctor is constant, it might contain non-*_CST
4072 elements, such as addresses or trapping values like
4073 1.0/0.0 - 1.0/0.0. Such expressions don't belong
4074 in VECTOR_CST nodes. */
4075 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
4076 if (!CONSTANT_CLASS_P (value))
4078 constant_p = false;
4079 break;
4082 if (constant_p)
4084 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
4085 break;
4088 TREE_CONSTANT (ctor) = 0;
4091 /* Vector types use CONSTRUCTOR all the way through gimple
4092 compilation as a general initializer. */
4093 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
4095 enum gimplify_status tret;
4096 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
4097 fb_rvalue);
4098 if (tret == GS_ERROR)
4099 ret = GS_ERROR;
4101 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
4102 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
4104 break;
4106 default:
4107 /* So how did we get a CONSTRUCTOR for a scalar type? */
4108 gcc_unreachable ();
4111 if (ret == GS_ERROR)
4112 return GS_ERROR;
4113 else if (want_value)
4115 *expr_p = object;
4116 return GS_OK;
4118 else
4120 /* If we have gimplified both sides of the initializer but have
4121 not emitted an assignment, do so now. */
4122 if (*expr_p)
4124 tree lhs = TREE_OPERAND (*expr_p, 0);
4125 tree rhs = TREE_OPERAND (*expr_p, 1);
4126 gassign *init = gimple_build_assign (lhs, rhs);
4127 gimplify_seq_add_stmt (pre_p, init);
4128 *expr_p = NULL;
4131 return GS_ALL_DONE;
4135 /* Given a pointer value OP0, return a simplified version of an
4136 indirection through OP0, or NULL_TREE if no simplification is
4137 possible. This may only be applied to a rhs of an expression.
4138 Note that the resulting type may be different from the type pointed
4139 to in the sense that it is still compatible from the langhooks
4140 point of view. */
4142 static tree
4143 gimple_fold_indirect_ref_rhs (tree t)
4145 return gimple_fold_indirect_ref (t);
4148 /* Subroutine of gimplify_modify_expr to do simplifications of
4149 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
4150 something changes. */
4152 static enum gimplify_status
4153 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
4154 gimple_seq *pre_p, gimple_seq *post_p,
4155 bool want_value)
4157 enum gimplify_status ret = GS_UNHANDLED;
4158 bool changed;
4162 changed = false;
4163 switch (TREE_CODE (*from_p))
4165 case VAR_DECL:
4166 /* If we're assigning from a read-only variable initialized with
4167 a constructor, do the direct assignment from the constructor,
4168 but only if neither source nor target are volatile since this
4169 latter assignment might end up being done on a per-field basis. */
4170 if (DECL_INITIAL (*from_p)
4171 && TREE_READONLY (*from_p)
4172 && !TREE_THIS_VOLATILE (*from_p)
4173 && !TREE_THIS_VOLATILE (*to_p)
4174 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR)
4176 tree old_from = *from_p;
4177 enum gimplify_status subret;
4179 /* Move the constructor into the RHS. */
4180 *from_p = unshare_expr (DECL_INITIAL (*from_p));
4182 /* Let's see if gimplify_init_constructor will need to put
4183 it in memory. */
4184 subret = gimplify_init_constructor (expr_p, NULL, NULL,
4185 false, true);
4186 if (subret == GS_ERROR)
4188 /* If so, revert the change. */
4189 *from_p = old_from;
4191 else
4193 ret = GS_OK;
4194 changed = true;
4197 break;
4198 case INDIRECT_REF:
4200 /* If we have code like
4202 *(const A*)(A*)&x
4204 where the type of "x" is a (possibly cv-qualified variant
4205 of "A"), treat the entire expression as identical to "x".
4206 This kind of code arises in C++ when an object is bound
4207 to a const reference, and if "x" is a TARGET_EXPR we want
4208 to take advantage of the optimization below. */
4209 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
4210 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
4211 if (t)
4213 if (TREE_THIS_VOLATILE (t) != volatile_p)
4215 if (DECL_P (t))
4216 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
4217 build_fold_addr_expr (t));
4218 if (REFERENCE_CLASS_P (t))
4219 TREE_THIS_VOLATILE (t) = volatile_p;
4221 *from_p = t;
4222 ret = GS_OK;
4223 changed = true;
4225 break;
4228 case TARGET_EXPR:
4230 /* If we are initializing something from a TARGET_EXPR, strip the
4231 TARGET_EXPR and initialize it directly, if possible. This can't
4232 be done if the initializer is void, since that implies that the
4233 temporary is set in some non-trivial way.
4235 ??? What about code that pulls out the temp and uses it
4236 elsewhere? I think that such code never uses the TARGET_EXPR as
4237 an initializer. If I'm wrong, we'll die because the temp won't
4238 have any RTL. In that case, I guess we'll need to replace
4239 references somehow. */
4240 tree init = TARGET_EXPR_INITIAL (*from_p);
4242 if (init
4243 && !VOID_TYPE_P (TREE_TYPE (init)))
4245 *from_p = init;
4246 ret = GS_OK;
4247 changed = true;
4250 break;
4252 case COMPOUND_EXPR:
4253 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
4254 caught. */
4255 gimplify_compound_expr (from_p, pre_p, true);
4256 ret = GS_OK;
4257 changed = true;
4258 break;
4260 case CONSTRUCTOR:
4261 /* If we already made some changes, let the front end have a
4262 crack at this before we break it down. */
4263 if (ret != GS_UNHANDLED)
4264 break;
4265 /* If we're initializing from a CONSTRUCTOR, break this into
4266 individual MODIFY_EXPRs. */
4267 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
4268 false);
4270 case COND_EXPR:
4271 /* If we're assigning to a non-register type, push the assignment
4272 down into the branches. This is mandatory for ADDRESSABLE types,
4273 since we cannot generate temporaries for such, but it saves a
4274 copy in other cases as well. */
4275 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
4277 /* This code should mirror the code in gimplify_cond_expr. */
4278 enum tree_code code = TREE_CODE (*expr_p);
4279 tree cond = *from_p;
4280 tree result = *to_p;
4282 ret = gimplify_expr (&result, pre_p, post_p,
4283 is_gimple_lvalue, fb_lvalue);
4284 if (ret != GS_ERROR)
4285 ret = GS_OK;
4287 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
4288 TREE_OPERAND (cond, 1)
4289 = build2 (code, void_type_node, result,
4290 TREE_OPERAND (cond, 1));
4291 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
4292 TREE_OPERAND (cond, 2)
4293 = build2 (code, void_type_node, unshare_expr (result),
4294 TREE_OPERAND (cond, 2));
4296 TREE_TYPE (cond) = void_type_node;
4297 recalculate_side_effects (cond);
4299 if (want_value)
4301 gimplify_and_add (cond, pre_p);
4302 *expr_p = unshare_expr (result);
4304 else
4305 *expr_p = cond;
4306 return ret;
4308 break;
4310 case CALL_EXPR:
4311 /* For calls that return in memory, give *to_p as the CALL_EXPR's
4312 return slot so that we don't generate a temporary. */
4313 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
4314 && aggregate_value_p (*from_p, *from_p))
4316 bool use_target;
4318 if (!(rhs_predicate_for (*to_p))(*from_p))
4319 /* If we need a temporary, *to_p isn't accurate. */
4320 use_target = false;
4321 /* It's OK to use the return slot directly unless it's an NRV. */
4322 else if (TREE_CODE (*to_p) == RESULT_DECL
4323 && DECL_NAME (*to_p) == NULL_TREE
4324 && needs_to_live_in_memory (*to_p))
4325 use_target = true;
4326 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
4327 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
4328 /* Don't force regs into memory. */
4329 use_target = false;
4330 else if (TREE_CODE (*expr_p) == INIT_EXPR)
4331 /* It's OK to use the target directly if it's being
4332 initialized. */
4333 use_target = true;
4334 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
4335 != INTEGER_CST)
4336 /* Always use the target and thus RSO for variable-sized types.
4337 GIMPLE cannot deal with a variable-sized assignment
4338 embedded in a call statement. */
4339 use_target = true;
4340 else if (TREE_CODE (*to_p) != SSA_NAME
4341 && (!is_gimple_variable (*to_p)
4342 || needs_to_live_in_memory (*to_p)))
4343 /* Don't use the original target if it's already addressable;
4344 if its address escapes, and the called function uses the
4345 NRV optimization, a conforming program could see *to_p
4346 change before the called function returns; see c++/19317.
4347 When optimizing, the return_slot pass marks more functions
4348 as safe after we have escape info. */
4349 use_target = false;
4350 else
4351 use_target = true;
4353 if (use_target)
4355 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
4356 mark_addressable (*to_p);
4359 break;
4361 case WITH_SIZE_EXPR:
4362 /* Likewise for calls that return an aggregate of non-constant size,
4363 since we would not be able to generate a temporary at all. */
4364 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
4366 *from_p = TREE_OPERAND (*from_p, 0);
4367 /* We don't change ret in this case because the
4368 WITH_SIZE_EXPR might have been added in
4369 gimplify_modify_expr, so returning GS_OK would lead to an
4370 infinite loop. */
4371 changed = true;
4373 break;
4375 /* If we're initializing from a container, push the initialization
4376 inside it. */
4377 case CLEANUP_POINT_EXPR:
4378 case BIND_EXPR:
4379 case STATEMENT_LIST:
4381 tree wrap = *from_p;
4382 tree t;
4384 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
4385 fb_lvalue);
4386 if (ret != GS_ERROR)
4387 ret = GS_OK;
4389 t = voidify_wrapper_expr (wrap, *expr_p);
4390 gcc_assert (t == *expr_p);
4392 if (want_value)
4394 gimplify_and_add (wrap, pre_p);
4395 *expr_p = unshare_expr (*to_p);
4397 else
4398 *expr_p = wrap;
4399 return GS_OK;
4402 case COMPOUND_LITERAL_EXPR:
4404 tree complit = TREE_OPERAND (*expr_p, 1);
4405 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
4406 tree decl = DECL_EXPR_DECL (decl_s);
4407 tree init = DECL_INITIAL (decl);
4409 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
4410 into struct T x = { 0, 1, 2 } if the address of the
4411 compound literal has never been taken. */
4412 if (!TREE_ADDRESSABLE (complit)
4413 && !TREE_ADDRESSABLE (decl)
4414 && init)
4416 *expr_p = copy_node (*expr_p);
4417 TREE_OPERAND (*expr_p, 1) = init;
4418 return GS_OK;
4422 default:
4423 break;
4426 while (changed);
4428 return ret;
4432 /* Return true if T looks like a valid GIMPLE statement. */
4434 static bool
4435 is_gimple_stmt (tree t)
4437 const enum tree_code code = TREE_CODE (t);
4439 switch (code)
4441 case NOP_EXPR:
4442 /* The only valid NOP_EXPR is the empty statement. */
4443 return IS_EMPTY_STMT (t);
4445 case BIND_EXPR:
4446 case COND_EXPR:
4447 /* These are only valid if they're void. */
4448 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
4450 case SWITCH_EXPR:
4451 case GOTO_EXPR:
4452 case RETURN_EXPR:
4453 case LABEL_EXPR:
4454 case CASE_LABEL_EXPR:
4455 case TRY_CATCH_EXPR:
4456 case TRY_FINALLY_EXPR:
4457 case EH_FILTER_EXPR:
4458 case CATCH_EXPR:
4459 case ASM_EXPR:
4460 case STATEMENT_LIST:
4461 case OACC_PARALLEL:
4462 case OACC_KERNELS:
4463 case OACC_DATA:
4464 case OACC_HOST_DATA:
4465 case OACC_DECLARE:
4466 case OACC_UPDATE:
4467 case OACC_ENTER_DATA:
4468 case OACC_EXIT_DATA:
4469 case OACC_CACHE:
4470 case OMP_PARALLEL:
4471 case OMP_FOR:
4472 case OMP_SIMD:
4473 case CILK_SIMD:
4474 case OMP_DISTRIBUTE:
4475 case OACC_LOOP:
4476 case OMP_SECTIONS:
4477 case OMP_SECTION:
4478 case OMP_SINGLE:
4479 case OMP_MASTER:
4480 case OMP_TASKGROUP:
4481 case OMP_ORDERED:
4482 case OMP_CRITICAL:
4483 case OMP_TASK:
4484 /* These are always void. */
4485 return true;
4487 case CALL_EXPR:
4488 case MODIFY_EXPR:
4489 case PREDICT_EXPR:
4490 /* These are valid regardless of their type. */
4491 return true;
4493 default:
4494 return false;
4499 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
4500 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
4501 DECL_GIMPLE_REG_P set.
4503 IMPORTANT NOTE: This promotion is performed by introducing a load of the
4504 other, unmodified part of the complex object just before the total store.
4505 As a consequence, if the object is still uninitialized, an undefined value
4506 will be loaded into a register, which may result in a spurious exception
4507 if the register is floating-point and the value happens to be a signaling
4508 NaN for example. Then the fully-fledged complex operations lowering pass
4509 followed by a DCE pass are necessary in order to fix things up. */
4511 static enum gimplify_status
4512 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
4513 bool want_value)
4515 enum tree_code code, ocode;
4516 tree lhs, rhs, new_rhs, other, realpart, imagpart;
4518 lhs = TREE_OPERAND (*expr_p, 0);
4519 rhs = TREE_OPERAND (*expr_p, 1);
4520 code = TREE_CODE (lhs);
4521 lhs = TREE_OPERAND (lhs, 0);
4523 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
4524 other = build1 (ocode, TREE_TYPE (rhs), lhs);
4525 TREE_NO_WARNING (other) = 1;
4526 other = get_formal_tmp_var (other, pre_p);
4528 realpart = code == REALPART_EXPR ? rhs : other;
4529 imagpart = code == REALPART_EXPR ? other : rhs;
4531 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
4532 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
4533 else
4534 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
4536 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
4537 *expr_p = (want_value) ? rhs : NULL_TREE;
4539 return GS_ALL_DONE;
4542 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
4544 modify_expr
4545 : varname '=' rhs
4546 | '*' ID '=' rhs
4548 PRE_P points to the list where side effects that must happen before
4549 *EXPR_P should be stored.
4551 POST_P points to the list where side effects that must happen after
4552 *EXPR_P should be stored.
4554 WANT_VALUE is nonzero iff we want to use the value of this expression
4555 in another expression. */
4557 static enum gimplify_status
4558 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4559 bool want_value)
4561 tree *from_p = &TREE_OPERAND (*expr_p, 1);
4562 tree *to_p = &TREE_OPERAND (*expr_p, 0);
4563 enum gimplify_status ret = GS_UNHANDLED;
4564 gimple assign;
4565 location_t loc = EXPR_LOCATION (*expr_p);
4566 gimple_stmt_iterator gsi;
4568 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
4569 || TREE_CODE (*expr_p) == INIT_EXPR);
4571 /* Trying to simplify a clobber using normal logic doesn't work,
4572 so handle it here. */
4573 if (TREE_CLOBBER_P (*from_p))
4575 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
4576 if (ret == GS_ERROR)
4577 return ret;
4578 gcc_assert (!want_value
4579 && (TREE_CODE (*to_p) == VAR_DECL
4580 || TREE_CODE (*to_p) == MEM_REF));
4581 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
4582 *expr_p = NULL;
4583 return GS_ALL_DONE;
4586 /* Insert pointer conversions required by the middle-end that are not
4587 required by the frontend. This fixes middle-end type checking for
4588 for example gcc.dg/redecl-6.c. */
4589 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
4591 STRIP_USELESS_TYPE_CONVERSION (*from_p);
4592 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
4593 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
4596 /* See if any simplifications can be done based on what the RHS is. */
4597 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
4598 want_value);
4599 if (ret != GS_UNHANDLED)
4600 return ret;
4602 /* For zero sized types only gimplify the left hand side and right hand
4603 side as statements and throw away the assignment. Do this after
4604 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
4605 types properly. */
4606 if (zero_sized_type (TREE_TYPE (*from_p)) && !want_value)
4608 gimplify_stmt (from_p, pre_p);
4609 gimplify_stmt (to_p, pre_p);
4610 *expr_p = NULL_TREE;
4611 return GS_ALL_DONE;
4614 /* If the value being copied is of variable width, compute the length
4615 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
4616 before gimplifying any of the operands so that we can resolve any
4617 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
4618 the size of the expression to be copied, not of the destination, so
4619 that is what we must do here. */
4620 maybe_with_size_expr (from_p);
4622 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
4623 if (ret == GS_ERROR)
4624 return ret;
4626 /* As a special case, we have to temporarily allow for assignments
4627 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
4628 a toplevel statement, when gimplifying the GENERIC expression
4629 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
4630 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
4632 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
4633 prevent gimplify_expr from trying to create a new temporary for
4634 foo's LHS, we tell it that it should only gimplify until it
4635 reaches the CALL_EXPR. On return from gimplify_expr, the newly
4636 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
4637 and all we need to do here is set 'a' to be its LHS. */
4638 ret = gimplify_expr (from_p, pre_p, post_p, rhs_predicate_for (*to_p),
4639 fb_rvalue);
4640 if (ret == GS_ERROR)
4641 return ret;
4643 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
4644 size as argument to the the call. */
4645 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
4647 tree call = TREE_OPERAND (*from_p, 0);
4648 tree vlasize = TREE_OPERAND (*from_p, 1);
4650 if (TREE_CODE (call) == CALL_EXPR
4651 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
4653 int nargs = call_expr_nargs (call);
4654 tree type = TREE_TYPE (call);
4655 tree ap = CALL_EXPR_ARG (call, 0);
4656 tree tag = CALL_EXPR_ARG (call, 1);
4657 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
4658 IFN_VA_ARG, type,
4659 nargs + 1, ap, tag,
4660 vlasize);
4661 tree *call_p = &(TREE_OPERAND (*from_p, 0));
4662 *call_p = newcall;
4666 /* Now see if the above changed *from_p to something we handle specially. */
4667 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
4668 want_value);
4669 if (ret != GS_UNHANDLED)
4670 return ret;
4672 /* If we've got a variable sized assignment between two lvalues (i.e. does
4673 not involve a call), then we can make things a bit more straightforward
4674 by converting the assignment to memcpy or memset. */
4675 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
4677 tree from = TREE_OPERAND (*from_p, 0);
4678 tree size = TREE_OPERAND (*from_p, 1);
4680 if (TREE_CODE (from) == CONSTRUCTOR)
4681 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
4683 if (is_gimple_addressable (from))
4685 *from_p = from;
4686 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
4687 pre_p);
4691 /* Transform partial stores to non-addressable complex variables into
4692 total stores. This allows us to use real instead of virtual operands
4693 for these variables, which improves optimization. */
4694 if ((TREE_CODE (*to_p) == REALPART_EXPR
4695 || TREE_CODE (*to_p) == IMAGPART_EXPR)
4696 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
4697 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
4699 /* Try to alleviate the effects of the gimplification creating artificial
4700 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
4701 make sure not to create DECL_DEBUG_EXPR links across functions. */
4702 if (!gimplify_ctxp->into_ssa
4703 && TREE_CODE (*from_p) == VAR_DECL
4704 && DECL_IGNORED_P (*from_p)
4705 && DECL_P (*to_p)
4706 && !DECL_IGNORED_P (*to_p)
4707 && decl_function_context (*to_p) == current_function_decl)
4709 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
4710 DECL_NAME (*from_p)
4711 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
4712 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
4713 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
4716 if (want_value && TREE_THIS_VOLATILE (*to_p))
4717 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
4719 if (TREE_CODE (*from_p) == CALL_EXPR)
4721 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
4722 instead of a GIMPLE_ASSIGN. */
4723 gcall *call_stmt;
4724 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
4726 /* Gimplify internal functions created in the FEs. */
4727 int nargs = call_expr_nargs (*from_p), i;
4728 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
4729 auto_vec<tree> vargs (nargs);
4731 for (i = 0; i < nargs; i++)
4733 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
4734 EXPR_LOCATION (*from_p));
4735 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
4737 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
4738 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
4740 else
4742 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
4743 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
4744 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
4745 tree fndecl = get_callee_fndecl (*from_p);
4746 if (fndecl
4747 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL
4748 && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_EXPECT
4749 && call_expr_nargs (*from_p) == 3)
4750 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
4751 CALL_EXPR_ARG (*from_p, 0),
4752 CALL_EXPR_ARG (*from_p, 1),
4753 CALL_EXPR_ARG (*from_p, 2));
4754 else
4756 call_stmt = gimple_build_call_from_tree (*from_p);
4757 gimple_call_set_fntype (call_stmt, TREE_TYPE (fnptrtype));
4760 notice_special_calls (call_stmt);
4761 if (!gimple_call_noreturn_p (call_stmt))
4762 gimple_call_set_lhs (call_stmt, *to_p);
4763 assign = call_stmt;
4765 else
4767 assign = gimple_build_assign (*to_p, *from_p);
4768 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
4771 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
4773 /* We should have got an SSA name from the start. */
4774 gcc_assert (TREE_CODE (*to_p) == SSA_NAME);
4777 gimplify_seq_add_stmt (pre_p, assign);
4778 gsi = gsi_last (*pre_p);
4779 maybe_fold_stmt (&gsi);
4781 if (want_value)
4783 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
4784 return GS_OK;
4786 else
4787 *expr_p = NULL;
4789 return GS_ALL_DONE;
4792 /* Gimplify a comparison between two variable-sized objects. Do this
4793 with a call to BUILT_IN_MEMCMP. */
4795 static enum gimplify_status
4796 gimplify_variable_sized_compare (tree *expr_p)
4798 location_t loc = EXPR_LOCATION (*expr_p);
4799 tree op0 = TREE_OPERAND (*expr_p, 0);
4800 tree op1 = TREE_OPERAND (*expr_p, 1);
4801 tree t, arg, dest, src, expr;
4803 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
4804 arg = unshare_expr (arg);
4805 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
4806 src = build_fold_addr_expr_loc (loc, op1);
4807 dest = build_fold_addr_expr_loc (loc, op0);
4808 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
4809 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
4811 expr
4812 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
4813 SET_EXPR_LOCATION (expr, loc);
4814 *expr_p = expr;
4816 return GS_OK;
4819 /* Gimplify a comparison between two aggregate objects of integral scalar
4820 mode as a comparison between the bitwise equivalent scalar values. */
4822 static enum gimplify_status
4823 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
4825 location_t loc = EXPR_LOCATION (*expr_p);
4826 tree op0 = TREE_OPERAND (*expr_p, 0);
4827 tree op1 = TREE_OPERAND (*expr_p, 1);
4829 tree type = TREE_TYPE (op0);
4830 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
4832 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
4833 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
4835 *expr_p
4836 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
4838 return GS_OK;
4841 /* Gimplify an expression sequence. This function gimplifies each
4842 expression and rewrites the original expression with the last
4843 expression of the sequence in GIMPLE form.
4845 PRE_P points to the list where the side effects for all the
4846 expressions in the sequence will be emitted.
4848 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
4850 static enum gimplify_status
4851 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
4853 tree t = *expr_p;
4857 tree *sub_p = &TREE_OPERAND (t, 0);
4859 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
4860 gimplify_compound_expr (sub_p, pre_p, false);
4861 else
4862 gimplify_stmt (sub_p, pre_p);
4864 t = TREE_OPERAND (t, 1);
4866 while (TREE_CODE (t) == COMPOUND_EXPR);
4868 *expr_p = t;
4869 if (want_value)
4870 return GS_OK;
4871 else
4873 gimplify_stmt (expr_p, pre_p);
4874 return GS_ALL_DONE;
4878 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
4879 gimplify. After gimplification, EXPR_P will point to a new temporary
4880 that holds the original value of the SAVE_EXPR node.
4882 PRE_P points to the list where side effects that must happen before
4883 *EXPR_P should be stored. */
4885 static enum gimplify_status
4886 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
4888 enum gimplify_status ret = GS_ALL_DONE;
4889 tree val;
4891 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
4892 val = TREE_OPERAND (*expr_p, 0);
4894 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
4895 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
4897 /* The operand may be a void-valued expression such as SAVE_EXPRs
4898 generated by the Java frontend for class initialization. It is
4899 being executed only for its side-effects. */
4900 if (TREE_TYPE (val) == void_type_node)
4902 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
4903 is_gimple_stmt, fb_none);
4904 val = NULL;
4906 else
4907 val = get_initialized_tmp_var (val, pre_p, post_p);
4909 TREE_OPERAND (*expr_p, 0) = val;
4910 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
4913 *expr_p = val;
4915 return ret;
4918 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
4920 unary_expr
4921 : ...
4922 | '&' varname
4925 PRE_P points to the list where side effects that must happen before
4926 *EXPR_P should be stored.
4928 POST_P points to the list where side effects that must happen after
4929 *EXPR_P should be stored. */
4931 static enum gimplify_status
4932 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
4934 tree expr = *expr_p;
4935 tree op0 = TREE_OPERAND (expr, 0);
4936 enum gimplify_status ret;
4937 location_t loc = EXPR_LOCATION (*expr_p);
4939 switch (TREE_CODE (op0))
4941 case INDIRECT_REF:
4942 do_indirect_ref:
4943 /* Check if we are dealing with an expression of the form '&*ptr'.
4944 While the front end folds away '&*ptr' into 'ptr', these
4945 expressions may be generated internally by the compiler (e.g.,
4946 builtins like __builtin_va_end). */
4947 /* Caution: the silent array decomposition semantics we allow for
4948 ADDR_EXPR means we can't always discard the pair. */
4949 /* Gimplification of the ADDR_EXPR operand may drop
4950 cv-qualification conversions, so make sure we add them if
4951 needed. */
4953 tree op00 = TREE_OPERAND (op0, 0);
4954 tree t_expr = TREE_TYPE (expr);
4955 tree t_op00 = TREE_TYPE (op00);
4957 if (!useless_type_conversion_p (t_expr, t_op00))
4958 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
4959 *expr_p = op00;
4960 ret = GS_OK;
4962 break;
4964 case VIEW_CONVERT_EXPR:
4965 /* Take the address of our operand and then convert it to the type of
4966 this ADDR_EXPR.
4968 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
4969 all clear. The impact of this transformation is even less clear. */
4971 /* If the operand is a useless conversion, look through it. Doing so
4972 guarantees that the ADDR_EXPR and its operand will remain of the
4973 same type. */
4974 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
4975 op0 = TREE_OPERAND (op0, 0);
4977 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
4978 build_fold_addr_expr_loc (loc,
4979 TREE_OPERAND (op0, 0)));
4980 ret = GS_OK;
4981 break;
4983 default:
4984 /* If we see a call to a declared builtin or see its address
4985 being taken (we can unify those cases here) then we can mark
4986 the builtin for implicit generation by GCC. */
4987 if (TREE_CODE (op0) == FUNCTION_DECL
4988 && DECL_BUILT_IN_CLASS (op0) == BUILT_IN_NORMAL
4989 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
4990 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
4992 /* We use fb_either here because the C frontend sometimes takes
4993 the address of a call that returns a struct; see
4994 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
4995 the implied temporary explicit. */
4997 /* Make the operand addressable. */
4998 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
4999 is_gimple_addressable, fb_either);
5000 if (ret == GS_ERROR)
5001 break;
5003 /* Then mark it. Beware that it may not be possible to do so directly
5004 if a temporary has been created by the gimplification. */
5005 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
5007 op0 = TREE_OPERAND (expr, 0);
5009 /* For various reasons, the gimplification of the expression
5010 may have made a new INDIRECT_REF. */
5011 if (TREE_CODE (op0) == INDIRECT_REF)
5012 goto do_indirect_ref;
5014 mark_addressable (TREE_OPERAND (expr, 0));
5016 /* The FEs may end up building ADDR_EXPRs early on a decl with
5017 an incomplete type. Re-build ADDR_EXPRs in canonical form
5018 here. */
5019 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
5020 *expr_p = build_fold_addr_expr (op0);
5022 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
5023 recompute_tree_invariant_for_addr_expr (*expr_p);
5025 /* If we re-built the ADDR_EXPR add a conversion to the original type
5026 if required. */
5027 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
5028 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
5030 break;
5033 return ret;
5036 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
5037 value; output operands should be a gimple lvalue. */
5039 static enum gimplify_status
5040 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5042 tree expr;
5043 int noutputs;
5044 const char **oconstraints;
5045 int i;
5046 tree link;
5047 const char *constraint;
5048 bool allows_mem, allows_reg, is_inout;
5049 enum gimplify_status ret, tret;
5050 gasm *stmt;
5051 vec<tree, va_gc> *inputs;
5052 vec<tree, va_gc> *outputs;
5053 vec<tree, va_gc> *clobbers;
5054 vec<tree, va_gc> *labels;
5055 tree link_next;
5057 expr = *expr_p;
5058 noutputs = list_length (ASM_OUTPUTS (expr));
5059 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
5061 inputs = NULL;
5062 outputs = NULL;
5063 clobbers = NULL;
5064 labels = NULL;
5066 ret = GS_ALL_DONE;
5067 link_next = NULL_TREE;
5068 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
5070 bool ok;
5071 size_t constraint_len;
5073 link_next = TREE_CHAIN (link);
5075 oconstraints[i]
5076 = constraint
5077 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
5078 constraint_len = strlen (constraint);
5079 if (constraint_len == 0)
5080 continue;
5082 ok = parse_output_constraint (&constraint, i, 0, 0,
5083 &allows_mem, &allows_reg, &is_inout);
5084 if (!ok)
5086 ret = GS_ERROR;
5087 is_inout = false;
5090 if (!allows_reg && allows_mem)
5091 mark_addressable (TREE_VALUE (link));
5093 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5094 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
5095 fb_lvalue | fb_mayfail);
5096 if (tret == GS_ERROR)
5098 error ("invalid lvalue in asm output %d", i);
5099 ret = tret;
5102 vec_safe_push (outputs, link);
5103 TREE_CHAIN (link) = NULL_TREE;
5105 if (is_inout)
5107 /* An input/output operand. To give the optimizers more
5108 flexibility, split it into separate input and output
5109 operands. */
5110 tree input;
5111 char buf[10];
5113 /* Turn the in/out constraint into an output constraint. */
5114 char *p = xstrdup (constraint);
5115 p[0] = '=';
5116 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
5118 /* And add a matching input constraint. */
5119 if (allows_reg)
5121 sprintf (buf, "%d", i);
5123 /* If there are multiple alternatives in the constraint,
5124 handle each of them individually. Those that allow register
5125 will be replaced with operand number, the others will stay
5126 unchanged. */
5127 if (strchr (p, ',') != NULL)
5129 size_t len = 0, buflen = strlen (buf);
5130 char *beg, *end, *str, *dst;
5132 for (beg = p + 1;;)
5134 end = strchr (beg, ',');
5135 if (end == NULL)
5136 end = strchr (beg, '\0');
5137 if ((size_t) (end - beg) < buflen)
5138 len += buflen + 1;
5139 else
5140 len += end - beg + 1;
5141 if (*end)
5142 beg = end + 1;
5143 else
5144 break;
5147 str = (char *) alloca (len);
5148 for (beg = p + 1, dst = str;;)
5150 const char *tem;
5151 bool mem_p, reg_p, inout_p;
5153 end = strchr (beg, ',');
5154 if (end)
5155 *end = '\0';
5156 beg[-1] = '=';
5157 tem = beg - 1;
5158 parse_output_constraint (&tem, i, 0, 0,
5159 &mem_p, &reg_p, &inout_p);
5160 if (dst != str)
5161 *dst++ = ',';
5162 if (reg_p)
5164 memcpy (dst, buf, buflen);
5165 dst += buflen;
5167 else
5169 if (end)
5170 len = end - beg;
5171 else
5172 len = strlen (beg);
5173 memcpy (dst, beg, len);
5174 dst += len;
5176 if (end)
5177 beg = end + 1;
5178 else
5179 break;
5181 *dst = '\0';
5182 input = build_string (dst - str, str);
5184 else
5185 input = build_string (strlen (buf), buf);
5187 else
5188 input = build_string (constraint_len - 1, constraint + 1);
5190 free (p);
5192 input = build_tree_list (build_tree_list (NULL_TREE, input),
5193 unshare_expr (TREE_VALUE (link)));
5194 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
5198 link_next = NULL_TREE;
5199 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
5201 link_next = TREE_CHAIN (link);
5202 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
5203 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
5204 oconstraints, &allows_mem, &allows_reg);
5206 /* If we can't make copies, we can only accept memory. */
5207 if (TREE_ADDRESSABLE (TREE_TYPE (TREE_VALUE (link))))
5209 if (allows_mem)
5210 allows_reg = 0;
5211 else
5213 error ("impossible constraint in %<asm%>");
5214 error ("non-memory input %d must stay in memory", i);
5215 return GS_ERROR;
5219 /* If the operand is a memory input, it should be an lvalue. */
5220 if (!allows_reg && allows_mem)
5222 tree inputv = TREE_VALUE (link);
5223 STRIP_NOPS (inputv);
5224 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
5225 || TREE_CODE (inputv) == PREINCREMENT_EXPR
5226 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
5227 || TREE_CODE (inputv) == POSTINCREMENT_EXPR)
5228 TREE_VALUE (link) = error_mark_node;
5229 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5230 is_gimple_lvalue, fb_lvalue | fb_mayfail);
5231 mark_addressable (TREE_VALUE (link));
5232 if (tret == GS_ERROR)
5234 if (EXPR_HAS_LOCATION (TREE_VALUE (link)))
5235 input_location = EXPR_LOCATION (TREE_VALUE (link));
5236 error ("memory input %d is not directly addressable", i);
5237 ret = tret;
5240 else
5242 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5243 is_gimple_asm_val, fb_rvalue);
5244 if (tret == GS_ERROR)
5245 ret = tret;
5248 TREE_CHAIN (link) = NULL_TREE;
5249 vec_safe_push (inputs, link);
5252 link_next = NULL_TREE;
5253 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
5255 link_next = TREE_CHAIN (link);
5256 TREE_CHAIN (link) = NULL_TREE;
5257 vec_safe_push (clobbers, link);
5260 link_next = NULL_TREE;
5261 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
5263 link_next = TREE_CHAIN (link);
5264 TREE_CHAIN (link) = NULL_TREE;
5265 vec_safe_push (labels, link);
5268 /* Do not add ASMs with errors to the gimple IL stream. */
5269 if (ret != GS_ERROR)
5271 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
5272 inputs, outputs, clobbers, labels);
5274 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
5275 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
5277 gimplify_seq_add_stmt (pre_p, stmt);
5280 return ret;
5283 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
5284 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
5285 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
5286 return to this function.
5288 FIXME should we complexify the prequeue handling instead? Or use flags
5289 for all the cleanups and let the optimizer tighten them up? The current
5290 code seems pretty fragile; it will break on a cleanup within any
5291 non-conditional nesting. But any such nesting would be broken, anyway;
5292 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
5293 and continues out of it. We can do that at the RTL level, though, so
5294 having an optimizer to tighten up try/finally regions would be a Good
5295 Thing. */
5297 static enum gimplify_status
5298 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
5300 gimple_stmt_iterator iter;
5301 gimple_seq body_sequence = NULL;
5303 tree temp = voidify_wrapper_expr (*expr_p, NULL);
5305 /* We only care about the number of conditions between the innermost
5306 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
5307 any cleanups collected outside the CLEANUP_POINT_EXPR. */
5308 int old_conds = gimplify_ctxp->conditions;
5309 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
5310 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
5311 gimplify_ctxp->conditions = 0;
5312 gimplify_ctxp->conditional_cleanups = NULL;
5313 gimplify_ctxp->in_cleanup_point_expr = true;
5315 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
5317 gimplify_ctxp->conditions = old_conds;
5318 gimplify_ctxp->conditional_cleanups = old_cleanups;
5319 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
5321 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
5323 gimple wce = gsi_stmt (iter);
5325 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
5327 if (gsi_one_before_end_p (iter))
5329 /* Note that gsi_insert_seq_before and gsi_remove do not
5330 scan operands, unlike some other sequence mutators. */
5331 if (!gimple_wce_cleanup_eh_only (wce))
5332 gsi_insert_seq_before_without_update (&iter,
5333 gimple_wce_cleanup (wce),
5334 GSI_SAME_STMT);
5335 gsi_remove (&iter, true);
5336 break;
5338 else
5340 gtry *gtry;
5341 gimple_seq seq;
5342 enum gimple_try_flags kind;
5344 if (gimple_wce_cleanup_eh_only (wce))
5345 kind = GIMPLE_TRY_CATCH;
5346 else
5347 kind = GIMPLE_TRY_FINALLY;
5348 seq = gsi_split_seq_after (iter);
5350 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
5351 /* Do not use gsi_replace here, as it may scan operands.
5352 We want to do a simple structural modification only. */
5353 gsi_set_stmt (&iter, gtry);
5354 iter = gsi_start (gtry->eval);
5357 else
5358 gsi_next (&iter);
5361 gimplify_seq_add_seq (pre_p, body_sequence);
5362 if (temp)
5364 *expr_p = temp;
5365 return GS_OK;
5367 else
5369 *expr_p = NULL;
5370 return GS_ALL_DONE;
5374 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
5375 is the cleanup action required. EH_ONLY is true if the cleanup should
5376 only be executed if an exception is thrown, not on normal exit. */
5378 static void
5379 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p)
5381 gimple wce;
5382 gimple_seq cleanup_stmts = NULL;
5384 /* Errors can result in improperly nested cleanups. Which results in
5385 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
5386 if (seen_error ())
5387 return;
5389 if (gimple_conditional_context ())
5391 /* If we're in a conditional context, this is more complex. We only
5392 want to run the cleanup if we actually ran the initialization that
5393 necessitates it, but we want to run it after the end of the
5394 conditional context. So we wrap the try/finally around the
5395 condition and use a flag to determine whether or not to actually
5396 run the destructor. Thus
5398 test ? f(A()) : 0
5400 becomes (approximately)
5402 flag = 0;
5403 try {
5404 if (test) { A::A(temp); flag = 1; val = f(temp); }
5405 else { val = 0; }
5406 } finally {
5407 if (flag) A::~A(temp);
5411 tree flag = create_tmp_var (boolean_type_node, "cleanup");
5412 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
5413 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
5415 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
5416 gimplify_stmt (&cleanup, &cleanup_stmts);
5417 wce = gimple_build_wce (cleanup_stmts);
5419 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
5420 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
5421 gimplify_seq_add_stmt (pre_p, ftrue);
5423 /* Because of this manipulation, and the EH edges that jump
5424 threading cannot redirect, the temporary (VAR) will appear
5425 to be used uninitialized. Don't warn. */
5426 TREE_NO_WARNING (var) = 1;
5428 else
5430 gimplify_stmt (&cleanup, &cleanup_stmts);
5431 wce = gimple_build_wce (cleanup_stmts);
5432 gimple_wce_set_cleanup_eh_only (wce, eh_only);
5433 gimplify_seq_add_stmt (pre_p, wce);
5437 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
5439 static enum gimplify_status
5440 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5442 tree targ = *expr_p;
5443 tree temp = TARGET_EXPR_SLOT (targ);
5444 tree init = TARGET_EXPR_INITIAL (targ);
5445 enum gimplify_status ret;
5447 if (init)
5449 tree cleanup = NULL_TREE;
5451 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
5452 to the temps list. Handle also variable length TARGET_EXPRs. */
5453 if (TREE_CODE (DECL_SIZE (temp)) != INTEGER_CST)
5455 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
5456 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
5457 gimplify_vla_decl (temp, pre_p);
5459 else
5460 gimple_add_tmp_var (temp);
5462 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
5463 expression is supposed to initialize the slot. */
5464 if (VOID_TYPE_P (TREE_TYPE (init)))
5465 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
5466 else
5468 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
5469 init = init_expr;
5470 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
5471 init = NULL;
5472 ggc_free (init_expr);
5474 if (ret == GS_ERROR)
5476 /* PR c++/28266 Make sure this is expanded only once. */
5477 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
5478 return GS_ERROR;
5480 if (init)
5481 gimplify_and_add (init, pre_p);
5483 /* If needed, push the cleanup for the temp. */
5484 if (TARGET_EXPR_CLEANUP (targ))
5486 if (CLEANUP_EH_ONLY (targ))
5487 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
5488 CLEANUP_EH_ONLY (targ), pre_p);
5489 else
5490 cleanup = TARGET_EXPR_CLEANUP (targ);
5493 /* Add a clobber for the temporary going out of scope, like
5494 gimplify_bind_expr. */
5495 if (gimplify_ctxp->in_cleanup_point_expr
5496 && needs_to_live_in_memory (temp)
5497 && flag_stack_reuse == SR_ALL)
5499 tree clobber = build_constructor (TREE_TYPE (temp),
5500 NULL);
5501 TREE_THIS_VOLATILE (clobber) = true;
5502 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
5503 if (cleanup)
5504 cleanup = build2 (COMPOUND_EXPR, void_type_node, cleanup,
5505 clobber);
5506 else
5507 cleanup = clobber;
5510 if (cleanup)
5511 gimple_push_cleanup (temp, cleanup, false, pre_p);
5513 /* Only expand this once. */
5514 TREE_OPERAND (targ, 3) = init;
5515 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
5517 else
5518 /* We should have expanded this before. */
5519 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
5521 *expr_p = temp;
5522 return GS_OK;
5525 /* Gimplification of expression trees. */
5527 /* Gimplify an expression which appears at statement context. The
5528 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
5529 NULL, a new sequence is allocated.
5531 Return true if we actually added a statement to the queue. */
5533 bool
5534 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
5536 gimple_seq_node last;
5538 last = gimple_seq_last (*seq_p);
5539 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
5540 return last != gimple_seq_last (*seq_p);
5543 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
5544 to CTX. If entries already exist, force them to be some flavor of private.
5545 If there is no enclosing parallel, do nothing. */
5547 void
5548 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
5550 splay_tree_node n;
5552 if (decl == NULL || !DECL_P (decl))
5553 return;
5557 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5558 if (n != NULL)
5560 if (n->value & GOVD_SHARED)
5561 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
5562 else if (n->value & GOVD_MAP)
5563 n->value |= GOVD_MAP_TO_ONLY;
5564 else
5565 return;
5567 else if (ctx->region_type == ORT_TARGET)
5568 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
5569 else if (ctx->region_type != ORT_WORKSHARE
5570 && ctx->region_type != ORT_SIMD
5571 && ctx->region_type != ORT_TARGET_DATA)
5572 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
5574 ctx = ctx->outer_context;
5576 while (ctx);
5579 /* Similarly for each of the type sizes of TYPE. */
5581 static void
5582 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
5584 if (type == NULL || type == error_mark_node)
5585 return;
5586 type = TYPE_MAIN_VARIANT (type);
5588 if (ctx->privatized_types->add (type))
5589 return;
5591 switch (TREE_CODE (type))
5593 case INTEGER_TYPE:
5594 case ENUMERAL_TYPE:
5595 case BOOLEAN_TYPE:
5596 case REAL_TYPE:
5597 case FIXED_POINT_TYPE:
5598 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
5599 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
5600 break;
5602 case ARRAY_TYPE:
5603 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
5604 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
5605 break;
5607 case RECORD_TYPE:
5608 case UNION_TYPE:
5609 case QUAL_UNION_TYPE:
5611 tree field;
5612 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
5613 if (TREE_CODE (field) == FIELD_DECL)
5615 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
5616 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
5619 break;
5621 case POINTER_TYPE:
5622 case REFERENCE_TYPE:
5623 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
5624 break;
5626 default:
5627 break;
5630 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
5631 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
5632 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
5635 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
5637 static void
5638 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
5640 splay_tree_node n;
5641 unsigned int nflags;
5642 tree t;
5644 if (error_operand_p (decl))
5645 return;
5647 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
5648 there are constructors involved somewhere. */
5649 if (TREE_ADDRESSABLE (TREE_TYPE (decl))
5650 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
5651 flags |= GOVD_SEEN;
5653 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5654 if (n != NULL && n->value != GOVD_ALIGNED)
5656 /* We shouldn't be re-adding the decl with the same data
5657 sharing class. */
5658 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
5659 /* The only combination of data sharing classes we should see is
5660 FIRSTPRIVATE and LASTPRIVATE. */
5661 nflags = n->value | flags;
5662 gcc_assert ((nflags & GOVD_DATA_SHARE_CLASS)
5663 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE)
5664 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
5665 n->value = nflags;
5666 return;
5669 /* When adding a variable-sized variable, we have to handle all sorts
5670 of additional bits of data: the pointer replacement variable, and
5671 the parameters of the type. */
5672 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
5674 /* Add the pointer replacement variable as PRIVATE if the variable
5675 replacement is private, else FIRSTPRIVATE since we'll need the
5676 address of the original variable either for SHARED, or for the
5677 copy into or out of the context. */
5678 if (!(flags & GOVD_LOCAL))
5680 if (flags & GOVD_MAP)
5681 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
5682 else if (flags & GOVD_PRIVATE)
5683 nflags = GOVD_PRIVATE;
5684 else
5685 nflags = GOVD_FIRSTPRIVATE;
5686 nflags |= flags & GOVD_SEEN;
5687 t = DECL_VALUE_EXPR (decl);
5688 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
5689 t = TREE_OPERAND (t, 0);
5690 gcc_assert (DECL_P (t));
5691 omp_add_variable (ctx, t, nflags);
5694 /* Add all of the variable and type parameters (which should have
5695 been gimplified to a formal temporary) as FIRSTPRIVATE. */
5696 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
5697 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
5698 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
5700 /* The variable-sized variable itself is never SHARED, only some form
5701 of PRIVATE. The sharing would take place via the pointer variable
5702 which we remapped above. */
5703 if (flags & GOVD_SHARED)
5704 flags = GOVD_PRIVATE | GOVD_DEBUG_PRIVATE
5705 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
5707 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
5708 alloca statement we generate for the variable, so make sure it
5709 is available. This isn't automatically needed for the SHARED
5710 case, since we won't be allocating local storage then.
5711 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
5712 in this case omp_notice_variable will be called later
5713 on when it is gimplified. */
5714 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
5715 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
5716 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
5718 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
5719 && lang_hooks.decls.omp_privatize_by_reference (decl))
5721 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
5723 /* Similar to the direct variable sized case above, we'll need the
5724 size of references being privatized. */
5725 if ((flags & GOVD_SHARED) == 0)
5727 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
5728 if (TREE_CODE (t) != INTEGER_CST)
5729 omp_notice_variable (ctx, t, true);
5733 if (n != NULL)
5734 n->value |= flags;
5735 else
5736 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
5739 /* Notice a threadprivate variable DECL used in OMP context CTX.
5740 This just prints out diagnostics about threadprivate variable uses
5741 in untied tasks. If DECL2 is non-NULL, prevent this warning
5742 on that variable. */
5744 static bool
5745 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
5746 tree decl2)
5748 splay_tree_node n;
5749 struct gimplify_omp_ctx *octx;
5751 for (octx = ctx; octx; octx = octx->outer_context)
5752 if (octx->region_type == ORT_TARGET)
5754 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
5755 if (n == NULL)
5757 error ("threadprivate variable %qE used in target region",
5758 DECL_NAME (decl));
5759 error_at (octx->location, "enclosing target region");
5760 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
5762 if (decl2)
5763 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
5766 if (ctx->region_type != ORT_UNTIED_TASK)
5767 return false;
5768 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5769 if (n == NULL)
5771 error ("threadprivate variable %qE used in untied task",
5772 DECL_NAME (decl));
5773 error_at (ctx->location, "enclosing task");
5774 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
5776 if (decl2)
5777 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
5778 return false;
5781 /* Record the fact that DECL was used within the OMP context CTX.
5782 IN_CODE is true when real code uses DECL, and false when we should
5783 merely emit default(none) errors. Return true if DECL is going to
5784 be remapped and thus DECL shouldn't be gimplified into its
5785 DECL_VALUE_EXPR (if any). */
5787 static bool
5788 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
5790 splay_tree_node n;
5791 unsigned flags = in_code ? GOVD_SEEN : 0;
5792 bool ret = false, shared;
5794 if (error_operand_p (decl))
5795 return false;
5797 /* Threadprivate variables are predetermined. */
5798 if (is_global_var (decl))
5800 if (DECL_THREAD_LOCAL_P (decl))
5801 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
5803 if (DECL_HAS_VALUE_EXPR_P (decl))
5805 tree value = get_base_address (DECL_VALUE_EXPR (decl));
5807 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
5808 return omp_notice_threadprivate_variable (ctx, decl, value);
5812 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5813 if (ctx->region_type == ORT_TARGET)
5815 ret = lang_hooks.decls.omp_disregard_value_expr (decl, true);
5816 if (n == NULL)
5818 if (!lang_hooks.types.omp_mappable_type (TREE_TYPE (decl)))
5820 error ("%qD referenced in target region does not have "
5821 "a mappable type", decl);
5822 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_EXPLICIT | flags);
5824 else
5825 omp_add_variable (ctx, decl, GOVD_MAP | flags);
5827 else
5829 /* If nothing changed, there's nothing left to do. */
5830 if ((n->value & flags) == flags)
5831 return ret;
5832 n->value |= flags;
5834 goto do_outer;
5837 if (n == NULL)
5839 enum omp_clause_default_kind default_kind, kind;
5840 struct gimplify_omp_ctx *octx;
5842 if (ctx->region_type == ORT_WORKSHARE
5843 || ctx->region_type == ORT_SIMD
5844 || ctx->region_type == ORT_TARGET_DATA)
5845 goto do_outer;
5847 /* ??? Some compiler-generated variables (like SAVE_EXPRs) could be
5848 remapped firstprivate instead of shared. To some extent this is
5849 addressed in omp_firstprivatize_type_sizes, but not effectively. */
5850 default_kind = ctx->default_kind;
5851 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
5852 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
5853 default_kind = kind;
5855 switch (default_kind)
5857 case OMP_CLAUSE_DEFAULT_NONE:
5858 if ((ctx->region_type & ORT_PARALLEL) != 0)
5860 error ("%qE not specified in enclosing parallel",
5861 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5862 error_at (ctx->location, "enclosing parallel");
5864 else if ((ctx->region_type & ORT_TASK) != 0)
5866 error ("%qE not specified in enclosing task",
5867 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5868 error_at (ctx->location, "enclosing task");
5870 else if (ctx->region_type & ORT_TEAMS)
5872 error ("%qE not specified in enclosing teams construct",
5873 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5874 error_at (ctx->location, "enclosing teams construct");
5876 else
5877 gcc_unreachable ();
5878 /* FALLTHRU */
5879 case OMP_CLAUSE_DEFAULT_SHARED:
5880 flags |= GOVD_SHARED;
5881 break;
5882 case OMP_CLAUSE_DEFAULT_PRIVATE:
5883 flags |= GOVD_PRIVATE;
5884 break;
5885 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
5886 flags |= GOVD_FIRSTPRIVATE;
5887 break;
5888 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
5889 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
5890 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
5891 if (ctx->outer_context)
5892 omp_notice_variable (ctx->outer_context, decl, in_code);
5893 for (octx = ctx->outer_context; octx; octx = octx->outer_context)
5895 splay_tree_node n2;
5897 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0)
5898 continue;
5899 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
5900 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
5902 flags |= GOVD_FIRSTPRIVATE;
5903 break;
5905 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
5906 break;
5908 if (flags & GOVD_FIRSTPRIVATE)
5909 break;
5910 if (octx == NULL
5911 && (TREE_CODE (decl) == PARM_DECL
5912 || (!is_global_var (decl)
5913 && DECL_CONTEXT (decl) == current_function_decl)))
5915 flags |= GOVD_FIRSTPRIVATE;
5916 break;
5918 flags |= GOVD_SHARED;
5919 break;
5920 default:
5921 gcc_unreachable ();
5924 if ((flags & GOVD_PRIVATE)
5925 && lang_hooks.decls.omp_private_outer_ref (decl))
5926 flags |= GOVD_PRIVATE_OUTER_REF;
5928 omp_add_variable (ctx, decl, flags);
5930 shared = (flags & GOVD_SHARED) != 0;
5931 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
5932 goto do_outer;
5935 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
5936 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
5937 && DECL_SIZE (decl)
5938 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
5940 splay_tree_node n2;
5941 tree t = DECL_VALUE_EXPR (decl);
5942 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
5943 t = TREE_OPERAND (t, 0);
5944 gcc_assert (DECL_P (t));
5945 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
5946 n2->value |= GOVD_SEEN;
5949 shared = ((flags | n->value) & GOVD_SHARED) != 0;
5950 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
5952 /* If nothing changed, there's nothing left to do. */
5953 if ((n->value & flags) == flags)
5954 return ret;
5955 flags |= n->value;
5956 n->value = flags;
5958 do_outer:
5959 /* If the variable is private in the current context, then we don't
5960 need to propagate anything to an outer context. */
5961 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
5962 return ret;
5963 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
5964 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
5965 return ret;
5966 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
5967 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
5968 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
5969 return ret;
5970 if (ctx->outer_context
5971 && omp_notice_variable (ctx->outer_context, decl, in_code))
5972 return true;
5973 return ret;
5976 /* Verify that DECL is private within CTX. If there's specific information
5977 to the contrary in the innermost scope, generate an error. */
5979 static bool
5980 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
5982 splay_tree_node n;
5984 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5985 if (n != NULL)
5987 if (n->value & GOVD_SHARED)
5989 if (ctx == gimplify_omp_ctxp)
5991 if (simd)
5992 error ("iteration variable %qE is predetermined linear",
5993 DECL_NAME (decl));
5994 else
5995 error ("iteration variable %qE should be private",
5996 DECL_NAME (decl));
5997 n->value = GOVD_PRIVATE;
5998 return true;
6000 else
6001 return false;
6003 else if ((n->value & GOVD_EXPLICIT) != 0
6004 && (ctx == gimplify_omp_ctxp
6005 || (ctx->region_type == ORT_COMBINED_PARALLEL
6006 && gimplify_omp_ctxp->outer_context == ctx)))
6008 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
6009 error ("iteration variable %qE should not be firstprivate",
6010 DECL_NAME (decl));
6011 else if ((n->value & GOVD_REDUCTION) != 0)
6012 error ("iteration variable %qE should not be reduction",
6013 DECL_NAME (decl));
6014 else if (simd == 1 && (n->value & GOVD_LASTPRIVATE) != 0)
6015 error ("iteration variable %qE should not be lastprivate",
6016 DECL_NAME (decl));
6017 else if (simd && (n->value & GOVD_PRIVATE) != 0)
6018 error ("iteration variable %qE should not be private",
6019 DECL_NAME (decl));
6020 else if (simd == 2 && (n->value & GOVD_LINEAR) != 0)
6021 error ("iteration variable %qE is predetermined linear",
6022 DECL_NAME (decl));
6024 return (ctx == gimplify_omp_ctxp
6025 || (ctx->region_type == ORT_COMBINED_PARALLEL
6026 && gimplify_omp_ctxp->outer_context == ctx));
6029 if (ctx->region_type != ORT_WORKSHARE
6030 && ctx->region_type != ORT_SIMD)
6031 return false;
6032 else if (ctx->outer_context)
6033 return omp_is_private (ctx->outer_context, decl, simd);
6034 return false;
6037 /* Return true if DECL is private within a parallel region
6038 that binds to the current construct's context or in parallel
6039 region's REDUCTION clause. */
6041 static bool
6042 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
6044 splay_tree_node n;
6048 ctx = ctx->outer_context;
6049 if (ctx == NULL)
6050 return !(is_global_var (decl)
6051 /* References might be private, but might be shared too,
6052 when checking for copyprivate, assume they might be
6053 private, otherwise assume they might be shared. */
6054 || (!copyprivate
6055 && lang_hooks.decls.omp_privatize_by_reference (decl)));
6057 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0)
6058 continue;
6060 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6061 if (n != NULL)
6062 return (n->value & GOVD_SHARED) == 0;
6064 while (ctx->region_type == ORT_WORKSHARE
6065 || ctx->region_type == ORT_SIMD);
6066 return false;
6069 /* Return true if the CTX is combined with distribute and thus
6070 lastprivate can't be supported. */
6072 static bool
6073 omp_no_lastprivate (struct gimplify_omp_ctx *ctx)
6077 if (ctx->outer_context == NULL)
6078 return false;
6079 ctx = ctx->outer_context;
6080 switch (ctx->region_type)
6082 case ORT_WORKSHARE:
6083 if (!ctx->combined_loop)
6084 return false;
6085 if (ctx->distribute)
6086 return true;
6087 break;
6088 case ORT_COMBINED_PARALLEL:
6089 break;
6090 case ORT_COMBINED_TEAMS:
6091 return true;
6092 default:
6093 return false;
6096 while (1);
6099 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
6100 and previous omp contexts. */
6102 static void
6103 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
6104 enum omp_region_type region_type)
6106 struct gimplify_omp_ctx *ctx, *outer_ctx;
6107 tree c;
6109 ctx = new_omp_context (region_type);
6110 outer_ctx = ctx->outer_context;
6112 while ((c = *list_p) != NULL)
6114 bool remove = false;
6115 bool notice_outer = true;
6116 const char *check_non_private = NULL;
6117 unsigned int flags;
6118 tree decl;
6120 switch (OMP_CLAUSE_CODE (c))
6122 case OMP_CLAUSE_PRIVATE:
6123 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
6124 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
6126 flags |= GOVD_PRIVATE_OUTER_REF;
6127 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
6129 else
6130 notice_outer = false;
6131 goto do_add;
6132 case OMP_CLAUSE_SHARED:
6133 flags = GOVD_SHARED | GOVD_EXPLICIT;
6134 goto do_add;
6135 case OMP_CLAUSE_FIRSTPRIVATE:
6136 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
6137 check_non_private = "firstprivate";
6138 goto do_add;
6139 case OMP_CLAUSE_LASTPRIVATE:
6140 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
6141 check_non_private = "lastprivate";
6142 decl = OMP_CLAUSE_DECL (c);
6143 if (omp_no_lastprivate (ctx))
6145 notice_outer = false;
6146 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
6148 else if (error_operand_p (decl))
6149 goto do_add;
6150 else if (outer_ctx
6151 && outer_ctx->region_type == ORT_COMBINED_PARALLEL
6152 && splay_tree_lookup (outer_ctx->variables,
6153 (splay_tree_key) decl) == NULL)
6154 omp_add_variable (outer_ctx, decl, GOVD_SHARED | GOVD_SEEN);
6155 else if (outer_ctx
6156 && outer_ctx->region_type == ORT_WORKSHARE
6157 && outer_ctx->combined_loop
6158 && splay_tree_lookup (outer_ctx->variables,
6159 (splay_tree_key) decl) == NULL
6160 && !omp_check_private (outer_ctx, decl, false))
6162 omp_add_variable (outer_ctx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
6163 if (outer_ctx->outer_context
6164 && (outer_ctx->outer_context->region_type
6165 == ORT_COMBINED_PARALLEL)
6166 && splay_tree_lookup (outer_ctx->outer_context->variables,
6167 (splay_tree_key) decl) == NULL)
6168 omp_add_variable (outer_ctx->outer_context, decl,
6169 GOVD_SHARED | GOVD_SEEN);
6171 goto do_add;
6172 case OMP_CLAUSE_REDUCTION:
6173 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
6174 check_non_private = "reduction";
6175 goto do_add;
6176 case OMP_CLAUSE_LINEAR:
6177 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
6178 is_gimple_val, fb_rvalue) == GS_ERROR)
6180 remove = true;
6181 break;
6183 else
6185 /* For combined #pragma omp parallel for simd, need to put
6186 lastprivate and perhaps firstprivate too on the
6187 parallel. Similarly for #pragma omp for simd. */
6188 struct gimplify_omp_ctx *octx = outer_ctx;
6189 decl = NULL_TREE;
6190 if (omp_no_lastprivate (ctx))
6191 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
6194 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
6195 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
6196 break;
6197 decl = OMP_CLAUSE_DECL (c);
6198 if (error_operand_p (decl))
6200 decl = NULL_TREE;
6201 break;
6203 if (octx
6204 && octx->region_type == ORT_WORKSHARE
6205 && octx->combined_loop)
6207 if (octx->outer_context
6208 && (octx->outer_context->region_type
6209 == ORT_COMBINED_PARALLEL
6210 || (octx->outer_context->region_type
6211 == ORT_COMBINED_TEAMS)))
6212 octx = octx->outer_context;
6213 else if (omp_check_private (octx, decl, false))
6214 break;
6216 else
6217 break;
6218 gcc_checking_assert (splay_tree_lookup (octx->variables,
6219 (splay_tree_key)
6220 decl) == NULL);
6221 flags = GOVD_SEEN;
6222 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
6223 flags |= GOVD_FIRSTPRIVATE;
6224 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
6225 flags |= GOVD_LASTPRIVATE;
6226 omp_add_variable (octx, decl, flags);
6227 if (octx->outer_context == NULL)
6228 break;
6229 octx = octx->outer_context;
6231 while (1);
6232 if (octx
6233 && decl
6234 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
6235 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
6236 omp_notice_variable (octx, decl, true);
6238 flags = GOVD_LINEAR | GOVD_EXPLICIT;
6239 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
6240 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
6242 notice_outer = false;
6243 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
6245 goto do_add;
6247 case OMP_CLAUSE_MAP:
6248 decl = OMP_CLAUSE_DECL (c);
6249 if (error_operand_p (decl))
6251 remove = true;
6252 break;
6254 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6255 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
6256 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
6257 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
6258 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
6260 remove = true;
6261 break;
6263 if (!DECL_P (decl))
6265 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
6266 NULL, is_gimple_lvalue, fb_lvalue)
6267 == GS_ERROR)
6269 remove = true;
6270 break;
6272 break;
6274 flags = GOVD_MAP | GOVD_EXPLICIT;
6275 goto do_add;
6277 case OMP_CLAUSE_DEPEND:
6278 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
6280 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
6281 NULL, is_gimple_val, fb_rvalue);
6282 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
6284 if (error_operand_p (OMP_CLAUSE_DECL (c)))
6286 remove = true;
6287 break;
6289 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
6290 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
6291 is_gimple_val, fb_rvalue) == GS_ERROR)
6293 remove = true;
6294 break;
6296 break;
6298 case OMP_CLAUSE_TO:
6299 case OMP_CLAUSE_FROM:
6300 case OMP_CLAUSE__CACHE_:
6301 decl = OMP_CLAUSE_DECL (c);
6302 if (error_operand_p (decl))
6304 remove = true;
6305 break;
6307 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6308 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
6309 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
6310 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
6311 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
6313 remove = true;
6314 break;
6316 if (!DECL_P (decl))
6318 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
6319 NULL, is_gimple_lvalue, fb_lvalue)
6320 == GS_ERROR)
6322 remove = true;
6323 break;
6325 break;
6327 goto do_notice;
6329 do_add:
6330 decl = OMP_CLAUSE_DECL (c);
6331 if (error_operand_p (decl))
6333 remove = true;
6334 break;
6336 omp_add_variable (ctx, decl, flags);
6337 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
6338 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
6340 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
6341 GOVD_LOCAL | GOVD_SEEN);
6342 gimplify_omp_ctxp = ctx;
6343 push_gimplify_context ();
6345 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
6346 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
6348 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
6349 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
6350 pop_gimplify_context
6351 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
6352 push_gimplify_context ();
6353 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
6354 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
6355 pop_gimplify_context
6356 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
6357 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
6358 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
6360 gimplify_omp_ctxp = outer_ctx;
6362 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
6363 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
6365 gimplify_omp_ctxp = ctx;
6366 push_gimplify_context ();
6367 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
6369 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
6370 NULL, NULL);
6371 TREE_SIDE_EFFECTS (bind) = 1;
6372 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
6373 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
6375 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
6376 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
6377 pop_gimplify_context
6378 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
6379 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
6381 gimplify_omp_ctxp = outer_ctx;
6383 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
6384 && OMP_CLAUSE_LINEAR_STMT (c))
6386 gimplify_omp_ctxp = ctx;
6387 push_gimplify_context ();
6388 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
6390 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
6391 NULL, NULL);
6392 TREE_SIDE_EFFECTS (bind) = 1;
6393 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
6394 OMP_CLAUSE_LINEAR_STMT (c) = bind;
6396 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
6397 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
6398 pop_gimplify_context
6399 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
6400 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
6402 gimplify_omp_ctxp = outer_ctx;
6404 if (notice_outer)
6405 goto do_notice;
6406 break;
6408 case OMP_CLAUSE_COPYIN:
6409 case OMP_CLAUSE_COPYPRIVATE:
6410 decl = OMP_CLAUSE_DECL (c);
6411 if (error_operand_p (decl))
6413 remove = true;
6414 break;
6416 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
6417 && !remove
6418 && !omp_check_private (ctx, decl, true))
6420 remove = true;
6421 if (is_global_var (decl))
6423 if (DECL_THREAD_LOCAL_P (decl))
6424 remove = false;
6425 else if (DECL_HAS_VALUE_EXPR_P (decl))
6427 tree value = get_base_address (DECL_VALUE_EXPR (decl));
6429 if (value
6430 && DECL_P (value)
6431 && DECL_THREAD_LOCAL_P (value))
6432 remove = false;
6435 if (remove)
6436 error_at (OMP_CLAUSE_LOCATION (c),
6437 "copyprivate variable %qE is not threadprivate"
6438 " or private in outer context", DECL_NAME (decl));
6440 do_notice:
6441 if (outer_ctx)
6442 omp_notice_variable (outer_ctx, decl, true);
6443 if (check_non_private
6444 && region_type == ORT_WORKSHARE
6445 && omp_check_private (ctx, decl, false))
6447 error ("%s variable %qE is private in outer context",
6448 check_non_private, DECL_NAME (decl));
6449 remove = true;
6451 break;
6453 case OMP_CLAUSE_FINAL:
6454 case OMP_CLAUSE_IF:
6455 OMP_CLAUSE_OPERAND (c, 0)
6456 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
6457 /* Fall through. */
6459 case OMP_CLAUSE_SCHEDULE:
6460 case OMP_CLAUSE_NUM_THREADS:
6461 case OMP_CLAUSE_NUM_TEAMS:
6462 case OMP_CLAUSE_THREAD_LIMIT:
6463 case OMP_CLAUSE_DIST_SCHEDULE:
6464 case OMP_CLAUSE_DEVICE:
6465 case OMP_CLAUSE__CILK_FOR_COUNT_:
6466 case OMP_CLAUSE_ASYNC:
6467 case OMP_CLAUSE_WAIT:
6468 case OMP_CLAUSE_NUM_GANGS:
6469 case OMP_CLAUSE_NUM_WORKERS:
6470 case OMP_CLAUSE_VECTOR_LENGTH:
6471 case OMP_CLAUSE_GANG:
6472 case OMP_CLAUSE_WORKER:
6473 case OMP_CLAUSE_VECTOR:
6474 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
6475 is_gimple_val, fb_rvalue) == GS_ERROR)
6476 remove = true;
6477 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_GANG
6478 && gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
6479 is_gimple_val, fb_rvalue) == GS_ERROR)
6480 remove = true;
6481 break;
6483 case OMP_CLAUSE_DEVICE_RESIDENT:
6484 case OMP_CLAUSE_USE_DEVICE:
6485 case OMP_CLAUSE_INDEPENDENT:
6486 remove = true;
6487 break;
6489 case OMP_CLAUSE_NOWAIT:
6490 case OMP_CLAUSE_ORDERED:
6491 case OMP_CLAUSE_UNTIED:
6492 case OMP_CLAUSE_COLLAPSE:
6493 case OMP_CLAUSE_AUTO:
6494 case OMP_CLAUSE_SEQ:
6495 case OMP_CLAUSE_MERGEABLE:
6496 case OMP_CLAUSE_PROC_BIND:
6497 case OMP_CLAUSE_SAFELEN:
6498 break;
6500 case OMP_CLAUSE_ALIGNED:
6501 decl = OMP_CLAUSE_DECL (c);
6502 if (error_operand_p (decl))
6504 remove = true;
6505 break;
6507 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
6508 is_gimple_val, fb_rvalue) == GS_ERROR)
6510 remove = true;
6511 break;
6513 if (!is_global_var (decl)
6514 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
6515 omp_add_variable (ctx, decl, GOVD_ALIGNED);
6516 break;
6518 case OMP_CLAUSE_DEFAULT:
6519 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
6520 break;
6522 default:
6523 gcc_unreachable ();
6526 if (remove)
6527 *list_p = OMP_CLAUSE_CHAIN (c);
6528 else
6529 list_p = &OMP_CLAUSE_CHAIN (c);
6532 gimplify_omp_ctxp = ctx;
6535 struct gimplify_adjust_omp_clauses_data
6537 tree *list_p;
6538 gimple_seq *pre_p;
6541 /* For all variables that were not actually used within the context,
6542 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
6544 static int
6545 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
6547 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
6548 gimple_seq *pre_p
6549 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
6550 tree decl = (tree) n->key;
6551 unsigned flags = n->value;
6552 enum omp_clause_code code;
6553 tree clause;
6554 bool private_debug;
6556 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
6557 return 0;
6558 if ((flags & GOVD_SEEN) == 0)
6559 return 0;
6560 if (flags & GOVD_DEBUG_PRIVATE)
6562 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_PRIVATE);
6563 private_debug = true;
6565 else if (flags & GOVD_MAP)
6566 private_debug = false;
6567 else
6568 private_debug
6569 = lang_hooks.decls.omp_private_debug_clause (decl,
6570 !!(flags & GOVD_SHARED));
6571 if (private_debug)
6572 code = OMP_CLAUSE_PRIVATE;
6573 else if (flags & GOVD_MAP)
6574 code = OMP_CLAUSE_MAP;
6575 else if (flags & GOVD_SHARED)
6577 if (is_global_var (decl))
6579 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
6580 while (ctx != NULL)
6582 splay_tree_node on
6583 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6584 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
6585 | GOVD_PRIVATE | GOVD_REDUCTION
6586 | GOVD_LINEAR | GOVD_MAP)) != 0)
6587 break;
6588 ctx = ctx->outer_context;
6590 if (ctx == NULL)
6591 return 0;
6593 code = OMP_CLAUSE_SHARED;
6595 else if (flags & GOVD_PRIVATE)
6596 code = OMP_CLAUSE_PRIVATE;
6597 else if (flags & GOVD_FIRSTPRIVATE)
6598 code = OMP_CLAUSE_FIRSTPRIVATE;
6599 else if (flags & GOVD_LASTPRIVATE)
6600 code = OMP_CLAUSE_LASTPRIVATE;
6601 else if (flags & GOVD_ALIGNED)
6602 return 0;
6603 else
6604 gcc_unreachable ();
6606 clause = build_omp_clause (input_location, code);
6607 OMP_CLAUSE_DECL (clause) = decl;
6608 OMP_CLAUSE_CHAIN (clause) = *list_p;
6609 if (private_debug)
6610 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
6611 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
6612 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
6613 else if (code == OMP_CLAUSE_MAP)
6615 OMP_CLAUSE_SET_MAP_KIND (clause,
6616 flags & GOVD_MAP_TO_ONLY
6617 ? GOMP_MAP_TO
6618 : GOMP_MAP_TOFROM);
6619 if (DECL_SIZE (decl)
6620 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
6622 tree decl2 = DECL_VALUE_EXPR (decl);
6623 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6624 decl2 = TREE_OPERAND (decl2, 0);
6625 gcc_assert (DECL_P (decl2));
6626 tree mem = build_simple_mem_ref (decl2);
6627 OMP_CLAUSE_DECL (clause) = mem;
6628 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6629 if (gimplify_omp_ctxp->outer_context)
6631 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
6632 omp_notice_variable (ctx, decl2, true);
6633 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
6635 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
6636 OMP_CLAUSE_MAP);
6637 OMP_CLAUSE_DECL (nc) = decl;
6638 OMP_CLAUSE_SIZE (nc) = size_zero_node;
6639 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
6640 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
6641 OMP_CLAUSE_CHAIN (clause) = nc;
6643 else
6644 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
6646 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
6648 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
6649 OMP_CLAUSE_DECL (nc) = decl;
6650 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
6651 OMP_CLAUSE_CHAIN (nc) = *list_p;
6652 OMP_CLAUSE_CHAIN (clause) = nc;
6653 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6654 gimplify_omp_ctxp = ctx->outer_context;
6655 lang_hooks.decls.omp_finish_clause (nc, pre_p);
6656 gimplify_omp_ctxp = ctx;
6658 *list_p = clause;
6659 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6660 gimplify_omp_ctxp = ctx->outer_context;
6661 lang_hooks.decls.omp_finish_clause (clause, pre_p);
6662 gimplify_omp_ctxp = ctx;
6663 return 0;
6666 static void
6667 gimplify_adjust_omp_clauses (gimple_seq *pre_p, tree *list_p)
6669 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6670 tree c, decl;
6672 while ((c = *list_p) != NULL)
6674 splay_tree_node n;
6675 bool remove = false;
6677 switch (OMP_CLAUSE_CODE (c))
6679 case OMP_CLAUSE_PRIVATE:
6680 case OMP_CLAUSE_SHARED:
6681 case OMP_CLAUSE_FIRSTPRIVATE:
6682 case OMP_CLAUSE_LINEAR:
6683 decl = OMP_CLAUSE_DECL (c);
6684 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6685 remove = !(n->value & GOVD_SEEN);
6686 if (! remove)
6688 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
6689 if ((n->value & GOVD_DEBUG_PRIVATE)
6690 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
6692 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
6693 || ((n->value & GOVD_DATA_SHARE_CLASS)
6694 == GOVD_PRIVATE));
6695 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
6696 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
6699 break;
6701 case OMP_CLAUSE_LASTPRIVATE:
6702 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
6703 accurately reflect the presence of a FIRSTPRIVATE clause. */
6704 decl = OMP_CLAUSE_DECL (c);
6705 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6706 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
6707 = (n->value & GOVD_FIRSTPRIVATE) != 0;
6708 if (omp_no_lastprivate (ctx))
6710 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
6711 remove = true;
6712 else
6713 OMP_CLAUSE_CODE (c) = OMP_CLAUSE_PRIVATE;
6715 break;
6717 case OMP_CLAUSE_ALIGNED:
6718 decl = OMP_CLAUSE_DECL (c);
6719 if (!is_global_var (decl))
6721 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6722 remove = n == NULL || !(n->value & GOVD_SEEN);
6723 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
6725 struct gimplify_omp_ctx *octx;
6726 if (n != NULL
6727 && (n->value & (GOVD_DATA_SHARE_CLASS
6728 & ~GOVD_FIRSTPRIVATE)))
6729 remove = true;
6730 else
6731 for (octx = ctx->outer_context; octx;
6732 octx = octx->outer_context)
6734 n = splay_tree_lookup (octx->variables,
6735 (splay_tree_key) decl);
6736 if (n == NULL)
6737 continue;
6738 if (n->value & GOVD_LOCAL)
6739 break;
6740 /* We have to avoid assigning a shared variable
6741 to itself when trying to add
6742 __builtin_assume_aligned. */
6743 if (n->value & GOVD_SHARED)
6745 remove = true;
6746 break;
6751 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
6753 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6754 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
6755 remove = true;
6757 break;
6759 case OMP_CLAUSE_MAP:
6760 decl = OMP_CLAUSE_DECL (c);
6761 if (!DECL_P (decl))
6762 break;
6763 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6764 if (ctx->region_type == ORT_TARGET && !(n->value & GOVD_SEEN))
6765 remove = true;
6766 else if (DECL_SIZE (decl)
6767 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
6768 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER)
6770 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
6771 for these, TREE_CODE (DECL_SIZE (decl)) will always be
6772 INTEGER_CST. */
6773 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
6775 tree decl2 = DECL_VALUE_EXPR (decl);
6776 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6777 decl2 = TREE_OPERAND (decl2, 0);
6778 gcc_assert (DECL_P (decl2));
6779 tree mem = build_simple_mem_ref (decl2);
6780 OMP_CLAUSE_DECL (c) = mem;
6781 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6782 if (ctx->outer_context)
6784 omp_notice_variable (ctx->outer_context, decl2, true);
6785 omp_notice_variable (ctx->outer_context,
6786 OMP_CLAUSE_SIZE (c), true);
6788 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
6789 OMP_CLAUSE_MAP);
6790 OMP_CLAUSE_DECL (nc) = decl;
6791 OMP_CLAUSE_SIZE (nc) = size_zero_node;
6792 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
6793 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
6794 OMP_CLAUSE_CHAIN (c) = nc;
6795 c = nc;
6797 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6798 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
6799 break;
6801 case OMP_CLAUSE_TO:
6802 case OMP_CLAUSE_FROM:
6803 case OMP_CLAUSE__CACHE_:
6804 decl = OMP_CLAUSE_DECL (c);
6805 if (!DECL_P (decl))
6806 break;
6807 if (DECL_SIZE (decl)
6808 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
6810 tree decl2 = DECL_VALUE_EXPR (decl);
6811 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6812 decl2 = TREE_OPERAND (decl2, 0);
6813 gcc_assert (DECL_P (decl2));
6814 tree mem = build_simple_mem_ref (decl2);
6815 OMP_CLAUSE_DECL (c) = mem;
6816 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6817 if (ctx->outer_context)
6819 omp_notice_variable (ctx->outer_context, decl2, true);
6820 omp_notice_variable (ctx->outer_context,
6821 OMP_CLAUSE_SIZE (c), true);
6824 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6825 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
6826 break;
6828 case OMP_CLAUSE_REDUCTION:
6829 case OMP_CLAUSE_COPYIN:
6830 case OMP_CLAUSE_COPYPRIVATE:
6831 case OMP_CLAUSE_IF:
6832 case OMP_CLAUSE_NUM_THREADS:
6833 case OMP_CLAUSE_NUM_TEAMS:
6834 case OMP_CLAUSE_THREAD_LIMIT:
6835 case OMP_CLAUSE_DIST_SCHEDULE:
6836 case OMP_CLAUSE_DEVICE:
6837 case OMP_CLAUSE_SCHEDULE:
6838 case OMP_CLAUSE_NOWAIT:
6839 case OMP_CLAUSE_ORDERED:
6840 case OMP_CLAUSE_DEFAULT:
6841 case OMP_CLAUSE_UNTIED:
6842 case OMP_CLAUSE_COLLAPSE:
6843 case OMP_CLAUSE_FINAL:
6844 case OMP_CLAUSE_MERGEABLE:
6845 case OMP_CLAUSE_PROC_BIND:
6846 case OMP_CLAUSE_SAFELEN:
6847 case OMP_CLAUSE_DEPEND:
6848 case OMP_CLAUSE__CILK_FOR_COUNT_:
6849 case OMP_CLAUSE_ASYNC:
6850 case OMP_CLAUSE_WAIT:
6851 case OMP_CLAUSE_DEVICE_RESIDENT:
6852 case OMP_CLAUSE_USE_DEVICE:
6853 case OMP_CLAUSE_INDEPENDENT:
6854 case OMP_CLAUSE_NUM_GANGS:
6855 case OMP_CLAUSE_NUM_WORKERS:
6856 case OMP_CLAUSE_VECTOR_LENGTH:
6857 case OMP_CLAUSE_GANG:
6858 case OMP_CLAUSE_WORKER:
6859 case OMP_CLAUSE_VECTOR:
6860 case OMP_CLAUSE_AUTO:
6861 case OMP_CLAUSE_SEQ:
6862 break;
6864 default:
6865 gcc_unreachable ();
6868 if (remove)
6869 *list_p = OMP_CLAUSE_CHAIN (c);
6870 else
6871 list_p = &OMP_CLAUSE_CHAIN (c);
6874 /* Add in any implicit data sharing. */
6875 struct gimplify_adjust_omp_clauses_data data;
6876 data.list_p = list_p;
6877 data.pre_p = pre_p;
6878 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
6880 gimplify_omp_ctxp = ctx->outer_context;
6881 delete_omp_context (ctx);
6884 /* Gimplify OACC_CACHE. */
6886 static void
6887 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
6889 tree expr = *expr_p;
6891 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_WORKSHARE);
6892 gimplify_adjust_omp_clauses (pre_p, &OACC_CACHE_CLAUSES (expr));
6894 /* TODO: Do something sensible with this information. */
6896 *expr_p = NULL_TREE;
6899 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
6900 gimplification of the body, as well as scanning the body for used
6901 variables. We need to do this scan now, because variable-sized
6902 decls will be decomposed during gimplification. */
6904 static void
6905 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
6907 tree expr = *expr_p;
6908 gimple g;
6909 gimple_seq body = NULL;
6911 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
6912 OMP_PARALLEL_COMBINED (expr)
6913 ? ORT_COMBINED_PARALLEL
6914 : ORT_PARALLEL);
6916 push_gimplify_context ();
6918 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
6919 if (gimple_code (g) == GIMPLE_BIND)
6920 pop_gimplify_context (g);
6921 else
6922 pop_gimplify_context (NULL);
6924 gimplify_adjust_omp_clauses (pre_p, &OMP_PARALLEL_CLAUSES (expr));
6926 g = gimple_build_omp_parallel (body,
6927 OMP_PARALLEL_CLAUSES (expr),
6928 NULL_TREE, NULL_TREE);
6929 if (OMP_PARALLEL_COMBINED (expr))
6930 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
6931 gimplify_seq_add_stmt (pre_p, g);
6932 *expr_p = NULL_TREE;
6935 /* Gimplify the contents of an OMP_TASK statement. This involves
6936 gimplification of the body, as well as scanning the body for used
6937 variables. We need to do this scan now, because variable-sized
6938 decls will be decomposed during gimplification. */
6940 static void
6941 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
6943 tree expr = *expr_p;
6944 gimple g;
6945 gimple_seq body = NULL;
6947 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
6948 find_omp_clause (OMP_TASK_CLAUSES (expr),
6949 OMP_CLAUSE_UNTIED)
6950 ? ORT_UNTIED_TASK : ORT_TASK);
6952 push_gimplify_context ();
6954 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
6955 if (gimple_code (g) == GIMPLE_BIND)
6956 pop_gimplify_context (g);
6957 else
6958 pop_gimplify_context (NULL);
6960 gimplify_adjust_omp_clauses (pre_p, &OMP_TASK_CLAUSES (expr));
6962 g = gimple_build_omp_task (body,
6963 OMP_TASK_CLAUSES (expr),
6964 NULL_TREE, NULL_TREE,
6965 NULL_TREE, NULL_TREE, NULL_TREE);
6966 gimplify_seq_add_stmt (pre_p, g);
6967 *expr_p = NULL_TREE;
6970 /* Helper function of gimplify_omp_for, find OMP_FOR resp. OMP_SIMD
6971 with non-NULL OMP_FOR_INIT. */
6973 static tree
6974 find_combined_omp_for (tree *tp, int *walk_subtrees, void *)
6976 *walk_subtrees = 0;
6977 switch (TREE_CODE (*tp))
6979 case OMP_FOR:
6980 *walk_subtrees = 1;
6981 /* FALLTHRU */
6982 case OMP_SIMD:
6983 if (OMP_FOR_INIT (*tp) != NULL_TREE)
6984 return *tp;
6985 break;
6986 case BIND_EXPR:
6987 case STATEMENT_LIST:
6988 case OMP_PARALLEL:
6989 *walk_subtrees = 1;
6990 break;
6991 default:
6992 break;
6994 return NULL_TREE;
6997 /* Gimplify the gross structure of an OMP_FOR statement. */
6999 static enum gimplify_status
7000 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
7002 tree for_stmt, orig_for_stmt, decl, var, t;
7003 enum gimplify_status ret = GS_ALL_DONE;
7004 enum gimplify_status tret;
7005 gomp_for *gfor;
7006 gimple_seq for_body, for_pre_body;
7007 int i;
7008 bool simd;
7009 bitmap has_decl_expr = NULL;
7011 orig_for_stmt = for_stmt = *expr_p;
7013 switch (TREE_CODE (for_stmt))
7015 case OMP_FOR:
7016 case CILK_FOR:
7017 case OMP_DISTRIBUTE:
7018 case OACC_LOOP:
7019 simd = false;
7020 break;
7021 case OMP_SIMD:
7022 case CILK_SIMD:
7023 simd = true;
7024 break;
7025 default:
7026 gcc_unreachable ();
7029 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
7030 clause for the IV. */
7031 if (simd && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
7033 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
7034 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
7035 decl = TREE_OPERAND (t, 0);
7036 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
7037 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
7038 && OMP_CLAUSE_DECL (c) == decl)
7040 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
7041 break;
7045 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p,
7046 simd ? ORT_SIMD : ORT_WORKSHARE);
7047 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
7048 gimplify_omp_ctxp->distribute = true;
7050 /* Handle OMP_FOR_INIT. */
7051 for_pre_body = NULL;
7052 if (simd && OMP_FOR_PRE_BODY (for_stmt))
7054 has_decl_expr = BITMAP_ALLOC (NULL);
7055 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
7056 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
7057 == VAR_DECL)
7059 t = OMP_FOR_PRE_BODY (for_stmt);
7060 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
7062 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
7064 tree_stmt_iterator si;
7065 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
7066 tsi_next (&si))
7068 t = tsi_stmt (si);
7069 if (TREE_CODE (t) == DECL_EXPR
7070 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
7071 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
7075 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
7076 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
7078 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
7080 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
7081 for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt), find_combined_omp_for,
7082 NULL, NULL);
7083 gcc_assert (for_stmt != NULL_TREE);
7084 gimplify_omp_ctxp->combined_loop = true;
7087 for_body = NULL;
7088 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
7089 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
7090 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
7091 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
7092 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
7094 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
7095 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
7096 decl = TREE_OPERAND (t, 0);
7097 gcc_assert (DECL_P (decl));
7098 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
7099 || POINTER_TYPE_P (TREE_TYPE (decl)));
7101 /* Make sure the iteration variable is private. */
7102 tree c = NULL_TREE;
7103 tree c2 = NULL_TREE;
7104 if (orig_for_stmt != for_stmt)
7105 /* Do this only on innermost construct for combined ones. */;
7106 else if (simd)
7108 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
7109 (splay_tree_key)decl);
7110 omp_is_private (gimplify_omp_ctxp, decl,
7111 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
7112 != 1));
7113 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7114 omp_notice_variable (gimplify_omp_ctxp, decl, true);
7115 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
7117 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
7118 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
7119 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
7120 if ((has_decl_expr
7121 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
7122 || omp_no_lastprivate (gimplify_omp_ctxp))
7124 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
7125 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
7127 OMP_CLAUSE_DECL (c) = decl;
7128 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
7129 OMP_FOR_CLAUSES (for_stmt) = c;
7131 omp_add_variable (gimplify_omp_ctxp, decl, flags);
7132 struct gimplify_omp_ctx *outer
7133 = gimplify_omp_ctxp->outer_context;
7134 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
7136 if (outer->region_type == ORT_WORKSHARE
7137 && outer->combined_loop)
7139 if (outer->outer_context
7140 && (outer->outer_context->region_type
7141 == ORT_COMBINED_PARALLEL))
7142 outer = outer->outer_context;
7143 else if (omp_check_private (outer, decl, false))
7144 outer = NULL;
7146 else if (outer->region_type != ORT_COMBINED_PARALLEL)
7147 outer = NULL;
7148 if (outer)
7150 omp_add_variable (outer, decl,
7151 GOVD_LASTPRIVATE | GOVD_SEEN);
7152 if (outer->outer_context)
7153 omp_notice_variable (outer->outer_context, decl, true);
7157 else
7159 bool lastprivate
7160 = (!has_decl_expr
7161 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
7162 && !omp_no_lastprivate (gimplify_omp_ctxp);
7163 struct gimplify_omp_ctx *outer
7164 = gimplify_omp_ctxp->outer_context;
7165 if (outer && lastprivate)
7167 if (outer->region_type == ORT_WORKSHARE
7168 && outer->combined_loop)
7170 if (outer->outer_context
7171 && (outer->outer_context->region_type
7172 == ORT_COMBINED_PARALLEL))
7173 outer = outer->outer_context;
7174 else if (omp_check_private (outer, decl, false))
7175 outer = NULL;
7177 else if (outer->region_type != ORT_COMBINED_PARALLEL)
7178 outer = NULL;
7179 if (outer)
7181 omp_add_variable (outer, decl,
7182 GOVD_LASTPRIVATE | GOVD_SEEN);
7183 if (outer->outer_context)
7184 omp_notice_variable (outer->outer_context, decl, true);
7188 c = build_omp_clause (input_location,
7189 lastprivate ? OMP_CLAUSE_LASTPRIVATE
7190 : OMP_CLAUSE_PRIVATE);
7191 OMP_CLAUSE_DECL (c) = decl;
7192 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
7193 OMP_FOR_CLAUSES (for_stmt) = c;
7194 omp_add_variable (gimplify_omp_ctxp, decl,
7195 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
7196 | GOVD_EXPLICIT | GOVD_SEEN);
7197 c = NULL_TREE;
7200 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
7201 omp_notice_variable (gimplify_omp_ctxp, decl, true);
7202 else
7203 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
7205 /* If DECL is not a gimple register, create a temporary variable to act
7206 as an iteration counter. This is valid, since DECL cannot be
7207 modified in the body of the loop. Similarly for any iteration vars
7208 in simd with collapse > 1 where the iterator vars must be
7209 lastprivate. */
7210 if (orig_for_stmt != for_stmt)
7211 var = decl;
7212 else if (!is_gimple_reg (decl)
7213 || (simd && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1))
7215 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
7216 TREE_OPERAND (t, 0) = var;
7218 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
7220 if (simd && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
7222 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
7223 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
7224 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
7225 OMP_CLAUSE_DECL (c2) = var;
7226 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
7227 OMP_FOR_CLAUSES (for_stmt) = c2;
7228 omp_add_variable (gimplify_omp_ctxp, var,
7229 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
7230 if (c == NULL_TREE)
7232 c = c2;
7233 c2 = NULL_TREE;
7236 else
7237 omp_add_variable (gimplify_omp_ctxp, var,
7238 GOVD_PRIVATE | GOVD_SEEN);
7240 else
7241 var = decl;
7243 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7244 is_gimple_val, fb_rvalue);
7245 ret = MIN (ret, tret);
7246 if (ret == GS_ERROR)
7247 return ret;
7249 /* Handle OMP_FOR_COND. */
7250 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
7251 gcc_assert (COMPARISON_CLASS_P (t));
7252 gcc_assert (TREE_OPERAND (t, 0) == decl);
7254 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7255 is_gimple_val, fb_rvalue);
7256 ret = MIN (ret, tret);
7258 /* Handle OMP_FOR_INCR. */
7259 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7260 switch (TREE_CODE (t))
7262 case PREINCREMENT_EXPR:
7263 case POSTINCREMENT_EXPR:
7265 tree decl = TREE_OPERAND (t, 0);
7266 /* c_omp_for_incr_canonicalize_ptr() should have been
7267 called to massage things appropriately. */
7268 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
7270 if (orig_for_stmt != for_stmt)
7271 break;
7272 t = build_int_cst (TREE_TYPE (decl), 1);
7273 if (c)
7274 OMP_CLAUSE_LINEAR_STEP (c) = t;
7275 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
7276 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
7277 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
7278 break;
7281 case PREDECREMENT_EXPR:
7282 case POSTDECREMENT_EXPR:
7283 /* c_omp_for_incr_canonicalize_ptr() should have been
7284 called to massage things appropriately. */
7285 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
7286 if (orig_for_stmt != for_stmt)
7287 break;
7288 t = build_int_cst (TREE_TYPE (decl), -1);
7289 if (c)
7290 OMP_CLAUSE_LINEAR_STEP (c) = t;
7291 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
7292 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
7293 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
7294 break;
7296 case MODIFY_EXPR:
7297 gcc_assert (TREE_OPERAND (t, 0) == decl);
7298 TREE_OPERAND (t, 0) = var;
7300 t = TREE_OPERAND (t, 1);
7301 switch (TREE_CODE (t))
7303 case PLUS_EXPR:
7304 if (TREE_OPERAND (t, 1) == decl)
7306 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
7307 TREE_OPERAND (t, 0) = var;
7308 break;
7311 /* Fallthru. */
7312 case MINUS_EXPR:
7313 case POINTER_PLUS_EXPR:
7314 gcc_assert (TREE_OPERAND (t, 0) == decl);
7315 TREE_OPERAND (t, 0) = var;
7316 break;
7317 default:
7318 gcc_unreachable ();
7321 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7322 is_gimple_val, fb_rvalue);
7323 ret = MIN (ret, tret);
7324 if (c)
7326 tree step = TREE_OPERAND (t, 1);
7327 tree stept = TREE_TYPE (decl);
7328 if (POINTER_TYPE_P (stept))
7329 stept = sizetype;
7330 step = fold_convert (stept, step);
7331 if (TREE_CODE (t) == MINUS_EXPR)
7332 step = fold_build1 (NEGATE_EXPR, stept, step);
7333 OMP_CLAUSE_LINEAR_STEP (c) = step;
7334 if (step != TREE_OPERAND (t, 1))
7336 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
7337 &for_pre_body, NULL,
7338 is_gimple_val, fb_rvalue);
7339 ret = MIN (ret, tret);
7342 break;
7344 default:
7345 gcc_unreachable ();
7348 if (c2)
7350 gcc_assert (c);
7351 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
7354 if ((var != decl || TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
7355 && orig_for_stmt == for_stmt)
7357 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
7358 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
7359 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
7360 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
7361 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
7362 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
7363 && OMP_CLAUSE_DECL (c) == decl)
7365 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7366 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
7367 gcc_assert (TREE_OPERAND (t, 0) == var);
7368 t = TREE_OPERAND (t, 1);
7369 gcc_assert (TREE_CODE (t) == PLUS_EXPR
7370 || TREE_CODE (t) == MINUS_EXPR
7371 || TREE_CODE (t) == POINTER_PLUS_EXPR);
7372 gcc_assert (TREE_OPERAND (t, 0) == var);
7373 t = build2 (TREE_CODE (t), TREE_TYPE (decl), decl,
7374 TREE_OPERAND (t, 1));
7375 gimple_seq *seq;
7376 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
7377 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
7378 else
7379 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
7380 gimplify_assign (decl, t, seq);
7385 BITMAP_FREE (has_decl_expr);
7387 gimplify_and_add (OMP_FOR_BODY (orig_for_stmt), &for_body);
7389 if (orig_for_stmt != for_stmt)
7390 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
7392 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
7393 decl = TREE_OPERAND (t, 0);
7394 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
7395 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
7396 TREE_OPERAND (t, 0) = var;
7397 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7398 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
7399 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
7402 gimplify_adjust_omp_clauses (pre_p, &OMP_FOR_CLAUSES (orig_for_stmt));
7404 int kind;
7405 switch (TREE_CODE (orig_for_stmt))
7407 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
7408 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
7409 case CILK_SIMD: kind = GF_OMP_FOR_KIND_CILKSIMD; break;
7410 case CILK_FOR: kind = GF_OMP_FOR_KIND_CILKFOR; break;
7411 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
7412 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
7413 default:
7414 gcc_unreachable ();
7416 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
7417 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
7418 for_pre_body);
7419 if (orig_for_stmt != for_stmt)
7420 gimple_omp_for_set_combined_p (gfor, true);
7421 if (gimplify_omp_ctxp
7422 && (gimplify_omp_ctxp->combined_loop
7423 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
7424 && gimplify_omp_ctxp->outer_context
7425 && gimplify_omp_ctxp->outer_context->combined_loop)))
7427 gimple_omp_for_set_combined_into_p (gfor, true);
7428 if (gimplify_omp_ctxp->combined_loop)
7429 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
7430 else
7431 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
7434 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
7436 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
7437 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
7438 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
7439 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
7440 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
7441 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
7442 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7443 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
7446 gimplify_seq_add_stmt (pre_p, gfor);
7447 if (ret != GS_ALL_DONE)
7448 return GS_ERROR;
7449 *expr_p = NULL_TREE;
7450 return GS_ALL_DONE;
7453 /* Gimplify the gross structure of several OMP constructs. */
7455 static void
7456 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
7458 tree expr = *expr_p;
7459 gimple stmt;
7460 gimple_seq body = NULL;
7461 enum omp_region_type ort;
7463 switch (TREE_CODE (expr))
7465 case OMP_SECTIONS:
7466 case OMP_SINGLE:
7467 ort = ORT_WORKSHARE;
7468 break;
7469 case OACC_KERNELS:
7470 case OACC_PARALLEL:
7471 case OMP_TARGET:
7472 ort = ORT_TARGET;
7473 break;
7474 case OACC_DATA:
7475 case OMP_TARGET_DATA:
7476 ort = ORT_TARGET_DATA;
7477 break;
7478 case OMP_TEAMS:
7479 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
7480 break;
7481 default:
7482 gcc_unreachable ();
7484 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort);
7485 if (ort == ORT_TARGET || ort == ORT_TARGET_DATA)
7487 push_gimplify_context ();
7488 gimple g = gimplify_and_return_first (OMP_BODY (expr), &body);
7489 if (gimple_code (g) == GIMPLE_BIND)
7490 pop_gimplify_context (g);
7491 else
7492 pop_gimplify_context (NULL);
7493 if (ort == ORT_TARGET_DATA)
7495 enum built_in_function end_ix;
7496 switch (TREE_CODE (expr))
7498 case OACC_DATA:
7499 end_ix = BUILT_IN_GOACC_DATA_END;
7500 break;
7501 case OMP_TARGET_DATA:
7502 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
7503 break;
7504 default:
7505 gcc_unreachable ();
7507 tree fn = builtin_decl_explicit (end_ix);
7508 g = gimple_build_call (fn, 0);
7509 gimple_seq cleanup = NULL;
7510 gimple_seq_add_stmt (&cleanup, g);
7511 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
7512 body = NULL;
7513 gimple_seq_add_stmt (&body, g);
7516 else
7517 gimplify_and_add (OMP_BODY (expr), &body);
7518 gimplify_adjust_omp_clauses (pre_p, &OMP_CLAUSES (expr));
7520 switch (TREE_CODE (expr))
7522 case OACC_DATA:
7523 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
7524 OMP_CLAUSES (expr));
7525 break;
7526 case OACC_KERNELS:
7527 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
7528 OMP_CLAUSES (expr));
7529 break;
7530 case OACC_PARALLEL:
7531 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
7532 OMP_CLAUSES (expr));
7533 break;
7534 case OMP_SECTIONS:
7535 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
7536 break;
7537 case OMP_SINGLE:
7538 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
7539 break;
7540 case OMP_TARGET:
7541 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
7542 OMP_CLAUSES (expr));
7543 break;
7544 case OMP_TARGET_DATA:
7545 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
7546 OMP_CLAUSES (expr));
7547 break;
7548 case OMP_TEAMS:
7549 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
7550 break;
7551 default:
7552 gcc_unreachable ();
7555 gimplify_seq_add_stmt (pre_p, stmt);
7556 *expr_p = NULL_TREE;
7559 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
7560 target update constructs. */
7562 static void
7563 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
7565 tree expr = *expr_p;
7566 int kind;
7567 gomp_target *stmt;
7569 switch (TREE_CODE (expr))
7571 case OACC_ENTER_DATA:
7572 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
7573 break;
7574 case OACC_EXIT_DATA:
7575 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
7576 break;
7577 case OACC_UPDATE:
7578 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
7579 break;
7580 case OMP_TARGET_UPDATE:
7581 kind = GF_OMP_TARGET_KIND_UPDATE;
7582 break;
7583 default:
7584 gcc_unreachable ();
7586 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
7587 ORT_WORKSHARE);
7588 gimplify_adjust_omp_clauses (pre_p, &OMP_STANDALONE_CLAUSES (expr));
7589 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
7591 gimplify_seq_add_stmt (pre_p, stmt);
7592 *expr_p = NULL_TREE;
7595 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
7596 stabilized the lhs of the atomic operation as *ADDR. Return true if
7597 EXPR is this stabilized form. */
7599 static bool
7600 goa_lhs_expr_p (tree expr, tree addr)
7602 /* Also include casts to other type variants. The C front end is fond
7603 of adding these for e.g. volatile variables. This is like
7604 STRIP_TYPE_NOPS but includes the main variant lookup. */
7605 STRIP_USELESS_TYPE_CONVERSION (expr);
7607 if (TREE_CODE (expr) == INDIRECT_REF)
7609 expr = TREE_OPERAND (expr, 0);
7610 while (expr != addr
7611 && (CONVERT_EXPR_P (expr)
7612 || TREE_CODE (expr) == NON_LVALUE_EXPR)
7613 && TREE_CODE (expr) == TREE_CODE (addr)
7614 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
7616 expr = TREE_OPERAND (expr, 0);
7617 addr = TREE_OPERAND (addr, 0);
7619 if (expr == addr)
7620 return true;
7621 return (TREE_CODE (addr) == ADDR_EXPR
7622 && TREE_CODE (expr) == ADDR_EXPR
7623 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
7625 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
7626 return true;
7627 return false;
7630 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
7631 expression does not involve the lhs, evaluate it into a temporary.
7632 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
7633 or -1 if an error was encountered. */
7635 static int
7636 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
7637 tree lhs_var)
7639 tree expr = *expr_p;
7640 int saw_lhs;
7642 if (goa_lhs_expr_p (expr, lhs_addr))
7644 *expr_p = lhs_var;
7645 return 1;
7647 if (is_gimple_val (expr))
7648 return 0;
7650 saw_lhs = 0;
7651 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
7653 case tcc_binary:
7654 case tcc_comparison:
7655 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
7656 lhs_var);
7657 case tcc_unary:
7658 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
7659 lhs_var);
7660 break;
7661 case tcc_expression:
7662 switch (TREE_CODE (expr))
7664 case TRUTH_ANDIF_EXPR:
7665 case TRUTH_ORIF_EXPR:
7666 case TRUTH_AND_EXPR:
7667 case TRUTH_OR_EXPR:
7668 case TRUTH_XOR_EXPR:
7669 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
7670 lhs_addr, lhs_var);
7671 case TRUTH_NOT_EXPR:
7672 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
7673 lhs_addr, lhs_var);
7674 break;
7675 case COMPOUND_EXPR:
7676 /* Break out any preevaluations from cp_build_modify_expr. */
7677 for (; TREE_CODE (expr) == COMPOUND_EXPR;
7678 expr = TREE_OPERAND (expr, 1))
7679 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
7680 *expr_p = expr;
7681 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var);
7682 default:
7683 break;
7685 break;
7686 default:
7687 break;
7690 if (saw_lhs == 0)
7692 enum gimplify_status gs;
7693 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
7694 if (gs != GS_ALL_DONE)
7695 saw_lhs = -1;
7698 return saw_lhs;
7701 /* Gimplify an OMP_ATOMIC statement. */
7703 static enum gimplify_status
7704 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
7706 tree addr = TREE_OPERAND (*expr_p, 0);
7707 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
7708 ? NULL : TREE_OPERAND (*expr_p, 1);
7709 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
7710 tree tmp_load;
7711 gomp_atomic_load *loadstmt;
7712 gomp_atomic_store *storestmt;
7714 tmp_load = create_tmp_reg (type);
7715 if (rhs && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load) < 0)
7716 return GS_ERROR;
7718 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
7719 != GS_ALL_DONE)
7720 return GS_ERROR;
7722 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr);
7723 gimplify_seq_add_stmt (pre_p, loadstmt);
7724 if (rhs && gimplify_expr (&rhs, pre_p, NULL, is_gimple_val, fb_rvalue)
7725 != GS_ALL_DONE)
7726 return GS_ERROR;
7728 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
7729 rhs = tmp_load;
7730 storestmt = gimple_build_omp_atomic_store (rhs);
7731 gimplify_seq_add_stmt (pre_p, storestmt);
7732 if (OMP_ATOMIC_SEQ_CST (*expr_p))
7734 gimple_omp_atomic_set_seq_cst (loadstmt);
7735 gimple_omp_atomic_set_seq_cst (storestmt);
7737 switch (TREE_CODE (*expr_p))
7739 case OMP_ATOMIC_READ:
7740 case OMP_ATOMIC_CAPTURE_OLD:
7741 *expr_p = tmp_load;
7742 gimple_omp_atomic_set_need_value (loadstmt);
7743 break;
7744 case OMP_ATOMIC_CAPTURE_NEW:
7745 *expr_p = rhs;
7746 gimple_omp_atomic_set_need_value (storestmt);
7747 break;
7748 default:
7749 *expr_p = NULL;
7750 break;
7753 return GS_ALL_DONE;
7756 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
7757 body, and adding some EH bits. */
7759 static enum gimplify_status
7760 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
7762 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
7763 gimple body_stmt;
7764 gtransaction *trans_stmt;
7765 gimple_seq body = NULL;
7766 int subcode = 0;
7768 /* Wrap the transaction body in a BIND_EXPR so we have a context
7769 where to put decls for OMP. */
7770 if (TREE_CODE (tbody) != BIND_EXPR)
7772 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
7773 TREE_SIDE_EFFECTS (bind) = 1;
7774 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
7775 TRANSACTION_EXPR_BODY (expr) = bind;
7778 push_gimplify_context ();
7779 temp = voidify_wrapper_expr (*expr_p, NULL);
7781 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
7782 pop_gimplify_context (body_stmt);
7784 trans_stmt = gimple_build_transaction (body, NULL);
7785 if (TRANSACTION_EXPR_OUTER (expr))
7786 subcode = GTMA_IS_OUTER;
7787 else if (TRANSACTION_EXPR_RELAXED (expr))
7788 subcode = GTMA_IS_RELAXED;
7789 gimple_transaction_set_subcode (trans_stmt, subcode);
7791 gimplify_seq_add_stmt (pre_p, trans_stmt);
7793 if (temp)
7795 *expr_p = temp;
7796 return GS_OK;
7799 *expr_p = NULL_TREE;
7800 return GS_ALL_DONE;
7803 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
7804 expression produces a value to be used as an operand inside a GIMPLE
7805 statement, the value will be stored back in *EXPR_P. This value will
7806 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
7807 an SSA_NAME. The corresponding sequence of GIMPLE statements is
7808 emitted in PRE_P and POST_P.
7810 Additionally, this process may overwrite parts of the input
7811 expression during gimplification. Ideally, it should be
7812 possible to do non-destructive gimplification.
7814 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
7815 the expression needs to evaluate to a value to be used as
7816 an operand in a GIMPLE statement, this value will be stored in
7817 *EXPR_P on exit. This happens when the caller specifies one
7818 of fb_lvalue or fb_rvalue fallback flags.
7820 PRE_P will contain the sequence of GIMPLE statements corresponding
7821 to the evaluation of EXPR and all the side-effects that must
7822 be executed before the main expression. On exit, the last
7823 statement of PRE_P is the core statement being gimplified. For
7824 instance, when gimplifying 'if (++a)' the last statement in
7825 PRE_P will be 'if (t.1)' where t.1 is the result of
7826 pre-incrementing 'a'.
7828 POST_P will contain the sequence of GIMPLE statements corresponding
7829 to the evaluation of all the side-effects that must be executed
7830 after the main expression. If this is NULL, the post
7831 side-effects are stored at the end of PRE_P.
7833 The reason why the output is split in two is to handle post
7834 side-effects explicitly. In some cases, an expression may have
7835 inner and outer post side-effects which need to be emitted in
7836 an order different from the one given by the recursive
7837 traversal. For instance, for the expression (*p--)++ the post
7838 side-effects of '--' must actually occur *after* the post
7839 side-effects of '++'. However, gimplification will first visit
7840 the inner expression, so if a separate POST sequence was not
7841 used, the resulting sequence would be:
7843 1 t.1 = *p
7844 2 p = p - 1
7845 3 t.2 = t.1 + 1
7846 4 *p = t.2
7848 However, the post-decrement operation in line #2 must not be
7849 evaluated until after the store to *p at line #4, so the
7850 correct sequence should be:
7852 1 t.1 = *p
7853 2 t.2 = t.1 + 1
7854 3 *p = t.2
7855 4 p = p - 1
7857 So, by specifying a separate post queue, it is possible
7858 to emit the post side-effects in the correct order.
7859 If POST_P is NULL, an internal queue will be used. Before
7860 returning to the caller, the sequence POST_P is appended to
7861 the main output sequence PRE_P.
7863 GIMPLE_TEST_F points to a function that takes a tree T and
7864 returns nonzero if T is in the GIMPLE form requested by the
7865 caller. The GIMPLE predicates are in gimple.c.
7867 FALLBACK tells the function what sort of a temporary we want if
7868 gimplification cannot produce an expression that complies with
7869 GIMPLE_TEST_F.
7871 fb_none means that no temporary should be generated
7872 fb_rvalue means that an rvalue is OK to generate
7873 fb_lvalue means that an lvalue is OK to generate
7874 fb_either means that either is OK, but an lvalue is preferable.
7875 fb_mayfail means that gimplification may fail (in which case
7876 GS_ERROR will be returned)
7878 The return value is either GS_ERROR or GS_ALL_DONE, since this
7879 function iterates until EXPR is completely gimplified or an error
7880 occurs. */
7882 enum gimplify_status
7883 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
7884 bool (*gimple_test_f) (tree), fallback_t fallback)
7886 tree tmp;
7887 gimple_seq internal_pre = NULL;
7888 gimple_seq internal_post = NULL;
7889 tree save_expr;
7890 bool is_statement;
7891 location_t saved_location;
7892 enum gimplify_status ret;
7893 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
7895 save_expr = *expr_p;
7896 if (save_expr == NULL_TREE)
7897 return GS_ALL_DONE;
7899 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
7900 is_statement = gimple_test_f == is_gimple_stmt;
7901 if (is_statement)
7902 gcc_assert (pre_p);
7904 /* Consistency checks. */
7905 if (gimple_test_f == is_gimple_reg)
7906 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
7907 else if (gimple_test_f == is_gimple_val
7908 || gimple_test_f == is_gimple_call_addr
7909 || gimple_test_f == is_gimple_condexpr
7910 || gimple_test_f == is_gimple_mem_rhs
7911 || gimple_test_f == is_gimple_mem_rhs_or_call
7912 || gimple_test_f == is_gimple_reg_rhs
7913 || gimple_test_f == is_gimple_reg_rhs_or_call
7914 || gimple_test_f == is_gimple_asm_val
7915 || gimple_test_f == is_gimple_mem_ref_addr)
7916 gcc_assert (fallback & fb_rvalue);
7917 else if (gimple_test_f == is_gimple_min_lval
7918 || gimple_test_f == is_gimple_lvalue)
7919 gcc_assert (fallback & fb_lvalue);
7920 else if (gimple_test_f == is_gimple_addressable)
7921 gcc_assert (fallback & fb_either);
7922 else if (gimple_test_f == is_gimple_stmt)
7923 gcc_assert (fallback == fb_none);
7924 else
7926 /* We should have recognized the GIMPLE_TEST_F predicate to
7927 know what kind of fallback to use in case a temporary is
7928 needed to hold the value or address of *EXPR_P. */
7929 gcc_unreachable ();
7932 /* We used to check the predicate here and return immediately if it
7933 succeeds. This is wrong; the design is for gimplification to be
7934 idempotent, and for the predicates to only test for valid forms, not
7935 whether they are fully simplified. */
7936 if (pre_p == NULL)
7937 pre_p = &internal_pre;
7939 if (post_p == NULL)
7940 post_p = &internal_post;
7942 /* Remember the last statements added to PRE_P and POST_P. Every
7943 new statement added by the gimplification helpers needs to be
7944 annotated with location information. To centralize the
7945 responsibility, we remember the last statement that had been
7946 added to both queues before gimplifying *EXPR_P. If
7947 gimplification produces new statements in PRE_P and POST_P, those
7948 statements will be annotated with the same location information
7949 as *EXPR_P. */
7950 pre_last_gsi = gsi_last (*pre_p);
7951 post_last_gsi = gsi_last (*post_p);
7953 saved_location = input_location;
7954 if (save_expr != error_mark_node
7955 && EXPR_HAS_LOCATION (*expr_p))
7956 input_location = EXPR_LOCATION (*expr_p);
7958 /* Loop over the specific gimplifiers until the toplevel node
7959 remains the same. */
7962 /* Strip away as many useless type conversions as possible
7963 at the toplevel. */
7964 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
7966 /* Remember the expr. */
7967 save_expr = *expr_p;
7969 /* Die, die, die, my darling. */
7970 if (save_expr == error_mark_node
7971 || (TREE_TYPE (save_expr)
7972 && TREE_TYPE (save_expr) == error_mark_node))
7974 ret = GS_ERROR;
7975 break;
7978 /* Do any language-specific gimplification. */
7979 ret = ((enum gimplify_status)
7980 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
7981 if (ret == GS_OK)
7983 if (*expr_p == NULL_TREE)
7984 break;
7985 if (*expr_p != save_expr)
7986 continue;
7988 else if (ret != GS_UNHANDLED)
7989 break;
7991 /* Make sure that all the cases set 'ret' appropriately. */
7992 ret = GS_UNHANDLED;
7993 switch (TREE_CODE (*expr_p))
7995 /* First deal with the special cases. */
7997 case POSTINCREMENT_EXPR:
7998 case POSTDECREMENT_EXPR:
7999 case PREINCREMENT_EXPR:
8000 case PREDECREMENT_EXPR:
8001 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
8002 fallback != fb_none,
8003 TREE_TYPE (*expr_p));
8004 break;
8006 case VIEW_CONVERT_EXPR:
8007 if (is_gimple_reg_type (TREE_TYPE (*expr_p))
8008 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
8010 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8011 post_p, is_gimple_val, fb_rvalue);
8012 recalculate_side_effects (*expr_p);
8013 break;
8015 /* Fallthru. */
8017 case ARRAY_REF:
8018 case ARRAY_RANGE_REF:
8019 case REALPART_EXPR:
8020 case IMAGPART_EXPR:
8021 case COMPONENT_REF:
8022 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
8023 fallback ? fallback : fb_rvalue);
8024 break;
8026 case COND_EXPR:
8027 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
8029 /* C99 code may assign to an array in a structure value of a
8030 conditional expression, and this has undefined behavior
8031 only on execution, so create a temporary if an lvalue is
8032 required. */
8033 if (fallback == fb_lvalue)
8035 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
8036 mark_addressable (*expr_p);
8037 ret = GS_OK;
8039 break;
8041 case CALL_EXPR:
8042 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
8044 /* C99 code may assign to an array in a structure returned
8045 from a function, and this has undefined behavior only on
8046 execution, so create a temporary if an lvalue is
8047 required. */
8048 if (fallback == fb_lvalue)
8050 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
8051 mark_addressable (*expr_p);
8052 ret = GS_OK;
8054 break;
8056 case TREE_LIST:
8057 gcc_unreachable ();
8059 case COMPOUND_EXPR:
8060 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
8061 break;
8063 case COMPOUND_LITERAL_EXPR:
8064 ret = gimplify_compound_literal_expr (expr_p, pre_p,
8065 gimple_test_f, fallback);
8066 break;
8068 case MODIFY_EXPR:
8069 case INIT_EXPR:
8070 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
8071 fallback != fb_none);
8072 break;
8074 case TRUTH_ANDIF_EXPR:
8075 case TRUTH_ORIF_EXPR:
8077 /* Preserve the original type of the expression and the
8078 source location of the outer expression. */
8079 tree org_type = TREE_TYPE (*expr_p);
8080 *expr_p = gimple_boolify (*expr_p);
8081 *expr_p = build3_loc (input_location, COND_EXPR,
8082 org_type, *expr_p,
8083 fold_convert_loc
8084 (input_location,
8085 org_type, boolean_true_node),
8086 fold_convert_loc
8087 (input_location,
8088 org_type, boolean_false_node));
8089 ret = GS_OK;
8090 break;
8093 case TRUTH_NOT_EXPR:
8095 tree type = TREE_TYPE (*expr_p);
8096 /* The parsers are careful to generate TRUTH_NOT_EXPR
8097 only with operands that are always zero or one.
8098 We do not fold here but handle the only interesting case
8099 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
8100 *expr_p = gimple_boolify (*expr_p);
8101 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
8102 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
8103 TREE_TYPE (*expr_p),
8104 TREE_OPERAND (*expr_p, 0));
8105 else
8106 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
8107 TREE_TYPE (*expr_p),
8108 TREE_OPERAND (*expr_p, 0),
8109 build_int_cst (TREE_TYPE (*expr_p), 1));
8110 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
8111 *expr_p = fold_convert_loc (input_location, type, *expr_p);
8112 ret = GS_OK;
8113 break;
8116 case ADDR_EXPR:
8117 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
8118 break;
8120 case ANNOTATE_EXPR:
8122 tree cond = TREE_OPERAND (*expr_p, 0);
8123 tree kind = TREE_OPERAND (*expr_p, 1);
8124 tree type = TREE_TYPE (cond);
8125 if (!INTEGRAL_TYPE_P (type))
8127 *expr_p = cond;
8128 ret = GS_OK;
8129 break;
8131 tree tmp = create_tmp_var (type);
8132 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
8133 gcall *call
8134 = gimple_build_call_internal (IFN_ANNOTATE, 2, cond, kind);
8135 gimple_call_set_lhs (call, tmp);
8136 gimplify_seq_add_stmt (pre_p, call);
8137 *expr_p = tmp;
8138 ret = GS_ALL_DONE;
8139 break;
8142 case VA_ARG_EXPR:
8143 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
8144 break;
8146 CASE_CONVERT:
8147 if (IS_EMPTY_STMT (*expr_p))
8149 ret = GS_ALL_DONE;
8150 break;
8153 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
8154 || fallback == fb_none)
8156 /* Just strip a conversion to void (or in void context) and
8157 try again. */
8158 *expr_p = TREE_OPERAND (*expr_p, 0);
8159 ret = GS_OK;
8160 break;
8163 ret = gimplify_conversion (expr_p);
8164 if (ret == GS_ERROR)
8165 break;
8166 if (*expr_p != save_expr)
8167 break;
8168 /* FALLTHRU */
8170 case FIX_TRUNC_EXPR:
8171 /* unary_expr: ... | '(' cast ')' val | ... */
8172 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8173 is_gimple_val, fb_rvalue);
8174 recalculate_side_effects (*expr_p);
8175 break;
8177 case INDIRECT_REF:
8179 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
8180 bool notrap = TREE_THIS_NOTRAP (*expr_p);
8181 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
8183 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
8184 if (*expr_p != save_expr)
8186 ret = GS_OK;
8187 break;
8190 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8191 is_gimple_reg, fb_rvalue);
8192 if (ret == GS_ERROR)
8193 break;
8195 recalculate_side_effects (*expr_p);
8196 *expr_p = fold_build2_loc (input_location, MEM_REF,
8197 TREE_TYPE (*expr_p),
8198 TREE_OPERAND (*expr_p, 0),
8199 build_int_cst (saved_ptr_type, 0));
8200 TREE_THIS_VOLATILE (*expr_p) = volatilep;
8201 TREE_THIS_NOTRAP (*expr_p) = notrap;
8202 ret = GS_OK;
8203 break;
8206 /* We arrive here through the various re-gimplifcation paths. */
8207 case MEM_REF:
8208 /* First try re-folding the whole thing. */
8209 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
8210 TREE_OPERAND (*expr_p, 0),
8211 TREE_OPERAND (*expr_p, 1));
8212 if (tmp)
8214 *expr_p = tmp;
8215 recalculate_side_effects (*expr_p);
8216 ret = GS_OK;
8217 break;
8219 /* Avoid re-gimplifying the address operand if it is already
8220 in suitable form. Re-gimplifying would mark the address
8221 operand addressable. Always gimplify when not in SSA form
8222 as we still may have to gimplify decls with value-exprs. */
8223 if (!gimplify_ctxp || !gimplify_ctxp->into_ssa
8224 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
8226 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8227 is_gimple_mem_ref_addr, fb_rvalue);
8228 if (ret == GS_ERROR)
8229 break;
8231 recalculate_side_effects (*expr_p);
8232 ret = GS_ALL_DONE;
8233 break;
8235 /* Constants need not be gimplified. */
8236 case INTEGER_CST:
8237 case REAL_CST:
8238 case FIXED_CST:
8239 case STRING_CST:
8240 case COMPLEX_CST:
8241 case VECTOR_CST:
8242 /* Drop the overflow flag on constants, we do not want
8243 that in the GIMPLE IL. */
8244 if (TREE_OVERFLOW_P (*expr_p))
8245 *expr_p = drop_tree_overflow (*expr_p);
8246 ret = GS_ALL_DONE;
8247 break;
8249 case CONST_DECL:
8250 /* If we require an lvalue, such as for ADDR_EXPR, retain the
8251 CONST_DECL node. Otherwise the decl is replaceable by its
8252 value. */
8253 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
8254 if (fallback & fb_lvalue)
8255 ret = GS_ALL_DONE;
8256 else
8258 *expr_p = DECL_INITIAL (*expr_p);
8259 ret = GS_OK;
8261 break;
8263 case DECL_EXPR:
8264 ret = gimplify_decl_expr (expr_p, pre_p);
8265 break;
8267 case BIND_EXPR:
8268 ret = gimplify_bind_expr (expr_p, pre_p);
8269 break;
8271 case LOOP_EXPR:
8272 ret = gimplify_loop_expr (expr_p, pre_p);
8273 break;
8275 case SWITCH_EXPR:
8276 ret = gimplify_switch_expr (expr_p, pre_p);
8277 break;
8279 case EXIT_EXPR:
8280 ret = gimplify_exit_expr (expr_p);
8281 break;
8283 case GOTO_EXPR:
8284 /* If the target is not LABEL, then it is a computed jump
8285 and the target needs to be gimplified. */
8286 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
8288 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
8289 NULL, is_gimple_val, fb_rvalue);
8290 if (ret == GS_ERROR)
8291 break;
8293 gimplify_seq_add_stmt (pre_p,
8294 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
8295 ret = GS_ALL_DONE;
8296 break;
8298 case PREDICT_EXPR:
8299 gimplify_seq_add_stmt (pre_p,
8300 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
8301 PREDICT_EXPR_OUTCOME (*expr_p)));
8302 ret = GS_ALL_DONE;
8303 break;
8305 case LABEL_EXPR:
8306 ret = GS_ALL_DONE;
8307 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
8308 == current_function_decl);
8309 gimplify_seq_add_stmt (pre_p,
8310 gimple_build_label (LABEL_EXPR_LABEL (*expr_p)));
8311 break;
8313 case CASE_LABEL_EXPR:
8314 ret = gimplify_case_label_expr (expr_p, pre_p);
8315 break;
8317 case RETURN_EXPR:
8318 ret = gimplify_return_expr (*expr_p, pre_p);
8319 break;
8321 case CONSTRUCTOR:
8322 /* Don't reduce this in place; let gimplify_init_constructor work its
8323 magic. Buf if we're just elaborating this for side effects, just
8324 gimplify any element that has side-effects. */
8325 if (fallback == fb_none)
8327 unsigned HOST_WIDE_INT ix;
8328 tree val;
8329 tree temp = NULL_TREE;
8330 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
8331 if (TREE_SIDE_EFFECTS (val))
8332 append_to_statement_list (val, &temp);
8334 *expr_p = temp;
8335 ret = temp ? GS_OK : GS_ALL_DONE;
8337 /* C99 code may assign to an array in a constructed
8338 structure or union, and this has undefined behavior only
8339 on execution, so create a temporary if an lvalue is
8340 required. */
8341 else if (fallback == fb_lvalue)
8343 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
8344 mark_addressable (*expr_p);
8345 ret = GS_OK;
8347 else
8348 ret = GS_ALL_DONE;
8349 break;
8351 /* The following are special cases that are not handled by the
8352 original GIMPLE grammar. */
8354 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
8355 eliminated. */
8356 case SAVE_EXPR:
8357 ret = gimplify_save_expr (expr_p, pre_p, post_p);
8358 break;
8360 case BIT_FIELD_REF:
8361 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8362 post_p, is_gimple_lvalue, fb_either);
8363 recalculate_side_effects (*expr_p);
8364 break;
8366 case TARGET_MEM_REF:
8368 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
8370 if (TMR_BASE (*expr_p))
8371 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
8372 post_p, is_gimple_mem_ref_addr, fb_either);
8373 if (TMR_INDEX (*expr_p))
8374 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
8375 post_p, is_gimple_val, fb_rvalue);
8376 if (TMR_INDEX2 (*expr_p))
8377 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
8378 post_p, is_gimple_val, fb_rvalue);
8379 /* TMR_STEP and TMR_OFFSET are always integer constants. */
8380 ret = MIN (r0, r1);
8382 break;
8384 case NON_LVALUE_EXPR:
8385 /* This should have been stripped above. */
8386 gcc_unreachable ();
8388 case ASM_EXPR:
8389 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
8390 break;
8392 case TRY_FINALLY_EXPR:
8393 case TRY_CATCH_EXPR:
8395 gimple_seq eval, cleanup;
8396 gtry *try_;
8398 /* Calls to destructors are generated automatically in FINALLY/CATCH
8399 block. They should have location as UNKNOWN_LOCATION. However,
8400 gimplify_call_expr will reset these call stmts to input_location
8401 if it finds stmt's location is unknown. To prevent resetting for
8402 destructors, we set the input_location to unknown.
8403 Note that this only affects the destructor calls in FINALLY/CATCH
8404 block, and will automatically reset to its original value by the
8405 end of gimplify_expr. */
8406 input_location = UNKNOWN_LOCATION;
8407 eval = cleanup = NULL;
8408 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
8409 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
8410 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
8411 if (gimple_seq_empty_p (cleanup))
8413 gimple_seq_add_seq (pre_p, eval);
8414 ret = GS_ALL_DONE;
8415 break;
8417 try_ = gimple_build_try (eval, cleanup,
8418 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
8419 ? GIMPLE_TRY_FINALLY
8420 : GIMPLE_TRY_CATCH);
8421 if (EXPR_HAS_LOCATION (save_expr))
8422 gimple_set_location (try_, EXPR_LOCATION (save_expr));
8423 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
8424 gimple_set_location (try_, saved_location);
8425 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
8426 gimple_try_set_catch_is_cleanup (try_,
8427 TRY_CATCH_IS_CLEANUP (*expr_p));
8428 gimplify_seq_add_stmt (pre_p, try_);
8429 ret = GS_ALL_DONE;
8430 break;
8433 case CLEANUP_POINT_EXPR:
8434 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
8435 break;
8437 case TARGET_EXPR:
8438 ret = gimplify_target_expr (expr_p, pre_p, post_p);
8439 break;
8441 case CATCH_EXPR:
8443 gimple c;
8444 gimple_seq handler = NULL;
8445 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
8446 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
8447 gimplify_seq_add_stmt (pre_p, c);
8448 ret = GS_ALL_DONE;
8449 break;
8452 case EH_FILTER_EXPR:
8454 gimple ehf;
8455 gimple_seq failure = NULL;
8457 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
8458 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
8459 gimple_set_no_warning (ehf, TREE_NO_WARNING (*expr_p));
8460 gimplify_seq_add_stmt (pre_p, ehf);
8461 ret = GS_ALL_DONE;
8462 break;
8465 case OBJ_TYPE_REF:
8467 enum gimplify_status r0, r1;
8468 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
8469 post_p, is_gimple_val, fb_rvalue);
8470 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
8471 post_p, is_gimple_val, fb_rvalue);
8472 TREE_SIDE_EFFECTS (*expr_p) = 0;
8473 ret = MIN (r0, r1);
8475 break;
8477 case LABEL_DECL:
8478 /* We get here when taking the address of a label. We mark
8479 the label as "forced"; meaning it can never be removed and
8480 it is a potential target for any computed goto. */
8481 FORCED_LABEL (*expr_p) = 1;
8482 ret = GS_ALL_DONE;
8483 break;
8485 case STATEMENT_LIST:
8486 ret = gimplify_statement_list (expr_p, pre_p);
8487 break;
8489 case WITH_SIZE_EXPR:
8491 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8492 post_p == &internal_post ? NULL : post_p,
8493 gimple_test_f, fallback);
8494 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
8495 is_gimple_val, fb_rvalue);
8496 ret = GS_ALL_DONE;
8498 break;
8500 case VAR_DECL:
8501 case PARM_DECL:
8502 ret = gimplify_var_or_parm_decl (expr_p);
8503 break;
8505 case RESULT_DECL:
8506 /* When within an OMP context, notice uses of variables. */
8507 if (gimplify_omp_ctxp)
8508 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
8509 ret = GS_ALL_DONE;
8510 break;
8512 case SSA_NAME:
8513 /* Allow callbacks into the gimplifier during optimization. */
8514 ret = GS_ALL_DONE;
8515 break;
8517 case OMP_PARALLEL:
8518 gimplify_omp_parallel (expr_p, pre_p);
8519 ret = GS_ALL_DONE;
8520 break;
8522 case OMP_TASK:
8523 gimplify_omp_task (expr_p, pre_p);
8524 ret = GS_ALL_DONE;
8525 break;
8527 case OMP_FOR:
8528 case OMP_SIMD:
8529 case CILK_SIMD:
8530 case CILK_FOR:
8531 case OMP_DISTRIBUTE:
8532 case OACC_LOOP:
8533 ret = gimplify_omp_for (expr_p, pre_p);
8534 break;
8536 case OACC_CACHE:
8537 gimplify_oacc_cache (expr_p, pre_p);
8538 ret = GS_ALL_DONE;
8539 break;
8541 case OACC_HOST_DATA:
8542 case OACC_DECLARE:
8543 sorry ("directive not yet implemented");
8544 ret = GS_ALL_DONE;
8545 break;
8547 case OACC_KERNELS:
8548 if (OACC_KERNELS_COMBINED (*expr_p))
8549 sorry ("directive not yet implemented");
8550 else
8551 gimplify_omp_workshare (expr_p, pre_p);
8552 ret = GS_ALL_DONE;
8553 break;
8555 case OACC_PARALLEL:
8556 if (OACC_PARALLEL_COMBINED (*expr_p))
8557 sorry ("directive not yet implemented");
8558 else
8559 gimplify_omp_workshare (expr_p, pre_p);
8560 ret = GS_ALL_DONE;
8561 break;
8563 case OACC_DATA:
8564 case OMP_SECTIONS:
8565 case OMP_SINGLE:
8566 case OMP_TARGET:
8567 case OMP_TARGET_DATA:
8568 case OMP_TEAMS:
8569 gimplify_omp_workshare (expr_p, pre_p);
8570 ret = GS_ALL_DONE;
8571 break;
8573 case OACC_ENTER_DATA:
8574 case OACC_EXIT_DATA:
8575 case OACC_UPDATE:
8576 case OMP_TARGET_UPDATE:
8577 gimplify_omp_target_update (expr_p, pre_p);
8578 ret = GS_ALL_DONE;
8579 break;
8581 case OMP_SECTION:
8582 case OMP_MASTER:
8583 case OMP_TASKGROUP:
8584 case OMP_ORDERED:
8585 case OMP_CRITICAL:
8587 gimple_seq body = NULL;
8588 gimple g;
8590 gimplify_and_add (OMP_BODY (*expr_p), &body);
8591 switch (TREE_CODE (*expr_p))
8593 case OMP_SECTION:
8594 g = gimple_build_omp_section (body);
8595 break;
8596 case OMP_MASTER:
8597 g = gimple_build_omp_master (body);
8598 break;
8599 case OMP_TASKGROUP:
8601 gimple_seq cleanup = NULL;
8602 tree fn
8603 = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
8604 g = gimple_build_call (fn, 0);
8605 gimple_seq_add_stmt (&cleanup, g);
8606 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
8607 body = NULL;
8608 gimple_seq_add_stmt (&body, g);
8609 g = gimple_build_omp_taskgroup (body);
8611 break;
8612 case OMP_ORDERED:
8613 g = gimple_build_omp_ordered (body);
8614 break;
8615 case OMP_CRITICAL:
8616 g = gimple_build_omp_critical (body,
8617 OMP_CRITICAL_NAME (*expr_p));
8618 break;
8619 default:
8620 gcc_unreachable ();
8622 gimplify_seq_add_stmt (pre_p, g);
8623 ret = GS_ALL_DONE;
8624 break;
8627 case OMP_ATOMIC:
8628 case OMP_ATOMIC_READ:
8629 case OMP_ATOMIC_CAPTURE_OLD:
8630 case OMP_ATOMIC_CAPTURE_NEW:
8631 ret = gimplify_omp_atomic (expr_p, pre_p);
8632 break;
8634 case TRANSACTION_EXPR:
8635 ret = gimplify_transaction (expr_p, pre_p);
8636 break;
8638 case TRUTH_AND_EXPR:
8639 case TRUTH_OR_EXPR:
8640 case TRUTH_XOR_EXPR:
8642 tree orig_type = TREE_TYPE (*expr_p);
8643 tree new_type, xop0, xop1;
8644 *expr_p = gimple_boolify (*expr_p);
8645 new_type = TREE_TYPE (*expr_p);
8646 if (!useless_type_conversion_p (orig_type, new_type))
8648 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
8649 ret = GS_OK;
8650 break;
8653 /* Boolified binary truth expressions are semantically equivalent
8654 to bitwise binary expressions. Canonicalize them to the
8655 bitwise variant. */
8656 switch (TREE_CODE (*expr_p))
8658 case TRUTH_AND_EXPR:
8659 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
8660 break;
8661 case TRUTH_OR_EXPR:
8662 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
8663 break;
8664 case TRUTH_XOR_EXPR:
8665 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
8666 break;
8667 default:
8668 break;
8670 /* Now make sure that operands have compatible type to
8671 expression's new_type. */
8672 xop0 = TREE_OPERAND (*expr_p, 0);
8673 xop1 = TREE_OPERAND (*expr_p, 1);
8674 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
8675 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
8676 new_type,
8677 xop0);
8678 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
8679 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
8680 new_type,
8681 xop1);
8682 /* Continue classified as tcc_binary. */
8683 goto expr_2;
8686 case FMA_EXPR:
8687 case VEC_COND_EXPR:
8688 case VEC_PERM_EXPR:
8689 /* Classified as tcc_expression. */
8690 goto expr_3;
8692 case POINTER_PLUS_EXPR:
8694 enum gimplify_status r0, r1;
8695 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8696 post_p, is_gimple_val, fb_rvalue);
8697 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8698 post_p, is_gimple_val, fb_rvalue);
8699 recalculate_side_effects (*expr_p);
8700 ret = MIN (r0, r1);
8701 break;
8704 case CILK_SYNC_STMT:
8706 if (!fn_contains_cilk_spawn_p (cfun))
8708 error_at (EXPR_LOCATION (*expr_p),
8709 "expected %<_Cilk_spawn%> before %<_Cilk_sync%>");
8710 ret = GS_ERROR;
8712 else
8714 gimplify_cilk_sync (expr_p, pre_p);
8715 ret = GS_ALL_DONE;
8717 break;
8720 default:
8721 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
8723 case tcc_comparison:
8724 /* Handle comparison of objects of non scalar mode aggregates
8725 with a call to memcmp. It would be nice to only have to do
8726 this for variable-sized objects, but then we'd have to allow
8727 the same nest of reference nodes we allow for MODIFY_EXPR and
8728 that's too complex.
8730 Compare scalar mode aggregates as scalar mode values. Using
8731 memcmp for them would be very inefficient at best, and is
8732 plain wrong if bitfields are involved. */
8734 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
8736 /* Vector comparisons need no boolification. */
8737 if (TREE_CODE (type) == VECTOR_TYPE)
8738 goto expr_2;
8739 else if (!AGGREGATE_TYPE_P (type))
8741 tree org_type = TREE_TYPE (*expr_p);
8742 *expr_p = gimple_boolify (*expr_p);
8743 if (!useless_type_conversion_p (org_type,
8744 TREE_TYPE (*expr_p)))
8746 *expr_p = fold_convert_loc (input_location,
8747 org_type, *expr_p);
8748 ret = GS_OK;
8750 else
8751 goto expr_2;
8753 else if (TYPE_MODE (type) != BLKmode)
8754 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
8755 else
8756 ret = gimplify_variable_sized_compare (expr_p);
8758 break;
8761 /* If *EXPR_P does not need to be special-cased, handle it
8762 according to its class. */
8763 case tcc_unary:
8764 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8765 post_p, is_gimple_val, fb_rvalue);
8766 break;
8768 case tcc_binary:
8769 expr_2:
8771 enum gimplify_status r0, r1;
8773 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8774 post_p, is_gimple_val, fb_rvalue);
8775 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8776 post_p, is_gimple_val, fb_rvalue);
8778 ret = MIN (r0, r1);
8779 break;
8782 expr_3:
8784 enum gimplify_status r0, r1, r2;
8786 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8787 post_p, is_gimple_val, fb_rvalue);
8788 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8789 post_p, is_gimple_val, fb_rvalue);
8790 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
8791 post_p, is_gimple_val, fb_rvalue);
8793 ret = MIN (MIN (r0, r1), r2);
8794 break;
8797 case tcc_declaration:
8798 case tcc_constant:
8799 ret = GS_ALL_DONE;
8800 goto dont_recalculate;
8802 default:
8803 gcc_unreachable ();
8806 recalculate_side_effects (*expr_p);
8808 dont_recalculate:
8809 break;
8812 gcc_assert (*expr_p || ret != GS_OK);
8814 while (ret == GS_OK);
8816 /* If we encountered an error_mark somewhere nested inside, either
8817 stub out the statement or propagate the error back out. */
8818 if (ret == GS_ERROR)
8820 if (is_statement)
8821 *expr_p = NULL;
8822 goto out;
8825 /* This was only valid as a return value from the langhook, which
8826 we handled. Make sure it doesn't escape from any other context. */
8827 gcc_assert (ret != GS_UNHANDLED);
8829 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
8831 /* We aren't looking for a value, and we don't have a valid
8832 statement. If it doesn't have side-effects, throw it away. */
8833 if (!TREE_SIDE_EFFECTS (*expr_p))
8834 *expr_p = NULL;
8835 else if (!TREE_THIS_VOLATILE (*expr_p))
8837 /* This is probably a _REF that contains something nested that
8838 has side effects. Recurse through the operands to find it. */
8839 enum tree_code code = TREE_CODE (*expr_p);
8841 switch (code)
8843 case COMPONENT_REF:
8844 case REALPART_EXPR:
8845 case IMAGPART_EXPR:
8846 case VIEW_CONVERT_EXPR:
8847 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8848 gimple_test_f, fallback);
8849 break;
8851 case ARRAY_REF:
8852 case ARRAY_RANGE_REF:
8853 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8854 gimple_test_f, fallback);
8855 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
8856 gimple_test_f, fallback);
8857 break;
8859 default:
8860 /* Anything else with side-effects must be converted to
8861 a valid statement before we get here. */
8862 gcc_unreachable ();
8865 *expr_p = NULL;
8867 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
8868 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
8870 /* Historically, the compiler has treated a bare reference
8871 to a non-BLKmode volatile lvalue as forcing a load. */
8872 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
8874 /* Normally, we do not want to create a temporary for a
8875 TREE_ADDRESSABLE type because such a type should not be
8876 copied by bitwise-assignment. However, we make an
8877 exception here, as all we are doing here is ensuring that
8878 we read the bytes that make up the type. We use
8879 create_tmp_var_raw because create_tmp_var will abort when
8880 given a TREE_ADDRESSABLE type. */
8881 tree tmp = create_tmp_var_raw (type, "vol");
8882 gimple_add_tmp_var (tmp);
8883 gimplify_assign (tmp, *expr_p, pre_p);
8884 *expr_p = NULL;
8886 else
8887 /* We can't do anything useful with a volatile reference to
8888 an incomplete type, so just throw it away. Likewise for
8889 a BLKmode type, since any implicit inner load should
8890 already have been turned into an explicit one by the
8891 gimplification process. */
8892 *expr_p = NULL;
8895 /* If we are gimplifying at the statement level, we're done. Tack
8896 everything together and return. */
8897 if (fallback == fb_none || is_statement)
8899 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
8900 it out for GC to reclaim it. */
8901 *expr_p = NULL_TREE;
8903 if (!gimple_seq_empty_p (internal_pre)
8904 || !gimple_seq_empty_p (internal_post))
8906 gimplify_seq_add_seq (&internal_pre, internal_post);
8907 gimplify_seq_add_seq (pre_p, internal_pre);
8910 /* The result of gimplifying *EXPR_P is going to be the last few
8911 statements in *PRE_P and *POST_P. Add location information
8912 to all the statements that were added by the gimplification
8913 helpers. */
8914 if (!gimple_seq_empty_p (*pre_p))
8915 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
8917 if (!gimple_seq_empty_p (*post_p))
8918 annotate_all_with_location_after (*post_p, post_last_gsi,
8919 input_location);
8921 goto out;
8924 #ifdef ENABLE_GIMPLE_CHECKING
8925 if (*expr_p)
8927 enum tree_code code = TREE_CODE (*expr_p);
8928 /* These expressions should already be in gimple IR form. */
8929 gcc_assert (code != MODIFY_EXPR
8930 && code != ASM_EXPR
8931 && code != BIND_EXPR
8932 && code != CATCH_EXPR
8933 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
8934 && code != EH_FILTER_EXPR
8935 && code != GOTO_EXPR
8936 && code != LABEL_EXPR
8937 && code != LOOP_EXPR
8938 && code != SWITCH_EXPR
8939 && code != TRY_FINALLY_EXPR
8940 && code != OACC_PARALLEL
8941 && code != OACC_KERNELS
8942 && code != OACC_DATA
8943 && code != OACC_HOST_DATA
8944 && code != OACC_DECLARE
8945 && code != OACC_UPDATE
8946 && code != OACC_ENTER_DATA
8947 && code != OACC_EXIT_DATA
8948 && code != OACC_CACHE
8949 && code != OMP_CRITICAL
8950 && code != OMP_FOR
8951 && code != OACC_LOOP
8952 && code != OMP_MASTER
8953 && code != OMP_TASKGROUP
8954 && code != OMP_ORDERED
8955 && code != OMP_PARALLEL
8956 && code != OMP_SECTIONS
8957 && code != OMP_SECTION
8958 && code != OMP_SINGLE);
8960 #endif
8962 /* Otherwise we're gimplifying a subexpression, so the resulting
8963 value is interesting. If it's a valid operand that matches
8964 GIMPLE_TEST_F, we're done. Unless we are handling some
8965 post-effects internally; if that's the case, we need to copy into
8966 a temporary before adding the post-effects to POST_P. */
8967 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
8968 goto out;
8970 /* Otherwise, we need to create a new temporary for the gimplified
8971 expression. */
8973 /* We can't return an lvalue if we have an internal postqueue. The
8974 object the lvalue refers to would (probably) be modified by the
8975 postqueue; we need to copy the value out first, which means an
8976 rvalue. */
8977 if ((fallback & fb_lvalue)
8978 && gimple_seq_empty_p (internal_post)
8979 && is_gimple_addressable (*expr_p))
8981 /* An lvalue will do. Take the address of the expression, store it
8982 in a temporary, and replace the expression with an INDIRECT_REF of
8983 that temporary. */
8984 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
8985 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
8986 *expr_p = build_simple_mem_ref (tmp);
8988 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
8990 /* An rvalue will do. Assign the gimplified expression into a
8991 new temporary TMP and replace the original expression with
8992 TMP. First, make sure that the expression has a type so that
8993 it can be assigned into a temporary. */
8994 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
8995 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
8997 else
8999 #ifdef ENABLE_GIMPLE_CHECKING
9000 if (!(fallback & fb_mayfail))
9002 fprintf (stderr, "gimplification failed:\n");
9003 print_generic_expr (stderr, *expr_p, 0);
9004 debug_tree (*expr_p);
9005 internal_error ("gimplification failed");
9007 #endif
9008 gcc_assert (fallback & fb_mayfail);
9010 /* If this is an asm statement, and the user asked for the
9011 impossible, don't die. Fail and let gimplify_asm_expr
9012 issue an error. */
9013 ret = GS_ERROR;
9014 goto out;
9017 /* Make sure the temporary matches our predicate. */
9018 gcc_assert ((*gimple_test_f) (*expr_p));
9020 if (!gimple_seq_empty_p (internal_post))
9022 annotate_all_with_location (internal_post, input_location);
9023 gimplify_seq_add_seq (pre_p, internal_post);
9026 out:
9027 input_location = saved_location;
9028 return ret;
9031 /* Look through TYPE for variable-sized objects and gimplify each such
9032 size that we find. Add to LIST_P any statements generated. */
9034 void
9035 gimplify_type_sizes (tree type, gimple_seq *list_p)
9037 tree field, t;
9039 if (type == NULL || type == error_mark_node)
9040 return;
9042 /* We first do the main variant, then copy into any other variants. */
9043 type = TYPE_MAIN_VARIANT (type);
9045 /* Avoid infinite recursion. */
9046 if (TYPE_SIZES_GIMPLIFIED (type))
9047 return;
9049 TYPE_SIZES_GIMPLIFIED (type) = 1;
9051 switch (TREE_CODE (type))
9053 case INTEGER_TYPE:
9054 case ENUMERAL_TYPE:
9055 case BOOLEAN_TYPE:
9056 case REAL_TYPE:
9057 case FIXED_POINT_TYPE:
9058 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
9059 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
9061 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
9063 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
9064 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
9066 break;
9068 case ARRAY_TYPE:
9069 /* These types may not have declarations, so handle them here. */
9070 gimplify_type_sizes (TREE_TYPE (type), list_p);
9071 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
9072 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
9073 with assigned stack slots, for -O1+ -g they should be tracked
9074 by VTA. */
9075 if (!(TYPE_NAME (type)
9076 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
9077 && DECL_IGNORED_P (TYPE_NAME (type)))
9078 && TYPE_DOMAIN (type)
9079 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
9081 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
9082 if (t && TREE_CODE (t) == VAR_DECL && DECL_ARTIFICIAL (t))
9083 DECL_IGNORED_P (t) = 0;
9084 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
9085 if (t && TREE_CODE (t) == VAR_DECL && DECL_ARTIFICIAL (t))
9086 DECL_IGNORED_P (t) = 0;
9088 break;
9090 case RECORD_TYPE:
9091 case UNION_TYPE:
9092 case QUAL_UNION_TYPE:
9093 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
9094 if (TREE_CODE (field) == FIELD_DECL)
9096 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
9097 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
9098 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
9099 gimplify_type_sizes (TREE_TYPE (field), list_p);
9101 break;
9103 case POINTER_TYPE:
9104 case REFERENCE_TYPE:
9105 /* We used to recurse on the pointed-to type here, which turned out to
9106 be incorrect because its definition might refer to variables not
9107 yet initialized at this point if a forward declaration is involved.
9109 It was actually useful for anonymous pointed-to types to ensure
9110 that the sizes evaluation dominates every possible later use of the
9111 values. Restricting to such types here would be safe since there
9112 is no possible forward declaration around, but would introduce an
9113 undesirable middle-end semantic to anonymity. We then defer to
9114 front-ends the responsibility of ensuring that the sizes are
9115 evaluated both early and late enough, e.g. by attaching artificial
9116 type declarations to the tree. */
9117 break;
9119 default:
9120 break;
9123 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
9124 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
9126 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
9128 TYPE_SIZE (t) = TYPE_SIZE (type);
9129 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
9130 TYPE_SIZES_GIMPLIFIED (t) = 1;
9134 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
9135 a size or position, has had all of its SAVE_EXPRs evaluated.
9136 We add any required statements to *STMT_P. */
9138 void
9139 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
9141 tree expr = *expr_p;
9143 /* We don't do anything if the value isn't there, is constant, or contains
9144 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
9145 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
9146 will want to replace it with a new variable, but that will cause problems
9147 if this type is from outside the function. It's OK to have that here. */
9148 if (is_gimple_sizepos (expr))
9149 return;
9151 *expr_p = unshare_expr (expr);
9153 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue);
9156 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
9157 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
9158 is true, also gimplify the parameters. */
9160 gbind *
9161 gimplify_body (tree fndecl, bool do_parms)
9163 location_t saved_location = input_location;
9164 gimple_seq parm_stmts, seq;
9165 gimple outer_stmt;
9166 gbind *outer_bind;
9167 struct cgraph_node *cgn;
9169 timevar_push (TV_TREE_GIMPLIFY);
9171 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
9172 gimplification. */
9173 default_rtl_profile ();
9175 gcc_assert (gimplify_ctxp == NULL);
9176 push_gimplify_context ();
9178 if (flag_openacc || flag_openmp)
9180 gcc_assert (gimplify_omp_ctxp == NULL);
9181 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
9182 gimplify_omp_ctxp = new_omp_context (ORT_TARGET);
9185 /* Unshare most shared trees in the body and in that of any nested functions.
9186 It would seem we don't have to do this for nested functions because
9187 they are supposed to be output and then the outer function gimplified
9188 first, but the g++ front end doesn't always do it that way. */
9189 unshare_body (fndecl);
9190 unvisit_body (fndecl);
9192 cgn = cgraph_node::get (fndecl);
9193 if (cgn && cgn->origin)
9194 nonlocal_vlas = new hash_set<tree>;
9196 /* Make sure input_location isn't set to something weird. */
9197 input_location = DECL_SOURCE_LOCATION (fndecl);
9199 /* Resolve callee-copies. This has to be done before processing
9200 the body so that DECL_VALUE_EXPR gets processed correctly. */
9201 parm_stmts = do_parms ? gimplify_parameters () : NULL;
9203 /* Gimplify the function's body. */
9204 seq = NULL;
9205 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
9206 outer_stmt = gimple_seq_first_stmt (seq);
9207 if (!outer_stmt)
9209 outer_stmt = gimple_build_nop ();
9210 gimplify_seq_add_stmt (&seq, outer_stmt);
9213 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
9214 not the case, wrap everything in a GIMPLE_BIND to make it so. */
9215 if (gimple_code (outer_stmt) == GIMPLE_BIND
9216 && gimple_seq_first (seq) == gimple_seq_last (seq))
9217 outer_bind = as_a <gbind *> (outer_stmt);
9218 else
9219 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
9221 DECL_SAVED_TREE (fndecl) = NULL_TREE;
9223 /* If we had callee-copies statements, insert them at the beginning
9224 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
9225 if (!gimple_seq_empty_p (parm_stmts))
9227 tree parm;
9229 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
9230 gimple_bind_set_body (outer_bind, parm_stmts);
9232 for (parm = DECL_ARGUMENTS (current_function_decl);
9233 parm; parm = DECL_CHAIN (parm))
9234 if (DECL_HAS_VALUE_EXPR_P (parm))
9236 DECL_HAS_VALUE_EXPR_P (parm) = 0;
9237 DECL_IGNORED_P (parm) = 0;
9241 if (nonlocal_vlas)
9243 if (nonlocal_vla_vars)
9245 /* tree-nested.c may later on call declare_vars (..., true);
9246 which relies on BLOCK_VARS chain to be the tail of the
9247 gimple_bind_vars chain. Ensure we don't violate that
9248 assumption. */
9249 if (gimple_bind_block (outer_bind)
9250 == DECL_INITIAL (current_function_decl))
9251 declare_vars (nonlocal_vla_vars, outer_bind, true);
9252 else
9253 BLOCK_VARS (DECL_INITIAL (current_function_decl))
9254 = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl)),
9255 nonlocal_vla_vars);
9256 nonlocal_vla_vars = NULL_TREE;
9258 delete nonlocal_vlas;
9259 nonlocal_vlas = NULL;
9262 if ((flag_openacc || flag_openmp || flag_openmp_simd)
9263 && gimplify_omp_ctxp)
9265 delete_omp_context (gimplify_omp_ctxp);
9266 gimplify_omp_ctxp = NULL;
9269 pop_gimplify_context (outer_bind);
9270 gcc_assert (gimplify_ctxp == NULL);
9272 #ifdef ENABLE_CHECKING
9273 if (!seen_error ())
9274 verify_gimple_in_seq (gimple_bind_body (outer_bind));
9275 #endif
9277 timevar_pop (TV_TREE_GIMPLIFY);
9278 input_location = saved_location;
9280 return outer_bind;
9283 typedef char *char_p; /* For DEF_VEC_P. */
9285 /* Return whether we should exclude FNDECL from instrumentation. */
9287 static bool
9288 flag_instrument_functions_exclude_p (tree fndecl)
9290 vec<char_p> *v;
9292 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
9293 if (v && v->length () > 0)
9295 const char *name;
9296 int i;
9297 char *s;
9299 name = lang_hooks.decl_printable_name (fndecl, 0);
9300 FOR_EACH_VEC_ELT (*v, i, s)
9301 if (strstr (name, s) != NULL)
9302 return true;
9305 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
9306 if (v && v->length () > 0)
9308 const char *name;
9309 int i;
9310 char *s;
9312 name = DECL_SOURCE_FILE (fndecl);
9313 FOR_EACH_VEC_ELT (*v, i, s)
9314 if (strstr (name, s) != NULL)
9315 return true;
9318 return false;
9321 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
9322 node for the function we want to gimplify.
9324 Return the sequence of GIMPLE statements corresponding to the body
9325 of FNDECL. */
9327 void
9328 gimplify_function_tree (tree fndecl)
9330 tree parm, ret;
9331 gimple_seq seq;
9332 gbind *bind;
9334 gcc_assert (!gimple_body (fndecl));
9336 if (DECL_STRUCT_FUNCTION (fndecl))
9337 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
9338 else
9339 push_struct_function (fndecl);
9341 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
9342 if necessary. */
9343 cfun->curr_properties |= PROP_gimple_lva;
9345 for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = DECL_CHAIN (parm))
9347 /* Preliminarily mark non-addressed complex variables as eligible
9348 for promotion to gimple registers. We'll transform their uses
9349 as we find them. */
9350 if ((TREE_CODE (TREE_TYPE (parm)) == COMPLEX_TYPE
9351 || TREE_CODE (TREE_TYPE (parm)) == VECTOR_TYPE)
9352 && !TREE_THIS_VOLATILE (parm)
9353 && !needs_to_live_in_memory (parm))
9354 DECL_GIMPLE_REG_P (parm) = 1;
9357 ret = DECL_RESULT (fndecl);
9358 if ((TREE_CODE (TREE_TYPE (ret)) == COMPLEX_TYPE
9359 || TREE_CODE (TREE_TYPE (ret)) == VECTOR_TYPE)
9360 && !needs_to_live_in_memory (ret))
9361 DECL_GIMPLE_REG_P (ret) = 1;
9363 bind = gimplify_body (fndecl, true);
9365 /* The tree body of the function is no longer needed, replace it
9366 with the new GIMPLE body. */
9367 seq = NULL;
9368 gimple_seq_add_stmt (&seq, bind);
9369 gimple_set_body (fndecl, seq);
9371 /* If we're instrumenting function entry/exit, then prepend the call to
9372 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
9373 catch the exit hook. */
9374 /* ??? Add some way to ignore exceptions for this TFE. */
9375 if (flag_instrument_function_entry_exit
9376 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
9377 && !flag_instrument_functions_exclude_p (fndecl))
9379 tree x;
9380 gbind *new_bind;
9381 gimple tf;
9382 gimple_seq cleanup = NULL, body = NULL;
9383 tree tmp_var;
9384 gcall *call;
9386 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
9387 call = gimple_build_call (x, 1, integer_zero_node);
9388 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
9389 gimple_call_set_lhs (call, tmp_var);
9390 gimplify_seq_add_stmt (&cleanup, call);
9391 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
9392 call = gimple_build_call (x, 2,
9393 build_fold_addr_expr (current_function_decl),
9394 tmp_var);
9395 gimplify_seq_add_stmt (&cleanup, call);
9396 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
9398 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
9399 call = gimple_build_call (x, 1, integer_zero_node);
9400 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
9401 gimple_call_set_lhs (call, tmp_var);
9402 gimplify_seq_add_stmt (&body, call);
9403 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
9404 call = gimple_build_call (x, 2,
9405 build_fold_addr_expr (current_function_decl),
9406 tmp_var);
9407 gimplify_seq_add_stmt (&body, call);
9408 gimplify_seq_add_stmt (&body, tf);
9409 new_bind = gimple_build_bind (NULL, body, gimple_bind_block (bind));
9410 /* Clear the block for BIND, since it is no longer directly inside
9411 the function, but within a try block. */
9412 gimple_bind_set_block (bind, NULL);
9414 /* Replace the current function body with the body
9415 wrapped in the try/finally TF. */
9416 seq = NULL;
9417 gimple_seq_add_stmt (&seq, new_bind);
9418 gimple_set_body (fndecl, seq);
9419 bind = new_bind;
9422 if ((flag_sanitize & SANITIZE_THREAD) != 0
9423 && !lookup_attribute ("no_sanitize_thread", DECL_ATTRIBUTES (fndecl)))
9425 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
9426 gimple tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
9427 gbind *new_bind = gimple_build_bind (NULL, tf, gimple_bind_block (bind));
9428 /* Clear the block for BIND, since it is no longer directly inside
9429 the function, but within a try block. */
9430 gimple_bind_set_block (bind, NULL);
9431 /* Replace the current function body with the body
9432 wrapped in the try/finally TF. */
9433 seq = NULL;
9434 gimple_seq_add_stmt (&seq, new_bind);
9435 gimple_set_body (fndecl, seq);
9438 DECL_SAVED_TREE (fndecl) = NULL_TREE;
9439 cfun->curr_properties |= PROP_gimple_any;
9441 pop_cfun ();
9443 dump_function (TDI_generic, fndecl);
9446 /* Return a dummy expression of type TYPE in order to keep going after an
9447 error. */
9449 static tree
9450 dummy_object (tree type)
9452 tree t = build_int_cst (build_pointer_type (type), 0);
9453 return build2 (MEM_REF, type, t, t);
9456 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
9457 builtin function, but a very special sort of operator. */
9459 enum gimplify_status
9460 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
9461 gimple_seq *post_p ATTRIBUTE_UNUSED)
9463 tree promoted_type, have_va_type;
9464 tree valist = TREE_OPERAND (*expr_p, 0);
9465 tree type = TREE_TYPE (*expr_p);
9466 tree t, tag;
9467 location_t loc = EXPR_LOCATION (*expr_p);
9469 /* Verify that valist is of the proper type. */
9470 have_va_type = TREE_TYPE (valist);
9471 if (have_va_type == error_mark_node)
9472 return GS_ERROR;
9473 have_va_type = targetm.canonical_va_list_type (have_va_type);
9475 if (have_va_type == NULL_TREE)
9477 error_at (loc, "first argument to %<va_arg%> not of type %<va_list%>");
9478 return GS_ERROR;
9481 /* Generate a diagnostic for requesting data of a type that cannot
9482 be passed through `...' due to type promotion at the call site. */
9483 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
9484 != type)
9486 static bool gave_help;
9487 bool warned;
9489 /* Unfortunately, this is merely undefined, rather than a constraint
9490 violation, so we cannot make this an error. If this call is never
9491 executed, the program is still strictly conforming. */
9492 warned = warning_at (loc, 0,
9493 "%qT is promoted to %qT when passed through %<...%>",
9494 type, promoted_type);
9495 if (!gave_help && warned)
9497 gave_help = true;
9498 inform (loc, "(so you should pass %qT not %qT to %<va_arg%>)",
9499 promoted_type, type);
9502 /* We can, however, treat "undefined" any way we please.
9503 Call abort to encourage the user to fix the program. */
9504 if (warned)
9505 inform (loc, "if this code is reached, the program will abort");
9506 /* Before the abort, allow the evaluation of the va_list
9507 expression to exit or longjmp. */
9508 gimplify_and_add (valist, pre_p);
9509 t = build_call_expr_loc (loc,
9510 builtin_decl_implicit (BUILT_IN_TRAP), 0);
9511 gimplify_and_add (t, pre_p);
9513 /* This is dead code, but go ahead and finish so that the
9514 mode of the result comes out right. */
9515 *expr_p = dummy_object (type);
9516 return GS_ALL_DONE;
9519 tag = build_int_cst (build_pointer_type (type), 0);
9520 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 2, valist, tag);
9522 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
9523 needs to be expanded. */
9524 cfun->curr_properties &= ~PROP_gimple_lva;
9526 return GS_OK;
9529 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
9531 DST/SRC are the destination and source respectively. You can pass
9532 ungimplified trees in DST or SRC, in which case they will be
9533 converted to a gimple operand if necessary.
9535 This function returns the newly created GIMPLE_ASSIGN tuple. */
9537 gimple
9538 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
9540 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
9541 gimplify_and_add (t, seq_p);
9542 ggc_free (t);
9543 return gimple_seq_last_stmt (*seq_p);
9546 inline hashval_t
9547 gimplify_hasher::hash (const elt_t *p)
9549 tree t = p->val;
9550 return iterative_hash_expr (t, 0);
9553 inline bool
9554 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
9556 tree t1 = p1->val;
9557 tree t2 = p2->val;
9558 enum tree_code code = TREE_CODE (t1);
9560 if (TREE_CODE (t2) != code
9561 || TREE_TYPE (t1) != TREE_TYPE (t2))
9562 return false;
9564 if (!operand_equal_p (t1, t2, 0))
9565 return false;
9567 #ifdef ENABLE_CHECKING
9568 /* Only allow them to compare equal if they also hash equal; otherwise
9569 results are nondeterminate, and we fail bootstrap comparison. */
9570 gcc_assert (hash (p1) == hash (p2));
9571 #endif
9573 return true;