gcc/
[official-gcc.git] / gcc / gimplify.c
blob5f4936c32501147c8f9ce48f7517e5819c324cc6
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 "alias.h"
27 #include "symtab.h"
28 #include "options.h"
29 #include "tree.h"
30 #include "fold-const.h"
31 #include "tm.h"
32 #include "hard-reg-set.h"
33 #include "function.h"
34 #include "rtl.h"
35 #include "flags.h"
36 #include "insn-config.h"
37 #include "expmed.h"
38 #include "dojump.h"
39 #include "explow.h"
40 #include "calls.h"
41 #include "emit-rtl.h"
42 #include "varasm.h"
43 #include "stmt.h"
44 #include "expr.h"
45 #include "predict.h"
46 #include "basic-block.h"
47 #include "tree-ssa-alias.h"
48 #include "internal-fn.h"
49 #include "gimple-fold.h"
50 #include "tree-eh.h"
51 #include "gimple-expr.h"
52 #include "gimple.h"
53 #include "gimplify.h"
54 #include "gimple-iterator.h"
55 #include "stringpool.h"
56 #include "stor-layout.h"
57 #include "print-tree.h"
58 #include "tree-iterator.h"
59 #include "tree-inline.h"
60 #include "tree-pretty-print.h"
61 #include "langhooks.h"
62 #include "bitmap.h"
63 #include "gimple-ssa.h"
64 #include "plugin-api.h"
65 #include "ipa-ref.h"
66 #include "cgraph.h"
67 #include "tree-cfg.h"
68 #include "tree-ssanames.h"
69 #include "tree-ssa.h"
70 #include "diagnostic-core.h"
71 #include "target.h"
72 #include "splay-tree.h"
73 #include "omp-low.h"
74 #include "gimple-low.h"
75 #include "cilk.h"
76 #include "gomp-constants.h"
77 #include "tree-dump.h"
79 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
80 #include "tree-pass.h" /* FIXME: only for PROP_gimple_any */
81 #include "builtins.h"
83 enum gimplify_omp_var_data
85 GOVD_SEEN = 1,
86 GOVD_EXPLICIT = 2,
87 GOVD_SHARED = 4,
88 GOVD_PRIVATE = 8,
89 GOVD_FIRSTPRIVATE = 16,
90 GOVD_LASTPRIVATE = 32,
91 GOVD_REDUCTION = 64,
92 GOVD_LOCAL = 128,
93 GOVD_MAP = 256,
94 GOVD_DEBUG_PRIVATE = 512,
95 GOVD_PRIVATE_OUTER_REF = 1024,
96 GOVD_LINEAR = 2048,
97 GOVD_ALIGNED = 4096,
99 /* Flag for GOVD_MAP: don't copy back. */
100 GOVD_MAP_TO_ONLY = 8192,
102 /* Flag for GOVD_LINEAR or GOVD_LASTPRIVATE: no outer reference. */
103 GOVD_LINEAR_LASTPRIVATE_NO_OUTER = 16384,
105 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
106 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
107 | GOVD_LOCAL)
111 enum omp_region_type
113 ORT_WORKSHARE = 0,
114 ORT_SIMD = 1,
115 ORT_PARALLEL = 2,
116 ORT_COMBINED_PARALLEL = 3,
117 ORT_TASK = 4,
118 ORT_UNTIED_TASK = 5,
119 ORT_TEAMS = 8,
120 ORT_COMBINED_TEAMS = 9,
121 /* Data region. */
122 ORT_TARGET_DATA = 16,
123 /* Data region with offloading. */
124 ORT_TARGET = 32
127 /* Gimplify hashtable helper. */
129 struct gimplify_hasher : free_ptr_hash <elt_t>
131 static inline hashval_t hash (const elt_t *);
132 static inline bool equal (const elt_t *, const elt_t *);
135 struct gimplify_ctx
137 struct gimplify_ctx *prev_context;
139 vec<gbind *> bind_expr_stack;
140 tree temps;
141 gimple_seq conditional_cleanups;
142 tree exit_label;
143 tree return_temp;
145 vec<tree> case_labels;
146 /* The formal temporary table. Should this be persistent? */
147 hash_table<gimplify_hasher> *temp_htab;
149 int conditions;
150 bool save_stack;
151 bool into_ssa;
152 bool allow_rhs_cond_expr;
153 bool in_cleanup_point_expr;
156 struct gimplify_omp_ctx
158 struct gimplify_omp_ctx *outer_context;
159 splay_tree variables;
160 hash_set<tree> *privatized_types;
161 location_t location;
162 enum omp_clause_default_kind default_kind;
163 enum omp_region_type region_type;
164 bool combined_loop;
165 bool distribute;
168 static struct gimplify_ctx *gimplify_ctxp;
169 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
171 /* Forward declaration. */
172 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
174 /* Shorter alias name for the above function for use in gimplify.c
175 only. */
177 static inline void
178 gimplify_seq_add_stmt (gimple_seq *seq_p, gimple gs)
180 gimple_seq_add_stmt_without_update (seq_p, gs);
183 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
184 NULL, a new sequence is allocated. This function is
185 similar to gimple_seq_add_seq, but does not scan the operands.
186 During gimplification, we need to manipulate statement sequences
187 before the def/use vectors have been constructed. */
189 static void
190 gimplify_seq_add_seq (gimple_seq *dst_p, gimple_seq src)
192 gimple_stmt_iterator si;
194 if (src == NULL)
195 return;
197 si = gsi_last (*dst_p);
198 gsi_insert_seq_after_without_update (&si, src, GSI_NEW_STMT);
202 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
203 and popping gimplify contexts. */
205 static struct gimplify_ctx *ctx_pool = NULL;
207 /* Return a gimplify context struct from the pool. */
209 static inline struct gimplify_ctx *
210 ctx_alloc (void)
212 struct gimplify_ctx * c = ctx_pool;
214 if (c)
215 ctx_pool = c->prev_context;
216 else
217 c = XNEW (struct gimplify_ctx);
219 memset (c, '\0', sizeof (*c));
220 return c;
223 /* Put gimplify context C back into the pool. */
225 static inline void
226 ctx_free (struct gimplify_ctx *c)
228 c->prev_context = ctx_pool;
229 ctx_pool = c;
232 /* Free allocated ctx stack memory. */
234 void
235 free_gimplify_stack (void)
237 struct gimplify_ctx *c;
239 while ((c = ctx_pool))
241 ctx_pool = c->prev_context;
242 free (c);
247 /* Set up a context for the gimplifier. */
249 void
250 push_gimplify_context (bool in_ssa, bool rhs_cond_ok)
252 struct gimplify_ctx *c = ctx_alloc ();
254 c->prev_context = gimplify_ctxp;
255 gimplify_ctxp = c;
256 gimplify_ctxp->into_ssa = in_ssa;
257 gimplify_ctxp->allow_rhs_cond_expr = rhs_cond_ok;
260 /* Tear down a context for the gimplifier. If BODY is non-null, then
261 put the temporaries into the outer BIND_EXPR. Otherwise, put them
262 in the local_decls.
264 BODY is not a sequence, but the first tuple in a sequence. */
266 void
267 pop_gimplify_context (gimple body)
269 struct gimplify_ctx *c = gimplify_ctxp;
271 gcc_assert (c
272 && (!c->bind_expr_stack.exists ()
273 || c->bind_expr_stack.is_empty ()));
274 c->bind_expr_stack.release ();
275 gimplify_ctxp = c->prev_context;
277 if (body)
278 declare_vars (c->temps, body, false);
279 else
280 record_vars (c->temps);
282 delete c->temp_htab;
283 c->temp_htab = NULL;
284 ctx_free (c);
287 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
289 static void
290 gimple_push_bind_expr (gbind *bind_stmt)
292 gimplify_ctxp->bind_expr_stack.reserve (8);
293 gimplify_ctxp->bind_expr_stack.safe_push (bind_stmt);
296 /* Pop the first element off the stack of bindings. */
298 static void
299 gimple_pop_bind_expr (void)
301 gimplify_ctxp->bind_expr_stack.pop ();
304 /* Return the first element of the stack of bindings. */
306 gbind *
307 gimple_current_bind_expr (void)
309 return gimplify_ctxp->bind_expr_stack.last ();
312 /* Return the stack of bindings created during gimplification. */
314 vec<gbind *>
315 gimple_bind_expr_stack (void)
317 return gimplify_ctxp->bind_expr_stack;
320 /* Return true iff there is a COND_EXPR between us and the innermost
321 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
323 static bool
324 gimple_conditional_context (void)
326 return gimplify_ctxp->conditions > 0;
329 /* Note that we've entered a COND_EXPR. */
331 static void
332 gimple_push_condition (void)
334 #ifdef ENABLE_GIMPLE_CHECKING
335 if (gimplify_ctxp->conditions == 0)
336 gcc_assert (gimple_seq_empty_p (gimplify_ctxp->conditional_cleanups));
337 #endif
338 ++(gimplify_ctxp->conditions);
341 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
342 now, add any conditional cleanups we've seen to the prequeue. */
344 static void
345 gimple_pop_condition (gimple_seq *pre_p)
347 int conds = --(gimplify_ctxp->conditions);
349 gcc_assert (conds >= 0);
350 if (conds == 0)
352 gimplify_seq_add_seq (pre_p, gimplify_ctxp->conditional_cleanups);
353 gimplify_ctxp->conditional_cleanups = NULL;
357 /* A stable comparison routine for use with splay trees and DECLs. */
359 static int
360 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
362 tree a = (tree) xa;
363 tree b = (tree) xb;
365 return DECL_UID (a) - DECL_UID (b);
368 /* Create a new omp construct that deals with variable remapping. */
370 static struct gimplify_omp_ctx *
371 new_omp_context (enum omp_region_type region_type)
373 struct gimplify_omp_ctx *c;
375 c = XCNEW (struct gimplify_omp_ctx);
376 c->outer_context = gimplify_omp_ctxp;
377 c->variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
378 c->privatized_types = new hash_set<tree>;
379 c->location = input_location;
380 c->region_type = region_type;
381 if ((region_type & ORT_TASK) == 0)
382 c->default_kind = OMP_CLAUSE_DEFAULT_SHARED;
383 else
384 c->default_kind = OMP_CLAUSE_DEFAULT_UNSPECIFIED;
386 return c;
389 /* Destroy an omp construct that deals with variable remapping. */
391 static void
392 delete_omp_context (struct gimplify_omp_ctx *c)
394 splay_tree_delete (c->variables);
395 delete c->privatized_types;
396 XDELETE (c);
399 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
400 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
402 /* Both gimplify the statement T and append it to *SEQ_P. This function
403 behaves exactly as gimplify_stmt, but you don't have to pass T as a
404 reference. */
406 void
407 gimplify_and_add (tree t, gimple_seq *seq_p)
409 gimplify_stmt (&t, seq_p);
412 /* Gimplify statement T into sequence *SEQ_P, and return the first
413 tuple in the sequence of generated tuples for this statement.
414 Return NULL if gimplifying T produced no tuples. */
416 static gimple
417 gimplify_and_return_first (tree t, gimple_seq *seq_p)
419 gimple_stmt_iterator last = gsi_last (*seq_p);
421 gimplify_and_add (t, seq_p);
423 if (!gsi_end_p (last))
425 gsi_next (&last);
426 return gsi_stmt (last);
428 else
429 return gimple_seq_first_stmt (*seq_p);
432 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
433 LHS, or for a call argument. */
435 static bool
436 is_gimple_mem_rhs (tree t)
438 /* If we're dealing with a renamable type, either source or dest must be
439 a renamed variable. */
440 if (is_gimple_reg_type (TREE_TYPE (t)))
441 return is_gimple_val (t);
442 else
443 return is_gimple_val (t) || is_gimple_lvalue (t);
446 /* Return true if T is a CALL_EXPR or an expression that can be
447 assigned to a temporary. Note that this predicate should only be
448 used during gimplification. See the rationale for this in
449 gimplify_modify_expr. */
451 static bool
452 is_gimple_reg_rhs_or_call (tree t)
454 return (get_gimple_rhs_class (TREE_CODE (t)) != GIMPLE_INVALID_RHS
455 || TREE_CODE (t) == CALL_EXPR);
458 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
459 this predicate should only be used during gimplification. See the
460 rationale for this in gimplify_modify_expr. */
462 static bool
463 is_gimple_mem_rhs_or_call (tree t)
465 /* If we're dealing with a renamable type, either source or dest must be
466 a renamed variable. */
467 if (is_gimple_reg_type (TREE_TYPE (t)))
468 return is_gimple_val (t);
469 else
470 return (is_gimple_val (t) || is_gimple_lvalue (t)
471 || TREE_CODE (t) == CALL_EXPR);
474 /* Create a temporary with a name derived from VAL. Subroutine of
475 lookup_tmp_var; nobody else should call this function. */
477 static inline tree
478 create_tmp_from_val (tree val)
480 /* Drop all qualifiers and address-space information from the value type. */
481 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (val));
482 tree var = create_tmp_var (type, get_name (val));
483 if (TREE_CODE (TREE_TYPE (var)) == COMPLEX_TYPE
484 || TREE_CODE (TREE_TYPE (var)) == VECTOR_TYPE)
485 DECL_GIMPLE_REG_P (var) = 1;
486 return var;
489 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
490 an existing expression temporary. */
492 static tree
493 lookup_tmp_var (tree val, bool is_formal)
495 tree ret;
497 /* If not optimizing, never really reuse a temporary. local-alloc
498 won't allocate any variable that is used in more than one basic
499 block, which means it will go into memory, causing much extra
500 work in reload and final and poorer code generation, outweighing
501 the extra memory allocation here. */
502 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
503 ret = create_tmp_from_val (val);
504 else
506 elt_t elt, *elt_p;
507 elt_t **slot;
509 elt.val = val;
510 if (!gimplify_ctxp->temp_htab)
511 gimplify_ctxp->temp_htab = new hash_table<gimplify_hasher> (1000);
512 slot = gimplify_ctxp->temp_htab->find_slot (&elt, INSERT);
513 if (*slot == NULL)
515 elt_p = XNEW (elt_t);
516 elt_p->val = val;
517 elt_p->temp = ret = create_tmp_from_val (val);
518 *slot = elt_p;
520 else
522 elt_p = *slot;
523 ret = elt_p->temp;
527 return ret;
530 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
532 static tree
533 internal_get_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
534 bool is_formal)
536 tree t, mod;
538 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
539 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
540 gimplify_expr (&val, pre_p, post_p, is_gimple_reg_rhs_or_call,
541 fb_rvalue);
543 if (gimplify_ctxp->into_ssa
544 && is_gimple_reg_type (TREE_TYPE (val)))
545 t = make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val)));
546 else
547 t = lookup_tmp_var (val, is_formal);
549 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
551 SET_EXPR_LOCATION (mod, EXPR_LOC_OR_LOC (val, input_location));
553 /* gimplify_modify_expr might want to reduce this further. */
554 gimplify_and_add (mod, pre_p);
555 ggc_free (mod);
557 return t;
560 /* Return a formal temporary variable initialized with VAL. PRE_P is as
561 in gimplify_expr. Only use this function if:
563 1) The value of the unfactored expression represented by VAL will not
564 change between the initialization and use of the temporary, and
565 2) The temporary will not be otherwise modified.
567 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
568 and #2 means it is inappropriate for && temps.
570 For other cases, use get_initialized_tmp_var instead. */
572 tree
573 get_formal_tmp_var (tree val, gimple_seq *pre_p)
575 return internal_get_tmp_var (val, pre_p, NULL, true);
578 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
579 are as in gimplify_expr. */
581 tree
582 get_initialized_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p)
584 return internal_get_tmp_var (val, pre_p, post_p, false);
587 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
588 generate debug info for them; otherwise don't. */
590 void
591 declare_vars (tree vars, gimple gs, bool debug_info)
593 tree last = vars;
594 if (last)
596 tree temps, block;
598 gbind *scope = as_a <gbind *> (gs);
600 temps = nreverse (last);
602 block = gimple_bind_block (scope);
603 gcc_assert (!block || TREE_CODE (block) == BLOCK);
604 if (!block || !debug_info)
606 DECL_CHAIN (last) = gimple_bind_vars (scope);
607 gimple_bind_set_vars (scope, temps);
609 else
611 /* We need to attach the nodes both to the BIND_EXPR and to its
612 associated BLOCK for debugging purposes. The key point here
613 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
614 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
615 if (BLOCK_VARS (block))
616 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
617 else
619 gimple_bind_set_vars (scope,
620 chainon (gimple_bind_vars (scope), temps));
621 BLOCK_VARS (block) = temps;
627 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
628 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
629 no such upper bound can be obtained. */
631 static void
632 force_constant_size (tree var)
634 /* The only attempt we make is by querying the maximum size of objects
635 of the variable's type. */
637 HOST_WIDE_INT max_size;
639 gcc_assert (TREE_CODE (var) == VAR_DECL);
641 max_size = max_int_size_in_bytes (TREE_TYPE (var));
643 gcc_assert (max_size >= 0);
645 DECL_SIZE_UNIT (var)
646 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
647 DECL_SIZE (var)
648 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
651 /* Push the temporary variable TMP into the current binding. */
653 void
654 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
656 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
658 /* Later processing assumes that the object size is constant, which might
659 not be true at this point. Force the use of a constant upper bound in
660 this case. */
661 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp)))
662 force_constant_size (tmp);
664 DECL_CONTEXT (tmp) = fn->decl;
665 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
667 record_vars_into (tmp, fn->decl);
670 /* Push the temporary variable TMP into the current binding. */
672 void
673 gimple_add_tmp_var (tree tmp)
675 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
677 /* Later processing assumes that the object size is constant, which might
678 not be true at this point. Force the use of a constant upper bound in
679 this case. */
680 if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp)))
681 force_constant_size (tmp);
683 DECL_CONTEXT (tmp) = current_function_decl;
684 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
686 if (gimplify_ctxp)
688 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
689 gimplify_ctxp->temps = tmp;
691 /* Mark temporaries local within the nearest enclosing parallel. */
692 if (gimplify_omp_ctxp)
694 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
695 while (ctx
696 && (ctx->region_type == ORT_WORKSHARE
697 || ctx->region_type == ORT_SIMD))
698 ctx = ctx->outer_context;
699 if (ctx)
700 omp_add_variable (ctx, tmp, GOVD_LOCAL | GOVD_SEEN);
703 else if (cfun)
704 record_vars (tmp);
705 else
707 gimple_seq body_seq;
709 /* This case is for nested functions. We need to expose the locals
710 they create. */
711 body_seq = gimple_body (current_function_decl);
712 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
718 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
719 nodes that are referenced more than once in GENERIC functions. This is
720 necessary because gimplification (translation into GIMPLE) is performed
721 by modifying tree nodes in-place, so gimplication of a shared node in a
722 first context could generate an invalid GIMPLE form in a second context.
724 This is achieved with a simple mark/copy/unmark algorithm that walks the
725 GENERIC representation top-down, marks nodes with TREE_VISITED the first
726 time it encounters them, duplicates them if they already have TREE_VISITED
727 set, and finally removes the TREE_VISITED marks it has set.
729 The algorithm works only at the function level, i.e. it generates a GENERIC
730 representation of a function with no nodes shared within the function when
731 passed a GENERIC function (except for nodes that are allowed to be shared).
733 At the global level, it is also necessary to unshare tree nodes that are
734 referenced in more than one function, for the same aforementioned reason.
735 This requires some cooperation from the front-end. There are 2 strategies:
737 1. Manual unsharing. The front-end needs to call unshare_expr on every
738 expression that might end up being shared across functions.
740 2. Deep unsharing. This is an extension of regular unsharing. Instead
741 of calling unshare_expr on expressions that might be shared across
742 functions, the front-end pre-marks them with TREE_VISITED. This will
743 ensure that they are unshared on the first reference within functions
744 when the regular unsharing algorithm runs. The counterpart is that
745 this algorithm must look deeper than for manual unsharing, which is
746 specified by LANG_HOOKS_DEEP_UNSHARING.
748 If there are only few specific cases of node sharing across functions, it is
749 probably easier for a front-end to unshare the expressions manually. On the
750 contrary, if the expressions generated at the global level are as widespread
751 as expressions generated within functions, deep unsharing is very likely the
752 way to go. */
754 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
755 These nodes model computations that must be done once. If we were to
756 unshare something like SAVE_EXPR(i++), the gimplification process would
757 create wrong code. However, if DATA is non-null, it must hold a pointer
758 set that is used to unshare the subtrees of these nodes. */
760 static tree
761 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
763 tree t = *tp;
764 enum tree_code code = TREE_CODE (t);
766 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
767 copy their subtrees if we can make sure to do it only once. */
768 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
770 if (data && !((hash_set<tree> *)data)->add (t))
772 else
773 *walk_subtrees = 0;
776 /* Stop at types, decls, constants like copy_tree_r. */
777 else if (TREE_CODE_CLASS (code) == tcc_type
778 || TREE_CODE_CLASS (code) == tcc_declaration
779 || TREE_CODE_CLASS (code) == tcc_constant
780 /* We can't do anything sensible with a BLOCK used as an
781 expression, but we also can't just die when we see it
782 because of non-expression uses. So we avert our eyes
783 and cross our fingers. Silly Java. */
784 || code == BLOCK)
785 *walk_subtrees = 0;
787 /* Cope with the statement expression extension. */
788 else if (code == STATEMENT_LIST)
791 /* Leave the bulk of the work to copy_tree_r itself. */
792 else
793 copy_tree_r (tp, walk_subtrees, NULL);
795 return NULL_TREE;
798 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
799 If *TP has been visited already, then *TP is deeply copied by calling
800 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
802 static tree
803 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
805 tree t = *tp;
806 enum tree_code code = TREE_CODE (t);
808 /* Skip types, decls, and constants. But we do want to look at their
809 types and the bounds of types. Mark them as visited so we properly
810 unmark their subtrees on the unmark pass. If we've already seen them,
811 don't look down further. */
812 if (TREE_CODE_CLASS (code) == tcc_type
813 || TREE_CODE_CLASS (code) == tcc_declaration
814 || TREE_CODE_CLASS (code) == tcc_constant)
816 if (TREE_VISITED (t))
817 *walk_subtrees = 0;
818 else
819 TREE_VISITED (t) = 1;
822 /* If this node has been visited already, unshare it and don't look
823 any deeper. */
824 else if (TREE_VISITED (t))
826 walk_tree (tp, mostly_copy_tree_r, data, NULL);
827 *walk_subtrees = 0;
830 /* Otherwise, mark the node as visited and keep looking. */
831 else
832 TREE_VISITED (t) = 1;
834 return NULL_TREE;
837 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
838 copy_if_shared_r callback unmodified. */
840 static inline void
841 copy_if_shared (tree *tp, void *data)
843 walk_tree (tp, copy_if_shared_r, data, NULL);
846 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
847 any nested functions. */
849 static void
850 unshare_body (tree fndecl)
852 struct cgraph_node *cgn = cgraph_node::get (fndecl);
853 /* If the language requires deep unsharing, we need a pointer set to make
854 sure we don't repeatedly unshare subtrees of unshareable nodes. */
855 hash_set<tree> *visited
856 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
858 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
859 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
860 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
862 delete visited;
864 if (cgn)
865 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
866 unshare_body (cgn->decl);
869 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
870 Subtrees are walked until the first unvisited node is encountered. */
872 static tree
873 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
875 tree t = *tp;
877 /* If this node has been visited, unmark it and keep looking. */
878 if (TREE_VISITED (t))
879 TREE_VISITED (t) = 0;
881 /* Otherwise, don't look any deeper. */
882 else
883 *walk_subtrees = 0;
885 return NULL_TREE;
888 /* Unmark the visited trees rooted at *TP. */
890 static inline void
891 unmark_visited (tree *tp)
893 walk_tree (tp, unmark_visited_r, NULL, NULL);
896 /* Likewise, but mark all trees as not visited. */
898 static void
899 unvisit_body (tree fndecl)
901 struct cgraph_node *cgn = cgraph_node::get (fndecl);
903 unmark_visited (&DECL_SAVED_TREE (fndecl));
904 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
905 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
907 if (cgn)
908 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
909 unvisit_body (cgn->decl);
912 /* Unconditionally make an unshared copy of EXPR. This is used when using
913 stored expressions which span multiple functions, such as BINFO_VTABLE,
914 as the normal unsharing process can't tell that they're shared. */
916 tree
917 unshare_expr (tree expr)
919 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
920 return expr;
923 /* Worker for unshare_expr_without_location. */
925 static tree
926 prune_expr_location (tree *tp, int *walk_subtrees, void *)
928 if (EXPR_P (*tp))
929 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
930 else
931 *walk_subtrees = 0;
932 return NULL_TREE;
935 /* Similar to unshare_expr but also prune all expression locations
936 from EXPR. */
938 tree
939 unshare_expr_without_location (tree expr)
941 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
942 if (EXPR_P (expr))
943 walk_tree (&expr, prune_expr_location, NULL, NULL);
944 return expr;
947 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
948 contain statements and have a value. Assign its value to a temporary
949 and give it void_type_node. Return the temporary, or NULL_TREE if
950 WRAPPER was already void. */
952 tree
953 voidify_wrapper_expr (tree wrapper, tree temp)
955 tree type = TREE_TYPE (wrapper);
956 if (type && !VOID_TYPE_P (type))
958 tree *p;
960 /* Set p to point to the body of the wrapper. Loop until we find
961 something that isn't a wrapper. */
962 for (p = &wrapper; p && *p; )
964 switch (TREE_CODE (*p))
966 case BIND_EXPR:
967 TREE_SIDE_EFFECTS (*p) = 1;
968 TREE_TYPE (*p) = void_type_node;
969 /* For a BIND_EXPR, the body is operand 1. */
970 p = &BIND_EXPR_BODY (*p);
971 break;
973 case CLEANUP_POINT_EXPR:
974 case TRY_FINALLY_EXPR:
975 case TRY_CATCH_EXPR:
976 TREE_SIDE_EFFECTS (*p) = 1;
977 TREE_TYPE (*p) = void_type_node;
978 p = &TREE_OPERAND (*p, 0);
979 break;
981 case STATEMENT_LIST:
983 tree_stmt_iterator i = tsi_last (*p);
984 TREE_SIDE_EFFECTS (*p) = 1;
985 TREE_TYPE (*p) = void_type_node;
986 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
988 break;
990 case COMPOUND_EXPR:
991 /* Advance to the last statement. Set all container types to
992 void. */
993 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
995 TREE_SIDE_EFFECTS (*p) = 1;
996 TREE_TYPE (*p) = void_type_node;
998 break;
1000 case TRANSACTION_EXPR:
1001 TREE_SIDE_EFFECTS (*p) = 1;
1002 TREE_TYPE (*p) = void_type_node;
1003 p = &TRANSACTION_EXPR_BODY (*p);
1004 break;
1006 default:
1007 /* Assume that any tree upon which voidify_wrapper_expr is
1008 directly called is a wrapper, and that its body is op0. */
1009 if (p == &wrapper)
1011 TREE_SIDE_EFFECTS (*p) = 1;
1012 TREE_TYPE (*p) = void_type_node;
1013 p = &TREE_OPERAND (*p, 0);
1014 break;
1016 goto out;
1020 out:
1021 if (p == NULL || IS_EMPTY_STMT (*p))
1022 temp = NULL_TREE;
1023 else if (temp)
1025 /* The wrapper is on the RHS of an assignment that we're pushing
1026 down. */
1027 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1028 || TREE_CODE (temp) == MODIFY_EXPR);
1029 TREE_OPERAND (temp, 1) = *p;
1030 *p = temp;
1032 else
1034 temp = create_tmp_var (type, "retval");
1035 *p = build2 (INIT_EXPR, type, temp, *p);
1038 return temp;
1041 return NULL_TREE;
1044 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1045 a temporary through which they communicate. */
1047 static void
1048 build_stack_save_restore (gcall **save, gcall **restore)
1050 tree tmp_var;
1052 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1053 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1054 gimple_call_set_lhs (*save, tmp_var);
1056 *restore
1057 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1058 1, tmp_var);
1061 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1063 static enum gimplify_status
1064 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1066 tree bind_expr = *expr_p;
1067 bool old_save_stack = gimplify_ctxp->save_stack;
1068 tree t;
1069 gbind *bind_stmt;
1070 gimple_seq body, cleanup;
1071 gcall *stack_save;
1072 location_t start_locus = 0, end_locus = 0;
1074 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1076 /* Mark variables seen in this bind expr. */
1077 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1079 if (TREE_CODE (t) == VAR_DECL)
1081 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1083 /* Mark variable as local. */
1084 if (ctx && !DECL_EXTERNAL (t)
1085 && (! DECL_SEEN_IN_BIND_EXPR_P (t)
1086 || splay_tree_lookup (ctx->variables,
1087 (splay_tree_key) t) == NULL))
1089 if (ctx->region_type == ORT_SIMD
1090 && TREE_ADDRESSABLE (t)
1091 && !TREE_STATIC (t))
1092 omp_add_variable (ctx, t, GOVD_PRIVATE | GOVD_SEEN);
1093 else
1094 omp_add_variable (ctx, t, GOVD_LOCAL | GOVD_SEEN);
1097 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1099 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1100 cfun->has_local_explicit_reg_vars = true;
1103 /* Preliminarily mark non-addressed complex variables as eligible
1104 for promotion to gimple registers. We'll transform their uses
1105 as we find them. */
1106 if ((TREE_CODE (TREE_TYPE (t)) == COMPLEX_TYPE
1107 || TREE_CODE (TREE_TYPE (t)) == VECTOR_TYPE)
1108 && !TREE_THIS_VOLATILE (t)
1109 && (TREE_CODE (t) == VAR_DECL && !DECL_HARD_REGISTER (t))
1110 && !needs_to_live_in_memory (t))
1111 DECL_GIMPLE_REG_P (t) = 1;
1114 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1115 BIND_EXPR_BLOCK (bind_expr));
1116 gimple_push_bind_expr (bind_stmt);
1118 gimplify_ctxp->save_stack = false;
1120 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1121 body = NULL;
1122 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1123 gimple_bind_set_body (bind_stmt, body);
1125 /* Source location wise, the cleanup code (stack_restore and clobbers)
1126 belongs to the end of the block, so propagate what we have. The
1127 stack_save operation belongs to the beginning of block, which we can
1128 infer from the bind_expr directly if the block has no explicit
1129 assignment. */
1130 if (BIND_EXPR_BLOCK (bind_expr))
1132 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1133 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1135 if (start_locus == 0)
1136 start_locus = EXPR_LOCATION (bind_expr);
1138 cleanup = NULL;
1139 stack_save = NULL;
1140 if (gimplify_ctxp->save_stack)
1142 gcall *stack_restore;
1144 /* Save stack on entry and restore it on exit. Add a try_finally
1145 block to achieve this. */
1146 build_stack_save_restore (&stack_save, &stack_restore);
1148 gimple_set_location (stack_save, start_locus);
1149 gimple_set_location (stack_restore, end_locus);
1151 gimplify_seq_add_stmt (&cleanup, stack_restore);
1154 /* Add clobbers for all variables that go out of scope. */
1155 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1157 if (TREE_CODE (t) == VAR_DECL
1158 && !is_global_var (t)
1159 && DECL_CONTEXT (t) == current_function_decl
1160 && !DECL_HARD_REGISTER (t)
1161 && !TREE_THIS_VOLATILE (t)
1162 && !DECL_HAS_VALUE_EXPR_P (t)
1163 /* Only care for variables that have to be in memory. Others
1164 will be rewritten into SSA names, hence moved to the top-level. */
1165 && !is_gimple_reg (t)
1166 && flag_stack_reuse != SR_NONE)
1168 tree clobber = build_constructor (TREE_TYPE (t), NULL);
1169 gimple clobber_stmt;
1170 TREE_THIS_VOLATILE (clobber) = 1;
1171 clobber_stmt = gimple_build_assign (t, clobber);
1172 gimple_set_location (clobber_stmt, end_locus);
1173 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1177 if (cleanup)
1179 gtry *gs;
1180 gimple_seq new_body;
1182 new_body = NULL;
1183 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1184 GIMPLE_TRY_FINALLY);
1186 if (stack_save)
1187 gimplify_seq_add_stmt (&new_body, stack_save);
1188 gimplify_seq_add_stmt (&new_body, gs);
1189 gimple_bind_set_body (bind_stmt, new_body);
1192 gimplify_ctxp->save_stack = old_save_stack;
1193 gimple_pop_bind_expr ();
1195 gimplify_seq_add_stmt (pre_p, bind_stmt);
1197 if (temp)
1199 *expr_p = temp;
1200 return GS_OK;
1203 *expr_p = NULL_TREE;
1204 return GS_ALL_DONE;
1207 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1208 GIMPLE value, it is assigned to a new temporary and the statement is
1209 re-written to return the temporary.
1211 PRE_P points to the sequence where side effects that must happen before
1212 STMT should be stored. */
1214 static enum gimplify_status
1215 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1217 greturn *ret;
1218 tree ret_expr = TREE_OPERAND (stmt, 0);
1219 tree result_decl, result;
1221 if (ret_expr == error_mark_node)
1222 return GS_ERROR;
1224 /* Implicit _Cilk_sync must be inserted right before any return statement
1225 if there is a _Cilk_spawn in the function. If the user has provided a
1226 _Cilk_sync, the optimizer should remove this duplicate one. */
1227 if (fn_contains_cilk_spawn_p (cfun))
1229 tree impl_sync = build0 (CILK_SYNC_STMT, void_type_node);
1230 gimplify_and_add (impl_sync, pre_p);
1233 if (!ret_expr
1234 || TREE_CODE (ret_expr) == RESULT_DECL
1235 || ret_expr == error_mark_node)
1237 greturn *ret = gimple_build_return (ret_expr);
1238 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1239 gimplify_seq_add_stmt (pre_p, ret);
1240 return GS_ALL_DONE;
1243 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1244 result_decl = NULL_TREE;
1245 else
1247 result_decl = TREE_OPERAND (ret_expr, 0);
1249 /* See through a return by reference. */
1250 if (TREE_CODE (result_decl) == INDIRECT_REF)
1251 result_decl = TREE_OPERAND (result_decl, 0);
1253 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1254 || TREE_CODE (ret_expr) == INIT_EXPR)
1255 && TREE_CODE (result_decl) == RESULT_DECL);
1258 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1259 Recall that aggregate_value_p is FALSE for any aggregate type that is
1260 returned in registers. If we're returning values in registers, then
1261 we don't want to extend the lifetime of the RESULT_DECL, particularly
1262 across another call. In addition, for those aggregates for which
1263 hard_function_value generates a PARALLEL, we'll die during normal
1264 expansion of structure assignments; there's special code in expand_return
1265 to handle this case that does not exist in expand_expr. */
1266 if (!result_decl)
1267 result = NULL_TREE;
1268 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1270 if (TREE_CODE (DECL_SIZE (result_decl)) != INTEGER_CST)
1272 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1273 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1274 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1275 should be effectively allocated by the caller, i.e. all calls to
1276 this function must be subject to the Return Slot Optimization. */
1277 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1278 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1280 result = result_decl;
1282 else if (gimplify_ctxp->return_temp)
1283 result = gimplify_ctxp->return_temp;
1284 else
1286 result = create_tmp_reg (TREE_TYPE (result_decl));
1288 /* ??? With complex control flow (usually involving abnormal edges),
1289 we can wind up warning about an uninitialized value for this. Due
1290 to how this variable is constructed and initialized, this is never
1291 true. Give up and never warn. */
1292 TREE_NO_WARNING (result) = 1;
1294 gimplify_ctxp->return_temp = result;
1297 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1298 Then gimplify the whole thing. */
1299 if (result != result_decl)
1300 TREE_OPERAND (ret_expr, 0) = result;
1302 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1304 ret = gimple_build_return (result);
1305 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1306 gimplify_seq_add_stmt (pre_p, ret);
1308 return GS_ALL_DONE;
1311 /* Gimplify a variable-length array DECL. */
1313 static void
1314 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1316 /* This is a variable-sized decl. Simplify its size and mark it
1317 for deferred expansion. */
1318 tree t, addr, ptr_type;
1320 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1321 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1323 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1324 if (DECL_HAS_VALUE_EXPR_P (decl))
1325 return;
1327 /* All occurrences of this decl in final gimplified code will be
1328 replaced by indirection. Setting DECL_VALUE_EXPR does two
1329 things: First, it lets the rest of the gimplifier know what
1330 replacement to use. Second, it lets the debug info know
1331 where to find the value. */
1332 ptr_type = build_pointer_type (TREE_TYPE (decl));
1333 addr = create_tmp_var (ptr_type, get_name (decl));
1334 DECL_IGNORED_P (addr) = 0;
1335 t = build_fold_indirect_ref (addr);
1336 TREE_THIS_NOTRAP (t) = 1;
1337 SET_DECL_VALUE_EXPR (decl, t);
1338 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1340 t = builtin_decl_explicit (BUILT_IN_ALLOCA_WITH_ALIGN);
1341 t = build_call_expr (t, 2, DECL_SIZE_UNIT (decl),
1342 size_int (DECL_ALIGN (decl)));
1343 /* The call has been built for a variable-sized object. */
1344 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1345 t = fold_convert (ptr_type, t);
1346 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1348 gimplify_and_add (t, seq_p);
1350 /* Indicate that we need to restore the stack level when the
1351 enclosing BIND_EXPR is exited. */
1352 gimplify_ctxp->save_stack = true;
1355 /* A helper function to be called via walk_tree. Mark all labels under *TP
1356 as being forced. To be called for DECL_INITIAL of static variables. */
1358 static tree
1359 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1361 if (TYPE_P (*tp))
1362 *walk_subtrees = 0;
1363 if (TREE_CODE (*tp) == LABEL_DECL)
1364 FORCED_LABEL (*tp) = 1;
1366 return NULL_TREE;
1369 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1370 and initialization explicit. */
1372 static enum gimplify_status
1373 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1375 tree stmt = *stmt_p;
1376 tree decl = DECL_EXPR_DECL (stmt);
1378 *stmt_p = NULL_TREE;
1380 if (TREE_TYPE (decl) == error_mark_node)
1381 return GS_ERROR;
1383 if ((TREE_CODE (decl) == TYPE_DECL
1384 || TREE_CODE (decl) == VAR_DECL)
1385 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1386 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1388 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1389 in case its size expressions contain problematic nodes like CALL_EXPR. */
1390 if (TREE_CODE (decl) == TYPE_DECL
1391 && DECL_ORIGINAL_TYPE (decl)
1392 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1393 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1395 if (TREE_CODE (decl) == VAR_DECL && !DECL_EXTERNAL (decl))
1397 tree init = DECL_INITIAL (decl);
1399 if (TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
1400 || (!TREE_STATIC (decl)
1401 && flag_stack_check == GENERIC_STACK_CHECK
1402 && compare_tree_int (DECL_SIZE_UNIT (decl),
1403 STACK_CHECK_MAX_VAR_SIZE) > 0))
1404 gimplify_vla_decl (decl, seq_p);
1406 /* Some front ends do not explicitly declare all anonymous
1407 artificial variables. We compensate here by declaring the
1408 variables, though it would be better if the front ends would
1409 explicitly declare them. */
1410 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1411 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1412 gimple_add_tmp_var (decl);
1414 if (init && init != error_mark_node)
1416 if (!TREE_STATIC (decl))
1418 DECL_INITIAL (decl) = NULL_TREE;
1419 init = build2 (INIT_EXPR, void_type_node, decl, init);
1420 gimplify_and_add (init, seq_p);
1421 ggc_free (init);
1423 else
1424 /* We must still examine initializers for static variables
1425 as they may contain a label address. */
1426 walk_tree (&init, force_labels_r, NULL, NULL);
1430 return GS_ALL_DONE;
1433 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1434 and replacing the LOOP_EXPR with goto, but if the loop contains an
1435 EXIT_EXPR, we need to append a label for it to jump to. */
1437 static enum gimplify_status
1438 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1440 tree saved_label = gimplify_ctxp->exit_label;
1441 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1443 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1445 gimplify_ctxp->exit_label = NULL_TREE;
1447 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1449 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
1451 if (gimplify_ctxp->exit_label)
1452 gimplify_seq_add_stmt (pre_p,
1453 gimple_build_label (gimplify_ctxp->exit_label));
1455 gimplify_ctxp->exit_label = saved_label;
1457 *expr_p = NULL;
1458 return GS_ALL_DONE;
1461 /* Gimplify a statement list onto a sequence. These may be created either
1462 by an enlightened front-end, or by shortcut_cond_expr. */
1464 static enum gimplify_status
1465 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
1467 tree temp = voidify_wrapper_expr (*expr_p, NULL);
1469 tree_stmt_iterator i = tsi_start (*expr_p);
1471 while (!tsi_end_p (i))
1473 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
1474 tsi_delink (&i);
1477 if (temp)
1479 *expr_p = temp;
1480 return GS_OK;
1483 return GS_ALL_DONE;
1487 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
1488 branch to. */
1490 static enum gimplify_status
1491 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
1493 tree switch_expr = *expr_p;
1494 gimple_seq switch_body_seq = NULL;
1495 enum gimplify_status ret;
1496 tree index_type = TREE_TYPE (switch_expr);
1497 if (index_type == NULL_TREE)
1498 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
1500 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
1501 fb_rvalue);
1502 if (ret == GS_ERROR || ret == GS_UNHANDLED)
1503 return ret;
1505 if (SWITCH_BODY (switch_expr))
1507 vec<tree> labels;
1508 vec<tree> saved_labels;
1509 tree default_case = NULL_TREE;
1510 gswitch *switch_stmt;
1512 /* If someone can be bothered to fill in the labels, they can
1513 be bothered to null out the body too. */
1514 gcc_assert (!SWITCH_LABELS (switch_expr));
1516 /* Save old labels, get new ones from body, then restore the old
1517 labels. Save all the things from the switch body to append after. */
1518 saved_labels = gimplify_ctxp->case_labels;
1519 gimplify_ctxp->case_labels.create (8);
1521 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
1522 labels = gimplify_ctxp->case_labels;
1523 gimplify_ctxp->case_labels = saved_labels;
1525 preprocess_case_label_vec_for_gimple (labels, index_type,
1526 &default_case);
1528 if (!default_case)
1530 glabel *new_default;
1532 default_case
1533 = build_case_label (NULL_TREE, NULL_TREE,
1534 create_artificial_label (UNKNOWN_LOCATION));
1535 new_default = gimple_build_label (CASE_LABEL (default_case));
1536 gimplify_seq_add_stmt (&switch_body_seq, new_default);
1539 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
1540 default_case, labels);
1541 gimplify_seq_add_stmt (pre_p, switch_stmt);
1542 gimplify_seq_add_seq (pre_p, switch_body_seq);
1543 labels.release ();
1545 else
1546 gcc_assert (SWITCH_LABELS (switch_expr));
1548 return GS_ALL_DONE;
1551 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
1553 static enum gimplify_status
1554 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
1556 struct gimplify_ctx *ctxp;
1557 glabel *label_stmt;
1559 /* Invalid programs can play Duff's Device type games with, for example,
1560 #pragma omp parallel. At least in the C front end, we don't
1561 detect such invalid branches until after gimplification, in the
1562 diagnose_omp_blocks pass. */
1563 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
1564 if (ctxp->case_labels.exists ())
1565 break;
1567 label_stmt = gimple_build_label (CASE_LABEL (*expr_p));
1568 ctxp->case_labels.safe_push (*expr_p);
1569 gimplify_seq_add_stmt (pre_p, label_stmt);
1571 return GS_ALL_DONE;
1574 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
1575 if necessary. */
1577 tree
1578 build_and_jump (tree *label_p)
1580 if (label_p == NULL)
1581 /* If there's nowhere to jump, just fall through. */
1582 return NULL_TREE;
1584 if (*label_p == NULL_TREE)
1586 tree label = create_artificial_label (UNKNOWN_LOCATION);
1587 *label_p = label;
1590 return build1 (GOTO_EXPR, void_type_node, *label_p);
1593 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
1594 This also involves building a label to jump to and communicating it to
1595 gimplify_loop_expr through gimplify_ctxp->exit_label. */
1597 static enum gimplify_status
1598 gimplify_exit_expr (tree *expr_p)
1600 tree cond = TREE_OPERAND (*expr_p, 0);
1601 tree expr;
1603 expr = build_and_jump (&gimplify_ctxp->exit_label);
1604 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
1605 *expr_p = expr;
1607 return GS_OK;
1610 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
1611 different from its canonical type, wrap the whole thing inside a
1612 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
1613 type.
1615 The canonical type of a COMPONENT_REF is the type of the field being
1616 referenced--unless the field is a bit-field which can be read directly
1617 in a smaller mode, in which case the canonical type is the
1618 sign-appropriate type corresponding to that mode. */
1620 static void
1621 canonicalize_component_ref (tree *expr_p)
1623 tree expr = *expr_p;
1624 tree type;
1626 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
1628 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
1629 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
1630 else
1631 type = TREE_TYPE (TREE_OPERAND (expr, 1));
1633 /* One could argue that all the stuff below is not necessary for
1634 the non-bitfield case and declare it a FE error if type
1635 adjustment would be needed. */
1636 if (TREE_TYPE (expr) != type)
1638 #ifdef ENABLE_TYPES_CHECKING
1639 tree old_type = TREE_TYPE (expr);
1640 #endif
1641 int type_quals;
1643 /* We need to preserve qualifiers and propagate them from
1644 operand 0. */
1645 type_quals = TYPE_QUALS (type)
1646 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
1647 if (TYPE_QUALS (type) != type_quals)
1648 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
1650 /* Set the type of the COMPONENT_REF to the underlying type. */
1651 TREE_TYPE (expr) = type;
1653 #ifdef ENABLE_TYPES_CHECKING
1654 /* It is now a FE error, if the conversion from the canonical
1655 type to the original expression type is not useless. */
1656 gcc_assert (useless_type_conversion_p (old_type, type));
1657 #endif
1661 /* If a NOP conversion is changing a pointer to array of foo to a pointer
1662 to foo, embed that change in the ADDR_EXPR by converting
1663 T array[U];
1664 (T *)&array
1666 &array[L]
1667 where L is the lower bound. For simplicity, only do this for constant
1668 lower bound.
1669 The constraint is that the type of &array[L] is trivially convertible
1670 to T *. */
1672 static void
1673 canonicalize_addr_expr (tree *expr_p)
1675 tree expr = *expr_p;
1676 tree addr_expr = TREE_OPERAND (expr, 0);
1677 tree datype, ddatype, pddatype;
1679 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
1680 if (!POINTER_TYPE_P (TREE_TYPE (expr))
1681 || TREE_CODE (addr_expr) != ADDR_EXPR)
1682 return;
1684 /* The addr_expr type should be a pointer to an array. */
1685 datype = TREE_TYPE (TREE_TYPE (addr_expr));
1686 if (TREE_CODE (datype) != ARRAY_TYPE)
1687 return;
1689 /* The pointer to element type shall be trivially convertible to
1690 the expression pointer type. */
1691 ddatype = TREE_TYPE (datype);
1692 pddatype = build_pointer_type (ddatype);
1693 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
1694 pddatype))
1695 return;
1697 /* The lower bound and element sizes must be constant. */
1698 if (!TYPE_SIZE_UNIT (ddatype)
1699 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
1700 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
1701 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
1702 return;
1704 /* All checks succeeded. Build a new node to merge the cast. */
1705 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
1706 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
1707 NULL_TREE, NULL_TREE);
1708 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
1710 /* We can have stripped a required restrict qualifier above. */
1711 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
1712 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
1715 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
1716 underneath as appropriate. */
1718 static enum gimplify_status
1719 gimplify_conversion (tree *expr_p)
1721 location_t loc = EXPR_LOCATION (*expr_p);
1722 gcc_assert (CONVERT_EXPR_P (*expr_p));
1724 /* Then strip away all but the outermost conversion. */
1725 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
1727 /* And remove the outermost conversion if it's useless. */
1728 if (tree_ssa_useless_type_conversion (*expr_p))
1729 *expr_p = TREE_OPERAND (*expr_p, 0);
1731 /* If we still have a conversion at the toplevel,
1732 then canonicalize some constructs. */
1733 if (CONVERT_EXPR_P (*expr_p))
1735 tree sub = TREE_OPERAND (*expr_p, 0);
1737 /* If a NOP conversion is changing the type of a COMPONENT_REF
1738 expression, then canonicalize its type now in order to expose more
1739 redundant conversions. */
1740 if (TREE_CODE (sub) == COMPONENT_REF)
1741 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
1743 /* If a NOP conversion is changing a pointer to array of foo
1744 to a pointer to foo, embed that change in the ADDR_EXPR. */
1745 else if (TREE_CODE (sub) == ADDR_EXPR)
1746 canonicalize_addr_expr (expr_p);
1749 /* If we have a conversion to a non-register type force the
1750 use of a VIEW_CONVERT_EXPR instead. */
1751 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
1752 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
1753 TREE_OPERAND (*expr_p, 0));
1755 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
1756 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
1757 TREE_SET_CODE (*expr_p, NOP_EXPR);
1759 return GS_OK;
1762 /* Nonlocal VLAs seen in the current function. */
1763 static hash_set<tree> *nonlocal_vlas;
1765 /* The VAR_DECLs created for nonlocal VLAs for debug info purposes. */
1766 static tree nonlocal_vla_vars;
1768 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
1769 DECL_VALUE_EXPR, and it's worth re-examining things. */
1771 static enum gimplify_status
1772 gimplify_var_or_parm_decl (tree *expr_p)
1774 tree decl = *expr_p;
1776 /* ??? If this is a local variable, and it has not been seen in any
1777 outer BIND_EXPR, then it's probably the result of a duplicate
1778 declaration, for which we've already issued an error. It would
1779 be really nice if the front end wouldn't leak these at all.
1780 Currently the only known culprit is C++ destructors, as seen
1781 in g++.old-deja/g++.jason/binding.C. */
1782 if (TREE_CODE (decl) == VAR_DECL
1783 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
1784 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
1785 && decl_function_context (decl) == current_function_decl)
1787 gcc_assert (seen_error ());
1788 return GS_ERROR;
1791 /* When within an OMP context, notice uses of variables. */
1792 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
1793 return GS_ALL_DONE;
1795 /* If the decl is an alias for another expression, substitute it now. */
1796 if (DECL_HAS_VALUE_EXPR_P (decl))
1798 tree value_expr = DECL_VALUE_EXPR (decl);
1800 /* For referenced nonlocal VLAs add a decl for debugging purposes
1801 to the current function. */
1802 if (TREE_CODE (decl) == VAR_DECL
1803 && TREE_CODE (DECL_SIZE_UNIT (decl)) != INTEGER_CST
1804 && nonlocal_vlas != NULL
1805 && TREE_CODE (value_expr) == INDIRECT_REF
1806 && TREE_CODE (TREE_OPERAND (value_expr, 0)) == VAR_DECL
1807 && decl_function_context (decl) != current_function_decl)
1809 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1810 while (ctx
1811 && (ctx->region_type == ORT_WORKSHARE
1812 || ctx->region_type == ORT_SIMD))
1813 ctx = ctx->outer_context;
1814 if (!ctx && !nonlocal_vlas->add (decl))
1816 tree copy = copy_node (decl);
1818 lang_hooks.dup_lang_specific_decl (copy);
1819 SET_DECL_RTL (copy, 0);
1820 TREE_USED (copy) = 1;
1821 DECL_CHAIN (copy) = nonlocal_vla_vars;
1822 nonlocal_vla_vars = copy;
1823 SET_DECL_VALUE_EXPR (copy, unshare_expr (value_expr));
1824 DECL_HAS_VALUE_EXPR_P (copy) = 1;
1828 *expr_p = unshare_expr (value_expr);
1829 return GS_OK;
1832 return GS_ALL_DONE;
1835 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
1837 static void
1838 recalculate_side_effects (tree t)
1840 enum tree_code code = TREE_CODE (t);
1841 int len = TREE_OPERAND_LENGTH (t);
1842 int i;
1844 switch (TREE_CODE_CLASS (code))
1846 case tcc_expression:
1847 switch (code)
1849 case INIT_EXPR:
1850 case MODIFY_EXPR:
1851 case VA_ARG_EXPR:
1852 case PREDECREMENT_EXPR:
1853 case PREINCREMENT_EXPR:
1854 case POSTDECREMENT_EXPR:
1855 case POSTINCREMENT_EXPR:
1856 /* All of these have side-effects, no matter what their
1857 operands are. */
1858 return;
1860 default:
1861 break;
1863 /* Fall through. */
1865 case tcc_comparison: /* a comparison expression */
1866 case tcc_unary: /* a unary arithmetic expression */
1867 case tcc_binary: /* a binary arithmetic expression */
1868 case tcc_reference: /* a reference */
1869 case tcc_vl_exp: /* a function call */
1870 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
1871 for (i = 0; i < len; ++i)
1873 tree op = TREE_OPERAND (t, i);
1874 if (op && TREE_SIDE_EFFECTS (op))
1875 TREE_SIDE_EFFECTS (t) = 1;
1877 break;
1879 case tcc_constant:
1880 /* No side-effects. */
1881 return;
1883 default:
1884 gcc_unreachable ();
1888 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
1889 node *EXPR_P.
1891 compound_lval
1892 : min_lval '[' val ']'
1893 | min_lval '.' ID
1894 | compound_lval '[' val ']'
1895 | compound_lval '.' ID
1897 This is not part of the original SIMPLE definition, which separates
1898 array and member references, but it seems reasonable to handle them
1899 together. Also, this way we don't run into problems with union
1900 aliasing; gcc requires that for accesses through a union to alias, the
1901 union reference must be explicit, which was not always the case when we
1902 were splitting up array and member refs.
1904 PRE_P points to the sequence where side effects that must happen before
1905 *EXPR_P should be stored.
1907 POST_P points to the sequence where side effects that must happen after
1908 *EXPR_P should be stored. */
1910 static enum gimplify_status
1911 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
1912 fallback_t fallback)
1914 tree *p;
1915 enum gimplify_status ret = GS_ALL_DONE, tret;
1916 int i;
1917 location_t loc = EXPR_LOCATION (*expr_p);
1918 tree expr = *expr_p;
1920 /* Create a stack of the subexpressions so later we can walk them in
1921 order from inner to outer. */
1922 auto_vec<tree, 10> expr_stack;
1924 /* We can handle anything that get_inner_reference can deal with. */
1925 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
1927 restart:
1928 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
1929 if (TREE_CODE (*p) == INDIRECT_REF)
1930 *p = fold_indirect_ref_loc (loc, *p);
1932 if (handled_component_p (*p))
1934 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
1935 additional COMPONENT_REFs. */
1936 else if ((TREE_CODE (*p) == VAR_DECL || TREE_CODE (*p) == PARM_DECL)
1937 && gimplify_var_or_parm_decl (p) == GS_OK)
1938 goto restart;
1939 else
1940 break;
1942 expr_stack.safe_push (*p);
1945 gcc_assert (expr_stack.length ());
1947 /* Now EXPR_STACK is a stack of pointers to all the refs we've
1948 walked through and P points to the innermost expression.
1950 Java requires that we elaborated nodes in source order. That
1951 means we must gimplify the inner expression followed by each of
1952 the indices, in order. But we can't gimplify the inner
1953 expression until we deal with any variable bounds, sizes, or
1954 positions in order to deal with PLACEHOLDER_EXPRs.
1956 So we do this in three steps. First we deal with the annotations
1957 for any variables in the components, then we gimplify the base,
1958 then we gimplify any indices, from left to right. */
1959 for (i = expr_stack.length () - 1; i >= 0; i--)
1961 tree t = expr_stack[i];
1963 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
1965 /* Gimplify the low bound and element type size and put them into
1966 the ARRAY_REF. If these values are set, they have already been
1967 gimplified. */
1968 if (TREE_OPERAND (t, 2) == NULL_TREE)
1970 tree low = unshare_expr (array_ref_low_bound (t));
1971 if (!is_gimple_min_invariant (low))
1973 TREE_OPERAND (t, 2) = low;
1974 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
1975 post_p, is_gimple_reg,
1976 fb_rvalue);
1977 ret = MIN (ret, tret);
1980 else
1982 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1983 is_gimple_reg, fb_rvalue);
1984 ret = MIN (ret, tret);
1987 if (TREE_OPERAND (t, 3) == NULL_TREE)
1989 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
1990 tree elmt_size = unshare_expr (array_ref_element_size (t));
1991 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
1993 /* Divide the element size by the alignment of the element
1994 type (above). */
1995 elmt_size
1996 = size_binop_loc (loc, EXACT_DIV_EXPR, elmt_size, factor);
1998 if (!is_gimple_min_invariant (elmt_size))
2000 TREE_OPERAND (t, 3) = elmt_size;
2001 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
2002 post_p, is_gimple_reg,
2003 fb_rvalue);
2004 ret = MIN (ret, tret);
2007 else
2009 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
2010 is_gimple_reg, fb_rvalue);
2011 ret = MIN (ret, tret);
2014 else if (TREE_CODE (t) == COMPONENT_REF)
2016 /* Set the field offset into T and gimplify it. */
2017 if (TREE_OPERAND (t, 2) == NULL_TREE)
2019 tree offset = unshare_expr (component_ref_field_offset (t));
2020 tree field = TREE_OPERAND (t, 1);
2021 tree factor
2022 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
2024 /* Divide the offset by its alignment. */
2025 offset = size_binop_loc (loc, EXACT_DIV_EXPR, offset, factor);
2027 if (!is_gimple_min_invariant (offset))
2029 TREE_OPERAND (t, 2) = offset;
2030 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
2031 post_p, is_gimple_reg,
2032 fb_rvalue);
2033 ret = MIN (ret, tret);
2036 else
2038 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
2039 is_gimple_reg, fb_rvalue);
2040 ret = MIN (ret, tret);
2045 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
2046 so as to match the min_lval predicate. Failure to do so may result
2047 in the creation of large aggregate temporaries. */
2048 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
2049 fallback | fb_lvalue);
2050 ret = MIN (ret, tret);
2052 /* And finally, the indices and operands of ARRAY_REF. During this
2053 loop we also remove any useless conversions. */
2054 for (; expr_stack.length () > 0; )
2056 tree t = expr_stack.pop ();
2058 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
2060 /* Gimplify the dimension. */
2061 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
2063 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
2064 is_gimple_val, fb_rvalue);
2065 ret = MIN (ret, tret);
2069 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
2071 /* The innermost expression P may have originally had
2072 TREE_SIDE_EFFECTS set which would have caused all the outer
2073 expressions in *EXPR_P leading to P to also have had
2074 TREE_SIDE_EFFECTS set. */
2075 recalculate_side_effects (t);
2078 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
2079 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
2081 canonicalize_component_ref (expr_p);
2084 expr_stack.release ();
2086 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
2088 return ret;
2091 /* Gimplify the self modifying expression pointed to by EXPR_P
2092 (++, --, +=, -=).
2094 PRE_P points to the list where side effects that must happen before
2095 *EXPR_P should be stored.
2097 POST_P points to the list where side effects that must happen after
2098 *EXPR_P should be stored.
2100 WANT_VALUE is nonzero iff we want to use the value of this expression
2101 in another expression.
2103 ARITH_TYPE is the type the computation should be performed in. */
2105 enum gimplify_status
2106 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
2107 bool want_value, tree arith_type)
2109 enum tree_code code;
2110 tree lhs, lvalue, rhs, t1;
2111 gimple_seq post = NULL, *orig_post_p = post_p;
2112 bool postfix;
2113 enum tree_code arith_code;
2114 enum gimplify_status ret;
2115 location_t loc = EXPR_LOCATION (*expr_p);
2117 code = TREE_CODE (*expr_p);
2119 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
2120 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
2122 /* Prefix or postfix? */
2123 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
2124 /* Faster to treat as prefix if result is not used. */
2125 postfix = want_value;
2126 else
2127 postfix = false;
2129 /* For postfix, make sure the inner expression's post side effects
2130 are executed after side effects from this expression. */
2131 if (postfix)
2132 post_p = &post;
2134 /* Add or subtract? */
2135 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
2136 arith_code = PLUS_EXPR;
2137 else
2138 arith_code = MINUS_EXPR;
2140 /* Gimplify the LHS into a GIMPLE lvalue. */
2141 lvalue = TREE_OPERAND (*expr_p, 0);
2142 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
2143 if (ret == GS_ERROR)
2144 return ret;
2146 /* Extract the operands to the arithmetic operation. */
2147 lhs = lvalue;
2148 rhs = TREE_OPERAND (*expr_p, 1);
2150 /* For postfix operator, we evaluate the LHS to an rvalue and then use
2151 that as the result value and in the postqueue operation. */
2152 if (postfix)
2154 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
2155 if (ret == GS_ERROR)
2156 return ret;
2158 lhs = get_initialized_tmp_var (lhs, pre_p, NULL);
2161 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
2162 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
2164 rhs = convert_to_ptrofftype_loc (loc, rhs);
2165 if (arith_code == MINUS_EXPR)
2166 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
2167 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
2169 else
2170 t1 = fold_convert (TREE_TYPE (*expr_p),
2171 fold_build2 (arith_code, arith_type,
2172 fold_convert (arith_type, lhs),
2173 fold_convert (arith_type, rhs)));
2175 if (postfix)
2177 gimplify_assign (lvalue, t1, pre_p);
2178 gimplify_seq_add_seq (orig_post_p, post);
2179 *expr_p = lhs;
2180 return GS_ALL_DONE;
2182 else
2184 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
2185 return GS_OK;
2189 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
2191 static void
2192 maybe_with_size_expr (tree *expr_p)
2194 tree expr = *expr_p;
2195 tree type = TREE_TYPE (expr);
2196 tree size;
2198 /* If we've already wrapped this or the type is error_mark_node, we can't do
2199 anything. */
2200 if (TREE_CODE (expr) == WITH_SIZE_EXPR
2201 || type == error_mark_node)
2202 return;
2204 /* If the size isn't known or is a constant, we have nothing to do. */
2205 size = TYPE_SIZE_UNIT (type);
2206 if (!size || TREE_CODE (size) == INTEGER_CST)
2207 return;
2209 /* Otherwise, make a WITH_SIZE_EXPR. */
2210 size = unshare_expr (size);
2211 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
2212 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
2215 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
2216 Store any side-effects in PRE_P. CALL_LOCATION is the location of
2217 the CALL_EXPR. */
2219 enum gimplify_status
2220 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location)
2222 bool (*test) (tree);
2223 fallback_t fb;
2225 /* In general, we allow lvalues for function arguments to avoid
2226 extra overhead of copying large aggregates out of even larger
2227 aggregates into temporaries only to copy the temporaries to
2228 the argument list. Make optimizers happy by pulling out to
2229 temporaries those types that fit in registers. */
2230 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
2231 test = is_gimple_val, fb = fb_rvalue;
2232 else
2234 test = is_gimple_lvalue, fb = fb_either;
2235 /* Also strip a TARGET_EXPR that would force an extra copy. */
2236 if (TREE_CODE (*arg_p) == TARGET_EXPR)
2238 tree init = TARGET_EXPR_INITIAL (*arg_p);
2239 if (init
2240 && !VOID_TYPE_P (TREE_TYPE (init)))
2241 *arg_p = init;
2245 /* If this is a variable sized type, we must remember the size. */
2246 maybe_with_size_expr (arg_p);
2248 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
2249 /* Make sure arguments have the same location as the function call
2250 itself. */
2251 protected_set_expr_location (*arg_p, call_location);
2253 /* There is a sequence point before a function call. Side effects in
2254 the argument list must occur before the actual call. So, when
2255 gimplifying arguments, force gimplify_expr to use an internal
2256 post queue which is then appended to the end of PRE_P. */
2257 return gimplify_expr (arg_p, pre_p, NULL, test, fb);
2260 /* Don't fold inside offloading regions: it can break code by adding decl
2261 references that weren't in the source. We'll do it during omplower pass
2262 instead. */
2264 static bool
2265 maybe_fold_stmt (gimple_stmt_iterator *gsi)
2267 struct gimplify_omp_ctx *ctx;
2268 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
2269 if (ctx->region_type == ORT_TARGET)
2270 return false;
2271 return fold_stmt (gsi);
2274 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
2275 WANT_VALUE is true if the result of the call is desired. */
2277 static enum gimplify_status
2278 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
2280 tree fndecl, parms, p, fnptrtype;
2281 enum gimplify_status ret;
2282 int i, nargs;
2283 gcall *call;
2284 bool builtin_va_start_p = false;
2285 location_t loc = EXPR_LOCATION (*expr_p);
2287 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
2289 /* For reliable diagnostics during inlining, it is necessary that
2290 every call_expr be annotated with file and line. */
2291 if (! EXPR_HAS_LOCATION (*expr_p))
2292 SET_EXPR_LOCATION (*expr_p, input_location);
2294 /* Gimplify internal functions created in the FEs. */
2295 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
2297 if (want_value)
2298 return GS_ALL_DONE;
2300 nargs = call_expr_nargs (*expr_p);
2301 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
2302 auto_vec<tree> vargs (nargs);
2304 for (i = 0; i < nargs; i++)
2306 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
2307 EXPR_LOCATION (*expr_p));
2308 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
2310 gimple call = gimple_build_call_internal_vec (ifn, vargs);
2311 gimplify_seq_add_stmt (pre_p, call);
2312 return GS_ALL_DONE;
2315 /* This may be a call to a builtin function.
2317 Builtin function calls may be transformed into different
2318 (and more efficient) builtin function calls under certain
2319 circumstances. Unfortunately, gimplification can muck things
2320 up enough that the builtin expanders are not aware that certain
2321 transformations are still valid.
2323 So we attempt transformation/gimplification of the call before
2324 we gimplify the CALL_EXPR. At this time we do not manage to
2325 transform all calls in the same manner as the expanders do, but
2326 we do transform most of them. */
2327 fndecl = get_callee_fndecl (*expr_p);
2328 if (fndecl
2329 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL)
2330 switch (DECL_FUNCTION_CODE (fndecl))
2332 case BUILT_IN_VA_START:
2334 builtin_va_start_p = TRUE;
2335 if (call_expr_nargs (*expr_p) < 2)
2337 error ("too few arguments to function %<va_start%>");
2338 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
2339 return GS_OK;
2342 if (fold_builtin_next_arg (*expr_p, true))
2344 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
2345 return GS_OK;
2347 break;
2349 case BUILT_IN_LINE:
2351 *expr_p = build_int_cst (TREE_TYPE (*expr_p),
2352 LOCATION_LINE (EXPR_LOCATION (*expr_p)));
2353 return GS_OK;
2355 case BUILT_IN_FILE:
2357 const char *locfile = LOCATION_FILE (EXPR_LOCATION (*expr_p));
2358 *expr_p = build_string_literal (strlen (locfile) + 1, locfile);
2359 return GS_OK;
2361 case BUILT_IN_FUNCTION:
2363 const char *function;
2364 function = IDENTIFIER_POINTER (DECL_NAME (current_function_decl));
2365 *expr_p = build_string_literal (strlen (function) + 1, function);
2366 return GS_OK;
2368 default:
2371 if (fndecl && DECL_BUILT_IN (fndecl))
2373 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
2374 if (new_tree && new_tree != *expr_p)
2376 /* There was a transformation of this call which computes the
2377 same value, but in a more efficient way. Return and try
2378 again. */
2379 *expr_p = new_tree;
2380 return GS_OK;
2384 /* Remember the original function pointer type. */
2385 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
2387 /* There is a sequence point before the call, so any side effects in
2388 the calling expression must occur before the actual call. Force
2389 gimplify_expr to use an internal post queue. */
2390 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
2391 is_gimple_call_addr, fb_rvalue);
2393 nargs = call_expr_nargs (*expr_p);
2395 /* Get argument types for verification. */
2396 fndecl = get_callee_fndecl (*expr_p);
2397 parms = NULL_TREE;
2398 if (fndecl)
2399 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
2400 else
2401 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
2403 if (fndecl && DECL_ARGUMENTS (fndecl))
2404 p = DECL_ARGUMENTS (fndecl);
2405 else if (parms)
2406 p = parms;
2407 else
2408 p = NULL_TREE;
2409 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
2412 /* If the last argument is __builtin_va_arg_pack () and it is not
2413 passed as a named argument, decrease the number of CALL_EXPR
2414 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
2415 if (!p
2416 && i < nargs
2417 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
2419 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
2420 tree last_arg_fndecl = get_callee_fndecl (last_arg);
2422 if (last_arg_fndecl
2423 && TREE_CODE (last_arg_fndecl) == FUNCTION_DECL
2424 && DECL_BUILT_IN_CLASS (last_arg_fndecl) == BUILT_IN_NORMAL
2425 && DECL_FUNCTION_CODE (last_arg_fndecl) == BUILT_IN_VA_ARG_PACK)
2427 tree call = *expr_p;
2429 --nargs;
2430 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
2431 CALL_EXPR_FN (call),
2432 nargs, CALL_EXPR_ARGP (call));
2434 /* Copy all CALL_EXPR flags, location and block, except
2435 CALL_EXPR_VA_ARG_PACK flag. */
2436 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
2437 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
2438 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
2439 = CALL_EXPR_RETURN_SLOT_OPT (call);
2440 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
2441 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
2443 /* Set CALL_EXPR_VA_ARG_PACK. */
2444 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
2448 /* Gimplify the function arguments. */
2449 if (nargs > 0)
2451 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
2452 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
2453 PUSH_ARGS_REVERSED ? i-- : i++)
2455 enum gimplify_status t;
2457 /* Avoid gimplifying the second argument to va_start, which needs to
2458 be the plain PARM_DECL. */
2459 if ((i != 1) || !builtin_va_start_p)
2461 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
2462 EXPR_LOCATION (*expr_p));
2464 if (t == GS_ERROR)
2465 ret = GS_ERROR;
2470 /* Gimplify the static chain. */
2471 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
2473 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
2474 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
2475 else
2477 enum gimplify_status t;
2478 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
2479 EXPR_LOCATION (*expr_p));
2480 if (t == GS_ERROR)
2481 ret = GS_ERROR;
2485 /* Verify the function result. */
2486 if (want_value && fndecl
2487 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
2489 error_at (loc, "using result of function returning %<void%>");
2490 ret = GS_ERROR;
2493 /* Try this again in case gimplification exposed something. */
2494 if (ret != GS_ERROR)
2496 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
2498 if (new_tree && new_tree != *expr_p)
2500 /* There was a transformation of this call which computes the
2501 same value, but in a more efficient way. Return and try
2502 again. */
2503 *expr_p = new_tree;
2504 return GS_OK;
2507 else
2509 *expr_p = error_mark_node;
2510 return GS_ERROR;
2513 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
2514 decl. This allows us to eliminate redundant or useless
2515 calls to "const" functions. */
2516 if (TREE_CODE (*expr_p) == CALL_EXPR)
2518 int flags = call_expr_flags (*expr_p);
2519 if (flags & (ECF_CONST | ECF_PURE)
2520 /* An infinite loop is considered a side effect. */
2521 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
2522 TREE_SIDE_EFFECTS (*expr_p) = 0;
2525 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
2526 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
2527 form and delegate the creation of a GIMPLE_CALL to
2528 gimplify_modify_expr. This is always possible because when
2529 WANT_VALUE is true, the caller wants the result of this call into
2530 a temporary, which means that we will emit an INIT_EXPR in
2531 internal_get_tmp_var which will then be handled by
2532 gimplify_modify_expr. */
2533 if (!want_value)
2535 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
2536 have to do is replicate it as a GIMPLE_CALL tuple. */
2537 gimple_stmt_iterator gsi;
2538 call = gimple_build_call_from_tree (*expr_p);
2539 gimple_call_set_fntype (call, TREE_TYPE (fnptrtype));
2540 notice_special_calls (call);
2541 gimplify_seq_add_stmt (pre_p, call);
2542 gsi = gsi_last (*pre_p);
2543 maybe_fold_stmt (&gsi);
2544 *expr_p = NULL_TREE;
2546 else
2547 /* Remember the original function type. */
2548 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
2549 CALL_EXPR_FN (*expr_p));
2551 return ret;
2554 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
2555 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
2557 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
2558 condition is true or false, respectively. If null, we should generate
2559 our own to skip over the evaluation of this specific expression.
2561 LOCUS is the source location of the COND_EXPR.
2563 This function is the tree equivalent of do_jump.
2565 shortcut_cond_r should only be called by shortcut_cond_expr. */
2567 static tree
2568 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
2569 location_t locus)
2571 tree local_label = NULL_TREE;
2572 tree t, expr = NULL;
2574 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
2575 retain the shortcut semantics. Just insert the gotos here;
2576 shortcut_cond_expr will append the real blocks later. */
2577 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
2579 location_t new_locus;
2581 /* Turn if (a && b) into
2583 if (a); else goto no;
2584 if (b) goto yes; else goto no;
2585 (no:) */
2587 if (false_label_p == NULL)
2588 false_label_p = &local_label;
2590 /* Keep the original source location on the first 'if'. */
2591 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
2592 append_to_statement_list (t, &expr);
2594 /* Set the source location of the && on the second 'if'. */
2595 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
2596 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
2597 new_locus);
2598 append_to_statement_list (t, &expr);
2600 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
2602 location_t new_locus;
2604 /* Turn if (a || b) into
2606 if (a) goto yes;
2607 if (b) goto yes; else goto no;
2608 (yes:) */
2610 if (true_label_p == NULL)
2611 true_label_p = &local_label;
2613 /* Keep the original source location on the first 'if'. */
2614 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
2615 append_to_statement_list (t, &expr);
2617 /* Set the source location of the || on the second 'if'. */
2618 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
2619 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
2620 new_locus);
2621 append_to_statement_list (t, &expr);
2623 else if (TREE_CODE (pred) == COND_EXPR
2624 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
2625 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
2627 location_t new_locus;
2629 /* As long as we're messing with gotos, turn if (a ? b : c) into
2630 if (a)
2631 if (b) goto yes; else goto no;
2632 else
2633 if (c) goto yes; else goto no;
2635 Don't do this if one of the arms has void type, which can happen
2636 in C++ when the arm is throw. */
2638 /* Keep the original source location on the first 'if'. Set the source
2639 location of the ? on the second 'if'. */
2640 new_locus = EXPR_HAS_LOCATION (pred) ? EXPR_LOCATION (pred) : locus;
2641 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
2642 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
2643 false_label_p, locus),
2644 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
2645 false_label_p, new_locus));
2647 else
2649 expr = build3 (COND_EXPR, void_type_node, pred,
2650 build_and_jump (true_label_p),
2651 build_and_jump (false_label_p));
2652 SET_EXPR_LOCATION (expr, locus);
2655 if (local_label)
2657 t = build1 (LABEL_EXPR, void_type_node, local_label);
2658 append_to_statement_list (t, &expr);
2661 return expr;
2664 /* Given a conditional expression EXPR with short-circuit boolean
2665 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
2666 predicate apart into the equivalent sequence of conditionals. */
2668 static tree
2669 shortcut_cond_expr (tree expr)
2671 tree pred = TREE_OPERAND (expr, 0);
2672 tree then_ = TREE_OPERAND (expr, 1);
2673 tree else_ = TREE_OPERAND (expr, 2);
2674 tree true_label, false_label, end_label, t;
2675 tree *true_label_p;
2676 tree *false_label_p;
2677 bool emit_end, emit_false, jump_over_else;
2678 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
2679 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
2681 /* First do simple transformations. */
2682 if (!else_se)
2684 /* If there is no 'else', turn
2685 if (a && b) then c
2686 into
2687 if (a) if (b) then c. */
2688 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
2690 /* Keep the original source location on the first 'if'. */
2691 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
2692 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
2693 /* Set the source location of the && on the second 'if'. */
2694 if (EXPR_HAS_LOCATION (pred))
2695 SET_EXPR_LOCATION (expr, EXPR_LOCATION (pred));
2696 then_ = shortcut_cond_expr (expr);
2697 then_se = then_ && TREE_SIDE_EFFECTS (then_);
2698 pred = TREE_OPERAND (pred, 0);
2699 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
2700 SET_EXPR_LOCATION (expr, locus);
2704 if (!then_se)
2706 /* If there is no 'then', turn
2707 if (a || b); else d
2708 into
2709 if (a); else if (b); else d. */
2710 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
2712 /* Keep the original source location on the first 'if'. */
2713 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
2714 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
2715 /* Set the source location of the || on the second 'if'. */
2716 if (EXPR_HAS_LOCATION (pred))
2717 SET_EXPR_LOCATION (expr, EXPR_LOCATION (pred));
2718 else_ = shortcut_cond_expr (expr);
2719 else_se = else_ && TREE_SIDE_EFFECTS (else_);
2720 pred = TREE_OPERAND (pred, 0);
2721 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
2722 SET_EXPR_LOCATION (expr, locus);
2726 /* If we're done, great. */
2727 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
2728 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
2729 return expr;
2731 /* Otherwise we need to mess with gotos. Change
2732 if (a) c; else d;
2734 if (a); else goto no;
2735 c; goto end;
2736 no: d; end:
2737 and recursively gimplify the condition. */
2739 true_label = false_label = end_label = NULL_TREE;
2741 /* If our arms just jump somewhere, hijack those labels so we don't
2742 generate jumps to jumps. */
2744 if (then_
2745 && TREE_CODE (then_) == GOTO_EXPR
2746 && TREE_CODE (GOTO_DESTINATION (then_)) == LABEL_DECL)
2748 true_label = GOTO_DESTINATION (then_);
2749 then_ = NULL;
2750 then_se = false;
2753 if (else_
2754 && TREE_CODE (else_) == GOTO_EXPR
2755 && TREE_CODE (GOTO_DESTINATION (else_)) == LABEL_DECL)
2757 false_label = GOTO_DESTINATION (else_);
2758 else_ = NULL;
2759 else_se = false;
2762 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
2763 if (true_label)
2764 true_label_p = &true_label;
2765 else
2766 true_label_p = NULL;
2768 /* The 'else' branch also needs a label if it contains interesting code. */
2769 if (false_label || else_se)
2770 false_label_p = &false_label;
2771 else
2772 false_label_p = NULL;
2774 /* If there was nothing else in our arms, just forward the label(s). */
2775 if (!then_se && !else_se)
2776 return shortcut_cond_r (pred, true_label_p, false_label_p,
2777 EXPR_LOC_OR_LOC (expr, input_location));
2779 /* If our last subexpression already has a terminal label, reuse it. */
2780 if (else_se)
2781 t = expr_last (else_);
2782 else if (then_se)
2783 t = expr_last (then_);
2784 else
2785 t = NULL;
2786 if (t && TREE_CODE (t) == LABEL_EXPR)
2787 end_label = LABEL_EXPR_LABEL (t);
2789 /* If we don't care about jumping to the 'else' branch, jump to the end
2790 if the condition is false. */
2791 if (!false_label_p)
2792 false_label_p = &end_label;
2794 /* We only want to emit these labels if we aren't hijacking them. */
2795 emit_end = (end_label == NULL_TREE);
2796 emit_false = (false_label == NULL_TREE);
2798 /* We only emit the jump over the else clause if we have to--if the
2799 then clause may fall through. Otherwise we can wind up with a
2800 useless jump and a useless label at the end of gimplified code,
2801 which will cause us to think that this conditional as a whole
2802 falls through even if it doesn't. If we then inline a function
2803 which ends with such a condition, that can cause us to issue an
2804 inappropriate warning about control reaching the end of a
2805 non-void function. */
2806 jump_over_else = block_may_fallthru (then_);
2808 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
2809 EXPR_LOC_OR_LOC (expr, input_location));
2811 expr = NULL;
2812 append_to_statement_list (pred, &expr);
2814 append_to_statement_list (then_, &expr);
2815 if (else_se)
2817 if (jump_over_else)
2819 tree last = expr_last (expr);
2820 t = build_and_jump (&end_label);
2821 if (EXPR_HAS_LOCATION (last))
2822 SET_EXPR_LOCATION (t, EXPR_LOCATION (last));
2823 append_to_statement_list (t, &expr);
2825 if (emit_false)
2827 t = build1 (LABEL_EXPR, void_type_node, false_label);
2828 append_to_statement_list (t, &expr);
2830 append_to_statement_list (else_, &expr);
2832 if (emit_end && end_label)
2834 t = build1 (LABEL_EXPR, void_type_node, end_label);
2835 append_to_statement_list (t, &expr);
2838 return expr;
2841 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
2843 tree
2844 gimple_boolify (tree expr)
2846 tree type = TREE_TYPE (expr);
2847 location_t loc = EXPR_LOCATION (expr);
2849 if (TREE_CODE (expr) == NE_EXPR
2850 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
2851 && integer_zerop (TREE_OPERAND (expr, 1)))
2853 tree call = TREE_OPERAND (expr, 0);
2854 tree fn = get_callee_fndecl (call);
2856 /* For __builtin_expect ((long) (x), y) recurse into x as well
2857 if x is truth_value_p. */
2858 if (fn
2859 && DECL_BUILT_IN_CLASS (fn) == BUILT_IN_NORMAL
2860 && DECL_FUNCTION_CODE (fn) == BUILT_IN_EXPECT
2861 && call_expr_nargs (call) == 2)
2863 tree arg = CALL_EXPR_ARG (call, 0);
2864 if (arg)
2866 if (TREE_CODE (arg) == NOP_EXPR
2867 && TREE_TYPE (arg) == TREE_TYPE (call))
2868 arg = TREE_OPERAND (arg, 0);
2869 if (truth_value_p (TREE_CODE (arg)))
2871 arg = gimple_boolify (arg);
2872 CALL_EXPR_ARG (call, 0)
2873 = fold_convert_loc (loc, TREE_TYPE (call), arg);
2879 switch (TREE_CODE (expr))
2881 case TRUTH_AND_EXPR:
2882 case TRUTH_OR_EXPR:
2883 case TRUTH_XOR_EXPR:
2884 case TRUTH_ANDIF_EXPR:
2885 case TRUTH_ORIF_EXPR:
2886 /* Also boolify the arguments of truth exprs. */
2887 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
2888 /* FALLTHRU */
2890 case TRUTH_NOT_EXPR:
2891 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2893 /* These expressions always produce boolean results. */
2894 if (TREE_CODE (type) != BOOLEAN_TYPE)
2895 TREE_TYPE (expr) = boolean_type_node;
2896 return expr;
2898 case ANNOTATE_EXPR:
2899 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
2901 case annot_expr_ivdep_kind:
2902 case annot_expr_no_vector_kind:
2903 case annot_expr_vector_kind:
2904 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2905 if (TREE_CODE (type) != BOOLEAN_TYPE)
2906 TREE_TYPE (expr) = boolean_type_node;
2907 return expr;
2908 default:
2909 gcc_unreachable ();
2912 default:
2913 if (COMPARISON_CLASS_P (expr))
2915 /* There expressions always prduce boolean results. */
2916 if (TREE_CODE (type) != BOOLEAN_TYPE)
2917 TREE_TYPE (expr) = boolean_type_node;
2918 return expr;
2920 /* Other expressions that get here must have boolean values, but
2921 might need to be converted to the appropriate mode. */
2922 if (TREE_CODE (type) == BOOLEAN_TYPE)
2923 return expr;
2924 return fold_convert_loc (loc, boolean_type_node, expr);
2928 /* Given a conditional expression *EXPR_P without side effects, gimplify
2929 its operands. New statements are inserted to PRE_P. */
2931 static enum gimplify_status
2932 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
2934 tree expr = *expr_p, cond;
2935 enum gimplify_status ret, tret;
2936 enum tree_code code;
2938 cond = gimple_boolify (COND_EXPR_COND (expr));
2940 /* We need to handle && and || specially, as their gimplification
2941 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
2942 code = TREE_CODE (cond);
2943 if (code == TRUTH_ANDIF_EXPR)
2944 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
2945 else if (code == TRUTH_ORIF_EXPR)
2946 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
2947 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_condexpr, fb_rvalue);
2948 COND_EXPR_COND (*expr_p) = cond;
2950 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
2951 is_gimple_val, fb_rvalue);
2952 ret = MIN (ret, tret);
2953 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
2954 is_gimple_val, fb_rvalue);
2956 return MIN (ret, tret);
2959 /* Return true if evaluating EXPR could trap.
2960 EXPR is GENERIC, while tree_could_trap_p can be called
2961 only on GIMPLE. */
2963 static bool
2964 generic_expr_could_trap_p (tree expr)
2966 unsigned i, n;
2968 if (!expr || is_gimple_val (expr))
2969 return false;
2971 if (!EXPR_P (expr) || tree_could_trap_p (expr))
2972 return true;
2974 n = TREE_OPERAND_LENGTH (expr);
2975 for (i = 0; i < n; i++)
2976 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
2977 return true;
2979 return false;
2982 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
2983 into
2985 if (p) if (p)
2986 t1 = a; a;
2987 else or else
2988 t1 = b; b;
2991 The second form is used when *EXPR_P is of type void.
2993 PRE_P points to the list where side effects that must happen before
2994 *EXPR_P should be stored. */
2996 static enum gimplify_status
2997 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
2999 tree expr = *expr_p;
3000 tree type = TREE_TYPE (expr);
3001 location_t loc = EXPR_LOCATION (expr);
3002 tree tmp, arm1, arm2;
3003 enum gimplify_status ret;
3004 tree label_true, label_false, label_cont;
3005 bool have_then_clause_p, have_else_clause_p;
3006 gcond *cond_stmt;
3007 enum tree_code pred_code;
3008 gimple_seq seq = NULL;
3010 /* If this COND_EXPR has a value, copy the values into a temporary within
3011 the arms. */
3012 if (!VOID_TYPE_P (type))
3014 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
3015 tree result;
3017 /* If either an rvalue is ok or we do not require an lvalue, create the
3018 temporary. But we cannot do that if the type is addressable. */
3019 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
3020 && !TREE_ADDRESSABLE (type))
3022 if (gimplify_ctxp->allow_rhs_cond_expr
3023 /* If either branch has side effects or could trap, it can't be
3024 evaluated unconditionally. */
3025 && !TREE_SIDE_EFFECTS (then_)
3026 && !generic_expr_could_trap_p (then_)
3027 && !TREE_SIDE_EFFECTS (else_)
3028 && !generic_expr_could_trap_p (else_))
3029 return gimplify_pure_cond_expr (expr_p, pre_p);
3031 tmp = create_tmp_var (type, "iftmp");
3032 result = tmp;
3035 /* Otherwise, only create and copy references to the values. */
3036 else
3038 type = build_pointer_type (type);
3040 if (!VOID_TYPE_P (TREE_TYPE (then_)))
3041 then_ = build_fold_addr_expr_loc (loc, then_);
3043 if (!VOID_TYPE_P (TREE_TYPE (else_)))
3044 else_ = build_fold_addr_expr_loc (loc, else_);
3046 expr
3047 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
3049 tmp = create_tmp_var (type, "iftmp");
3050 result = build_simple_mem_ref_loc (loc, tmp);
3053 /* Build the new then clause, `tmp = then_;'. But don't build the
3054 assignment if the value is void; in C++ it can be if it's a throw. */
3055 if (!VOID_TYPE_P (TREE_TYPE (then_)))
3056 TREE_OPERAND (expr, 1) = build2 (MODIFY_EXPR, type, tmp, then_);
3058 /* Similarly, build the new else clause, `tmp = else_;'. */
3059 if (!VOID_TYPE_P (TREE_TYPE (else_)))
3060 TREE_OPERAND (expr, 2) = build2 (MODIFY_EXPR, type, tmp, else_);
3062 TREE_TYPE (expr) = void_type_node;
3063 recalculate_side_effects (expr);
3065 /* Move the COND_EXPR to the prequeue. */
3066 gimplify_stmt (&expr, pre_p);
3068 *expr_p = result;
3069 return GS_ALL_DONE;
3072 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
3073 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
3074 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
3075 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
3077 /* Make sure the condition has BOOLEAN_TYPE. */
3078 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3080 /* Break apart && and || conditions. */
3081 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
3082 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
3084 expr = shortcut_cond_expr (expr);
3086 if (expr != *expr_p)
3088 *expr_p = expr;
3090 /* We can't rely on gimplify_expr to re-gimplify the expanded
3091 form properly, as cleanups might cause the target labels to be
3092 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
3093 set up a conditional context. */
3094 gimple_push_condition ();
3095 gimplify_stmt (expr_p, &seq);
3096 gimple_pop_condition (pre_p);
3097 gimple_seq_add_seq (pre_p, seq);
3099 return GS_ALL_DONE;
3103 /* Now do the normal gimplification. */
3105 /* Gimplify condition. */
3106 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL, is_gimple_condexpr,
3107 fb_rvalue);
3108 if (ret == GS_ERROR)
3109 return GS_ERROR;
3110 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
3112 gimple_push_condition ();
3114 have_then_clause_p = have_else_clause_p = false;
3115 if (TREE_OPERAND (expr, 1) != NULL
3116 && TREE_CODE (TREE_OPERAND (expr, 1)) == GOTO_EXPR
3117 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr, 1))) == LABEL_DECL
3118 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr, 1)))
3119 == current_function_decl)
3120 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3121 have different locations, otherwise we end up with incorrect
3122 location information on the branches. */
3123 && (optimize
3124 || !EXPR_HAS_LOCATION (expr)
3125 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr, 1))
3126 || EXPR_LOCATION (expr) == EXPR_LOCATION (TREE_OPERAND (expr, 1))))
3128 label_true = GOTO_DESTINATION (TREE_OPERAND (expr, 1));
3129 have_then_clause_p = true;
3131 else
3132 label_true = create_artificial_label (UNKNOWN_LOCATION);
3133 if (TREE_OPERAND (expr, 2) != NULL
3134 && TREE_CODE (TREE_OPERAND (expr, 2)) == GOTO_EXPR
3135 && TREE_CODE (GOTO_DESTINATION (TREE_OPERAND (expr, 2))) == LABEL_DECL
3136 && (DECL_CONTEXT (GOTO_DESTINATION (TREE_OPERAND (expr, 2)))
3137 == current_function_decl)
3138 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
3139 have different locations, otherwise we end up with incorrect
3140 location information on the branches. */
3141 && (optimize
3142 || !EXPR_HAS_LOCATION (expr)
3143 || !EXPR_HAS_LOCATION (TREE_OPERAND (expr, 2))
3144 || EXPR_LOCATION (expr) == EXPR_LOCATION (TREE_OPERAND (expr, 2))))
3146 label_false = GOTO_DESTINATION (TREE_OPERAND (expr, 2));
3147 have_else_clause_p = true;
3149 else
3150 label_false = create_artificial_label (UNKNOWN_LOCATION);
3152 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
3153 &arm2);
3155 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
3156 label_false);
3158 gimplify_seq_add_stmt (&seq, cond_stmt);
3159 label_cont = NULL_TREE;
3160 if (!have_then_clause_p)
3162 /* For if (...) {} else { code; } put label_true after
3163 the else block. */
3164 if (TREE_OPERAND (expr, 1) == NULL_TREE
3165 && !have_else_clause_p
3166 && TREE_OPERAND (expr, 2) != NULL_TREE)
3167 label_cont = label_true;
3168 else
3170 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
3171 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
3172 /* For if (...) { code; } else {} or
3173 if (...) { code; } else goto label; or
3174 if (...) { code; return; } else { ... }
3175 label_cont isn't needed. */
3176 if (!have_else_clause_p
3177 && TREE_OPERAND (expr, 2) != NULL_TREE
3178 && gimple_seq_may_fallthru (seq))
3180 gimple g;
3181 label_cont = create_artificial_label (UNKNOWN_LOCATION);
3183 g = gimple_build_goto (label_cont);
3185 /* GIMPLE_COND's are very low level; they have embedded
3186 gotos. This particular embedded goto should not be marked
3187 with the location of the original COND_EXPR, as it would
3188 correspond to the COND_EXPR's condition, not the ELSE or the
3189 THEN arms. To avoid marking it with the wrong location, flag
3190 it as "no location". */
3191 gimple_set_do_not_emit_location (g);
3193 gimplify_seq_add_stmt (&seq, g);
3197 if (!have_else_clause_p)
3199 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
3200 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
3202 if (label_cont)
3203 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
3205 gimple_pop_condition (pre_p);
3206 gimple_seq_add_seq (pre_p, seq);
3208 if (ret == GS_ERROR)
3209 ; /* Do nothing. */
3210 else if (have_then_clause_p || have_else_clause_p)
3211 ret = GS_ALL_DONE;
3212 else
3214 /* Both arms are empty; replace the COND_EXPR with its predicate. */
3215 expr = TREE_OPERAND (expr, 0);
3216 gimplify_stmt (&expr, pre_p);
3219 *expr_p = NULL;
3220 return ret;
3223 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
3224 to be marked addressable.
3226 We cannot rely on such an expression being directly markable if a temporary
3227 has been created by the gimplification. In this case, we create another
3228 temporary and initialize it with a copy, which will become a store after we
3229 mark it addressable. This can happen if the front-end passed us something
3230 that it could not mark addressable yet, like a Fortran pass-by-reference
3231 parameter (int) floatvar. */
3233 static void
3234 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
3236 while (handled_component_p (*expr_p))
3237 expr_p = &TREE_OPERAND (*expr_p, 0);
3238 if (is_gimple_reg (*expr_p))
3240 tree var = get_initialized_tmp_var (*expr_p, seq_p, NULL);
3241 DECL_GIMPLE_REG_P (var) = 0;
3242 *expr_p = var;
3246 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
3247 a call to __builtin_memcpy. */
3249 static enum gimplify_status
3250 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
3251 gimple_seq *seq_p)
3253 tree t, to, to_ptr, from, from_ptr;
3254 gcall *gs;
3255 location_t loc = EXPR_LOCATION (*expr_p);
3257 to = TREE_OPERAND (*expr_p, 0);
3258 from = TREE_OPERAND (*expr_p, 1);
3260 /* Mark the RHS addressable. Beware that it may not be possible to do so
3261 directly if a temporary has been created by the gimplification. */
3262 prepare_gimple_addressable (&from, seq_p);
3264 mark_addressable (from);
3265 from_ptr = build_fold_addr_expr_loc (loc, from);
3266 gimplify_arg (&from_ptr, seq_p, loc);
3268 mark_addressable (to);
3269 to_ptr = build_fold_addr_expr_loc (loc, to);
3270 gimplify_arg (&to_ptr, seq_p, loc);
3272 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
3274 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
3276 if (want_value)
3278 /* tmp = memcpy() */
3279 t = create_tmp_var (TREE_TYPE (to_ptr));
3280 gimple_call_set_lhs (gs, t);
3281 gimplify_seq_add_stmt (seq_p, gs);
3283 *expr_p = build_simple_mem_ref (t);
3284 return GS_ALL_DONE;
3287 gimplify_seq_add_stmt (seq_p, gs);
3288 *expr_p = NULL;
3289 return GS_ALL_DONE;
3292 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
3293 a call to __builtin_memset. In this case we know that the RHS is
3294 a CONSTRUCTOR with an empty element list. */
3296 static enum gimplify_status
3297 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
3298 gimple_seq *seq_p)
3300 tree t, from, to, to_ptr;
3301 gcall *gs;
3302 location_t loc = EXPR_LOCATION (*expr_p);
3304 /* Assert our assumptions, to abort instead of producing wrong code
3305 silently if they are not met. Beware that the RHS CONSTRUCTOR might
3306 not be immediately exposed. */
3307 from = TREE_OPERAND (*expr_p, 1);
3308 if (TREE_CODE (from) == WITH_SIZE_EXPR)
3309 from = TREE_OPERAND (from, 0);
3311 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
3312 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
3314 /* Now proceed. */
3315 to = TREE_OPERAND (*expr_p, 0);
3317 to_ptr = build_fold_addr_expr_loc (loc, to);
3318 gimplify_arg (&to_ptr, seq_p, loc);
3319 t = builtin_decl_implicit (BUILT_IN_MEMSET);
3321 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
3323 if (want_value)
3325 /* tmp = memset() */
3326 t = create_tmp_var (TREE_TYPE (to_ptr));
3327 gimple_call_set_lhs (gs, t);
3328 gimplify_seq_add_stmt (seq_p, gs);
3330 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
3331 return GS_ALL_DONE;
3334 gimplify_seq_add_stmt (seq_p, gs);
3335 *expr_p = NULL;
3336 return GS_ALL_DONE;
3339 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
3340 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
3341 assignment. Return non-null if we detect a potential overlap. */
3343 struct gimplify_init_ctor_preeval_data
3345 /* The base decl of the lhs object. May be NULL, in which case we
3346 have to assume the lhs is indirect. */
3347 tree lhs_base_decl;
3349 /* The alias set of the lhs object. */
3350 alias_set_type lhs_alias_set;
3353 static tree
3354 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
3356 struct gimplify_init_ctor_preeval_data *data
3357 = (struct gimplify_init_ctor_preeval_data *) xdata;
3358 tree t = *tp;
3360 /* If we find the base object, obviously we have overlap. */
3361 if (data->lhs_base_decl == t)
3362 return t;
3364 /* If the constructor component is indirect, determine if we have a
3365 potential overlap with the lhs. The only bits of information we
3366 have to go on at this point are addressability and alias sets. */
3367 if ((INDIRECT_REF_P (t)
3368 || TREE_CODE (t) == MEM_REF)
3369 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
3370 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
3371 return t;
3373 /* If the constructor component is a call, determine if it can hide a
3374 potential overlap with the lhs through an INDIRECT_REF like above.
3375 ??? Ugh - this is completely broken. In fact this whole analysis
3376 doesn't look conservative. */
3377 if (TREE_CODE (t) == CALL_EXPR)
3379 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
3381 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
3382 if (POINTER_TYPE_P (TREE_VALUE (type))
3383 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
3384 && alias_sets_conflict_p (data->lhs_alias_set,
3385 get_alias_set
3386 (TREE_TYPE (TREE_VALUE (type)))))
3387 return t;
3390 if (IS_TYPE_OR_DECL_P (t))
3391 *walk_subtrees = 0;
3392 return NULL;
3395 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
3396 force values that overlap with the lhs (as described by *DATA)
3397 into temporaries. */
3399 static void
3400 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3401 struct gimplify_init_ctor_preeval_data *data)
3403 enum gimplify_status one;
3405 /* If the value is constant, then there's nothing to pre-evaluate. */
3406 if (TREE_CONSTANT (*expr_p))
3408 /* Ensure it does not have side effects, it might contain a reference to
3409 the object we're initializing. */
3410 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
3411 return;
3414 /* If the type has non-trivial constructors, we can't pre-evaluate. */
3415 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
3416 return;
3418 /* Recurse for nested constructors. */
3419 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
3421 unsigned HOST_WIDE_INT ix;
3422 constructor_elt *ce;
3423 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
3425 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
3426 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
3428 return;
3431 /* If this is a variable sized type, we must remember the size. */
3432 maybe_with_size_expr (expr_p);
3434 /* Gimplify the constructor element to something appropriate for the rhs
3435 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
3436 the gimplifier will consider this a store to memory. Doing this
3437 gimplification now means that we won't have to deal with complicated
3438 language-specific trees, nor trees like SAVE_EXPR that can induce
3439 exponential search behavior. */
3440 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
3441 if (one == GS_ERROR)
3443 *expr_p = NULL;
3444 return;
3447 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
3448 with the lhs, since "a = { .x=a }" doesn't make sense. This will
3449 always be true for all scalars, since is_gimple_mem_rhs insists on a
3450 temporary variable for them. */
3451 if (DECL_P (*expr_p))
3452 return;
3454 /* If this is of variable size, we have no choice but to assume it doesn't
3455 overlap since we can't make a temporary for it. */
3456 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
3457 return;
3459 /* Otherwise, we must search for overlap ... */
3460 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
3461 return;
3463 /* ... and if found, force the value into a temporary. */
3464 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
3467 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
3468 a RANGE_EXPR in a CONSTRUCTOR for an array.
3470 var = lower;
3471 loop_entry:
3472 object[var] = value;
3473 if (var == upper)
3474 goto loop_exit;
3475 var = var + 1;
3476 goto loop_entry;
3477 loop_exit:
3479 We increment var _after_ the loop exit check because we might otherwise
3480 fail if upper == TYPE_MAX_VALUE (type for upper).
3482 Note that we never have to deal with SAVE_EXPRs here, because this has
3483 already been taken care of for us, in gimplify_init_ctor_preeval(). */
3485 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
3486 gimple_seq *, bool);
3488 static void
3489 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
3490 tree value, tree array_elt_type,
3491 gimple_seq *pre_p, bool cleared)
3493 tree loop_entry_label, loop_exit_label, fall_thru_label;
3494 tree var, var_type, cref, tmp;
3496 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
3497 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
3498 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
3500 /* Create and initialize the index variable. */
3501 var_type = TREE_TYPE (upper);
3502 var = create_tmp_var (var_type);
3503 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
3505 /* Add the loop entry label. */
3506 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
3508 /* Build the reference. */
3509 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
3510 var, NULL_TREE, NULL_TREE);
3512 /* If we are a constructor, just call gimplify_init_ctor_eval to do
3513 the store. Otherwise just assign value to the reference. */
3515 if (TREE_CODE (value) == CONSTRUCTOR)
3516 /* NB we might have to call ourself recursively through
3517 gimplify_init_ctor_eval if the value is a constructor. */
3518 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
3519 pre_p, cleared);
3520 else
3521 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
3523 /* We exit the loop when the index var is equal to the upper bound. */
3524 gimplify_seq_add_stmt (pre_p,
3525 gimple_build_cond (EQ_EXPR, var, upper,
3526 loop_exit_label, fall_thru_label));
3528 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
3530 /* Otherwise, increment the index var... */
3531 tmp = build2 (PLUS_EXPR, var_type, var,
3532 fold_convert (var_type, integer_one_node));
3533 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
3535 /* ...and jump back to the loop entry. */
3536 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
3538 /* Add the loop exit label. */
3539 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
3542 /* Return true if FDECL is accessing a field that is zero sized. */
3544 static bool
3545 zero_sized_field_decl (const_tree fdecl)
3547 if (TREE_CODE (fdecl) == FIELD_DECL && DECL_SIZE (fdecl)
3548 && integer_zerop (DECL_SIZE (fdecl)))
3549 return true;
3550 return false;
3553 /* Return true if TYPE is zero sized. */
3555 static bool
3556 zero_sized_type (const_tree type)
3558 if (AGGREGATE_TYPE_P (type) && TYPE_SIZE (type)
3559 && integer_zerop (TYPE_SIZE (type)))
3560 return true;
3561 return false;
3564 /* A subroutine of gimplify_init_constructor. Generate individual
3565 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
3566 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
3567 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
3568 zeroed first. */
3570 static void
3571 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
3572 gimple_seq *pre_p, bool cleared)
3574 tree array_elt_type = NULL;
3575 unsigned HOST_WIDE_INT ix;
3576 tree purpose, value;
3578 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
3579 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
3581 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
3583 tree cref;
3585 /* NULL values are created above for gimplification errors. */
3586 if (value == NULL)
3587 continue;
3589 if (cleared && initializer_zerop (value))
3590 continue;
3592 /* ??? Here's to hoping the front end fills in all of the indices,
3593 so we don't have to figure out what's missing ourselves. */
3594 gcc_assert (purpose);
3596 /* Skip zero-sized fields, unless value has side-effects. This can
3597 happen with calls to functions returning a zero-sized type, which
3598 we shouldn't discard. As a number of downstream passes don't
3599 expect sets of zero-sized fields, we rely on the gimplification of
3600 the MODIFY_EXPR we make below to drop the assignment statement. */
3601 if (! TREE_SIDE_EFFECTS (value) && zero_sized_field_decl (purpose))
3602 continue;
3604 /* If we have a RANGE_EXPR, we have to build a loop to assign the
3605 whole range. */
3606 if (TREE_CODE (purpose) == RANGE_EXPR)
3608 tree lower = TREE_OPERAND (purpose, 0);
3609 tree upper = TREE_OPERAND (purpose, 1);
3611 /* If the lower bound is equal to upper, just treat it as if
3612 upper was the index. */
3613 if (simple_cst_equal (lower, upper))
3614 purpose = upper;
3615 else
3617 gimplify_init_ctor_eval_range (object, lower, upper, value,
3618 array_elt_type, pre_p, cleared);
3619 continue;
3623 if (array_elt_type)
3625 /* Do not use bitsizetype for ARRAY_REF indices. */
3626 if (TYPE_DOMAIN (TREE_TYPE (object)))
3627 purpose
3628 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
3629 purpose);
3630 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
3631 purpose, NULL_TREE, NULL_TREE);
3633 else
3635 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
3636 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
3637 unshare_expr (object), purpose, NULL_TREE);
3640 if (TREE_CODE (value) == CONSTRUCTOR
3641 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
3642 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
3643 pre_p, cleared);
3644 else
3646 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
3647 gimplify_and_add (init, pre_p);
3648 ggc_free (init);
3653 /* Return the appropriate RHS predicate for this LHS. */
3655 gimple_predicate
3656 rhs_predicate_for (tree lhs)
3658 if (is_gimple_reg (lhs))
3659 return is_gimple_reg_rhs_or_call;
3660 else
3661 return is_gimple_mem_rhs_or_call;
3664 /* Gimplify a C99 compound literal expression. This just means adding
3665 the DECL_EXPR before the current statement and using its anonymous
3666 decl instead. */
3668 static enum gimplify_status
3669 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
3670 bool (*gimple_test_f) (tree),
3671 fallback_t fallback)
3673 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
3674 tree decl = DECL_EXPR_DECL (decl_s);
3675 tree init = DECL_INITIAL (decl);
3676 /* Mark the decl as addressable if the compound literal
3677 expression is addressable now, otherwise it is marked too late
3678 after we gimplify the initialization expression. */
3679 if (TREE_ADDRESSABLE (*expr_p))
3680 TREE_ADDRESSABLE (decl) = 1;
3681 /* Otherwise, if we don't need an lvalue and have a literal directly
3682 substitute it. Check if it matches the gimple predicate, as
3683 otherwise we'd generate a new temporary, and we can as well just
3684 use the decl we already have. */
3685 else if (!TREE_ADDRESSABLE (decl)
3686 && init
3687 && (fallback & fb_lvalue) == 0
3688 && gimple_test_f (init))
3690 *expr_p = init;
3691 return GS_OK;
3694 /* Preliminarily mark non-addressed complex variables as eligible
3695 for promotion to gimple registers. We'll transform their uses
3696 as we find them. */
3697 if ((TREE_CODE (TREE_TYPE (decl)) == COMPLEX_TYPE
3698 || TREE_CODE (TREE_TYPE (decl)) == VECTOR_TYPE)
3699 && !TREE_THIS_VOLATILE (decl)
3700 && !needs_to_live_in_memory (decl))
3701 DECL_GIMPLE_REG_P (decl) = 1;
3703 /* If the decl is not addressable, then it is being used in some
3704 expression or on the right hand side of a statement, and it can
3705 be put into a readonly data section. */
3706 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
3707 TREE_READONLY (decl) = 1;
3709 /* This decl isn't mentioned in the enclosing block, so add it to the
3710 list of temps. FIXME it seems a bit of a kludge to say that
3711 anonymous artificial vars aren't pushed, but everything else is. */
3712 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
3713 gimple_add_tmp_var (decl);
3715 gimplify_and_add (decl_s, pre_p);
3716 *expr_p = decl;
3717 return GS_OK;
3720 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
3721 return a new CONSTRUCTOR if something changed. */
3723 static tree
3724 optimize_compound_literals_in_ctor (tree orig_ctor)
3726 tree ctor = orig_ctor;
3727 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
3728 unsigned int idx, num = vec_safe_length (elts);
3730 for (idx = 0; idx < num; idx++)
3732 tree value = (*elts)[idx].value;
3733 tree newval = value;
3734 if (TREE_CODE (value) == CONSTRUCTOR)
3735 newval = optimize_compound_literals_in_ctor (value);
3736 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
3738 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
3739 tree decl = DECL_EXPR_DECL (decl_s);
3740 tree init = DECL_INITIAL (decl);
3742 if (!TREE_ADDRESSABLE (value)
3743 && !TREE_ADDRESSABLE (decl)
3744 && init
3745 && TREE_CODE (init) == CONSTRUCTOR)
3746 newval = optimize_compound_literals_in_ctor (init);
3748 if (newval == value)
3749 continue;
3751 if (ctor == orig_ctor)
3753 ctor = copy_node (orig_ctor);
3754 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
3755 elts = CONSTRUCTOR_ELTS (ctor);
3757 (*elts)[idx].value = newval;
3759 return ctor;
3762 /* A subroutine of gimplify_modify_expr. Break out elements of a
3763 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
3765 Note that we still need to clear any elements that don't have explicit
3766 initializers, so if not all elements are initialized we keep the
3767 original MODIFY_EXPR, we just remove all of the constructor elements.
3769 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
3770 GS_ERROR if we would have to create a temporary when gimplifying
3771 this constructor. Otherwise, return GS_OK.
3773 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
3775 static enum gimplify_status
3776 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3777 bool want_value, bool notify_temp_creation)
3779 tree object, ctor, type;
3780 enum gimplify_status ret;
3781 vec<constructor_elt, va_gc> *elts;
3783 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
3785 if (!notify_temp_creation)
3787 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3788 is_gimple_lvalue, fb_lvalue);
3789 if (ret == GS_ERROR)
3790 return ret;
3793 object = TREE_OPERAND (*expr_p, 0);
3794 ctor = TREE_OPERAND (*expr_p, 1) =
3795 optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
3796 type = TREE_TYPE (ctor);
3797 elts = CONSTRUCTOR_ELTS (ctor);
3798 ret = GS_ALL_DONE;
3800 switch (TREE_CODE (type))
3802 case RECORD_TYPE:
3803 case UNION_TYPE:
3804 case QUAL_UNION_TYPE:
3805 case ARRAY_TYPE:
3807 struct gimplify_init_ctor_preeval_data preeval_data;
3808 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
3809 bool cleared, complete_p, valid_const_initializer;
3811 /* Aggregate types must lower constructors to initialization of
3812 individual elements. The exception is that a CONSTRUCTOR node
3813 with no elements indicates zero-initialization of the whole. */
3814 if (vec_safe_is_empty (elts))
3816 if (notify_temp_creation)
3817 return GS_OK;
3818 break;
3821 /* Fetch information about the constructor to direct later processing.
3822 We might want to make static versions of it in various cases, and
3823 can only do so if it known to be a valid constant initializer. */
3824 valid_const_initializer
3825 = categorize_ctor_elements (ctor, &num_nonzero_elements,
3826 &num_ctor_elements, &complete_p);
3828 /* If a const aggregate variable is being initialized, then it
3829 should never be a lose to promote the variable to be static. */
3830 if (valid_const_initializer
3831 && num_nonzero_elements > 1
3832 && TREE_READONLY (object)
3833 && TREE_CODE (object) == VAR_DECL
3834 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object)))
3836 if (notify_temp_creation)
3837 return GS_ERROR;
3838 DECL_INITIAL (object) = ctor;
3839 TREE_STATIC (object) = 1;
3840 if (!DECL_NAME (object))
3841 DECL_NAME (object) = create_tmp_var_name ("C");
3842 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
3844 /* ??? C++ doesn't automatically append a .<number> to the
3845 assembler name, and even when it does, it looks at FE private
3846 data structures to figure out what that number should be,
3847 which are not set for this variable. I suppose this is
3848 important for local statics for inline functions, which aren't
3849 "local" in the object file sense. So in order to get a unique
3850 TU-local symbol, we must invoke the lhd version now. */
3851 lhd_set_decl_assembler_name (object);
3853 *expr_p = NULL_TREE;
3854 break;
3857 /* If there are "lots" of initialized elements, even discounting
3858 those that are not address constants (and thus *must* be
3859 computed at runtime), then partition the constructor into
3860 constant and non-constant parts. Block copy the constant
3861 parts in, then generate code for the non-constant parts. */
3862 /* TODO. There's code in cp/typeck.c to do this. */
3864 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
3865 /* store_constructor will ignore the clearing of variable-sized
3866 objects. Initializers for such objects must explicitly set
3867 every field that needs to be set. */
3868 cleared = false;
3869 else if (!complete_p && !CONSTRUCTOR_NO_CLEARING (ctor))
3870 /* If the constructor isn't complete, clear the whole object
3871 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
3873 ??? This ought not to be needed. For any element not present
3874 in the initializer, we should simply set them to zero. Except
3875 we'd need to *find* the elements that are not present, and that
3876 requires trickery to avoid quadratic compile-time behavior in
3877 large cases or excessive memory use in small cases. */
3878 cleared = true;
3879 else if (num_ctor_elements - num_nonzero_elements
3880 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
3881 && num_nonzero_elements < num_ctor_elements / 4)
3882 /* If there are "lots" of zeros, it's more efficient to clear
3883 the memory and then set the nonzero elements. */
3884 cleared = true;
3885 else
3886 cleared = false;
3888 /* If there are "lots" of initialized elements, and all of them
3889 are valid address constants, then the entire initializer can
3890 be dropped to memory, and then memcpy'd out. Don't do this
3891 for sparse arrays, though, as it's more efficient to follow
3892 the standard CONSTRUCTOR behavior of memset followed by
3893 individual element initialization. Also don't do this for small
3894 all-zero initializers (which aren't big enough to merit
3895 clearing), and don't try to make bitwise copies of
3896 TREE_ADDRESSABLE types.
3898 We cannot apply such transformation when compiling chkp static
3899 initializer because creation of initializer image in the memory
3900 will require static initialization of bounds for it. It should
3901 result in another gimplification of similar initializer and we
3902 may fall into infinite loop. */
3903 if (valid_const_initializer
3904 && !(cleared || num_nonzero_elements == 0)
3905 && !TREE_ADDRESSABLE (type)
3906 && (!current_function_decl
3907 || !lookup_attribute ("chkp ctor",
3908 DECL_ATTRIBUTES (current_function_decl))))
3910 HOST_WIDE_INT size = int_size_in_bytes (type);
3911 unsigned int align;
3913 /* ??? We can still get unbounded array types, at least
3914 from the C++ front end. This seems wrong, but attempt
3915 to work around it for now. */
3916 if (size < 0)
3918 size = int_size_in_bytes (TREE_TYPE (object));
3919 if (size >= 0)
3920 TREE_TYPE (ctor) = type = TREE_TYPE (object);
3923 /* Find the maximum alignment we can assume for the object. */
3924 /* ??? Make use of DECL_OFFSET_ALIGN. */
3925 if (DECL_P (object))
3926 align = DECL_ALIGN (object);
3927 else
3928 align = TYPE_ALIGN (type);
3930 /* Do a block move either if the size is so small as to make
3931 each individual move a sub-unit move on average, or if it
3932 is so large as to make individual moves inefficient. */
3933 if (size > 0
3934 && num_nonzero_elements > 1
3935 && (size < num_nonzero_elements
3936 || !can_move_by_pieces (size, align)))
3938 if (notify_temp_creation)
3939 return GS_ERROR;
3941 walk_tree (&ctor, force_labels_r, NULL, NULL);
3942 ctor = tree_output_constant_def (ctor);
3943 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
3944 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
3945 TREE_OPERAND (*expr_p, 1) = ctor;
3947 /* This is no longer an assignment of a CONSTRUCTOR, but
3948 we still may have processing to do on the LHS. So
3949 pretend we didn't do anything here to let that happen. */
3950 return GS_UNHANDLED;
3954 /* If the target is volatile, we have non-zero elements and more than
3955 one field to assign, initialize the target from a temporary. */
3956 if (TREE_THIS_VOLATILE (object)
3957 && !TREE_ADDRESSABLE (type)
3958 && num_nonzero_elements > 0
3959 && vec_safe_length (elts) > 1)
3961 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
3962 TREE_OPERAND (*expr_p, 0) = temp;
3963 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
3964 *expr_p,
3965 build2 (MODIFY_EXPR, void_type_node,
3966 object, temp));
3967 return GS_OK;
3970 if (notify_temp_creation)
3971 return GS_OK;
3973 /* If there are nonzero elements and if needed, pre-evaluate to capture
3974 elements overlapping with the lhs into temporaries. We must do this
3975 before clearing to fetch the values before they are zeroed-out. */
3976 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
3978 preeval_data.lhs_base_decl = get_base_address (object);
3979 if (!DECL_P (preeval_data.lhs_base_decl))
3980 preeval_data.lhs_base_decl = NULL;
3981 preeval_data.lhs_alias_set = get_alias_set (object);
3983 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
3984 pre_p, post_p, &preeval_data);
3987 bool ctor_has_side_effects_p
3988 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
3990 if (cleared)
3992 /* Zap the CONSTRUCTOR element list, which simplifies this case.
3993 Note that we still have to gimplify, in order to handle the
3994 case of variable sized types. Avoid shared tree structures. */
3995 CONSTRUCTOR_ELTS (ctor) = NULL;
3996 TREE_SIDE_EFFECTS (ctor) = 0;
3997 object = unshare_expr (object);
3998 gimplify_stmt (expr_p, pre_p);
4001 /* If we have not block cleared the object, or if there are nonzero
4002 elements in the constructor, or if the constructor has side effects,
4003 add assignments to the individual scalar fields of the object. */
4004 if (!cleared
4005 || num_nonzero_elements > 0
4006 || ctor_has_side_effects_p)
4007 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
4009 *expr_p = NULL_TREE;
4011 break;
4013 case COMPLEX_TYPE:
4015 tree r, i;
4017 if (notify_temp_creation)
4018 return GS_OK;
4020 /* Extract the real and imaginary parts out of the ctor. */
4021 gcc_assert (elts->length () == 2);
4022 r = (*elts)[0].value;
4023 i = (*elts)[1].value;
4024 if (r == NULL || i == NULL)
4026 tree zero = build_zero_cst (TREE_TYPE (type));
4027 if (r == NULL)
4028 r = zero;
4029 if (i == NULL)
4030 i = zero;
4033 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
4034 represent creation of a complex value. */
4035 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
4037 ctor = build_complex (type, r, i);
4038 TREE_OPERAND (*expr_p, 1) = ctor;
4040 else
4042 ctor = build2 (COMPLEX_EXPR, type, r, i);
4043 TREE_OPERAND (*expr_p, 1) = ctor;
4044 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
4045 pre_p,
4046 post_p,
4047 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
4048 fb_rvalue);
4051 break;
4053 case VECTOR_TYPE:
4055 unsigned HOST_WIDE_INT ix;
4056 constructor_elt *ce;
4058 if (notify_temp_creation)
4059 return GS_OK;
4061 /* Go ahead and simplify constant constructors to VECTOR_CST. */
4062 if (TREE_CONSTANT (ctor))
4064 bool constant_p = true;
4065 tree value;
4067 /* Even when ctor is constant, it might contain non-*_CST
4068 elements, such as addresses or trapping values like
4069 1.0/0.0 - 1.0/0.0. Such expressions don't belong
4070 in VECTOR_CST nodes. */
4071 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
4072 if (!CONSTANT_CLASS_P (value))
4074 constant_p = false;
4075 break;
4078 if (constant_p)
4080 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
4081 break;
4084 TREE_CONSTANT (ctor) = 0;
4087 /* Vector types use CONSTRUCTOR all the way through gimple
4088 compilation as a general initializer. */
4089 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
4091 enum gimplify_status tret;
4092 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
4093 fb_rvalue);
4094 if (tret == GS_ERROR)
4095 ret = GS_ERROR;
4097 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
4098 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
4100 break;
4102 default:
4103 /* So how did we get a CONSTRUCTOR for a scalar type? */
4104 gcc_unreachable ();
4107 if (ret == GS_ERROR)
4108 return GS_ERROR;
4109 else if (want_value)
4111 *expr_p = object;
4112 return GS_OK;
4114 else
4116 /* If we have gimplified both sides of the initializer but have
4117 not emitted an assignment, do so now. */
4118 if (*expr_p)
4120 tree lhs = TREE_OPERAND (*expr_p, 0);
4121 tree rhs = TREE_OPERAND (*expr_p, 1);
4122 gassign *init = gimple_build_assign (lhs, rhs);
4123 gimplify_seq_add_stmt (pre_p, init);
4124 *expr_p = NULL;
4127 return GS_ALL_DONE;
4131 /* Given a pointer value OP0, return a simplified version of an
4132 indirection through OP0, or NULL_TREE if no simplification is
4133 possible. This may only be applied to a rhs of an expression.
4134 Note that the resulting type may be different from the type pointed
4135 to in the sense that it is still compatible from the langhooks
4136 point of view. */
4138 static tree
4139 gimple_fold_indirect_ref_rhs (tree t)
4141 return gimple_fold_indirect_ref (t);
4144 /* Subroutine of gimplify_modify_expr to do simplifications of
4145 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
4146 something changes. */
4148 static enum gimplify_status
4149 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
4150 gimple_seq *pre_p, gimple_seq *post_p,
4151 bool want_value)
4153 enum gimplify_status ret = GS_UNHANDLED;
4154 bool changed;
4158 changed = false;
4159 switch (TREE_CODE (*from_p))
4161 case VAR_DECL:
4162 /* If we're assigning from a read-only variable initialized with
4163 a constructor, do the direct assignment from the constructor,
4164 but only if neither source nor target are volatile since this
4165 latter assignment might end up being done on a per-field basis. */
4166 if (DECL_INITIAL (*from_p)
4167 && TREE_READONLY (*from_p)
4168 && !TREE_THIS_VOLATILE (*from_p)
4169 && !TREE_THIS_VOLATILE (*to_p)
4170 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR)
4172 tree old_from = *from_p;
4173 enum gimplify_status subret;
4175 /* Move the constructor into the RHS. */
4176 *from_p = unshare_expr (DECL_INITIAL (*from_p));
4178 /* Let's see if gimplify_init_constructor will need to put
4179 it in memory. */
4180 subret = gimplify_init_constructor (expr_p, NULL, NULL,
4181 false, true);
4182 if (subret == GS_ERROR)
4184 /* If so, revert the change. */
4185 *from_p = old_from;
4187 else
4189 ret = GS_OK;
4190 changed = true;
4193 break;
4194 case INDIRECT_REF:
4196 /* If we have code like
4198 *(const A*)(A*)&x
4200 where the type of "x" is a (possibly cv-qualified variant
4201 of "A"), treat the entire expression as identical to "x".
4202 This kind of code arises in C++ when an object is bound
4203 to a const reference, and if "x" is a TARGET_EXPR we want
4204 to take advantage of the optimization below. */
4205 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
4206 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
4207 if (t)
4209 if (TREE_THIS_VOLATILE (t) != volatile_p)
4211 if (DECL_P (t))
4212 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
4213 build_fold_addr_expr (t));
4214 if (REFERENCE_CLASS_P (t))
4215 TREE_THIS_VOLATILE (t) = volatile_p;
4217 *from_p = t;
4218 ret = GS_OK;
4219 changed = true;
4221 break;
4224 case TARGET_EXPR:
4226 /* If we are initializing something from a TARGET_EXPR, strip the
4227 TARGET_EXPR and initialize it directly, if possible. This can't
4228 be done if the initializer is void, since that implies that the
4229 temporary is set in some non-trivial way.
4231 ??? What about code that pulls out the temp and uses it
4232 elsewhere? I think that such code never uses the TARGET_EXPR as
4233 an initializer. If I'm wrong, we'll die because the temp won't
4234 have any RTL. In that case, I guess we'll need to replace
4235 references somehow. */
4236 tree init = TARGET_EXPR_INITIAL (*from_p);
4238 if (init
4239 && !VOID_TYPE_P (TREE_TYPE (init)))
4241 *from_p = init;
4242 ret = GS_OK;
4243 changed = true;
4246 break;
4248 case COMPOUND_EXPR:
4249 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
4250 caught. */
4251 gimplify_compound_expr (from_p, pre_p, true);
4252 ret = GS_OK;
4253 changed = true;
4254 break;
4256 case CONSTRUCTOR:
4257 /* If we already made some changes, let the front end have a
4258 crack at this before we break it down. */
4259 if (ret != GS_UNHANDLED)
4260 break;
4261 /* If we're initializing from a CONSTRUCTOR, break this into
4262 individual MODIFY_EXPRs. */
4263 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
4264 false);
4266 case COND_EXPR:
4267 /* If we're assigning to a non-register type, push the assignment
4268 down into the branches. This is mandatory for ADDRESSABLE types,
4269 since we cannot generate temporaries for such, but it saves a
4270 copy in other cases as well. */
4271 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
4273 /* This code should mirror the code in gimplify_cond_expr. */
4274 enum tree_code code = TREE_CODE (*expr_p);
4275 tree cond = *from_p;
4276 tree result = *to_p;
4278 ret = gimplify_expr (&result, pre_p, post_p,
4279 is_gimple_lvalue, fb_lvalue);
4280 if (ret != GS_ERROR)
4281 ret = GS_OK;
4283 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
4284 TREE_OPERAND (cond, 1)
4285 = build2 (code, void_type_node, result,
4286 TREE_OPERAND (cond, 1));
4287 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
4288 TREE_OPERAND (cond, 2)
4289 = build2 (code, void_type_node, unshare_expr (result),
4290 TREE_OPERAND (cond, 2));
4292 TREE_TYPE (cond) = void_type_node;
4293 recalculate_side_effects (cond);
4295 if (want_value)
4297 gimplify_and_add (cond, pre_p);
4298 *expr_p = unshare_expr (result);
4300 else
4301 *expr_p = cond;
4302 return ret;
4304 break;
4306 case CALL_EXPR:
4307 /* For calls that return in memory, give *to_p as the CALL_EXPR's
4308 return slot so that we don't generate a temporary. */
4309 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
4310 && aggregate_value_p (*from_p, *from_p))
4312 bool use_target;
4314 if (!(rhs_predicate_for (*to_p))(*from_p))
4315 /* If we need a temporary, *to_p isn't accurate. */
4316 use_target = false;
4317 /* It's OK to use the return slot directly unless it's an NRV. */
4318 else if (TREE_CODE (*to_p) == RESULT_DECL
4319 && DECL_NAME (*to_p) == NULL_TREE
4320 && needs_to_live_in_memory (*to_p))
4321 use_target = true;
4322 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
4323 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
4324 /* Don't force regs into memory. */
4325 use_target = false;
4326 else if (TREE_CODE (*expr_p) == INIT_EXPR)
4327 /* It's OK to use the target directly if it's being
4328 initialized. */
4329 use_target = true;
4330 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
4331 != INTEGER_CST)
4332 /* Always use the target and thus RSO for variable-sized types.
4333 GIMPLE cannot deal with a variable-sized assignment
4334 embedded in a call statement. */
4335 use_target = true;
4336 else if (TREE_CODE (*to_p) != SSA_NAME
4337 && (!is_gimple_variable (*to_p)
4338 || needs_to_live_in_memory (*to_p)))
4339 /* Don't use the original target if it's already addressable;
4340 if its address escapes, and the called function uses the
4341 NRV optimization, a conforming program could see *to_p
4342 change before the called function returns; see c++/19317.
4343 When optimizing, the return_slot pass marks more functions
4344 as safe after we have escape info. */
4345 use_target = false;
4346 else
4347 use_target = true;
4349 if (use_target)
4351 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
4352 mark_addressable (*to_p);
4355 break;
4357 case WITH_SIZE_EXPR:
4358 /* Likewise for calls that return an aggregate of non-constant size,
4359 since we would not be able to generate a temporary at all. */
4360 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
4362 *from_p = TREE_OPERAND (*from_p, 0);
4363 /* We don't change ret in this case because the
4364 WITH_SIZE_EXPR might have been added in
4365 gimplify_modify_expr, so returning GS_OK would lead to an
4366 infinite loop. */
4367 changed = true;
4369 break;
4371 /* If we're initializing from a container, push the initialization
4372 inside it. */
4373 case CLEANUP_POINT_EXPR:
4374 case BIND_EXPR:
4375 case STATEMENT_LIST:
4377 tree wrap = *from_p;
4378 tree t;
4380 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
4381 fb_lvalue);
4382 if (ret != GS_ERROR)
4383 ret = GS_OK;
4385 t = voidify_wrapper_expr (wrap, *expr_p);
4386 gcc_assert (t == *expr_p);
4388 if (want_value)
4390 gimplify_and_add (wrap, pre_p);
4391 *expr_p = unshare_expr (*to_p);
4393 else
4394 *expr_p = wrap;
4395 return GS_OK;
4398 case COMPOUND_LITERAL_EXPR:
4400 tree complit = TREE_OPERAND (*expr_p, 1);
4401 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
4402 tree decl = DECL_EXPR_DECL (decl_s);
4403 tree init = DECL_INITIAL (decl);
4405 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
4406 into struct T x = { 0, 1, 2 } if the address of the
4407 compound literal has never been taken. */
4408 if (!TREE_ADDRESSABLE (complit)
4409 && !TREE_ADDRESSABLE (decl)
4410 && init)
4412 *expr_p = copy_node (*expr_p);
4413 TREE_OPERAND (*expr_p, 1) = init;
4414 return GS_OK;
4418 default:
4419 break;
4422 while (changed);
4424 return ret;
4428 /* Return true if T looks like a valid GIMPLE statement. */
4430 static bool
4431 is_gimple_stmt (tree t)
4433 const enum tree_code code = TREE_CODE (t);
4435 switch (code)
4437 case NOP_EXPR:
4438 /* The only valid NOP_EXPR is the empty statement. */
4439 return IS_EMPTY_STMT (t);
4441 case BIND_EXPR:
4442 case COND_EXPR:
4443 /* These are only valid if they're void. */
4444 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
4446 case SWITCH_EXPR:
4447 case GOTO_EXPR:
4448 case RETURN_EXPR:
4449 case LABEL_EXPR:
4450 case CASE_LABEL_EXPR:
4451 case TRY_CATCH_EXPR:
4452 case TRY_FINALLY_EXPR:
4453 case EH_FILTER_EXPR:
4454 case CATCH_EXPR:
4455 case ASM_EXPR:
4456 case STATEMENT_LIST:
4457 case OACC_PARALLEL:
4458 case OACC_KERNELS:
4459 case OACC_DATA:
4460 case OACC_HOST_DATA:
4461 case OACC_DECLARE:
4462 case OACC_UPDATE:
4463 case OACC_ENTER_DATA:
4464 case OACC_EXIT_DATA:
4465 case OACC_CACHE:
4466 case OMP_PARALLEL:
4467 case OMP_FOR:
4468 case OMP_SIMD:
4469 case CILK_SIMD:
4470 case OMP_DISTRIBUTE:
4471 case OACC_LOOP:
4472 case OMP_SECTIONS:
4473 case OMP_SECTION:
4474 case OMP_SINGLE:
4475 case OMP_MASTER:
4476 case OMP_TASKGROUP:
4477 case OMP_ORDERED:
4478 case OMP_CRITICAL:
4479 case OMP_TASK:
4480 /* These are always void. */
4481 return true;
4483 case CALL_EXPR:
4484 case MODIFY_EXPR:
4485 case PREDICT_EXPR:
4486 /* These are valid regardless of their type. */
4487 return true;
4489 default:
4490 return false;
4495 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
4496 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
4497 DECL_GIMPLE_REG_P set.
4499 IMPORTANT NOTE: This promotion is performed by introducing a load of the
4500 other, unmodified part of the complex object just before the total store.
4501 As a consequence, if the object is still uninitialized, an undefined value
4502 will be loaded into a register, which may result in a spurious exception
4503 if the register is floating-point and the value happens to be a signaling
4504 NaN for example. Then the fully-fledged complex operations lowering pass
4505 followed by a DCE pass are necessary in order to fix things up. */
4507 static enum gimplify_status
4508 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
4509 bool want_value)
4511 enum tree_code code, ocode;
4512 tree lhs, rhs, new_rhs, other, realpart, imagpart;
4514 lhs = TREE_OPERAND (*expr_p, 0);
4515 rhs = TREE_OPERAND (*expr_p, 1);
4516 code = TREE_CODE (lhs);
4517 lhs = TREE_OPERAND (lhs, 0);
4519 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
4520 other = build1 (ocode, TREE_TYPE (rhs), lhs);
4521 TREE_NO_WARNING (other) = 1;
4522 other = get_formal_tmp_var (other, pre_p);
4524 realpart = code == REALPART_EXPR ? rhs : other;
4525 imagpart = code == REALPART_EXPR ? other : rhs;
4527 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
4528 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
4529 else
4530 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
4532 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
4533 *expr_p = (want_value) ? rhs : NULL_TREE;
4535 return GS_ALL_DONE;
4538 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
4540 modify_expr
4541 : varname '=' rhs
4542 | '*' ID '=' rhs
4544 PRE_P points to the list where side effects that must happen before
4545 *EXPR_P should be stored.
4547 POST_P points to the list where side effects that must happen after
4548 *EXPR_P should be stored.
4550 WANT_VALUE is nonzero iff we want to use the value of this expression
4551 in another expression. */
4553 static enum gimplify_status
4554 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4555 bool want_value)
4557 tree *from_p = &TREE_OPERAND (*expr_p, 1);
4558 tree *to_p = &TREE_OPERAND (*expr_p, 0);
4559 enum gimplify_status ret = GS_UNHANDLED;
4560 gimple assign;
4561 location_t loc = EXPR_LOCATION (*expr_p);
4562 gimple_stmt_iterator gsi;
4564 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
4565 || TREE_CODE (*expr_p) == INIT_EXPR);
4567 /* Trying to simplify a clobber using normal logic doesn't work,
4568 so handle it here. */
4569 if (TREE_CLOBBER_P (*from_p))
4571 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
4572 if (ret == GS_ERROR)
4573 return ret;
4574 gcc_assert (!want_value
4575 && (TREE_CODE (*to_p) == VAR_DECL
4576 || TREE_CODE (*to_p) == MEM_REF));
4577 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
4578 *expr_p = NULL;
4579 return GS_ALL_DONE;
4582 /* Insert pointer conversions required by the middle-end that are not
4583 required by the frontend. This fixes middle-end type checking for
4584 for example gcc.dg/redecl-6.c. */
4585 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
4587 STRIP_USELESS_TYPE_CONVERSION (*from_p);
4588 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
4589 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
4592 /* See if any simplifications can be done based on what the RHS is. */
4593 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
4594 want_value);
4595 if (ret != GS_UNHANDLED)
4596 return ret;
4598 /* For zero sized types only gimplify the left hand side and right hand
4599 side as statements and throw away the assignment. Do this after
4600 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
4601 types properly. */
4602 if (zero_sized_type (TREE_TYPE (*from_p)) && !want_value)
4604 gimplify_stmt (from_p, pre_p);
4605 gimplify_stmt (to_p, pre_p);
4606 *expr_p = NULL_TREE;
4607 return GS_ALL_DONE;
4610 /* If the value being copied is of variable width, compute the length
4611 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
4612 before gimplifying any of the operands so that we can resolve any
4613 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
4614 the size of the expression to be copied, not of the destination, so
4615 that is what we must do here. */
4616 maybe_with_size_expr (from_p);
4618 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
4619 if (ret == GS_ERROR)
4620 return ret;
4622 /* As a special case, we have to temporarily allow for assignments
4623 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
4624 a toplevel statement, when gimplifying the GENERIC expression
4625 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
4626 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
4628 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
4629 prevent gimplify_expr from trying to create a new temporary for
4630 foo's LHS, we tell it that it should only gimplify until it
4631 reaches the CALL_EXPR. On return from gimplify_expr, the newly
4632 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
4633 and all we need to do here is set 'a' to be its LHS. */
4634 ret = gimplify_expr (from_p, pre_p, post_p, rhs_predicate_for (*to_p),
4635 fb_rvalue);
4636 if (ret == GS_ERROR)
4637 return ret;
4639 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
4640 size as argument to the the call. */
4641 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
4643 tree call = TREE_OPERAND (*from_p, 0);
4644 tree vlasize = TREE_OPERAND (*from_p, 1);
4646 if (TREE_CODE (call) == CALL_EXPR
4647 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
4649 int nargs = call_expr_nargs (call);
4650 tree type = TREE_TYPE (call);
4651 tree ap = CALL_EXPR_ARG (call, 0);
4652 tree tag = CALL_EXPR_ARG (call, 1);
4653 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
4654 IFN_VA_ARG, type,
4655 nargs + 1, ap, tag,
4656 vlasize);
4657 tree *call_p = &(TREE_OPERAND (*from_p, 0));
4658 *call_p = newcall;
4662 /* Now see if the above changed *from_p to something we handle specially. */
4663 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
4664 want_value);
4665 if (ret != GS_UNHANDLED)
4666 return ret;
4668 /* If we've got a variable sized assignment between two lvalues (i.e. does
4669 not involve a call), then we can make things a bit more straightforward
4670 by converting the assignment to memcpy or memset. */
4671 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
4673 tree from = TREE_OPERAND (*from_p, 0);
4674 tree size = TREE_OPERAND (*from_p, 1);
4676 if (TREE_CODE (from) == CONSTRUCTOR)
4677 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
4679 if (is_gimple_addressable (from))
4681 *from_p = from;
4682 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
4683 pre_p);
4687 /* Transform partial stores to non-addressable complex variables into
4688 total stores. This allows us to use real instead of virtual operands
4689 for these variables, which improves optimization. */
4690 if ((TREE_CODE (*to_p) == REALPART_EXPR
4691 || TREE_CODE (*to_p) == IMAGPART_EXPR)
4692 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
4693 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
4695 /* Try to alleviate the effects of the gimplification creating artificial
4696 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
4697 make sure not to create DECL_DEBUG_EXPR links across functions. */
4698 if (!gimplify_ctxp->into_ssa
4699 && TREE_CODE (*from_p) == VAR_DECL
4700 && DECL_IGNORED_P (*from_p)
4701 && DECL_P (*to_p)
4702 && !DECL_IGNORED_P (*to_p)
4703 && decl_function_context (*to_p) == current_function_decl)
4705 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
4706 DECL_NAME (*from_p)
4707 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
4708 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
4709 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
4712 if (want_value && TREE_THIS_VOLATILE (*to_p))
4713 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
4715 if (TREE_CODE (*from_p) == CALL_EXPR)
4717 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
4718 instead of a GIMPLE_ASSIGN. */
4719 gcall *call_stmt;
4720 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
4722 /* Gimplify internal functions created in the FEs. */
4723 int nargs = call_expr_nargs (*from_p), i;
4724 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
4725 auto_vec<tree> vargs (nargs);
4727 for (i = 0; i < nargs; i++)
4729 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
4730 EXPR_LOCATION (*from_p));
4731 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
4733 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
4734 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
4736 else
4738 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
4739 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
4740 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
4741 tree fndecl = get_callee_fndecl (*from_p);
4742 if (fndecl
4743 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL
4744 && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_EXPECT
4745 && call_expr_nargs (*from_p) == 3)
4746 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
4747 CALL_EXPR_ARG (*from_p, 0),
4748 CALL_EXPR_ARG (*from_p, 1),
4749 CALL_EXPR_ARG (*from_p, 2));
4750 else
4752 call_stmt = gimple_build_call_from_tree (*from_p);
4753 gimple_call_set_fntype (call_stmt, TREE_TYPE (fnptrtype));
4756 notice_special_calls (call_stmt);
4757 if (!gimple_call_noreturn_p (call_stmt))
4758 gimple_call_set_lhs (call_stmt, *to_p);
4759 assign = call_stmt;
4761 else
4763 assign = gimple_build_assign (*to_p, *from_p);
4764 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
4767 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
4769 /* We should have got an SSA name from the start. */
4770 gcc_assert (TREE_CODE (*to_p) == SSA_NAME);
4773 gimplify_seq_add_stmt (pre_p, assign);
4774 gsi = gsi_last (*pre_p);
4775 maybe_fold_stmt (&gsi);
4777 if (want_value)
4779 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
4780 return GS_OK;
4782 else
4783 *expr_p = NULL;
4785 return GS_ALL_DONE;
4788 /* Gimplify a comparison between two variable-sized objects. Do this
4789 with a call to BUILT_IN_MEMCMP. */
4791 static enum gimplify_status
4792 gimplify_variable_sized_compare (tree *expr_p)
4794 location_t loc = EXPR_LOCATION (*expr_p);
4795 tree op0 = TREE_OPERAND (*expr_p, 0);
4796 tree op1 = TREE_OPERAND (*expr_p, 1);
4797 tree t, arg, dest, src, expr;
4799 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
4800 arg = unshare_expr (arg);
4801 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
4802 src = build_fold_addr_expr_loc (loc, op1);
4803 dest = build_fold_addr_expr_loc (loc, op0);
4804 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
4805 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
4807 expr
4808 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
4809 SET_EXPR_LOCATION (expr, loc);
4810 *expr_p = expr;
4812 return GS_OK;
4815 /* Gimplify a comparison between two aggregate objects of integral scalar
4816 mode as a comparison between the bitwise equivalent scalar values. */
4818 static enum gimplify_status
4819 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
4821 location_t loc = EXPR_LOCATION (*expr_p);
4822 tree op0 = TREE_OPERAND (*expr_p, 0);
4823 tree op1 = TREE_OPERAND (*expr_p, 1);
4825 tree type = TREE_TYPE (op0);
4826 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
4828 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
4829 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
4831 *expr_p
4832 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
4834 return GS_OK;
4837 /* Gimplify an expression sequence. This function gimplifies each
4838 expression and rewrites the original expression with the last
4839 expression of the sequence in GIMPLE form.
4841 PRE_P points to the list where the side effects for all the
4842 expressions in the sequence will be emitted.
4844 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
4846 static enum gimplify_status
4847 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
4849 tree t = *expr_p;
4853 tree *sub_p = &TREE_OPERAND (t, 0);
4855 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
4856 gimplify_compound_expr (sub_p, pre_p, false);
4857 else
4858 gimplify_stmt (sub_p, pre_p);
4860 t = TREE_OPERAND (t, 1);
4862 while (TREE_CODE (t) == COMPOUND_EXPR);
4864 *expr_p = t;
4865 if (want_value)
4866 return GS_OK;
4867 else
4869 gimplify_stmt (expr_p, pre_p);
4870 return GS_ALL_DONE;
4874 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
4875 gimplify. After gimplification, EXPR_P will point to a new temporary
4876 that holds the original value of the SAVE_EXPR node.
4878 PRE_P points to the list where side effects that must happen before
4879 *EXPR_P should be stored. */
4881 static enum gimplify_status
4882 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
4884 enum gimplify_status ret = GS_ALL_DONE;
4885 tree val;
4887 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
4888 val = TREE_OPERAND (*expr_p, 0);
4890 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
4891 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
4893 /* The operand may be a void-valued expression such as SAVE_EXPRs
4894 generated by the Java frontend for class initialization. It is
4895 being executed only for its side-effects. */
4896 if (TREE_TYPE (val) == void_type_node)
4898 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
4899 is_gimple_stmt, fb_none);
4900 val = NULL;
4902 else
4903 val = get_initialized_tmp_var (val, pre_p, post_p);
4905 TREE_OPERAND (*expr_p, 0) = val;
4906 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
4909 *expr_p = val;
4911 return ret;
4914 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
4916 unary_expr
4917 : ...
4918 | '&' varname
4921 PRE_P points to the list where side effects that must happen before
4922 *EXPR_P should be stored.
4924 POST_P points to the list where side effects that must happen after
4925 *EXPR_P should be stored. */
4927 static enum gimplify_status
4928 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
4930 tree expr = *expr_p;
4931 tree op0 = TREE_OPERAND (expr, 0);
4932 enum gimplify_status ret;
4933 location_t loc = EXPR_LOCATION (*expr_p);
4935 switch (TREE_CODE (op0))
4937 case INDIRECT_REF:
4938 do_indirect_ref:
4939 /* Check if we are dealing with an expression of the form '&*ptr'.
4940 While the front end folds away '&*ptr' into 'ptr', these
4941 expressions may be generated internally by the compiler (e.g.,
4942 builtins like __builtin_va_end). */
4943 /* Caution: the silent array decomposition semantics we allow for
4944 ADDR_EXPR means we can't always discard the pair. */
4945 /* Gimplification of the ADDR_EXPR operand may drop
4946 cv-qualification conversions, so make sure we add them if
4947 needed. */
4949 tree op00 = TREE_OPERAND (op0, 0);
4950 tree t_expr = TREE_TYPE (expr);
4951 tree t_op00 = TREE_TYPE (op00);
4953 if (!useless_type_conversion_p (t_expr, t_op00))
4954 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
4955 *expr_p = op00;
4956 ret = GS_OK;
4958 break;
4960 case VIEW_CONVERT_EXPR:
4961 /* Take the address of our operand and then convert it to the type of
4962 this ADDR_EXPR.
4964 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
4965 all clear. The impact of this transformation is even less clear. */
4967 /* If the operand is a useless conversion, look through it. Doing so
4968 guarantees that the ADDR_EXPR and its operand will remain of the
4969 same type. */
4970 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
4971 op0 = TREE_OPERAND (op0, 0);
4973 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
4974 build_fold_addr_expr_loc (loc,
4975 TREE_OPERAND (op0, 0)));
4976 ret = GS_OK;
4977 break;
4979 default:
4980 /* If we see a call to a declared builtin or see its address
4981 being taken (we can unify those cases here) then we can mark
4982 the builtin for implicit generation by GCC. */
4983 if (TREE_CODE (op0) == FUNCTION_DECL
4984 && DECL_BUILT_IN_CLASS (op0) == BUILT_IN_NORMAL
4985 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
4986 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
4988 /* We use fb_either here because the C frontend sometimes takes
4989 the address of a call that returns a struct; see
4990 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
4991 the implied temporary explicit. */
4993 /* Make the operand addressable. */
4994 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
4995 is_gimple_addressable, fb_either);
4996 if (ret == GS_ERROR)
4997 break;
4999 /* Then mark it. Beware that it may not be possible to do so directly
5000 if a temporary has been created by the gimplification. */
5001 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
5003 op0 = TREE_OPERAND (expr, 0);
5005 /* For various reasons, the gimplification of the expression
5006 may have made a new INDIRECT_REF. */
5007 if (TREE_CODE (op0) == INDIRECT_REF)
5008 goto do_indirect_ref;
5010 mark_addressable (TREE_OPERAND (expr, 0));
5012 /* The FEs may end up building ADDR_EXPRs early on a decl with
5013 an incomplete type. Re-build ADDR_EXPRs in canonical form
5014 here. */
5015 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
5016 *expr_p = build_fold_addr_expr (op0);
5018 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
5019 recompute_tree_invariant_for_addr_expr (*expr_p);
5021 /* If we re-built the ADDR_EXPR add a conversion to the original type
5022 if required. */
5023 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
5024 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
5026 break;
5029 return ret;
5032 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
5033 value; output operands should be a gimple lvalue. */
5035 static enum gimplify_status
5036 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5038 tree expr;
5039 int noutputs;
5040 const char **oconstraints;
5041 int i;
5042 tree link;
5043 const char *constraint;
5044 bool allows_mem, allows_reg, is_inout;
5045 enum gimplify_status ret, tret;
5046 gasm *stmt;
5047 vec<tree, va_gc> *inputs;
5048 vec<tree, va_gc> *outputs;
5049 vec<tree, va_gc> *clobbers;
5050 vec<tree, va_gc> *labels;
5051 tree link_next;
5053 expr = *expr_p;
5054 noutputs = list_length (ASM_OUTPUTS (expr));
5055 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
5057 inputs = NULL;
5058 outputs = NULL;
5059 clobbers = NULL;
5060 labels = NULL;
5062 ret = GS_ALL_DONE;
5063 link_next = NULL_TREE;
5064 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
5066 bool ok;
5067 size_t constraint_len;
5069 link_next = TREE_CHAIN (link);
5071 oconstraints[i]
5072 = constraint
5073 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
5074 constraint_len = strlen (constraint);
5075 if (constraint_len == 0)
5076 continue;
5078 ok = parse_output_constraint (&constraint, i, 0, 0,
5079 &allows_mem, &allows_reg, &is_inout);
5080 if (!ok)
5082 ret = GS_ERROR;
5083 is_inout = false;
5086 if (!allows_reg && allows_mem)
5087 mark_addressable (TREE_VALUE (link));
5089 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5090 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
5091 fb_lvalue | fb_mayfail);
5092 if (tret == GS_ERROR)
5094 error ("invalid lvalue in asm output %d", i);
5095 ret = tret;
5098 vec_safe_push (outputs, link);
5099 TREE_CHAIN (link) = NULL_TREE;
5101 if (is_inout)
5103 /* An input/output operand. To give the optimizers more
5104 flexibility, split it into separate input and output
5105 operands. */
5106 tree input;
5107 char buf[10];
5109 /* Turn the in/out constraint into an output constraint. */
5110 char *p = xstrdup (constraint);
5111 p[0] = '=';
5112 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
5114 /* And add a matching input constraint. */
5115 if (allows_reg)
5117 sprintf (buf, "%d", i);
5119 /* If there are multiple alternatives in the constraint,
5120 handle each of them individually. Those that allow register
5121 will be replaced with operand number, the others will stay
5122 unchanged. */
5123 if (strchr (p, ',') != NULL)
5125 size_t len = 0, buflen = strlen (buf);
5126 char *beg, *end, *str, *dst;
5128 for (beg = p + 1;;)
5130 end = strchr (beg, ',');
5131 if (end == NULL)
5132 end = strchr (beg, '\0');
5133 if ((size_t) (end - beg) < buflen)
5134 len += buflen + 1;
5135 else
5136 len += end - beg + 1;
5137 if (*end)
5138 beg = end + 1;
5139 else
5140 break;
5143 str = (char *) alloca (len);
5144 for (beg = p + 1, dst = str;;)
5146 const char *tem;
5147 bool mem_p, reg_p, inout_p;
5149 end = strchr (beg, ',');
5150 if (end)
5151 *end = '\0';
5152 beg[-1] = '=';
5153 tem = beg - 1;
5154 parse_output_constraint (&tem, i, 0, 0,
5155 &mem_p, &reg_p, &inout_p);
5156 if (dst != str)
5157 *dst++ = ',';
5158 if (reg_p)
5160 memcpy (dst, buf, buflen);
5161 dst += buflen;
5163 else
5165 if (end)
5166 len = end - beg;
5167 else
5168 len = strlen (beg);
5169 memcpy (dst, beg, len);
5170 dst += len;
5172 if (end)
5173 beg = end + 1;
5174 else
5175 break;
5177 *dst = '\0';
5178 input = build_string (dst - str, str);
5180 else
5181 input = build_string (strlen (buf), buf);
5183 else
5184 input = build_string (constraint_len - 1, constraint + 1);
5186 free (p);
5188 input = build_tree_list (build_tree_list (NULL_TREE, input),
5189 unshare_expr (TREE_VALUE (link)));
5190 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
5194 link_next = NULL_TREE;
5195 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
5197 link_next = TREE_CHAIN (link);
5198 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
5199 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
5200 oconstraints, &allows_mem, &allows_reg);
5202 /* If we can't make copies, we can only accept memory. */
5203 if (TREE_ADDRESSABLE (TREE_TYPE (TREE_VALUE (link))))
5205 if (allows_mem)
5206 allows_reg = 0;
5207 else
5209 error ("impossible constraint in %<asm%>");
5210 error ("non-memory input %d must stay in memory", i);
5211 return GS_ERROR;
5215 /* If the operand is a memory input, it should be an lvalue. */
5216 if (!allows_reg && allows_mem)
5218 tree inputv = TREE_VALUE (link);
5219 STRIP_NOPS (inputv);
5220 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
5221 || TREE_CODE (inputv) == PREINCREMENT_EXPR
5222 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
5223 || TREE_CODE (inputv) == POSTINCREMENT_EXPR)
5224 TREE_VALUE (link) = error_mark_node;
5225 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5226 is_gimple_lvalue, fb_lvalue | fb_mayfail);
5227 mark_addressable (TREE_VALUE (link));
5228 if (tret == GS_ERROR)
5230 if (EXPR_HAS_LOCATION (TREE_VALUE (link)))
5231 input_location = EXPR_LOCATION (TREE_VALUE (link));
5232 error ("memory input %d is not directly addressable", i);
5233 ret = tret;
5236 else
5238 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5239 is_gimple_asm_val, fb_rvalue);
5240 if (tret == GS_ERROR)
5241 ret = tret;
5244 TREE_CHAIN (link) = NULL_TREE;
5245 vec_safe_push (inputs, link);
5248 link_next = NULL_TREE;
5249 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
5251 link_next = TREE_CHAIN (link);
5252 TREE_CHAIN (link) = NULL_TREE;
5253 vec_safe_push (clobbers, link);
5256 link_next = NULL_TREE;
5257 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
5259 link_next = TREE_CHAIN (link);
5260 TREE_CHAIN (link) = NULL_TREE;
5261 vec_safe_push (labels, link);
5264 /* Do not add ASMs with errors to the gimple IL stream. */
5265 if (ret != GS_ERROR)
5267 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
5268 inputs, outputs, clobbers, labels);
5270 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
5271 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
5273 gimplify_seq_add_stmt (pre_p, stmt);
5276 return ret;
5279 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
5280 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
5281 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
5282 return to this function.
5284 FIXME should we complexify the prequeue handling instead? Or use flags
5285 for all the cleanups and let the optimizer tighten them up? The current
5286 code seems pretty fragile; it will break on a cleanup within any
5287 non-conditional nesting. But any such nesting would be broken, anyway;
5288 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
5289 and continues out of it. We can do that at the RTL level, though, so
5290 having an optimizer to tighten up try/finally regions would be a Good
5291 Thing. */
5293 static enum gimplify_status
5294 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
5296 gimple_stmt_iterator iter;
5297 gimple_seq body_sequence = NULL;
5299 tree temp = voidify_wrapper_expr (*expr_p, NULL);
5301 /* We only care about the number of conditions between the innermost
5302 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
5303 any cleanups collected outside the CLEANUP_POINT_EXPR. */
5304 int old_conds = gimplify_ctxp->conditions;
5305 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
5306 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
5307 gimplify_ctxp->conditions = 0;
5308 gimplify_ctxp->conditional_cleanups = NULL;
5309 gimplify_ctxp->in_cleanup_point_expr = true;
5311 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
5313 gimplify_ctxp->conditions = old_conds;
5314 gimplify_ctxp->conditional_cleanups = old_cleanups;
5315 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
5317 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
5319 gimple wce = gsi_stmt (iter);
5321 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
5323 if (gsi_one_before_end_p (iter))
5325 /* Note that gsi_insert_seq_before and gsi_remove do not
5326 scan operands, unlike some other sequence mutators. */
5327 if (!gimple_wce_cleanup_eh_only (wce))
5328 gsi_insert_seq_before_without_update (&iter,
5329 gimple_wce_cleanup (wce),
5330 GSI_SAME_STMT);
5331 gsi_remove (&iter, true);
5332 break;
5334 else
5336 gtry *gtry;
5337 gimple_seq seq;
5338 enum gimple_try_flags kind;
5340 if (gimple_wce_cleanup_eh_only (wce))
5341 kind = GIMPLE_TRY_CATCH;
5342 else
5343 kind = GIMPLE_TRY_FINALLY;
5344 seq = gsi_split_seq_after (iter);
5346 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
5347 /* Do not use gsi_replace here, as it may scan operands.
5348 We want to do a simple structural modification only. */
5349 gsi_set_stmt (&iter, gtry);
5350 iter = gsi_start (gtry->eval);
5353 else
5354 gsi_next (&iter);
5357 gimplify_seq_add_seq (pre_p, body_sequence);
5358 if (temp)
5360 *expr_p = temp;
5361 return GS_OK;
5363 else
5365 *expr_p = NULL;
5366 return GS_ALL_DONE;
5370 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
5371 is the cleanup action required. EH_ONLY is true if the cleanup should
5372 only be executed if an exception is thrown, not on normal exit. */
5374 static void
5375 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p)
5377 gimple wce;
5378 gimple_seq cleanup_stmts = NULL;
5380 /* Errors can result in improperly nested cleanups. Which results in
5381 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
5382 if (seen_error ())
5383 return;
5385 if (gimple_conditional_context ())
5387 /* If we're in a conditional context, this is more complex. We only
5388 want to run the cleanup if we actually ran the initialization that
5389 necessitates it, but we want to run it after the end of the
5390 conditional context. So we wrap the try/finally around the
5391 condition and use a flag to determine whether or not to actually
5392 run the destructor. Thus
5394 test ? f(A()) : 0
5396 becomes (approximately)
5398 flag = 0;
5399 try {
5400 if (test) { A::A(temp); flag = 1; val = f(temp); }
5401 else { val = 0; }
5402 } finally {
5403 if (flag) A::~A(temp);
5407 tree flag = create_tmp_var (boolean_type_node, "cleanup");
5408 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
5409 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
5411 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
5412 gimplify_stmt (&cleanup, &cleanup_stmts);
5413 wce = gimple_build_wce (cleanup_stmts);
5415 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
5416 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
5417 gimplify_seq_add_stmt (pre_p, ftrue);
5419 /* Because of this manipulation, and the EH edges that jump
5420 threading cannot redirect, the temporary (VAR) will appear
5421 to be used uninitialized. Don't warn. */
5422 TREE_NO_WARNING (var) = 1;
5424 else
5426 gimplify_stmt (&cleanup, &cleanup_stmts);
5427 wce = gimple_build_wce (cleanup_stmts);
5428 gimple_wce_set_cleanup_eh_only (wce, eh_only);
5429 gimplify_seq_add_stmt (pre_p, wce);
5433 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
5435 static enum gimplify_status
5436 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5438 tree targ = *expr_p;
5439 tree temp = TARGET_EXPR_SLOT (targ);
5440 tree init = TARGET_EXPR_INITIAL (targ);
5441 enum gimplify_status ret;
5443 if (init)
5445 tree cleanup = NULL_TREE;
5447 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
5448 to the temps list. Handle also variable length TARGET_EXPRs. */
5449 if (TREE_CODE (DECL_SIZE (temp)) != INTEGER_CST)
5451 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
5452 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
5453 gimplify_vla_decl (temp, pre_p);
5455 else
5456 gimple_add_tmp_var (temp);
5458 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
5459 expression is supposed to initialize the slot. */
5460 if (VOID_TYPE_P (TREE_TYPE (init)))
5461 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
5462 else
5464 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
5465 init = init_expr;
5466 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
5467 init = NULL;
5468 ggc_free (init_expr);
5470 if (ret == GS_ERROR)
5472 /* PR c++/28266 Make sure this is expanded only once. */
5473 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
5474 return GS_ERROR;
5476 if (init)
5477 gimplify_and_add (init, pre_p);
5479 /* If needed, push the cleanup for the temp. */
5480 if (TARGET_EXPR_CLEANUP (targ))
5482 if (CLEANUP_EH_ONLY (targ))
5483 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
5484 CLEANUP_EH_ONLY (targ), pre_p);
5485 else
5486 cleanup = TARGET_EXPR_CLEANUP (targ);
5489 /* Add a clobber for the temporary going out of scope, like
5490 gimplify_bind_expr. */
5491 if (gimplify_ctxp->in_cleanup_point_expr
5492 && needs_to_live_in_memory (temp)
5493 && flag_stack_reuse == SR_ALL)
5495 tree clobber = build_constructor (TREE_TYPE (temp),
5496 NULL);
5497 TREE_THIS_VOLATILE (clobber) = true;
5498 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
5499 if (cleanup)
5500 cleanup = build2 (COMPOUND_EXPR, void_type_node, cleanup,
5501 clobber);
5502 else
5503 cleanup = clobber;
5506 if (cleanup)
5507 gimple_push_cleanup (temp, cleanup, false, pre_p);
5509 /* Only expand this once. */
5510 TREE_OPERAND (targ, 3) = init;
5511 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
5513 else
5514 /* We should have expanded this before. */
5515 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
5517 *expr_p = temp;
5518 return GS_OK;
5521 /* Gimplification of expression trees. */
5523 /* Gimplify an expression which appears at statement context. The
5524 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
5525 NULL, a new sequence is allocated.
5527 Return true if we actually added a statement to the queue. */
5529 bool
5530 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
5532 gimple_seq_node last;
5534 last = gimple_seq_last (*seq_p);
5535 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
5536 return last != gimple_seq_last (*seq_p);
5539 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
5540 to CTX. If entries already exist, force them to be some flavor of private.
5541 If there is no enclosing parallel, do nothing. */
5543 void
5544 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
5546 splay_tree_node n;
5548 if (decl == NULL || !DECL_P (decl))
5549 return;
5553 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5554 if (n != NULL)
5556 if (n->value & GOVD_SHARED)
5557 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
5558 else if (n->value & GOVD_MAP)
5559 n->value |= GOVD_MAP_TO_ONLY;
5560 else
5561 return;
5563 else if (ctx->region_type == ORT_TARGET)
5564 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
5565 else if (ctx->region_type != ORT_WORKSHARE
5566 && ctx->region_type != ORT_SIMD
5567 && ctx->region_type != ORT_TARGET_DATA)
5568 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
5570 ctx = ctx->outer_context;
5572 while (ctx);
5575 /* Similarly for each of the type sizes of TYPE. */
5577 static void
5578 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
5580 if (type == NULL || type == error_mark_node)
5581 return;
5582 type = TYPE_MAIN_VARIANT (type);
5584 if (ctx->privatized_types->add (type))
5585 return;
5587 switch (TREE_CODE (type))
5589 case INTEGER_TYPE:
5590 case ENUMERAL_TYPE:
5591 case BOOLEAN_TYPE:
5592 case REAL_TYPE:
5593 case FIXED_POINT_TYPE:
5594 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
5595 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
5596 break;
5598 case ARRAY_TYPE:
5599 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
5600 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
5601 break;
5603 case RECORD_TYPE:
5604 case UNION_TYPE:
5605 case QUAL_UNION_TYPE:
5607 tree field;
5608 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
5609 if (TREE_CODE (field) == FIELD_DECL)
5611 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
5612 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
5615 break;
5617 case POINTER_TYPE:
5618 case REFERENCE_TYPE:
5619 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
5620 break;
5622 default:
5623 break;
5626 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
5627 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
5628 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
5631 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
5633 static void
5634 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
5636 splay_tree_node n;
5637 unsigned int nflags;
5638 tree t;
5640 if (error_operand_p (decl))
5641 return;
5643 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
5644 there are constructors involved somewhere. */
5645 if (TREE_ADDRESSABLE (TREE_TYPE (decl))
5646 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
5647 flags |= GOVD_SEEN;
5649 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5650 if (n != NULL && n->value != GOVD_ALIGNED)
5652 /* We shouldn't be re-adding the decl with the same data
5653 sharing class. */
5654 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
5655 /* The only combination of data sharing classes we should see is
5656 FIRSTPRIVATE and LASTPRIVATE. */
5657 nflags = n->value | flags;
5658 gcc_assert ((nflags & GOVD_DATA_SHARE_CLASS)
5659 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE)
5660 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
5661 n->value = nflags;
5662 return;
5665 /* When adding a variable-sized variable, we have to handle all sorts
5666 of additional bits of data: the pointer replacement variable, and
5667 the parameters of the type. */
5668 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
5670 /* Add the pointer replacement variable as PRIVATE if the variable
5671 replacement is private, else FIRSTPRIVATE since we'll need the
5672 address of the original variable either for SHARED, or for the
5673 copy into or out of the context. */
5674 if (!(flags & GOVD_LOCAL))
5676 if (flags & GOVD_MAP)
5677 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
5678 else if (flags & GOVD_PRIVATE)
5679 nflags = GOVD_PRIVATE;
5680 else
5681 nflags = GOVD_FIRSTPRIVATE;
5682 nflags |= flags & GOVD_SEEN;
5683 t = DECL_VALUE_EXPR (decl);
5684 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
5685 t = TREE_OPERAND (t, 0);
5686 gcc_assert (DECL_P (t));
5687 omp_add_variable (ctx, t, nflags);
5690 /* Add all of the variable and type parameters (which should have
5691 been gimplified to a formal temporary) as FIRSTPRIVATE. */
5692 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
5693 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
5694 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
5696 /* The variable-sized variable itself is never SHARED, only some form
5697 of PRIVATE. The sharing would take place via the pointer variable
5698 which we remapped above. */
5699 if (flags & GOVD_SHARED)
5700 flags = GOVD_PRIVATE | GOVD_DEBUG_PRIVATE
5701 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
5703 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
5704 alloca statement we generate for the variable, so make sure it
5705 is available. This isn't automatically needed for the SHARED
5706 case, since we won't be allocating local storage then.
5707 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
5708 in this case omp_notice_variable will be called later
5709 on when it is gimplified. */
5710 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
5711 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
5712 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
5714 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
5715 && lang_hooks.decls.omp_privatize_by_reference (decl))
5717 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
5719 /* Similar to the direct variable sized case above, we'll need the
5720 size of references being privatized. */
5721 if ((flags & GOVD_SHARED) == 0)
5723 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
5724 if (TREE_CODE (t) != INTEGER_CST)
5725 omp_notice_variable (ctx, t, true);
5729 if (n != NULL)
5730 n->value |= flags;
5731 else
5732 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
5735 /* Notice a threadprivate variable DECL used in OMP context CTX.
5736 This just prints out diagnostics about threadprivate variable uses
5737 in untied tasks. If DECL2 is non-NULL, prevent this warning
5738 on that variable. */
5740 static bool
5741 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
5742 tree decl2)
5744 splay_tree_node n;
5745 struct gimplify_omp_ctx *octx;
5747 for (octx = ctx; octx; octx = octx->outer_context)
5748 if (octx->region_type == ORT_TARGET)
5750 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
5751 if (n == NULL)
5753 error ("threadprivate variable %qE used in target region",
5754 DECL_NAME (decl));
5755 error_at (octx->location, "enclosing target region");
5756 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
5758 if (decl2)
5759 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
5762 if (ctx->region_type != ORT_UNTIED_TASK)
5763 return false;
5764 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5765 if (n == NULL)
5767 error ("threadprivate variable %qE used in untied task",
5768 DECL_NAME (decl));
5769 error_at (ctx->location, "enclosing task");
5770 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
5772 if (decl2)
5773 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
5774 return false;
5777 /* Record the fact that DECL was used within the OMP context CTX.
5778 IN_CODE is true when real code uses DECL, and false when we should
5779 merely emit default(none) errors. Return true if DECL is going to
5780 be remapped and thus DECL shouldn't be gimplified into its
5781 DECL_VALUE_EXPR (if any). */
5783 static bool
5784 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
5786 splay_tree_node n;
5787 unsigned flags = in_code ? GOVD_SEEN : 0;
5788 bool ret = false, shared;
5790 if (error_operand_p (decl))
5791 return false;
5793 /* Threadprivate variables are predetermined. */
5794 if (is_global_var (decl))
5796 if (DECL_THREAD_LOCAL_P (decl))
5797 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
5799 if (DECL_HAS_VALUE_EXPR_P (decl))
5801 tree value = get_base_address (DECL_VALUE_EXPR (decl));
5803 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
5804 return omp_notice_threadprivate_variable (ctx, decl, value);
5808 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5809 if (ctx->region_type == ORT_TARGET)
5811 ret = lang_hooks.decls.omp_disregard_value_expr (decl, true);
5812 if (n == NULL)
5814 if (!lang_hooks.types.omp_mappable_type (TREE_TYPE (decl)))
5816 error ("%qD referenced in target region does not have "
5817 "a mappable type", decl);
5818 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_EXPLICIT | flags);
5820 else
5821 omp_add_variable (ctx, decl, GOVD_MAP | flags);
5823 else
5825 /* If nothing changed, there's nothing left to do. */
5826 if ((n->value & flags) == flags)
5827 return ret;
5828 n->value |= flags;
5830 goto do_outer;
5833 if (n == NULL)
5835 enum omp_clause_default_kind default_kind, kind;
5836 struct gimplify_omp_ctx *octx;
5838 if (ctx->region_type == ORT_WORKSHARE
5839 || ctx->region_type == ORT_SIMD
5840 || ctx->region_type == ORT_TARGET_DATA)
5841 goto do_outer;
5843 /* ??? Some compiler-generated variables (like SAVE_EXPRs) could be
5844 remapped firstprivate instead of shared. To some extent this is
5845 addressed in omp_firstprivatize_type_sizes, but not effectively. */
5846 default_kind = ctx->default_kind;
5847 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
5848 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
5849 default_kind = kind;
5851 switch (default_kind)
5853 case OMP_CLAUSE_DEFAULT_NONE:
5854 if ((ctx->region_type & ORT_PARALLEL) != 0)
5856 error ("%qE not specified in enclosing parallel",
5857 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5858 error_at (ctx->location, "enclosing parallel");
5860 else if ((ctx->region_type & ORT_TASK) != 0)
5862 error ("%qE not specified in enclosing task",
5863 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5864 error_at (ctx->location, "enclosing task");
5866 else if (ctx->region_type & ORT_TEAMS)
5868 error ("%qE not specified in enclosing teams construct",
5869 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5870 error_at (ctx->location, "enclosing teams construct");
5872 else
5873 gcc_unreachable ();
5874 /* FALLTHRU */
5875 case OMP_CLAUSE_DEFAULT_SHARED:
5876 flags |= GOVD_SHARED;
5877 break;
5878 case OMP_CLAUSE_DEFAULT_PRIVATE:
5879 flags |= GOVD_PRIVATE;
5880 break;
5881 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
5882 flags |= GOVD_FIRSTPRIVATE;
5883 break;
5884 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
5885 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
5886 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
5887 if (ctx->outer_context)
5888 omp_notice_variable (ctx->outer_context, decl, in_code);
5889 for (octx = ctx->outer_context; octx; octx = octx->outer_context)
5891 splay_tree_node n2;
5893 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0)
5894 continue;
5895 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
5896 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
5898 flags |= GOVD_FIRSTPRIVATE;
5899 break;
5901 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
5902 break;
5904 if (flags & GOVD_FIRSTPRIVATE)
5905 break;
5906 if (octx == NULL
5907 && (TREE_CODE (decl) == PARM_DECL
5908 || (!is_global_var (decl)
5909 && DECL_CONTEXT (decl) == current_function_decl)))
5911 flags |= GOVD_FIRSTPRIVATE;
5912 break;
5914 flags |= GOVD_SHARED;
5915 break;
5916 default:
5917 gcc_unreachable ();
5920 if ((flags & GOVD_PRIVATE)
5921 && lang_hooks.decls.omp_private_outer_ref (decl))
5922 flags |= GOVD_PRIVATE_OUTER_REF;
5924 omp_add_variable (ctx, decl, flags);
5926 shared = (flags & GOVD_SHARED) != 0;
5927 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
5928 goto do_outer;
5931 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
5932 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
5933 && DECL_SIZE (decl)
5934 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
5936 splay_tree_node n2;
5937 tree t = DECL_VALUE_EXPR (decl);
5938 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
5939 t = TREE_OPERAND (t, 0);
5940 gcc_assert (DECL_P (t));
5941 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
5942 n2->value |= GOVD_SEEN;
5945 shared = ((flags | n->value) & GOVD_SHARED) != 0;
5946 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
5948 /* If nothing changed, there's nothing left to do. */
5949 if ((n->value & flags) == flags)
5950 return ret;
5951 flags |= n->value;
5952 n->value = flags;
5954 do_outer:
5955 /* If the variable is private in the current context, then we don't
5956 need to propagate anything to an outer context. */
5957 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
5958 return ret;
5959 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
5960 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
5961 return ret;
5962 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
5963 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
5964 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
5965 return ret;
5966 if (ctx->outer_context
5967 && omp_notice_variable (ctx->outer_context, decl, in_code))
5968 return true;
5969 return ret;
5972 /* Verify that DECL is private within CTX. If there's specific information
5973 to the contrary in the innermost scope, generate an error. */
5975 static bool
5976 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
5978 splay_tree_node n;
5980 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5981 if (n != NULL)
5983 if (n->value & GOVD_SHARED)
5985 if (ctx == gimplify_omp_ctxp)
5987 if (simd)
5988 error ("iteration variable %qE is predetermined linear",
5989 DECL_NAME (decl));
5990 else
5991 error ("iteration variable %qE should be private",
5992 DECL_NAME (decl));
5993 n->value = GOVD_PRIVATE;
5994 return true;
5996 else
5997 return false;
5999 else if ((n->value & GOVD_EXPLICIT) != 0
6000 && (ctx == gimplify_omp_ctxp
6001 || (ctx->region_type == ORT_COMBINED_PARALLEL
6002 && gimplify_omp_ctxp->outer_context == ctx)))
6004 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
6005 error ("iteration variable %qE should not be firstprivate",
6006 DECL_NAME (decl));
6007 else if ((n->value & GOVD_REDUCTION) != 0)
6008 error ("iteration variable %qE should not be reduction",
6009 DECL_NAME (decl));
6010 else if (simd == 1 && (n->value & GOVD_LASTPRIVATE) != 0)
6011 error ("iteration variable %qE should not be lastprivate",
6012 DECL_NAME (decl));
6013 else if (simd && (n->value & GOVD_PRIVATE) != 0)
6014 error ("iteration variable %qE should not be private",
6015 DECL_NAME (decl));
6016 else if (simd == 2 && (n->value & GOVD_LINEAR) != 0)
6017 error ("iteration variable %qE is predetermined linear",
6018 DECL_NAME (decl));
6020 return (ctx == gimplify_omp_ctxp
6021 || (ctx->region_type == ORT_COMBINED_PARALLEL
6022 && gimplify_omp_ctxp->outer_context == ctx));
6025 if (ctx->region_type != ORT_WORKSHARE
6026 && ctx->region_type != ORT_SIMD)
6027 return false;
6028 else if (ctx->outer_context)
6029 return omp_is_private (ctx->outer_context, decl, simd);
6030 return false;
6033 /* Return true if DECL is private within a parallel region
6034 that binds to the current construct's context or in parallel
6035 region's REDUCTION clause. */
6037 static bool
6038 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
6040 splay_tree_node n;
6044 ctx = ctx->outer_context;
6045 if (ctx == NULL)
6046 return !(is_global_var (decl)
6047 /* References might be private, but might be shared too,
6048 when checking for copyprivate, assume they might be
6049 private, otherwise assume they might be shared. */
6050 || (!copyprivate
6051 && lang_hooks.decls.omp_privatize_by_reference (decl)));
6053 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0)
6054 continue;
6056 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6057 if (n != NULL)
6058 return (n->value & GOVD_SHARED) == 0;
6060 while (ctx->region_type == ORT_WORKSHARE
6061 || ctx->region_type == ORT_SIMD);
6062 return false;
6065 /* Return true if the CTX is combined with distribute and thus
6066 lastprivate can't be supported. */
6068 static bool
6069 omp_no_lastprivate (struct gimplify_omp_ctx *ctx)
6073 if (ctx->outer_context == NULL)
6074 return false;
6075 ctx = ctx->outer_context;
6076 switch (ctx->region_type)
6078 case ORT_WORKSHARE:
6079 if (!ctx->combined_loop)
6080 return false;
6081 if (ctx->distribute)
6082 return true;
6083 break;
6084 case ORT_COMBINED_PARALLEL:
6085 break;
6086 case ORT_COMBINED_TEAMS:
6087 return true;
6088 default:
6089 return false;
6092 while (1);
6095 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
6096 and previous omp contexts. */
6098 static void
6099 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
6100 enum omp_region_type region_type)
6102 struct gimplify_omp_ctx *ctx, *outer_ctx;
6103 tree c;
6105 ctx = new_omp_context (region_type);
6106 outer_ctx = ctx->outer_context;
6108 while ((c = *list_p) != NULL)
6110 bool remove = false;
6111 bool notice_outer = true;
6112 const char *check_non_private = NULL;
6113 unsigned int flags;
6114 tree decl;
6116 switch (OMP_CLAUSE_CODE (c))
6118 case OMP_CLAUSE_PRIVATE:
6119 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
6120 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
6122 flags |= GOVD_PRIVATE_OUTER_REF;
6123 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
6125 else
6126 notice_outer = false;
6127 goto do_add;
6128 case OMP_CLAUSE_SHARED:
6129 flags = GOVD_SHARED | GOVD_EXPLICIT;
6130 goto do_add;
6131 case OMP_CLAUSE_FIRSTPRIVATE:
6132 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
6133 check_non_private = "firstprivate";
6134 goto do_add;
6135 case OMP_CLAUSE_LASTPRIVATE:
6136 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
6137 check_non_private = "lastprivate";
6138 decl = OMP_CLAUSE_DECL (c);
6139 if (omp_no_lastprivate (ctx))
6141 notice_outer = false;
6142 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
6144 else if (error_operand_p (decl))
6145 goto do_add;
6146 else if (outer_ctx
6147 && outer_ctx->region_type == ORT_COMBINED_PARALLEL
6148 && splay_tree_lookup (outer_ctx->variables,
6149 (splay_tree_key) decl) == NULL)
6150 omp_add_variable (outer_ctx, decl, GOVD_SHARED | GOVD_SEEN);
6151 else if (outer_ctx
6152 && outer_ctx->region_type == ORT_WORKSHARE
6153 && outer_ctx->combined_loop
6154 && splay_tree_lookup (outer_ctx->variables,
6155 (splay_tree_key) decl) == NULL
6156 && !omp_check_private (outer_ctx, decl, false))
6158 omp_add_variable (outer_ctx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
6159 if (outer_ctx->outer_context
6160 && (outer_ctx->outer_context->region_type
6161 == ORT_COMBINED_PARALLEL)
6162 && splay_tree_lookup (outer_ctx->outer_context->variables,
6163 (splay_tree_key) decl) == NULL)
6164 omp_add_variable (outer_ctx->outer_context, decl,
6165 GOVD_SHARED | GOVD_SEEN);
6167 goto do_add;
6168 case OMP_CLAUSE_REDUCTION:
6169 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
6170 check_non_private = "reduction";
6171 goto do_add;
6172 case OMP_CLAUSE_LINEAR:
6173 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
6174 is_gimple_val, fb_rvalue) == GS_ERROR)
6176 remove = true;
6177 break;
6179 else
6181 /* For combined #pragma omp parallel for simd, need to put
6182 lastprivate and perhaps firstprivate too on the
6183 parallel. Similarly for #pragma omp for simd. */
6184 struct gimplify_omp_ctx *octx = outer_ctx;
6185 decl = NULL_TREE;
6186 if (omp_no_lastprivate (ctx))
6187 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
6190 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
6191 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
6192 break;
6193 decl = OMP_CLAUSE_DECL (c);
6194 if (error_operand_p (decl))
6196 decl = NULL_TREE;
6197 break;
6199 if (octx
6200 && octx->region_type == ORT_WORKSHARE
6201 && octx->combined_loop)
6203 if (octx->outer_context
6204 && (octx->outer_context->region_type
6205 == ORT_COMBINED_PARALLEL
6206 || (octx->outer_context->region_type
6207 == ORT_COMBINED_TEAMS)))
6208 octx = octx->outer_context;
6209 else if (omp_check_private (octx, decl, false))
6210 break;
6212 else
6213 break;
6214 gcc_checking_assert (splay_tree_lookup (octx->variables,
6215 (splay_tree_key)
6216 decl) == NULL);
6217 flags = GOVD_SEEN;
6218 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
6219 flags |= GOVD_FIRSTPRIVATE;
6220 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
6221 flags |= GOVD_LASTPRIVATE;
6222 omp_add_variable (octx, decl, flags);
6223 if (octx->outer_context == NULL)
6224 break;
6225 octx = octx->outer_context;
6227 while (1);
6228 if (octx
6229 && decl
6230 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
6231 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
6232 omp_notice_variable (octx, decl, true);
6234 flags = GOVD_LINEAR | GOVD_EXPLICIT;
6235 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
6236 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
6238 notice_outer = false;
6239 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
6241 goto do_add;
6243 case OMP_CLAUSE_MAP:
6244 decl = OMP_CLAUSE_DECL (c);
6245 if (error_operand_p (decl))
6247 remove = true;
6248 break;
6250 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6251 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
6252 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
6253 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
6254 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
6256 remove = true;
6257 break;
6259 if (!DECL_P (decl))
6261 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
6262 NULL, is_gimple_lvalue, fb_lvalue)
6263 == GS_ERROR)
6265 remove = true;
6266 break;
6268 break;
6270 flags = GOVD_MAP | GOVD_EXPLICIT;
6271 goto do_add;
6273 case OMP_CLAUSE_DEPEND:
6274 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
6276 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
6277 NULL, is_gimple_val, fb_rvalue);
6278 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
6280 if (error_operand_p (OMP_CLAUSE_DECL (c)))
6282 remove = true;
6283 break;
6285 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
6286 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
6287 is_gimple_val, fb_rvalue) == GS_ERROR)
6289 remove = true;
6290 break;
6292 break;
6294 case OMP_CLAUSE_TO:
6295 case OMP_CLAUSE_FROM:
6296 case OMP_CLAUSE__CACHE_:
6297 decl = OMP_CLAUSE_DECL (c);
6298 if (error_operand_p (decl))
6300 remove = true;
6301 break;
6303 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6304 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
6305 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
6306 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
6307 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
6309 remove = true;
6310 break;
6312 if (!DECL_P (decl))
6314 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
6315 NULL, is_gimple_lvalue, fb_lvalue)
6316 == GS_ERROR)
6318 remove = true;
6319 break;
6321 break;
6323 goto do_notice;
6325 do_add:
6326 decl = OMP_CLAUSE_DECL (c);
6327 if (error_operand_p (decl))
6329 remove = true;
6330 break;
6332 omp_add_variable (ctx, decl, flags);
6333 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
6334 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
6336 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
6337 GOVD_LOCAL | GOVD_SEEN);
6338 gimplify_omp_ctxp = ctx;
6339 push_gimplify_context ();
6341 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
6342 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
6344 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
6345 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
6346 pop_gimplify_context
6347 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
6348 push_gimplify_context ();
6349 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
6350 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
6351 pop_gimplify_context
6352 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
6353 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
6354 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
6356 gimplify_omp_ctxp = outer_ctx;
6358 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
6359 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
6361 gimplify_omp_ctxp = ctx;
6362 push_gimplify_context ();
6363 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
6365 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
6366 NULL, NULL);
6367 TREE_SIDE_EFFECTS (bind) = 1;
6368 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
6369 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
6371 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
6372 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
6373 pop_gimplify_context
6374 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
6375 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
6377 gimplify_omp_ctxp = outer_ctx;
6379 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
6380 && OMP_CLAUSE_LINEAR_STMT (c))
6382 gimplify_omp_ctxp = ctx;
6383 push_gimplify_context ();
6384 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
6386 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
6387 NULL, NULL);
6388 TREE_SIDE_EFFECTS (bind) = 1;
6389 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
6390 OMP_CLAUSE_LINEAR_STMT (c) = bind;
6392 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
6393 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
6394 pop_gimplify_context
6395 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
6396 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
6398 gimplify_omp_ctxp = outer_ctx;
6400 if (notice_outer)
6401 goto do_notice;
6402 break;
6404 case OMP_CLAUSE_COPYIN:
6405 case OMP_CLAUSE_COPYPRIVATE:
6406 decl = OMP_CLAUSE_DECL (c);
6407 if (error_operand_p (decl))
6409 remove = true;
6410 break;
6412 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
6413 && !remove
6414 && !omp_check_private (ctx, decl, true))
6416 remove = true;
6417 if (is_global_var (decl))
6419 if (DECL_THREAD_LOCAL_P (decl))
6420 remove = false;
6421 else if (DECL_HAS_VALUE_EXPR_P (decl))
6423 tree value = get_base_address (DECL_VALUE_EXPR (decl));
6425 if (value
6426 && DECL_P (value)
6427 && DECL_THREAD_LOCAL_P (value))
6428 remove = false;
6431 if (remove)
6432 error_at (OMP_CLAUSE_LOCATION (c),
6433 "copyprivate variable %qE is not threadprivate"
6434 " or private in outer context", DECL_NAME (decl));
6436 do_notice:
6437 if (outer_ctx)
6438 omp_notice_variable (outer_ctx, decl, true);
6439 if (check_non_private
6440 && region_type == ORT_WORKSHARE
6441 && omp_check_private (ctx, decl, false))
6443 error ("%s variable %qE is private in outer context",
6444 check_non_private, DECL_NAME (decl));
6445 remove = true;
6447 break;
6449 case OMP_CLAUSE_FINAL:
6450 case OMP_CLAUSE_IF:
6451 OMP_CLAUSE_OPERAND (c, 0)
6452 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
6453 /* Fall through. */
6455 case OMP_CLAUSE_SCHEDULE:
6456 case OMP_CLAUSE_NUM_THREADS:
6457 case OMP_CLAUSE_NUM_TEAMS:
6458 case OMP_CLAUSE_THREAD_LIMIT:
6459 case OMP_CLAUSE_DIST_SCHEDULE:
6460 case OMP_CLAUSE_DEVICE:
6461 case OMP_CLAUSE__CILK_FOR_COUNT_:
6462 case OMP_CLAUSE_ASYNC:
6463 case OMP_CLAUSE_WAIT:
6464 case OMP_CLAUSE_NUM_GANGS:
6465 case OMP_CLAUSE_NUM_WORKERS:
6466 case OMP_CLAUSE_VECTOR_LENGTH:
6467 case OMP_CLAUSE_GANG:
6468 case OMP_CLAUSE_WORKER:
6469 case OMP_CLAUSE_VECTOR:
6470 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
6471 is_gimple_val, fb_rvalue) == GS_ERROR)
6472 remove = true;
6473 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_GANG
6474 && gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
6475 is_gimple_val, fb_rvalue) == GS_ERROR)
6476 remove = true;
6477 break;
6479 case OMP_CLAUSE_DEVICE_RESIDENT:
6480 case OMP_CLAUSE_USE_DEVICE:
6481 case OMP_CLAUSE_INDEPENDENT:
6482 remove = true;
6483 break;
6485 case OMP_CLAUSE_NOWAIT:
6486 case OMP_CLAUSE_ORDERED:
6487 case OMP_CLAUSE_UNTIED:
6488 case OMP_CLAUSE_COLLAPSE:
6489 case OMP_CLAUSE_AUTO:
6490 case OMP_CLAUSE_SEQ:
6491 case OMP_CLAUSE_MERGEABLE:
6492 case OMP_CLAUSE_PROC_BIND:
6493 case OMP_CLAUSE_SAFELEN:
6494 break;
6496 case OMP_CLAUSE_ALIGNED:
6497 decl = OMP_CLAUSE_DECL (c);
6498 if (error_operand_p (decl))
6500 remove = true;
6501 break;
6503 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
6504 is_gimple_val, fb_rvalue) == GS_ERROR)
6506 remove = true;
6507 break;
6509 if (!is_global_var (decl)
6510 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
6511 omp_add_variable (ctx, decl, GOVD_ALIGNED);
6512 break;
6514 case OMP_CLAUSE_DEFAULT:
6515 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
6516 break;
6518 default:
6519 gcc_unreachable ();
6522 if (remove)
6523 *list_p = OMP_CLAUSE_CHAIN (c);
6524 else
6525 list_p = &OMP_CLAUSE_CHAIN (c);
6528 gimplify_omp_ctxp = ctx;
6531 struct gimplify_adjust_omp_clauses_data
6533 tree *list_p;
6534 gimple_seq *pre_p;
6537 /* For all variables that were not actually used within the context,
6538 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
6540 static int
6541 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
6543 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
6544 gimple_seq *pre_p
6545 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
6546 tree decl = (tree) n->key;
6547 unsigned flags = n->value;
6548 enum omp_clause_code code;
6549 tree clause;
6550 bool private_debug;
6552 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
6553 return 0;
6554 if ((flags & GOVD_SEEN) == 0)
6555 return 0;
6556 if (flags & GOVD_DEBUG_PRIVATE)
6558 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_PRIVATE);
6559 private_debug = true;
6561 else if (flags & GOVD_MAP)
6562 private_debug = false;
6563 else
6564 private_debug
6565 = lang_hooks.decls.omp_private_debug_clause (decl,
6566 !!(flags & GOVD_SHARED));
6567 if (private_debug)
6568 code = OMP_CLAUSE_PRIVATE;
6569 else if (flags & GOVD_MAP)
6570 code = OMP_CLAUSE_MAP;
6571 else if (flags & GOVD_SHARED)
6573 if (is_global_var (decl))
6575 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
6576 while (ctx != NULL)
6578 splay_tree_node on
6579 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6580 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
6581 | GOVD_PRIVATE | GOVD_REDUCTION
6582 | GOVD_LINEAR | GOVD_MAP)) != 0)
6583 break;
6584 ctx = ctx->outer_context;
6586 if (ctx == NULL)
6587 return 0;
6589 code = OMP_CLAUSE_SHARED;
6591 else if (flags & GOVD_PRIVATE)
6592 code = OMP_CLAUSE_PRIVATE;
6593 else if (flags & GOVD_FIRSTPRIVATE)
6594 code = OMP_CLAUSE_FIRSTPRIVATE;
6595 else if (flags & GOVD_LASTPRIVATE)
6596 code = OMP_CLAUSE_LASTPRIVATE;
6597 else if (flags & GOVD_ALIGNED)
6598 return 0;
6599 else
6600 gcc_unreachable ();
6602 clause = build_omp_clause (input_location, code);
6603 OMP_CLAUSE_DECL (clause) = decl;
6604 OMP_CLAUSE_CHAIN (clause) = *list_p;
6605 if (private_debug)
6606 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
6607 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
6608 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
6609 else if (code == OMP_CLAUSE_MAP)
6611 OMP_CLAUSE_SET_MAP_KIND (clause,
6612 flags & GOVD_MAP_TO_ONLY
6613 ? GOMP_MAP_TO
6614 : GOMP_MAP_TOFROM);
6615 if (DECL_SIZE (decl)
6616 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
6618 tree decl2 = DECL_VALUE_EXPR (decl);
6619 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6620 decl2 = TREE_OPERAND (decl2, 0);
6621 gcc_assert (DECL_P (decl2));
6622 tree mem = build_simple_mem_ref (decl2);
6623 OMP_CLAUSE_DECL (clause) = mem;
6624 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6625 if (gimplify_omp_ctxp->outer_context)
6627 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
6628 omp_notice_variable (ctx, decl2, true);
6629 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
6631 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
6632 OMP_CLAUSE_MAP);
6633 OMP_CLAUSE_DECL (nc) = decl;
6634 OMP_CLAUSE_SIZE (nc) = size_zero_node;
6635 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
6636 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
6637 OMP_CLAUSE_CHAIN (clause) = nc;
6639 else
6640 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
6642 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
6644 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
6645 OMP_CLAUSE_DECL (nc) = decl;
6646 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
6647 OMP_CLAUSE_CHAIN (nc) = *list_p;
6648 OMP_CLAUSE_CHAIN (clause) = nc;
6649 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6650 gimplify_omp_ctxp = ctx->outer_context;
6651 lang_hooks.decls.omp_finish_clause (nc, pre_p);
6652 gimplify_omp_ctxp = ctx;
6654 *list_p = clause;
6655 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6656 gimplify_omp_ctxp = ctx->outer_context;
6657 lang_hooks.decls.omp_finish_clause (clause, pre_p);
6658 gimplify_omp_ctxp = ctx;
6659 return 0;
6662 static void
6663 gimplify_adjust_omp_clauses (gimple_seq *pre_p, tree *list_p)
6665 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6666 tree c, decl;
6668 while ((c = *list_p) != NULL)
6670 splay_tree_node n;
6671 bool remove = false;
6673 switch (OMP_CLAUSE_CODE (c))
6675 case OMP_CLAUSE_PRIVATE:
6676 case OMP_CLAUSE_SHARED:
6677 case OMP_CLAUSE_FIRSTPRIVATE:
6678 case OMP_CLAUSE_LINEAR:
6679 decl = OMP_CLAUSE_DECL (c);
6680 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6681 remove = !(n->value & GOVD_SEEN);
6682 if (! remove)
6684 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
6685 if ((n->value & GOVD_DEBUG_PRIVATE)
6686 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
6688 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
6689 || ((n->value & GOVD_DATA_SHARE_CLASS)
6690 == GOVD_PRIVATE));
6691 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
6692 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
6695 break;
6697 case OMP_CLAUSE_LASTPRIVATE:
6698 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
6699 accurately reflect the presence of a FIRSTPRIVATE clause. */
6700 decl = OMP_CLAUSE_DECL (c);
6701 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6702 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
6703 = (n->value & GOVD_FIRSTPRIVATE) != 0;
6704 if (omp_no_lastprivate (ctx))
6706 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
6707 remove = true;
6708 else
6709 OMP_CLAUSE_CODE (c) = OMP_CLAUSE_PRIVATE;
6711 break;
6713 case OMP_CLAUSE_ALIGNED:
6714 decl = OMP_CLAUSE_DECL (c);
6715 if (!is_global_var (decl))
6717 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6718 remove = n == NULL || !(n->value & GOVD_SEEN);
6719 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
6721 struct gimplify_omp_ctx *octx;
6722 if (n != NULL
6723 && (n->value & (GOVD_DATA_SHARE_CLASS
6724 & ~GOVD_FIRSTPRIVATE)))
6725 remove = true;
6726 else
6727 for (octx = ctx->outer_context; octx;
6728 octx = octx->outer_context)
6730 n = splay_tree_lookup (octx->variables,
6731 (splay_tree_key) decl);
6732 if (n == NULL)
6733 continue;
6734 if (n->value & GOVD_LOCAL)
6735 break;
6736 /* We have to avoid assigning a shared variable
6737 to itself when trying to add
6738 __builtin_assume_aligned. */
6739 if (n->value & GOVD_SHARED)
6741 remove = true;
6742 break;
6747 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
6749 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6750 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
6751 remove = true;
6753 break;
6755 case OMP_CLAUSE_MAP:
6756 decl = OMP_CLAUSE_DECL (c);
6757 if (!DECL_P (decl))
6758 break;
6759 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6760 if (ctx->region_type == ORT_TARGET && !(n->value & GOVD_SEEN))
6761 remove = true;
6762 else if (DECL_SIZE (decl)
6763 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
6764 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER)
6766 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
6767 for these, TREE_CODE (DECL_SIZE (decl)) will always be
6768 INTEGER_CST. */
6769 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
6771 tree decl2 = DECL_VALUE_EXPR (decl);
6772 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6773 decl2 = TREE_OPERAND (decl2, 0);
6774 gcc_assert (DECL_P (decl2));
6775 tree mem = build_simple_mem_ref (decl2);
6776 OMP_CLAUSE_DECL (c) = mem;
6777 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6778 if (ctx->outer_context)
6780 omp_notice_variable (ctx->outer_context, decl2, true);
6781 omp_notice_variable (ctx->outer_context,
6782 OMP_CLAUSE_SIZE (c), true);
6784 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
6785 OMP_CLAUSE_MAP);
6786 OMP_CLAUSE_DECL (nc) = decl;
6787 OMP_CLAUSE_SIZE (nc) = size_zero_node;
6788 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
6789 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
6790 OMP_CLAUSE_CHAIN (c) = nc;
6791 c = nc;
6793 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6794 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
6795 break;
6797 case OMP_CLAUSE_TO:
6798 case OMP_CLAUSE_FROM:
6799 case OMP_CLAUSE__CACHE_:
6800 decl = OMP_CLAUSE_DECL (c);
6801 if (!DECL_P (decl))
6802 break;
6803 if (DECL_SIZE (decl)
6804 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
6806 tree decl2 = DECL_VALUE_EXPR (decl);
6807 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6808 decl2 = TREE_OPERAND (decl2, 0);
6809 gcc_assert (DECL_P (decl2));
6810 tree mem = build_simple_mem_ref (decl2);
6811 OMP_CLAUSE_DECL (c) = mem;
6812 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6813 if (ctx->outer_context)
6815 omp_notice_variable (ctx->outer_context, decl2, true);
6816 omp_notice_variable (ctx->outer_context,
6817 OMP_CLAUSE_SIZE (c), true);
6820 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6821 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
6822 break;
6824 case OMP_CLAUSE_REDUCTION:
6825 case OMP_CLAUSE_COPYIN:
6826 case OMP_CLAUSE_COPYPRIVATE:
6827 case OMP_CLAUSE_IF:
6828 case OMP_CLAUSE_NUM_THREADS:
6829 case OMP_CLAUSE_NUM_TEAMS:
6830 case OMP_CLAUSE_THREAD_LIMIT:
6831 case OMP_CLAUSE_DIST_SCHEDULE:
6832 case OMP_CLAUSE_DEVICE:
6833 case OMP_CLAUSE_SCHEDULE:
6834 case OMP_CLAUSE_NOWAIT:
6835 case OMP_CLAUSE_ORDERED:
6836 case OMP_CLAUSE_DEFAULT:
6837 case OMP_CLAUSE_UNTIED:
6838 case OMP_CLAUSE_COLLAPSE:
6839 case OMP_CLAUSE_FINAL:
6840 case OMP_CLAUSE_MERGEABLE:
6841 case OMP_CLAUSE_PROC_BIND:
6842 case OMP_CLAUSE_SAFELEN:
6843 case OMP_CLAUSE_DEPEND:
6844 case OMP_CLAUSE__CILK_FOR_COUNT_:
6845 case OMP_CLAUSE_ASYNC:
6846 case OMP_CLAUSE_WAIT:
6847 case OMP_CLAUSE_DEVICE_RESIDENT:
6848 case OMP_CLAUSE_USE_DEVICE:
6849 case OMP_CLAUSE_INDEPENDENT:
6850 case OMP_CLAUSE_NUM_GANGS:
6851 case OMP_CLAUSE_NUM_WORKERS:
6852 case OMP_CLAUSE_VECTOR_LENGTH:
6853 case OMP_CLAUSE_GANG:
6854 case OMP_CLAUSE_WORKER:
6855 case OMP_CLAUSE_VECTOR:
6856 case OMP_CLAUSE_AUTO:
6857 case OMP_CLAUSE_SEQ:
6858 break;
6860 default:
6861 gcc_unreachable ();
6864 if (remove)
6865 *list_p = OMP_CLAUSE_CHAIN (c);
6866 else
6867 list_p = &OMP_CLAUSE_CHAIN (c);
6870 /* Add in any implicit data sharing. */
6871 struct gimplify_adjust_omp_clauses_data data;
6872 data.list_p = list_p;
6873 data.pre_p = pre_p;
6874 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
6876 gimplify_omp_ctxp = ctx->outer_context;
6877 delete_omp_context (ctx);
6880 /* Gimplify OACC_CACHE. */
6882 static void
6883 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
6885 tree expr = *expr_p;
6887 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_WORKSHARE);
6888 gimplify_adjust_omp_clauses (pre_p, &OACC_CACHE_CLAUSES (expr));
6890 /* TODO: Do something sensible with this information. */
6892 *expr_p = NULL_TREE;
6895 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
6896 gimplification of the body, as well as scanning the body for used
6897 variables. We need to do this scan now, because variable-sized
6898 decls will be decomposed during gimplification. */
6900 static void
6901 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
6903 tree expr = *expr_p;
6904 gimple g;
6905 gimple_seq body = NULL;
6907 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
6908 OMP_PARALLEL_COMBINED (expr)
6909 ? ORT_COMBINED_PARALLEL
6910 : ORT_PARALLEL);
6912 push_gimplify_context ();
6914 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
6915 if (gimple_code (g) == GIMPLE_BIND)
6916 pop_gimplify_context (g);
6917 else
6918 pop_gimplify_context (NULL);
6920 gimplify_adjust_omp_clauses (pre_p, &OMP_PARALLEL_CLAUSES (expr));
6922 g = gimple_build_omp_parallel (body,
6923 OMP_PARALLEL_CLAUSES (expr),
6924 NULL_TREE, NULL_TREE);
6925 if (OMP_PARALLEL_COMBINED (expr))
6926 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
6927 gimplify_seq_add_stmt (pre_p, g);
6928 *expr_p = NULL_TREE;
6931 /* Gimplify the contents of an OMP_TASK statement. This involves
6932 gimplification of the body, as well as scanning the body for used
6933 variables. We need to do this scan now, because variable-sized
6934 decls will be decomposed during gimplification. */
6936 static void
6937 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
6939 tree expr = *expr_p;
6940 gimple g;
6941 gimple_seq body = NULL;
6943 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
6944 find_omp_clause (OMP_TASK_CLAUSES (expr),
6945 OMP_CLAUSE_UNTIED)
6946 ? ORT_UNTIED_TASK : ORT_TASK);
6948 push_gimplify_context ();
6950 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
6951 if (gimple_code (g) == GIMPLE_BIND)
6952 pop_gimplify_context (g);
6953 else
6954 pop_gimplify_context (NULL);
6956 gimplify_adjust_omp_clauses (pre_p, &OMP_TASK_CLAUSES (expr));
6958 g = gimple_build_omp_task (body,
6959 OMP_TASK_CLAUSES (expr),
6960 NULL_TREE, NULL_TREE,
6961 NULL_TREE, NULL_TREE, NULL_TREE);
6962 gimplify_seq_add_stmt (pre_p, g);
6963 *expr_p = NULL_TREE;
6966 /* Helper function of gimplify_omp_for, find OMP_FOR resp. OMP_SIMD
6967 with non-NULL OMP_FOR_INIT. */
6969 static tree
6970 find_combined_omp_for (tree *tp, int *walk_subtrees, void *)
6972 *walk_subtrees = 0;
6973 switch (TREE_CODE (*tp))
6975 case OMP_FOR:
6976 *walk_subtrees = 1;
6977 /* FALLTHRU */
6978 case OMP_SIMD:
6979 if (OMP_FOR_INIT (*tp) != NULL_TREE)
6980 return *tp;
6981 break;
6982 case BIND_EXPR:
6983 case STATEMENT_LIST:
6984 case OMP_PARALLEL:
6985 *walk_subtrees = 1;
6986 break;
6987 default:
6988 break;
6990 return NULL_TREE;
6993 /* Gimplify the gross structure of an OMP_FOR statement. */
6995 static enum gimplify_status
6996 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
6998 tree for_stmt, orig_for_stmt, decl, var, t;
6999 enum gimplify_status ret = GS_ALL_DONE;
7000 enum gimplify_status tret;
7001 gomp_for *gfor;
7002 gimple_seq for_body, for_pre_body;
7003 int i;
7004 bool simd;
7005 bitmap has_decl_expr = NULL;
7007 orig_for_stmt = for_stmt = *expr_p;
7009 switch (TREE_CODE (for_stmt))
7011 case OMP_FOR:
7012 case CILK_FOR:
7013 case OMP_DISTRIBUTE:
7014 case OACC_LOOP:
7015 simd = false;
7016 break;
7017 case OMP_SIMD:
7018 case CILK_SIMD:
7019 simd = true;
7020 break;
7021 default:
7022 gcc_unreachable ();
7025 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
7026 clause for the IV. */
7027 if (simd && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
7029 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
7030 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
7031 decl = TREE_OPERAND (t, 0);
7032 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
7033 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
7034 && OMP_CLAUSE_DECL (c) == decl)
7036 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
7037 break;
7041 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p,
7042 simd ? ORT_SIMD : ORT_WORKSHARE);
7043 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
7044 gimplify_omp_ctxp->distribute = true;
7046 /* Handle OMP_FOR_INIT. */
7047 for_pre_body = NULL;
7048 if (simd && OMP_FOR_PRE_BODY (for_stmt))
7050 has_decl_expr = BITMAP_ALLOC (NULL);
7051 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
7052 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
7053 == VAR_DECL)
7055 t = OMP_FOR_PRE_BODY (for_stmt);
7056 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
7058 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
7060 tree_stmt_iterator si;
7061 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
7062 tsi_next (&si))
7064 t = tsi_stmt (si);
7065 if (TREE_CODE (t) == DECL_EXPR
7066 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
7067 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
7071 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
7072 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
7074 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
7076 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
7077 for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt), find_combined_omp_for,
7078 NULL, NULL);
7079 gcc_assert (for_stmt != NULL_TREE);
7080 gimplify_omp_ctxp->combined_loop = true;
7083 for_body = NULL;
7084 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
7085 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
7086 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
7087 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
7088 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
7090 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
7091 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
7092 decl = TREE_OPERAND (t, 0);
7093 gcc_assert (DECL_P (decl));
7094 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
7095 || POINTER_TYPE_P (TREE_TYPE (decl)));
7097 /* Make sure the iteration variable is private. */
7098 tree c = NULL_TREE;
7099 tree c2 = NULL_TREE;
7100 if (orig_for_stmt != for_stmt)
7101 /* Do this only on innermost construct for combined ones. */;
7102 else if (simd)
7104 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
7105 (splay_tree_key)decl);
7106 omp_is_private (gimplify_omp_ctxp, decl,
7107 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
7108 != 1));
7109 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7110 omp_notice_variable (gimplify_omp_ctxp, decl, true);
7111 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
7113 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
7114 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
7115 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
7116 if ((has_decl_expr
7117 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
7118 || omp_no_lastprivate (gimplify_omp_ctxp))
7120 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
7121 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
7123 OMP_CLAUSE_DECL (c) = decl;
7124 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
7125 OMP_FOR_CLAUSES (for_stmt) = c;
7127 omp_add_variable (gimplify_omp_ctxp, decl, flags);
7128 struct gimplify_omp_ctx *outer
7129 = gimplify_omp_ctxp->outer_context;
7130 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
7132 if (outer->region_type == ORT_WORKSHARE
7133 && outer->combined_loop)
7135 if (outer->outer_context
7136 && (outer->outer_context->region_type
7137 == ORT_COMBINED_PARALLEL))
7138 outer = outer->outer_context;
7139 else if (omp_check_private (outer, decl, false))
7140 outer = NULL;
7142 else if (outer->region_type != ORT_COMBINED_PARALLEL)
7143 outer = NULL;
7144 if (outer)
7146 omp_add_variable (outer, decl,
7147 GOVD_LASTPRIVATE | GOVD_SEEN);
7148 if (outer->outer_context)
7149 omp_notice_variable (outer->outer_context, decl, true);
7153 else
7155 bool lastprivate
7156 = (!has_decl_expr
7157 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
7158 && !omp_no_lastprivate (gimplify_omp_ctxp);
7159 struct gimplify_omp_ctx *outer
7160 = gimplify_omp_ctxp->outer_context;
7161 if (outer && lastprivate)
7163 if (outer->region_type == ORT_WORKSHARE
7164 && outer->combined_loop)
7166 if (outer->outer_context
7167 && (outer->outer_context->region_type
7168 == ORT_COMBINED_PARALLEL))
7169 outer = outer->outer_context;
7170 else if (omp_check_private (outer, decl, false))
7171 outer = NULL;
7173 else if (outer->region_type != ORT_COMBINED_PARALLEL)
7174 outer = NULL;
7175 if (outer)
7177 omp_add_variable (outer, decl,
7178 GOVD_LASTPRIVATE | GOVD_SEEN);
7179 if (outer->outer_context)
7180 omp_notice_variable (outer->outer_context, decl, true);
7184 c = build_omp_clause (input_location,
7185 lastprivate ? OMP_CLAUSE_LASTPRIVATE
7186 : OMP_CLAUSE_PRIVATE);
7187 OMP_CLAUSE_DECL (c) = decl;
7188 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
7189 OMP_FOR_CLAUSES (for_stmt) = c;
7190 omp_add_variable (gimplify_omp_ctxp, decl,
7191 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
7192 | GOVD_EXPLICIT | GOVD_SEEN);
7193 c = NULL_TREE;
7196 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
7197 omp_notice_variable (gimplify_omp_ctxp, decl, true);
7198 else
7199 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
7201 /* If DECL is not a gimple register, create a temporary variable to act
7202 as an iteration counter. This is valid, since DECL cannot be
7203 modified in the body of the loop. Similarly for any iteration vars
7204 in simd with collapse > 1 where the iterator vars must be
7205 lastprivate. */
7206 if (orig_for_stmt != for_stmt)
7207 var = decl;
7208 else if (!is_gimple_reg (decl)
7209 || (simd && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1))
7211 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
7212 TREE_OPERAND (t, 0) = var;
7214 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
7216 if (simd && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
7218 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
7219 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
7220 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
7221 OMP_CLAUSE_DECL (c2) = var;
7222 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
7223 OMP_FOR_CLAUSES (for_stmt) = c2;
7224 omp_add_variable (gimplify_omp_ctxp, var,
7225 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
7226 if (c == NULL_TREE)
7228 c = c2;
7229 c2 = NULL_TREE;
7232 else
7233 omp_add_variable (gimplify_omp_ctxp, var,
7234 GOVD_PRIVATE | GOVD_SEEN);
7236 else
7237 var = decl;
7239 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7240 is_gimple_val, fb_rvalue);
7241 ret = MIN (ret, tret);
7242 if (ret == GS_ERROR)
7243 return ret;
7245 /* Handle OMP_FOR_COND. */
7246 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
7247 gcc_assert (COMPARISON_CLASS_P (t));
7248 gcc_assert (TREE_OPERAND (t, 0) == decl);
7250 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7251 is_gimple_val, fb_rvalue);
7252 ret = MIN (ret, tret);
7254 /* Handle OMP_FOR_INCR. */
7255 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7256 switch (TREE_CODE (t))
7258 case PREINCREMENT_EXPR:
7259 case POSTINCREMENT_EXPR:
7261 tree decl = TREE_OPERAND (t, 0);
7262 /* c_omp_for_incr_canonicalize_ptr() should have been
7263 called to massage things appropriately. */
7264 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
7266 if (orig_for_stmt != for_stmt)
7267 break;
7268 t = build_int_cst (TREE_TYPE (decl), 1);
7269 if (c)
7270 OMP_CLAUSE_LINEAR_STEP (c) = t;
7271 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
7272 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
7273 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
7274 break;
7277 case PREDECREMENT_EXPR:
7278 case POSTDECREMENT_EXPR:
7279 /* c_omp_for_incr_canonicalize_ptr() should have been
7280 called to massage things appropriately. */
7281 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
7282 if (orig_for_stmt != for_stmt)
7283 break;
7284 t = build_int_cst (TREE_TYPE (decl), -1);
7285 if (c)
7286 OMP_CLAUSE_LINEAR_STEP (c) = t;
7287 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
7288 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
7289 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
7290 break;
7292 case MODIFY_EXPR:
7293 gcc_assert (TREE_OPERAND (t, 0) == decl);
7294 TREE_OPERAND (t, 0) = var;
7296 t = TREE_OPERAND (t, 1);
7297 switch (TREE_CODE (t))
7299 case PLUS_EXPR:
7300 if (TREE_OPERAND (t, 1) == decl)
7302 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
7303 TREE_OPERAND (t, 0) = var;
7304 break;
7307 /* Fallthru. */
7308 case MINUS_EXPR:
7309 case POINTER_PLUS_EXPR:
7310 gcc_assert (TREE_OPERAND (t, 0) == decl);
7311 TREE_OPERAND (t, 0) = var;
7312 break;
7313 default:
7314 gcc_unreachable ();
7317 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7318 is_gimple_val, fb_rvalue);
7319 ret = MIN (ret, tret);
7320 if (c)
7322 tree step = TREE_OPERAND (t, 1);
7323 tree stept = TREE_TYPE (decl);
7324 if (POINTER_TYPE_P (stept))
7325 stept = sizetype;
7326 step = fold_convert (stept, step);
7327 if (TREE_CODE (t) == MINUS_EXPR)
7328 step = fold_build1 (NEGATE_EXPR, stept, step);
7329 OMP_CLAUSE_LINEAR_STEP (c) = step;
7330 if (step != TREE_OPERAND (t, 1))
7332 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
7333 &for_pre_body, NULL,
7334 is_gimple_val, fb_rvalue);
7335 ret = MIN (ret, tret);
7338 break;
7340 default:
7341 gcc_unreachable ();
7344 if (c2)
7346 gcc_assert (c);
7347 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
7350 if ((var != decl || TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
7351 && orig_for_stmt == for_stmt)
7353 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
7354 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
7355 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
7356 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
7357 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
7358 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
7359 && OMP_CLAUSE_DECL (c) == decl)
7361 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7362 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
7363 gcc_assert (TREE_OPERAND (t, 0) == var);
7364 t = TREE_OPERAND (t, 1);
7365 gcc_assert (TREE_CODE (t) == PLUS_EXPR
7366 || TREE_CODE (t) == MINUS_EXPR
7367 || TREE_CODE (t) == POINTER_PLUS_EXPR);
7368 gcc_assert (TREE_OPERAND (t, 0) == var);
7369 t = build2 (TREE_CODE (t), TREE_TYPE (decl), decl,
7370 TREE_OPERAND (t, 1));
7371 gimple_seq *seq;
7372 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
7373 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
7374 else
7375 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
7376 gimplify_assign (decl, t, seq);
7381 BITMAP_FREE (has_decl_expr);
7383 gimplify_and_add (OMP_FOR_BODY (orig_for_stmt), &for_body);
7385 if (orig_for_stmt != for_stmt)
7386 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
7388 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
7389 decl = TREE_OPERAND (t, 0);
7390 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
7391 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
7392 TREE_OPERAND (t, 0) = var;
7393 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7394 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
7395 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
7398 gimplify_adjust_omp_clauses (pre_p, &OMP_FOR_CLAUSES (orig_for_stmt));
7400 int kind;
7401 switch (TREE_CODE (orig_for_stmt))
7403 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
7404 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
7405 case CILK_SIMD: kind = GF_OMP_FOR_KIND_CILKSIMD; break;
7406 case CILK_FOR: kind = GF_OMP_FOR_KIND_CILKFOR; break;
7407 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
7408 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
7409 default:
7410 gcc_unreachable ();
7412 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
7413 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
7414 for_pre_body);
7415 if (orig_for_stmt != for_stmt)
7416 gimple_omp_for_set_combined_p (gfor, true);
7417 if (gimplify_omp_ctxp
7418 && (gimplify_omp_ctxp->combined_loop
7419 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
7420 && gimplify_omp_ctxp->outer_context
7421 && gimplify_omp_ctxp->outer_context->combined_loop)))
7423 gimple_omp_for_set_combined_into_p (gfor, true);
7424 if (gimplify_omp_ctxp->combined_loop)
7425 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
7426 else
7427 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
7430 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
7432 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
7433 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
7434 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
7435 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
7436 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
7437 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
7438 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7439 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
7442 gimplify_seq_add_stmt (pre_p, gfor);
7443 if (ret != GS_ALL_DONE)
7444 return GS_ERROR;
7445 *expr_p = NULL_TREE;
7446 return GS_ALL_DONE;
7449 /* Gimplify the gross structure of several OMP constructs. */
7451 static void
7452 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
7454 tree expr = *expr_p;
7455 gimple stmt;
7456 gimple_seq body = NULL;
7457 enum omp_region_type ort;
7459 switch (TREE_CODE (expr))
7461 case OMP_SECTIONS:
7462 case OMP_SINGLE:
7463 ort = ORT_WORKSHARE;
7464 break;
7465 case OACC_KERNELS:
7466 case OACC_PARALLEL:
7467 case OMP_TARGET:
7468 ort = ORT_TARGET;
7469 break;
7470 case OACC_DATA:
7471 case OMP_TARGET_DATA:
7472 ort = ORT_TARGET_DATA;
7473 break;
7474 case OMP_TEAMS:
7475 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
7476 break;
7477 default:
7478 gcc_unreachable ();
7480 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort);
7481 if (ort == ORT_TARGET || ort == ORT_TARGET_DATA)
7483 push_gimplify_context ();
7484 gimple g = gimplify_and_return_first (OMP_BODY (expr), &body);
7485 if (gimple_code (g) == GIMPLE_BIND)
7486 pop_gimplify_context (g);
7487 else
7488 pop_gimplify_context (NULL);
7489 if (ort == ORT_TARGET_DATA)
7491 enum built_in_function end_ix;
7492 switch (TREE_CODE (expr))
7494 case OACC_DATA:
7495 end_ix = BUILT_IN_GOACC_DATA_END;
7496 break;
7497 case OMP_TARGET_DATA:
7498 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
7499 break;
7500 default:
7501 gcc_unreachable ();
7503 tree fn = builtin_decl_explicit (end_ix);
7504 g = gimple_build_call (fn, 0);
7505 gimple_seq cleanup = NULL;
7506 gimple_seq_add_stmt (&cleanup, g);
7507 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
7508 body = NULL;
7509 gimple_seq_add_stmt (&body, g);
7512 else
7513 gimplify_and_add (OMP_BODY (expr), &body);
7514 gimplify_adjust_omp_clauses (pre_p, &OMP_CLAUSES (expr));
7516 switch (TREE_CODE (expr))
7518 case OACC_DATA:
7519 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
7520 OMP_CLAUSES (expr));
7521 break;
7522 case OACC_KERNELS:
7523 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
7524 OMP_CLAUSES (expr));
7525 break;
7526 case OACC_PARALLEL:
7527 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
7528 OMP_CLAUSES (expr));
7529 break;
7530 case OMP_SECTIONS:
7531 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
7532 break;
7533 case OMP_SINGLE:
7534 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
7535 break;
7536 case OMP_TARGET:
7537 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
7538 OMP_CLAUSES (expr));
7539 break;
7540 case OMP_TARGET_DATA:
7541 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
7542 OMP_CLAUSES (expr));
7543 break;
7544 case OMP_TEAMS:
7545 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
7546 break;
7547 default:
7548 gcc_unreachable ();
7551 gimplify_seq_add_stmt (pre_p, stmt);
7552 *expr_p = NULL_TREE;
7555 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
7556 target update constructs. */
7558 static void
7559 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
7561 tree expr = *expr_p;
7562 int kind;
7563 gomp_target *stmt;
7565 switch (TREE_CODE (expr))
7567 case OACC_ENTER_DATA:
7568 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
7569 break;
7570 case OACC_EXIT_DATA:
7571 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
7572 break;
7573 case OACC_UPDATE:
7574 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
7575 break;
7576 case OMP_TARGET_UPDATE:
7577 kind = GF_OMP_TARGET_KIND_UPDATE;
7578 break;
7579 default:
7580 gcc_unreachable ();
7582 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
7583 ORT_WORKSHARE);
7584 gimplify_adjust_omp_clauses (pre_p, &OMP_STANDALONE_CLAUSES (expr));
7585 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
7587 gimplify_seq_add_stmt (pre_p, stmt);
7588 *expr_p = NULL_TREE;
7591 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
7592 stabilized the lhs of the atomic operation as *ADDR. Return true if
7593 EXPR is this stabilized form. */
7595 static bool
7596 goa_lhs_expr_p (tree expr, tree addr)
7598 /* Also include casts to other type variants. The C front end is fond
7599 of adding these for e.g. volatile variables. This is like
7600 STRIP_TYPE_NOPS but includes the main variant lookup. */
7601 STRIP_USELESS_TYPE_CONVERSION (expr);
7603 if (TREE_CODE (expr) == INDIRECT_REF)
7605 expr = TREE_OPERAND (expr, 0);
7606 while (expr != addr
7607 && (CONVERT_EXPR_P (expr)
7608 || TREE_CODE (expr) == NON_LVALUE_EXPR)
7609 && TREE_CODE (expr) == TREE_CODE (addr)
7610 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
7612 expr = TREE_OPERAND (expr, 0);
7613 addr = TREE_OPERAND (addr, 0);
7615 if (expr == addr)
7616 return true;
7617 return (TREE_CODE (addr) == ADDR_EXPR
7618 && TREE_CODE (expr) == ADDR_EXPR
7619 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
7621 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
7622 return true;
7623 return false;
7626 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
7627 expression does not involve the lhs, evaluate it into a temporary.
7628 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
7629 or -1 if an error was encountered. */
7631 static int
7632 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
7633 tree lhs_var)
7635 tree expr = *expr_p;
7636 int saw_lhs;
7638 if (goa_lhs_expr_p (expr, lhs_addr))
7640 *expr_p = lhs_var;
7641 return 1;
7643 if (is_gimple_val (expr))
7644 return 0;
7646 saw_lhs = 0;
7647 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
7649 case tcc_binary:
7650 case tcc_comparison:
7651 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
7652 lhs_var);
7653 case tcc_unary:
7654 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
7655 lhs_var);
7656 break;
7657 case tcc_expression:
7658 switch (TREE_CODE (expr))
7660 case TRUTH_ANDIF_EXPR:
7661 case TRUTH_ORIF_EXPR:
7662 case TRUTH_AND_EXPR:
7663 case TRUTH_OR_EXPR:
7664 case TRUTH_XOR_EXPR:
7665 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
7666 lhs_addr, lhs_var);
7667 case TRUTH_NOT_EXPR:
7668 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
7669 lhs_addr, lhs_var);
7670 break;
7671 case COMPOUND_EXPR:
7672 /* Break out any preevaluations from cp_build_modify_expr. */
7673 for (; TREE_CODE (expr) == COMPOUND_EXPR;
7674 expr = TREE_OPERAND (expr, 1))
7675 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
7676 *expr_p = expr;
7677 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var);
7678 default:
7679 break;
7681 break;
7682 default:
7683 break;
7686 if (saw_lhs == 0)
7688 enum gimplify_status gs;
7689 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
7690 if (gs != GS_ALL_DONE)
7691 saw_lhs = -1;
7694 return saw_lhs;
7697 /* Gimplify an OMP_ATOMIC statement. */
7699 static enum gimplify_status
7700 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
7702 tree addr = TREE_OPERAND (*expr_p, 0);
7703 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
7704 ? NULL : TREE_OPERAND (*expr_p, 1);
7705 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
7706 tree tmp_load;
7707 gomp_atomic_load *loadstmt;
7708 gomp_atomic_store *storestmt;
7710 tmp_load = create_tmp_reg (type);
7711 if (rhs && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load) < 0)
7712 return GS_ERROR;
7714 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
7715 != GS_ALL_DONE)
7716 return GS_ERROR;
7718 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr);
7719 gimplify_seq_add_stmt (pre_p, loadstmt);
7720 if (rhs && gimplify_expr (&rhs, pre_p, NULL, is_gimple_val, fb_rvalue)
7721 != GS_ALL_DONE)
7722 return GS_ERROR;
7724 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
7725 rhs = tmp_load;
7726 storestmt = gimple_build_omp_atomic_store (rhs);
7727 gimplify_seq_add_stmt (pre_p, storestmt);
7728 if (OMP_ATOMIC_SEQ_CST (*expr_p))
7730 gimple_omp_atomic_set_seq_cst (loadstmt);
7731 gimple_omp_atomic_set_seq_cst (storestmt);
7733 switch (TREE_CODE (*expr_p))
7735 case OMP_ATOMIC_READ:
7736 case OMP_ATOMIC_CAPTURE_OLD:
7737 *expr_p = tmp_load;
7738 gimple_omp_atomic_set_need_value (loadstmt);
7739 break;
7740 case OMP_ATOMIC_CAPTURE_NEW:
7741 *expr_p = rhs;
7742 gimple_omp_atomic_set_need_value (storestmt);
7743 break;
7744 default:
7745 *expr_p = NULL;
7746 break;
7749 return GS_ALL_DONE;
7752 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
7753 body, and adding some EH bits. */
7755 static enum gimplify_status
7756 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
7758 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
7759 gimple body_stmt;
7760 gtransaction *trans_stmt;
7761 gimple_seq body = NULL;
7762 int subcode = 0;
7764 /* Wrap the transaction body in a BIND_EXPR so we have a context
7765 where to put decls for OMP. */
7766 if (TREE_CODE (tbody) != BIND_EXPR)
7768 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
7769 TREE_SIDE_EFFECTS (bind) = 1;
7770 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
7771 TRANSACTION_EXPR_BODY (expr) = bind;
7774 push_gimplify_context ();
7775 temp = voidify_wrapper_expr (*expr_p, NULL);
7777 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
7778 pop_gimplify_context (body_stmt);
7780 trans_stmt = gimple_build_transaction (body, NULL);
7781 if (TRANSACTION_EXPR_OUTER (expr))
7782 subcode = GTMA_IS_OUTER;
7783 else if (TRANSACTION_EXPR_RELAXED (expr))
7784 subcode = GTMA_IS_RELAXED;
7785 gimple_transaction_set_subcode (trans_stmt, subcode);
7787 gimplify_seq_add_stmt (pre_p, trans_stmt);
7789 if (temp)
7791 *expr_p = temp;
7792 return GS_OK;
7795 *expr_p = NULL_TREE;
7796 return GS_ALL_DONE;
7799 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
7800 expression produces a value to be used as an operand inside a GIMPLE
7801 statement, the value will be stored back in *EXPR_P. This value will
7802 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
7803 an SSA_NAME. The corresponding sequence of GIMPLE statements is
7804 emitted in PRE_P and POST_P.
7806 Additionally, this process may overwrite parts of the input
7807 expression during gimplification. Ideally, it should be
7808 possible to do non-destructive gimplification.
7810 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
7811 the expression needs to evaluate to a value to be used as
7812 an operand in a GIMPLE statement, this value will be stored in
7813 *EXPR_P on exit. This happens when the caller specifies one
7814 of fb_lvalue or fb_rvalue fallback flags.
7816 PRE_P will contain the sequence of GIMPLE statements corresponding
7817 to the evaluation of EXPR and all the side-effects that must
7818 be executed before the main expression. On exit, the last
7819 statement of PRE_P is the core statement being gimplified. For
7820 instance, when gimplifying 'if (++a)' the last statement in
7821 PRE_P will be 'if (t.1)' where t.1 is the result of
7822 pre-incrementing 'a'.
7824 POST_P will contain the sequence of GIMPLE statements corresponding
7825 to the evaluation of all the side-effects that must be executed
7826 after the main expression. If this is NULL, the post
7827 side-effects are stored at the end of PRE_P.
7829 The reason why the output is split in two is to handle post
7830 side-effects explicitly. In some cases, an expression may have
7831 inner and outer post side-effects which need to be emitted in
7832 an order different from the one given by the recursive
7833 traversal. For instance, for the expression (*p--)++ the post
7834 side-effects of '--' must actually occur *after* the post
7835 side-effects of '++'. However, gimplification will first visit
7836 the inner expression, so if a separate POST sequence was not
7837 used, the resulting sequence would be:
7839 1 t.1 = *p
7840 2 p = p - 1
7841 3 t.2 = t.1 + 1
7842 4 *p = t.2
7844 However, the post-decrement operation in line #2 must not be
7845 evaluated until after the store to *p at line #4, so the
7846 correct sequence should be:
7848 1 t.1 = *p
7849 2 t.2 = t.1 + 1
7850 3 *p = t.2
7851 4 p = p - 1
7853 So, by specifying a separate post queue, it is possible
7854 to emit the post side-effects in the correct order.
7855 If POST_P is NULL, an internal queue will be used. Before
7856 returning to the caller, the sequence POST_P is appended to
7857 the main output sequence PRE_P.
7859 GIMPLE_TEST_F points to a function that takes a tree T and
7860 returns nonzero if T is in the GIMPLE form requested by the
7861 caller. The GIMPLE predicates are in gimple.c.
7863 FALLBACK tells the function what sort of a temporary we want if
7864 gimplification cannot produce an expression that complies with
7865 GIMPLE_TEST_F.
7867 fb_none means that no temporary should be generated
7868 fb_rvalue means that an rvalue is OK to generate
7869 fb_lvalue means that an lvalue is OK to generate
7870 fb_either means that either is OK, but an lvalue is preferable.
7871 fb_mayfail means that gimplification may fail (in which case
7872 GS_ERROR will be returned)
7874 The return value is either GS_ERROR or GS_ALL_DONE, since this
7875 function iterates until EXPR is completely gimplified or an error
7876 occurs. */
7878 enum gimplify_status
7879 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
7880 bool (*gimple_test_f) (tree), fallback_t fallback)
7882 tree tmp;
7883 gimple_seq internal_pre = NULL;
7884 gimple_seq internal_post = NULL;
7885 tree save_expr;
7886 bool is_statement;
7887 location_t saved_location;
7888 enum gimplify_status ret;
7889 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
7891 save_expr = *expr_p;
7892 if (save_expr == NULL_TREE)
7893 return GS_ALL_DONE;
7895 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
7896 is_statement = gimple_test_f == is_gimple_stmt;
7897 if (is_statement)
7898 gcc_assert (pre_p);
7900 /* Consistency checks. */
7901 if (gimple_test_f == is_gimple_reg)
7902 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
7903 else if (gimple_test_f == is_gimple_val
7904 || gimple_test_f == is_gimple_call_addr
7905 || gimple_test_f == is_gimple_condexpr
7906 || gimple_test_f == is_gimple_mem_rhs
7907 || gimple_test_f == is_gimple_mem_rhs_or_call
7908 || gimple_test_f == is_gimple_reg_rhs
7909 || gimple_test_f == is_gimple_reg_rhs_or_call
7910 || gimple_test_f == is_gimple_asm_val
7911 || gimple_test_f == is_gimple_mem_ref_addr)
7912 gcc_assert (fallback & fb_rvalue);
7913 else if (gimple_test_f == is_gimple_min_lval
7914 || gimple_test_f == is_gimple_lvalue)
7915 gcc_assert (fallback & fb_lvalue);
7916 else if (gimple_test_f == is_gimple_addressable)
7917 gcc_assert (fallback & fb_either);
7918 else if (gimple_test_f == is_gimple_stmt)
7919 gcc_assert (fallback == fb_none);
7920 else
7922 /* We should have recognized the GIMPLE_TEST_F predicate to
7923 know what kind of fallback to use in case a temporary is
7924 needed to hold the value or address of *EXPR_P. */
7925 gcc_unreachable ();
7928 /* We used to check the predicate here and return immediately if it
7929 succeeds. This is wrong; the design is for gimplification to be
7930 idempotent, and for the predicates to only test for valid forms, not
7931 whether they are fully simplified. */
7932 if (pre_p == NULL)
7933 pre_p = &internal_pre;
7935 if (post_p == NULL)
7936 post_p = &internal_post;
7938 /* Remember the last statements added to PRE_P and POST_P. Every
7939 new statement added by the gimplification helpers needs to be
7940 annotated with location information. To centralize the
7941 responsibility, we remember the last statement that had been
7942 added to both queues before gimplifying *EXPR_P. If
7943 gimplification produces new statements in PRE_P and POST_P, those
7944 statements will be annotated with the same location information
7945 as *EXPR_P. */
7946 pre_last_gsi = gsi_last (*pre_p);
7947 post_last_gsi = gsi_last (*post_p);
7949 saved_location = input_location;
7950 if (save_expr != error_mark_node
7951 && EXPR_HAS_LOCATION (*expr_p))
7952 input_location = EXPR_LOCATION (*expr_p);
7954 /* Loop over the specific gimplifiers until the toplevel node
7955 remains the same. */
7958 /* Strip away as many useless type conversions as possible
7959 at the toplevel. */
7960 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
7962 /* Remember the expr. */
7963 save_expr = *expr_p;
7965 /* Die, die, die, my darling. */
7966 if (save_expr == error_mark_node
7967 || (TREE_TYPE (save_expr)
7968 && TREE_TYPE (save_expr) == error_mark_node))
7970 ret = GS_ERROR;
7971 break;
7974 /* Do any language-specific gimplification. */
7975 ret = ((enum gimplify_status)
7976 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
7977 if (ret == GS_OK)
7979 if (*expr_p == NULL_TREE)
7980 break;
7981 if (*expr_p != save_expr)
7982 continue;
7984 else if (ret != GS_UNHANDLED)
7985 break;
7987 /* Make sure that all the cases set 'ret' appropriately. */
7988 ret = GS_UNHANDLED;
7989 switch (TREE_CODE (*expr_p))
7991 /* First deal with the special cases. */
7993 case POSTINCREMENT_EXPR:
7994 case POSTDECREMENT_EXPR:
7995 case PREINCREMENT_EXPR:
7996 case PREDECREMENT_EXPR:
7997 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
7998 fallback != fb_none,
7999 TREE_TYPE (*expr_p));
8000 break;
8002 case VIEW_CONVERT_EXPR:
8003 if (is_gimple_reg_type (TREE_TYPE (*expr_p))
8004 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
8006 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8007 post_p, is_gimple_val, fb_rvalue);
8008 recalculate_side_effects (*expr_p);
8009 break;
8011 /* Fallthru. */
8013 case ARRAY_REF:
8014 case ARRAY_RANGE_REF:
8015 case REALPART_EXPR:
8016 case IMAGPART_EXPR:
8017 case COMPONENT_REF:
8018 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
8019 fallback ? fallback : fb_rvalue);
8020 break;
8022 case COND_EXPR:
8023 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
8025 /* C99 code may assign to an array in a structure value of a
8026 conditional expression, and this has undefined behavior
8027 only on execution, so create a temporary if an lvalue is
8028 required. */
8029 if (fallback == fb_lvalue)
8031 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
8032 mark_addressable (*expr_p);
8033 ret = GS_OK;
8035 break;
8037 case CALL_EXPR:
8038 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
8040 /* C99 code may assign to an array in a structure returned
8041 from a function, and this has undefined behavior only on
8042 execution, so create a temporary if an lvalue is
8043 required. */
8044 if (fallback == fb_lvalue)
8046 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
8047 mark_addressable (*expr_p);
8048 ret = GS_OK;
8050 break;
8052 case TREE_LIST:
8053 gcc_unreachable ();
8055 case COMPOUND_EXPR:
8056 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
8057 break;
8059 case COMPOUND_LITERAL_EXPR:
8060 ret = gimplify_compound_literal_expr (expr_p, pre_p,
8061 gimple_test_f, fallback);
8062 break;
8064 case MODIFY_EXPR:
8065 case INIT_EXPR:
8066 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
8067 fallback != fb_none);
8068 break;
8070 case TRUTH_ANDIF_EXPR:
8071 case TRUTH_ORIF_EXPR:
8073 /* Preserve the original type of the expression and the
8074 source location of the outer expression. */
8075 tree org_type = TREE_TYPE (*expr_p);
8076 *expr_p = gimple_boolify (*expr_p);
8077 *expr_p = build3_loc (input_location, COND_EXPR,
8078 org_type, *expr_p,
8079 fold_convert_loc
8080 (input_location,
8081 org_type, boolean_true_node),
8082 fold_convert_loc
8083 (input_location,
8084 org_type, boolean_false_node));
8085 ret = GS_OK;
8086 break;
8089 case TRUTH_NOT_EXPR:
8091 tree type = TREE_TYPE (*expr_p);
8092 /* The parsers are careful to generate TRUTH_NOT_EXPR
8093 only with operands that are always zero or one.
8094 We do not fold here but handle the only interesting case
8095 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
8096 *expr_p = gimple_boolify (*expr_p);
8097 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
8098 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
8099 TREE_TYPE (*expr_p),
8100 TREE_OPERAND (*expr_p, 0));
8101 else
8102 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
8103 TREE_TYPE (*expr_p),
8104 TREE_OPERAND (*expr_p, 0),
8105 build_int_cst (TREE_TYPE (*expr_p), 1));
8106 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
8107 *expr_p = fold_convert_loc (input_location, type, *expr_p);
8108 ret = GS_OK;
8109 break;
8112 case ADDR_EXPR:
8113 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
8114 break;
8116 case ANNOTATE_EXPR:
8118 tree cond = TREE_OPERAND (*expr_p, 0);
8119 tree kind = TREE_OPERAND (*expr_p, 1);
8120 tree type = TREE_TYPE (cond);
8121 if (!INTEGRAL_TYPE_P (type))
8123 *expr_p = cond;
8124 ret = GS_OK;
8125 break;
8127 tree tmp = create_tmp_var (type);
8128 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
8129 gcall *call
8130 = gimple_build_call_internal (IFN_ANNOTATE, 2, cond, kind);
8131 gimple_call_set_lhs (call, tmp);
8132 gimplify_seq_add_stmt (pre_p, call);
8133 *expr_p = tmp;
8134 ret = GS_ALL_DONE;
8135 break;
8138 case VA_ARG_EXPR:
8139 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
8140 break;
8142 CASE_CONVERT:
8143 if (IS_EMPTY_STMT (*expr_p))
8145 ret = GS_ALL_DONE;
8146 break;
8149 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
8150 || fallback == fb_none)
8152 /* Just strip a conversion to void (or in void context) and
8153 try again. */
8154 *expr_p = TREE_OPERAND (*expr_p, 0);
8155 ret = GS_OK;
8156 break;
8159 ret = gimplify_conversion (expr_p);
8160 if (ret == GS_ERROR)
8161 break;
8162 if (*expr_p != save_expr)
8163 break;
8164 /* FALLTHRU */
8166 case FIX_TRUNC_EXPR:
8167 /* unary_expr: ... | '(' cast ')' val | ... */
8168 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8169 is_gimple_val, fb_rvalue);
8170 recalculate_side_effects (*expr_p);
8171 break;
8173 case INDIRECT_REF:
8175 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
8176 bool notrap = TREE_THIS_NOTRAP (*expr_p);
8177 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
8179 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
8180 if (*expr_p != save_expr)
8182 ret = GS_OK;
8183 break;
8186 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8187 is_gimple_reg, fb_rvalue);
8188 if (ret == GS_ERROR)
8189 break;
8191 recalculate_side_effects (*expr_p);
8192 *expr_p = fold_build2_loc (input_location, MEM_REF,
8193 TREE_TYPE (*expr_p),
8194 TREE_OPERAND (*expr_p, 0),
8195 build_int_cst (saved_ptr_type, 0));
8196 TREE_THIS_VOLATILE (*expr_p) = volatilep;
8197 TREE_THIS_NOTRAP (*expr_p) = notrap;
8198 ret = GS_OK;
8199 break;
8202 /* We arrive here through the various re-gimplifcation paths. */
8203 case MEM_REF:
8204 /* First try re-folding the whole thing. */
8205 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
8206 TREE_OPERAND (*expr_p, 0),
8207 TREE_OPERAND (*expr_p, 1));
8208 if (tmp)
8210 *expr_p = tmp;
8211 recalculate_side_effects (*expr_p);
8212 ret = GS_OK;
8213 break;
8215 /* Avoid re-gimplifying the address operand if it is already
8216 in suitable form. Re-gimplifying would mark the address
8217 operand addressable. Always gimplify when not in SSA form
8218 as we still may have to gimplify decls with value-exprs. */
8219 if (!gimplify_ctxp || !gimplify_ctxp->into_ssa
8220 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
8222 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8223 is_gimple_mem_ref_addr, fb_rvalue);
8224 if (ret == GS_ERROR)
8225 break;
8227 recalculate_side_effects (*expr_p);
8228 ret = GS_ALL_DONE;
8229 break;
8231 /* Constants need not be gimplified. */
8232 case INTEGER_CST:
8233 case REAL_CST:
8234 case FIXED_CST:
8235 case STRING_CST:
8236 case COMPLEX_CST:
8237 case VECTOR_CST:
8238 /* Drop the overflow flag on constants, we do not want
8239 that in the GIMPLE IL. */
8240 if (TREE_OVERFLOW_P (*expr_p))
8241 *expr_p = drop_tree_overflow (*expr_p);
8242 ret = GS_ALL_DONE;
8243 break;
8245 case CONST_DECL:
8246 /* If we require an lvalue, such as for ADDR_EXPR, retain the
8247 CONST_DECL node. Otherwise the decl is replaceable by its
8248 value. */
8249 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
8250 if (fallback & fb_lvalue)
8251 ret = GS_ALL_DONE;
8252 else
8254 *expr_p = DECL_INITIAL (*expr_p);
8255 ret = GS_OK;
8257 break;
8259 case DECL_EXPR:
8260 ret = gimplify_decl_expr (expr_p, pre_p);
8261 break;
8263 case BIND_EXPR:
8264 ret = gimplify_bind_expr (expr_p, pre_p);
8265 break;
8267 case LOOP_EXPR:
8268 ret = gimplify_loop_expr (expr_p, pre_p);
8269 break;
8271 case SWITCH_EXPR:
8272 ret = gimplify_switch_expr (expr_p, pre_p);
8273 break;
8275 case EXIT_EXPR:
8276 ret = gimplify_exit_expr (expr_p);
8277 break;
8279 case GOTO_EXPR:
8280 /* If the target is not LABEL, then it is a computed jump
8281 and the target needs to be gimplified. */
8282 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
8284 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
8285 NULL, is_gimple_val, fb_rvalue);
8286 if (ret == GS_ERROR)
8287 break;
8289 gimplify_seq_add_stmt (pre_p,
8290 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
8291 ret = GS_ALL_DONE;
8292 break;
8294 case PREDICT_EXPR:
8295 gimplify_seq_add_stmt (pre_p,
8296 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
8297 PREDICT_EXPR_OUTCOME (*expr_p)));
8298 ret = GS_ALL_DONE;
8299 break;
8301 case LABEL_EXPR:
8302 ret = GS_ALL_DONE;
8303 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
8304 == current_function_decl);
8305 gimplify_seq_add_stmt (pre_p,
8306 gimple_build_label (LABEL_EXPR_LABEL (*expr_p)));
8307 break;
8309 case CASE_LABEL_EXPR:
8310 ret = gimplify_case_label_expr (expr_p, pre_p);
8311 break;
8313 case RETURN_EXPR:
8314 ret = gimplify_return_expr (*expr_p, pre_p);
8315 break;
8317 case CONSTRUCTOR:
8318 /* Don't reduce this in place; let gimplify_init_constructor work its
8319 magic. Buf if we're just elaborating this for side effects, just
8320 gimplify any element that has side-effects. */
8321 if (fallback == fb_none)
8323 unsigned HOST_WIDE_INT ix;
8324 tree val;
8325 tree temp = NULL_TREE;
8326 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
8327 if (TREE_SIDE_EFFECTS (val))
8328 append_to_statement_list (val, &temp);
8330 *expr_p = temp;
8331 ret = temp ? GS_OK : GS_ALL_DONE;
8333 /* C99 code may assign to an array in a constructed
8334 structure or union, and this has undefined behavior only
8335 on execution, so create a temporary if an lvalue is
8336 required. */
8337 else if (fallback == fb_lvalue)
8339 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
8340 mark_addressable (*expr_p);
8341 ret = GS_OK;
8343 else
8344 ret = GS_ALL_DONE;
8345 break;
8347 /* The following are special cases that are not handled by the
8348 original GIMPLE grammar. */
8350 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
8351 eliminated. */
8352 case SAVE_EXPR:
8353 ret = gimplify_save_expr (expr_p, pre_p, post_p);
8354 break;
8356 case BIT_FIELD_REF:
8357 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8358 post_p, is_gimple_lvalue, fb_either);
8359 recalculate_side_effects (*expr_p);
8360 break;
8362 case TARGET_MEM_REF:
8364 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
8366 if (TMR_BASE (*expr_p))
8367 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
8368 post_p, is_gimple_mem_ref_addr, fb_either);
8369 if (TMR_INDEX (*expr_p))
8370 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
8371 post_p, is_gimple_val, fb_rvalue);
8372 if (TMR_INDEX2 (*expr_p))
8373 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
8374 post_p, is_gimple_val, fb_rvalue);
8375 /* TMR_STEP and TMR_OFFSET are always integer constants. */
8376 ret = MIN (r0, r1);
8378 break;
8380 case NON_LVALUE_EXPR:
8381 /* This should have been stripped above. */
8382 gcc_unreachable ();
8384 case ASM_EXPR:
8385 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
8386 break;
8388 case TRY_FINALLY_EXPR:
8389 case TRY_CATCH_EXPR:
8391 gimple_seq eval, cleanup;
8392 gtry *try_;
8394 /* Calls to destructors are generated automatically in FINALLY/CATCH
8395 block. They should have location as UNKNOWN_LOCATION. However,
8396 gimplify_call_expr will reset these call stmts to input_location
8397 if it finds stmt's location is unknown. To prevent resetting for
8398 destructors, we set the input_location to unknown.
8399 Note that this only affects the destructor calls in FINALLY/CATCH
8400 block, and will automatically reset to its original value by the
8401 end of gimplify_expr. */
8402 input_location = UNKNOWN_LOCATION;
8403 eval = cleanup = NULL;
8404 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
8405 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
8406 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
8407 if (gimple_seq_empty_p (cleanup))
8409 gimple_seq_add_seq (pre_p, eval);
8410 ret = GS_ALL_DONE;
8411 break;
8413 try_ = gimple_build_try (eval, cleanup,
8414 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
8415 ? GIMPLE_TRY_FINALLY
8416 : GIMPLE_TRY_CATCH);
8417 if (EXPR_HAS_LOCATION (save_expr))
8418 gimple_set_location (try_, EXPR_LOCATION (save_expr));
8419 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
8420 gimple_set_location (try_, saved_location);
8421 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
8422 gimple_try_set_catch_is_cleanup (try_,
8423 TRY_CATCH_IS_CLEANUP (*expr_p));
8424 gimplify_seq_add_stmt (pre_p, try_);
8425 ret = GS_ALL_DONE;
8426 break;
8429 case CLEANUP_POINT_EXPR:
8430 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
8431 break;
8433 case TARGET_EXPR:
8434 ret = gimplify_target_expr (expr_p, pre_p, post_p);
8435 break;
8437 case CATCH_EXPR:
8439 gimple c;
8440 gimple_seq handler = NULL;
8441 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
8442 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
8443 gimplify_seq_add_stmt (pre_p, c);
8444 ret = GS_ALL_DONE;
8445 break;
8448 case EH_FILTER_EXPR:
8450 gimple ehf;
8451 gimple_seq failure = NULL;
8453 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
8454 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
8455 gimple_set_no_warning (ehf, TREE_NO_WARNING (*expr_p));
8456 gimplify_seq_add_stmt (pre_p, ehf);
8457 ret = GS_ALL_DONE;
8458 break;
8461 case OBJ_TYPE_REF:
8463 enum gimplify_status r0, r1;
8464 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
8465 post_p, is_gimple_val, fb_rvalue);
8466 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
8467 post_p, is_gimple_val, fb_rvalue);
8468 TREE_SIDE_EFFECTS (*expr_p) = 0;
8469 ret = MIN (r0, r1);
8471 break;
8473 case LABEL_DECL:
8474 /* We get here when taking the address of a label. We mark
8475 the label as "forced"; meaning it can never be removed and
8476 it is a potential target for any computed goto. */
8477 FORCED_LABEL (*expr_p) = 1;
8478 ret = GS_ALL_DONE;
8479 break;
8481 case STATEMENT_LIST:
8482 ret = gimplify_statement_list (expr_p, pre_p);
8483 break;
8485 case WITH_SIZE_EXPR:
8487 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8488 post_p == &internal_post ? NULL : post_p,
8489 gimple_test_f, fallback);
8490 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
8491 is_gimple_val, fb_rvalue);
8492 ret = GS_ALL_DONE;
8494 break;
8496 case VAR_DECL:
8497 case PARM_DECL:
8498 ret = gimplify_var_or_parm_decl (expr_p);
8499 break;
8501 case RESULT_DECL:
8502 /* When within an OMP context, notice uses of variables. */
8503 if (gimplify_omp_ctxp)
8504 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
8505 ret = GS_ALL_DONE;
8506 break;
8508 case SSA_NAME:
8509 /* Allow callbacks into the gimplifier during optimization. */
8510 ret = GS_ALL_DONE;
8511 break;
8513 case OMP_PARALLEL:
8514 gimplify_omp_parallel (expr_p, pre_p);
8515 ret = GS_ALL_DONE;
8516 break;
8518 case OMP_TASK:
8519 gimplify_omp_task (expr_p, pre_p);
8520 ret = GS_ALL_DONE;
8521 break;
8523 case OMP_FOR:
8524 case OMP_SIMD:
8525 case CILK_SIMD:
8526 case CILK_FOR:
8527 case OMP_DISTRIBUTE:
8528 case OACC_LOOP:
8529 ret = gimplify_omp_for (expr_p, pre_p);
8530 break;
8532 case OACC_CACHE:
8533 gimplify_oacc_cache (expr_p, pre_p);
8534 ret = GS_ALL_DONE;
8535 break;
8537 case OACC_HOST_DATA:
8538 case OACC_DECLARE:
8539 sorry ("directive not yet implemented");
8540 ret = GS_ALL_DONE;
8541 break;
8543 case OACC_KERNELS:
8544 if (OACC_KERNELS_COMBINED (*expr_p))
8545 sorry ("directive not yet implemented");
8546 else
8547 gimplify_omp_workshare (expr_p, pre_p);
8548 ret = GS_ALL_DONE;
8549 break;
8551 case OACC_PARALLEL:
8552 if (OACC_PARALLEL_COMBINED (*expr_p))
8553 sorry ("directive not yet implemented");
8554 else
8555 gimplify_omp_workshare (expr_p, pre_p);
8556 ret = GS_ALL_DONE;
8557 break;
8559 case OACC_DATA:
8560 case OMP_SECTIONS:
8561 case OMP_SINGLE:
8562 case OMP_TARGET:
8563 case OMP_TARGET_DATA:
8564 case OMP_TEAMS:
8565 gimplify_omp_workshare (expr_p, pre_p);
8566 ret = GS_ALL_DONE;
8567 break;
8569 case OACC_ENTER_DATA:
8570 case OACC_EXIT_DATA:
8571 case OACC_UPDATE:
8572 case OMP_TARGET_UPDATE:
8573 gimplify_omp_target_update (expr_p, pre_p);
8574 ret = GS_ALL_DONE;
8575 break;
8577 case OMP_SECTION:
8578 case OMP_MASTER:
8579 case OMP_TASKGROUP:
8580 case OMP_ORDERED:
8581 case OMP_CRITICAL:
8583 gimple_seq body = NULL;
8584 gimple g;
8586 gimplify_and_add (OMP_BODY (*expr_p), &body);
8587 switch (TREE_CODE (*expr_p))
8589 case OMP_SECTION:
8590 g = gimple_build_omp_section (body);
8591 break;
8592 case OMP_MASTER:
8593 g = gimple_build_omp_master (body);
8594 break;
8595 case OMP_TASKGROUP:
8597 gimple_seq cleanup = NULL;
8598 tree fn
8599 = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
8600 g = gimple_build_call (fn, 0);
8601 gimple_seq_add_stmt (&cleanup, g);
8602 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
8603 body = NULL;
8604 gimple_seq_add_stmt (&body, g);
8605 g = gimple_build_omp_taskgroup (body);
8607 break;
8608 case OMP_ORDERED:
8609 g = gimple_build_omp_ordered (body);
8610 break;
8611 case OMP_CRITICAL:
8612 g = gimple_build_omp_critical (body,
8613 OMP_CRITICAL_NAME (*expr_p));
8614 break;
8615 default:
8616 gcc_unreachable ();
8618 gimplify_seq_add_stmt (pre_p, g);
8619 ret = GS_ALL_DONE;
8620 break;
8623 case OMP_ATOMIC:
8624 case OMP_ATOMIC_READ:
8625 case OMP_ATOMIC_CAPTURE_OLD:
8626 case OMP_ATOMIC_CAPTURE_NEW:
8627 ret = gimplify_omp_atomic (expr_p, pre_p);
8628 break;
8630 case TRANSACTION_EXPR:
8631 ret = gimplify_transaction (expr_p, pre_p);
8632 break;
8634 case TRUTH_AND_EXPR:
8635 case TRUTH_OR_EXPR:
8636 case TRUTH_XOR_EXPR:
8638 tree orig_type = TREE_TYPE (*expr_p);
8639 tree new_type, xop0, xop1;
8640 *expr_p = gimple_boolify (*expr_p);
8641 new_type = TREE_TYPE (*expr_p);
8642 if (!useless_type_conversion_p (orig_type, new_type))
8644 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
8645 ret = GS_OK;
8646 break;
8649 /* Boolified binary truth expressions are semantically equivalent
8650 to bitwise binary expressions. Canonicalize them to the
8651 bitwise variant. */
8652 switch (TREE_CODE (*expr_p))
8654 case TRUTH_AND_EXPR:
8655 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
8656 break;
8657 case TRUTH_OR_EXPR:
8658 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
8659 break;
8660 case TRUTH_XOR_EXPR:
8661 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
8662 break;
8663 default:
8664 break;
8666 /* Now make sure that operands have compatible type to
8667 expression's new_type. */
8668 xop0 = TREE_OPERAND (*expr_p, 0);
8669 xop1 = TREE_OPERAND (*expr_p, 1);
8670 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
8671 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
8672 new_type,
8673 xop0);
8674 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
8675 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
8676 new_type,
8677 xop1);
8678 /* Continue classified as tcc_binary. */
8679 goto expr_2;
8682 case FMA_EXPR:
8683 case VEC_COND_EXPR:
8684 case VEC_PERM_EXPR:
8685 /* Classified as tcc_expression. */
8686 goto expr_3;
8688 case POINTER_PLUS_EXPR:
8690 enum gimplify_status r0, r1;
8691 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8692 post_p, is_gimple_val, fb_rvalue);
8693 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8694 post_p, is_gimple_val, fb_rvalue);
8695 recalculate_side_effects (*expr_p);
8696 ret = MIN (r0, r1);
8697 break;
8700 case CILK_SYNC_STMT:
8702 if (!fn_contains_cilk_spawn_p (cfun))
8704 error_at (EXPR_LOCATION (*expr_p),
8705 "expected %<_Cilk_spawn%> before %<_Cilk_sync%>");
8706 ret = GS_ERROR;
8708 else
8710 gimplify_cilk_sync (expr_p, pre_p);
8711 ret = GS_ALL_DONE;
8713 break;
8716 default:
8717 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
8719 case tcc_comparison:
8720 /* Handle comparison of objects of non scalar mode aggregates
8721 with a call to memcmp. It would be nice to only have to do
8722 this for variable-sized objects, but then we'd have to allow
8723 the same nest of reference nodes we allow for MODIFY_EXPR and
8724 that's too complex.
8726 Compare scalar mode aggregates as scalar mode values. Using
8727 memcmp for them would be very inefficient at best, and is
8728 plain wrong if bitfields are involved. */
8730 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
8732 /* Vector comparisons need no boolification. */
8733 if (TREE_CODE (type) == VECTOR_TYPE)
8734 goto expr_2;
8735 else if (!AGGREGATE_TYPE_P (type))
8737 tree org_type = TREE_TYPE (*expr_p);
8738 *expr_p = gimple_boolify (*expr_p);
8739 if (!useless_type_conversion_p (org_type,
8740 TREE_TYPE (*expr_p)))
8742 *expr_p = fold_convert_loc (input_location,
8743 org_type, *expr_p);
8744 ret = GS_OK;
8746 else
8747 goto expr_2;
8749 else if (TYPE_MODE (type) != BLKmode)
8750 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
8751 else
8752 ret = gimplify_variable_sized_compare (expr_p);
8754 break;
8757 /* If *EXPR_P does not need to be special-cased, handle it
8758 according to its class. */
8759 case tcc_unary:
8760 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8761 post_p, is_gimple_val, fb_rvalue);
8762 break;
8764 case tcc_binary:
8765 expr_2:
8767 enum gimplify_status r0, r1;
8769 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8770 post_p, is_gimple_val, fb_rvalue);
8771 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8772 post_p, is_gimple_val, fb_rvalue);
8774 ret = MIN (r0, r1);
8775 break;
8778 expr_3:
8780 enum gimplify_status r0, r1, r2;
8782 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8783 post_p, is_gimple_val, fb_rvalue);
8784 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8785 post_p, is_gimple_val, fb_rvalue);
8786 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
8787 post_p, is_gimple_val, fb_rvalue);
8789 ret = MIN (MIN (r0, r1), r2);
8790 break;
8793 case tcc_declaration:
8794 case tcc_constant:
8795 ret = GS_ALL_DONE;
8796 goto dont_recalculate;
8798 default:
8799 gcc_unreachable ();
8802 recalculate_side_effects (*expr_p);
8804 dont_recalculate:
8805 break;
8808 gcc_assert (*expr_p || ret != GS_OK);
8810 while (ret == GS_OK);
8812 /* If we encountered an error_mark somewhere nested inside, either
8813 stub out the statement or propagate the error back out. */
8814 if (ret == GS_ERROR)
8816 if (is_statement)
8817 *expr_p = NULL;
8818 goto out;
8821 /* This was only valid as a return value from the langhook, which
8822 we handled. Make sure it doesn't escape from any other context. */
8823 gcc_assert (ret != GS_UNHANDLED);
8825 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
8827 /* We aren't looking for a value, and we don't have a valid
8828 statement. If it doesn't have side-effects, throw it away. */
8829 if (!TREE_SIDE_EFFECTS (*expr_p))
8830 *expr_p = NULL;
8831 else if (!TREE_THIS_VOLATILE (*expr_p))
8833 /* This is probably a _REF that contains something nested that
8834 has side effects. Recurse through the operands to find it. */
8835 enum tree_code code = TREE_CODE (*expr_p);
8837 switch (code)
8839 case COMPONENT_REF:
8840 case REALPART_EXPR:
8841 case IMAGPART_EXPR:
8842 case VIEW_CONVERT_EXPR:
8843 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8844 gimple_test_f, fallback);
8845 break;
8847 case ARRAY_REF:
8848 case ARRAY_RANGE_REF:
8849 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8850 gimple_test_f, fallback);
8851 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
8852 gimple_test_f, fallback);
8853 break;
8855 default:
8856 /* Anything else with side-effects must be converted to
8857 a valid statement before we get here. */
8858 gcc_unreachable ();
8861 *expr_p = NULL;
8863 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
8864 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
8866 /* Historically, the compiler has treated a bare reference
8867 to a non-BLKmode volatile lvalue as forcing a load. */
8868 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
8870 /* Normally, we do not want to create a temporary for a
8871 TREE_ADDRESSABLE type because such a type should not be
8872 copied by bitwise-assignment. However, we make an
8873 exception here, as all we are doing here is ensuring that
8874 we read the bytes that make up the type. We use
8875 create_tmp_var_raw because create_tmp_var will abort when
8876 given a TREE_ADDRESSABLE type. */
8877 tree tmp = create_tmp_var_raw (type, "vol");
8878 gimple_add_tmp_var (tmp);
8879 gimplify_assign (tmp, *expr_p, pre_p);
8880 *expr_p = NULL;
8882 else
8883 /* We can't do anything useful with a volatile reference to
8884 an incomplete type, so just throw it away. Likewise for
8885 a BLKmode type, since any implicit inner load should
8886 already have been turned into an explicit one by the
8887 gimplification process. */
8888 *expr_p = NULL;
8891 /* If we are gimplifying at the statement level, we're done. Tack
8892 everything together and return. */
8893 if (fallback == fb_none || is_statement)
8895 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
8896 it out for GC to reclaim it. */
8897 *expr_p = NULL_TREE;
8899 if (!gimple_seq_empty_p (internal_pre)
8900 || !gimple_seq_empty_p (internal_post))
8902 gimplify_seq_add_seq (&internal_pre, internal_post);
8903 gimplify_seq_add_seq (pre_p, internal_pre);
8906 /* The result of gimplifying *EXPR_P is going to be the last few
8907 statements in *PRE_P and *POST_P. Add location information
8908 to all the statements that were added by the gimplification
8909 helpers. */
8910 if (!gimple_seq_empty_p (*pre_p))
8911 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
8913 if (!gimple_seq_empty_p (*post_p))
8914 annotate_all_with_location_after (*post_p, post_last_gsi,
8915 input_location);
8917 goto out;
8920 #ifdef ENABLE_GIMPLE_CHECKING
8921 if (*expr_p)
8923 enum tree_code code = TREE_CODE (*expr_p);
8924 /* These expressions should already be in gimple IR form. */
8925 gcc_assert (code != MODIFY_EXPR
8926 && code != ASM_EXPR
8927 && code != BIND_EXPR
8928 && code != CATCH_EXPR
8929 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
8930 && code != EH_FILTER_EXPR
8931 && code != GOTO_EXPR
8932 && code != LABEL_EXPR
8933 && code != LOOP_EXPR
8934 && code != SWITCH_EXPR
8935 && code != TRY_FINALLY_EXPR
8936 && code != OACC_PARALLEL
8937 && code != OACC_KERNELS
8938 && code != OACC_DATA
8939 && code != OACC_HOST_DATA
8940 && code != OACC_DECLARE
8941 && code != OACC_UPDATE
8942 && code != OACC_ENTER_DATA
8943 && code != OACC_EXIT_DATA
8944 && code != OACC_CACHE
8945 && code != OMP_CRITICAL
8946 && code != OMP_FOR
8947 && code != OACC_LOOP
8948 && code != OMP_MASTER
8949 && code != OMP_TASKGROUP
8950 && code != OMP_ORDERED
8951 && code != OMP_PARALLEL
8952 && code != OMP_SECTIONS
8953 && code != OMP_SECTION
8954 && code != OMP_SINGLE);
8956 #endif
8958 /* Otherwise we're gimplifying a subexpression, so the resulting
8959 value is interesting. If it's a valid operand that matches
8960 GIMPLE_TEST_F, we're done. Unless we are handling some
8961 post-effects internally; if that's the case, we need to copy into
8962 a temporary before adding the post-effects to POST_P. */
8963 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
8964 goto out;
8966 /* Otherwise, we need to create a new temporary for the gimplified
8967 expression. */
8969 /* We can't return an lvalue if we have an internal postqueue. The
8970 object the lvalue refers to would (probably) be modified by the
8971 postqueue; we need to copy the value out first, which means an
8972 rvalue. */
8973 if ((fallback & fb_lvalue)
8974 && gimple_seq_empty_p (internal_post)
8975 && is_gimple_addressable (*expr_p))
8977 /* An lvalue will do. Take the address of the expression, store it
8978 in a temporary, and replace the expression with an INDIRECT_REF of
8979 that temporary. */
8980 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
8981 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
8982 *expr_p = build_simple_mem_ref (tmp);
8984 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
8986 /* An rvalue will do. Assign the gimplified expression into a
8987 new temporary TMP and replace the original expression with
8988 TMP. First, make sure that the expression has a type so that
8989 it can be assigned into a temporary. */
8990 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
8991 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
8993 else
8995 #ifdef ENABLE_GIMPLE_CHECKING
8996 if (!(fallback & fb_mayfail))
8998 fprintf (stderr, "gimplification failed:\n");
8999 print_generic_expr (stderr, *expr_p, 0);
9000 debug_tree (*expr_p);
9001 internal_error ("gimplification failed");
9003 #endif
9004 gcc_assert (fallback & fb_mayfail);
9006 /* If this is an asm statement, and the user asked for the
9007 impossible, don't die. Fail and let gimplify_asm_expr
9008 issue an error. */
9009 ret = GS_ERROR;
9010 goto out;
9013 /* Make sure the temporary matches our predicate. */
9014 gcc_assert ((*gimple_test_f) (*expr_p));
9016 if (!gimple_seq_empty_p (internal_post))
9018 annotate_all_with_location (internal_post, input_location);
9019 gimplify_seq_add_seq (pre_p, internal_post);
9022 out:
9023 input_location = saved_location;
9024 return ret;
9027 /* Look through TYPE for variable-sized objects and gimplify each such
9028 size that we find. Add to LIST_P any statements generated. */
9030 void
9031 gimplify_type_sizes (tree type, gimple_seq *list_p)
9033 tree field, t;
9035 if (type == NULL || type == error_mark_node)
9036 return;
9038 /* We first do the main variant, then copy into any other variants. */
9039 type = TYPE_MAIN_VARIANT (type);
9041 /* Avoid infinite recursion. */
9042 if (TYPE_SIZES_GIMPLIFIED (type))
9043 return;
9045 TYPE_SIZES_GIMPLIFIED (type) = 1;
9047 switch (TREE_CODE (type))
9049 case INTEGER_TYPE:
9050 case ENUMERAL_TYPE:
9051 case BOOLEAN_TYPE:
9052 case REAL_TYPE:
9053 case FIXED_POINT_TYPE:
9054 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
9055 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
9057 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
9059 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
9060 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
9062 break;
9064 case ARRAY_TYPE:
9065 /* These types may not have declarations, so handle them here. */
9066 gimplify_type_sizes (TREE_TYPE (type), list_p);
9067 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
9068 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
9069 with assigned stack slots, for -O1+ -g they should be tracked
9070 by VTA. */
9071 if (!(TYPE_NAME (type)
9072 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
9073 && DECL_IGNORED_P (TYPE_NAME (type)))
9074 && TYPE_DOMAIN (type)
9075 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
9077 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
9078 if (t && TREE_CODE (t) == VAR_DECL && DECL_ARTIFICIAL (t))
9079 DECL_IGNORED_P (t) = 0;
9080 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
9081 if (t && TREE_CODE (t) == VAR_DECL && DECL_ARTIFICIAL (t))
9082 DECL_IGNORED_P (t) = 0;
9084 break;
9086 case RECORD_TYPE:
9087 case UNION_TYPE:
9088 case QUAL_UNION_TYPE:
9089 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
9090 if (TREE_CODE (field) == FIELD_DECL)
9092 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
9093 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
9094 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
9095 gimplify_type_sizes (TREE_TYPE (field), list_p);
9097 break;
9099 case POINTER_TYPE:
9100 case REFERENCE_TYPE:
9101 /* We used to recurse on the pointed-to type here, which turned out to
9102 be incorrect because its definition might refer to variables not
9103 yet initialized at this point if a forward declaration is involved.
9105 It was actually useful for anonymous pointed-to types to ensure
9106 that the sizes evaluation dominates every possible later use of the
9107 values. Restricting to such types here would be safe since there
9108 is no possible forward declaration around, but would introduce an
9109 undesirable middle-end semantic to anonymity. We then defer to
9110 front-ends the responsibility of ensuring that the sizes are
9111 evaluated both early and late enough, e.g. by attaching artificial
9112 type declarations to the tree. */
9113 break;
9115 default:
9116 break;
9119 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
9120 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
9122 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
9124 TYPE_SIZE (t) = TYPE_SIZE (type);
9125 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
9126 TYPE_SIZES_GIMPLIFIED (t) = 1;
9130 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
9131 a size or position, has had all of its SAVE_EXPRs evaluated.
9132 We add any required statements to *STMT_P. */
9134 void
9135 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
9137 tree expr = *expr_p;
9139 /* We don't do anything if the value isn't there, is constant, or contains
9140 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
9141 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
9142 will want to replace it with a new variable, but that will cause problems
9143 if this type is from outside the function. It's OK to have that here. */
9144 if (is_gimple_sizepos (expr))
9145 return;
9147 *expr_p = unshare_expr (expr);
9149 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue);
9152 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
9153 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
9154 is true, also gimplify the parameters. */
9156 gbind *
9157 gimplify_body (tree fndecl, bool do_parms)
9159 location_t saved_location = input_location;
9160 gimple_seq parm_stmts, seq;
9161 gimple outer_stmt;
9162 gbind *outer_bind;
9163 struct cgraph_node *cgn;
9165 timevar_push (TV_TREE_GIMPLIFY);
9167 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
9168 gimplification. */
9169 default_rtl_profile ();
9171 gcc_assert (gimplify_ctxp == NULL);
9172 push_gimplify_context ();
9174 if (flag_openacc || flag_openmp)
9176 gcc_assert (gimplify_omp_ctxp == NULL);
9177 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
9178 gimplify_omp_ctxp = new_omp_context (ORT_TARGET);
9181 /* Unshare most shared trees in the body and in that of any nested functions.
9182 It would seem we don't have to do this for nested functions because
9183 they are supposed to be output and then the outer function gimplified
9184 first, but the g++ front end doesn't always do it that way. */
9185 unshare_body (fndecl);
9186 unvisit_body (fndecl);
9188 cgn = cgraph_node::get (fndecl);
9189 if (cgn && cgn->origin)
9190 nonlocal_vlas = new hash_set<tree>;
9192 /* Make sure input_location isn't set to something weird. */
9193 input_location = DECL_SOURCE_LOCATION (fndecl);
9195 /* Resolve callee-copies. This has to be done before processing
9196 the body so that DECL_VALUE_EXPR gets processed correctly. */
9197 parm_stmts = do_parms ? gimplify_parameters () : NULL;
9199 /* Gimplify the function's body. */
9200 seq = NULL;
9201 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
9202 outer_stmt = gimple_seq_first_stmt (seq);
9203 if (!outer_stmt)
9205 outer_stmt = gimple_build_nop ();
9206 gimplify_seq_add_stmt (&seq, outer_stmt);
9209 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
9210 not the case, wrap everything in a GIMPLE_BIND to make it so. */
9211 if (gimple_code (outer_stmt) == GIMPLE_BIND
9212 && gimple_seq_first (seq) == gimple_seq_last (seq))
9213 outer_bind = as_a <gbind *> (outer_stmt);
9214 else
9215 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
9217 DECL_SAVED_TREE (fndecl) = NULL_TREE;
9219 /* If we had callee-copies statements, insert them at the beginning
9220 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
9221 if (!gimple_seq_empty_p (parm_stmts))
9223 tree parm;
9225 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
9226 gimple_bind_set_body (outer_bind, parm_stmts);
9228 for (parm = DECL_ARGUMENTS (current_function_decl);
9229 parm; parm = DECL_CHAIN (parm))
9230 if (DECL_HAS_VALUE_EXPR_P (parm))
9232 DECL_HAS_VALUE_EXPR_P (parm) = 0;
9233 DECL_IGNORED_P (parm) = 0;
9237 if (nonlocal_vlas)
9239 if (nonlocal_vla_vars)
9241 /* tree-nested.c may later on call declare_vars (..., true);
9242 which relies on BLOCK_VARS chain to be the tail of the
9243 gimple_bind_vars chain. Ensure we don't violate that
9244 assumption. */
9245 if (gimple_bind_block (outer_bind)
9246 == DECL_INITIAL (current_function_decl))
9247 declare_vars (nonlocal_vla_vars, outer_bind, true);
9248 else
9249 BLOCK_VARS (DECL_INITIAL (current_function_decl))
9250 = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl)),
9251 nonlocal_vla_vars);
9252 nonlocal_vla_vars = NULL_TREE;
9254 delete nonlocal_vlas;
9255 nonlocal_vlas = NULL;
9258 if ((flag_openacc || flag_openmp || flag_openmp_simd)
9259 && gimplify_omp_ctxp)
9261 delete_omp_context (gimplify_omp_ctxp);
9262 gimplify_omp_ctxp = NULL;
9265 pop_gimplify_context (outer_bind);
9266 gcc_assert (gimplify_ctxp == NULL);
9268 #ifdef ENABLE_CHECKING
9269 if (!seen_error ())
9270 verify_gimple_in_seq (gimple_bind_body (outer_bind));
9271 #endif
9273 timevar_pop (TV_TREE_GIMPLIFY);
9274 input_location = saved_location;
9276 return outer_bind;
9279 typedef char *char_p; /* For DEF_VEC_P. */
9281 /* Return whether we should exclude FNDECL from instrumentation. */
9283 static bool
9284 flag_instrument_functions_exclude_p (tree fndecl)
9286 vec<char_p> *v;
9288 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
9289 if (v && v->length () > 0)
9291 const char *name;
9292 int i;
9293 char *s;
9295 name = lang_hooks.decl_printable_name (fndecl, 0);
9296 FOR_EACH_VEC_ELT (*v, i, s)
9297 if (strstr (name, s) != NULL)
9298 return true;
9301 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
9302 if (v && v->length () > 0)
9304 const char *name;
9305 int i;
9306 char *s;
9308 name = DECL_SOURCE_FILE (fndecl);
9309 FOR_EACH_VEC_ELT (*v, i, s)
9310 if (strstr (name, s) != NULL)
9311 return true;
9314 return false;
9317 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
9318 node for the function we want to gimplify.
9320 Return the sequence of GIMPLE statements corresponding to the body
9321 of FNDECL. */
9323 void
9324 gimplify_function_tree (tree fndecl)
9326 tree parm, ret;
9327 gimple_seq seq;
9328 gbind *bind;
9330 gcc_assert (!gimple_body (fndecl));
9332 if (DECL_STRUCT_FUNCTION (fndecl))
9333 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
9334 else
9335 push_struct_function (fndecl);
9337 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
9338 if necessary. */
9339 cfun->curr_properties |= PROP_gimple_lva;
9341 for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = DECL_CHAIN (parm))
9343 /* Preliminarily mark non-addressed complex variables as eligible
9344 for promotion to gimple registers. We'll transform their uses
9345 as we find them. */
9346 if ((TREE_CODE (TREE_TYPE (parm)) == COMPLEX_TYPE
9347 || TREE_CODE (TREE_TYPE (parm)) == VECTOR_TYPE)
9348 && !TREE_THIS_VOLATILE (parm)
9349 && !needs_to_live_in_memory (parm))
9350 DECL_GIMPLE_REG_P (parm) = 1;
9353 ret = DECL_RESULT (fndecl);
9354 if ((TREE_CODE (TREE_TYPE (ret)) == COMPLEX_TYPE
9355 || TREE_CODE (TREE_TYPE (ret)) == VECTOR_TYPE)
9356 && !needs_to_live_in_memory (ret))
9357 DECL_GIMPLE_REG_P (ret) = 1;
9359 bind = gimplify_body (fndecl, true);
9361 /* The tree body of the function is no longer needed, replace it
9362 with the new GIMPLE body. */
9363 seq = NULL;
9364 gimple_seq_add_stmt (&seq, bind);
9365 gimple_set_body (fndecl, seq);
9367 /* If we're instrumenting function entry/exit, then prepend the call to
9368 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
9369 catch the exit hook. */
9370 /* ??? Add some way to ignore exceptions for this TFE. */
9371 if (flag_instrument_function_entry_exit
9372 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
9373 && !flag_instrument_functions_exclude_p (fndecl))
9375 tree x;
9376 gbind *new_bind;
9377 gimple tf;
9378 gimple_seq cleanup = NULL, body = NULL;
9379 tree tmp_var;
9380 gcall *call;
9382 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
9383 call = gimple_build_call (x, 1, integer_zero_node);
9384 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
9385 gimple_call_set_lhs (call, tmp_var);
9386 gimplify_seq_add_stmt (&cleanup, call);
9387 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
9388 call = gimple_build_call (x, 2,
9389 build_fold_addr_expr (current_function_decl),
9390 tmp_var);
9391 gimplify_seq_add_stmt (&cleanup, call);
9392 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
9394 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
9395 call = gimple_build_call (x, 1, integer_zero_node);
9396 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
9397 gimple_call_set_lhs (call, tmp_var);
9398 gimplify_seq_add_stmt (&body, call);
9399 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
9400 call = gimple_build_call (x, 2,
9401 build_fold_addr_expr (current_function_decl),
9402 tmp_var);
9403 gimplify_seq_add_stmt (&body, call);
9404 gimplify_seq_add_stmt (&body, tf);
9405 new_bind = gimple_build_bind (NULL, body, gimple_bind_block (bind));
9406 /* Clear the block for BIND, since it is no longer directly inside
9407 the function, but within a try block. */
9408 gimple_bind_set_block (bind, NULL);
9410 /* Replace the current function body with the body
9411 wrapped in the try/finally TF. */
9412 seq = NULL;
9413 gimple_seq_add_stmt (&seq, new_bind);
9414 gimple_set_body (fndecl, seq);
9415 bind = new_bind;
9418 if ((flag_sanitize & SANITIZE_THREAD) != 0
9419 && !lookup_attribute ("no_sanitize_thread", DECL_ATTRIBUTES (fndecl)))
9421 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
9422 gimple tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
9423 gbind *new_bind = gimple_build_bind (NULL, tf, gimple_bind_block (bind));
9424 /* Clear the block for BIND, since it is no longer directly inside
9425 the function, but within a try block. */
9426 gimple_bind_set_block (bind, NULL);
9427 /* Replace the current function body with the body
9428 wrapped in the try/finally TF. */
9429 seq = NULL;
9430 gimple_seq_add_stmt (&seq, new_bind);
9431 gimple_set_body (fndecl, seq);
9434 DECL_SAVED_TREE (fndecl) = NULL_TREE;
9435 cfun->curr_properties |= PROP_gimple_any;
9437 pop_cfun ();
9439 dump_function (TDI_generic, fndecl);
9442 /* Return a dummy expression of type TYPE in order to keep going after an
9443 error. */
9445 static tree
9446 dummy_object (tree type)
9448 tree t = build_int_cst (build_pointer_type (type), 0);
9449 return build2 (MEM_REF, type, t, t);
9452 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
9453 builtin function, but a very special sort of operator. */
9455 enum gimplify_status
9456 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
9457 gimple_seq *post_p ATTRIBUTE_UNUSED)
9459 tree promoted_type, have_va_type;
9460 tree valist = TREE_OPERAND (*expr_p, 0);
9461 tree type = TREE_TYPE (*expr_p);
9462 tree t, tag;
9463 location_t loc = EXPR_LOCATION (*expr_p);
9465 /* Verify that valist is of the proper type. */
9466 have_va_type = TREE_TYPE (valist);
9467 if (have_va_type == error_mark_node)
9468 return GS_ERROR;
9469 have_va_type = targetm.canonical_va_list_type (have_va_type);
9471 if (have_va_type == NULL_TREE)
9473 error_at (loc, "first argument to %<va_arg%> not of type %<va_list%>");
9474 return GS_ERROR;
9477 /* Generate a diagnostic for requesting data of a type that cannot
9478 be passed through `...' due to type promotion at the call site. */
9479 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
9480 != type)
9482 static bool gave_help;
9483 bool warned;
9485 /* Unfortunately, this is merely undefined, rather than a constraint
9486 violation, so we cannot make this an error. If this call is never
9487 executed, the program is still strictly conforming. */
9488 warned = warning_at (loc, 0,
9489 "%qT is promoted to %qT when passed through %<...%>",
9490 type, promoted_type);
9491 if (!gave_help && warned)
9493 gave_help = true;
9494 inform (loc, "(so you should pass %qT not %qT to %<va_arg%>)",
9495 promoted_type, type);
9498 /* We can, however, treat "undefined" any way we please.
9499 Call abort to encourage the user to fix the program. */
9500 if (warned)
9501 inform (loc, "if this code is reached, the program will abort");
9502 /* Before the abort, allow the evaluation of the va_list
9503 expression to exit or longjmp. */
9504 gimplify_and_add (valist, pre_p);
9505 t = build_call_expr_loc (loc,
9506 builtin_decl_implicit (BUILT_IN_TRAP), 0);
9507 gimplify_and_add (t, pre_p);
9509 /* This is dead code, but go ahead and finish so that the
9510 mode of the result comes out right. */
9511 *expr_p = dummy_object (type);
9512 return GS_ALL_DONE;
9515 tag = build_int_cst (build_pointer_type (type), 0);
9516 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 2, valist, tag);
9518 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
9519 needs to be expanded. */
9520 cfun->curr_properties &= ~PROP_gimple_lva;
9522 return GS_OK;
9525 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
9527 DST/SRC are the destination and source respectively. You can pass
9528 ungimplified trees in DST or SRC, in which case they will be
9529 converted to a gimple operand if necessary.
9531 This function returns the newly created GIMPLE_ASSIGN tuple. */
9533 gimple
9534 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
9536 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
9537 gimplify_and_add (t, seq_p);
9538 ggc_free (t);
9539 return gimple_seq_last_stmt (*seq_p);
9542 inline hashval_t
9543 gimplify_hasher::hash (const elt_t *p)
9545 tree t = p->val;
9546 return iterative_hash_expr (t, 0);
9549 inline bool
9550 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
9552 tree t1 = p1->val;
9553 tree t2 = p2->val;
9554 enum tree_code code = TREE_CODE (t1);
9556 if (TREE_CODE (t2) != code
9557 || TREE_TYPE (t1) != TREE_TYPE (t2))
9558 return false;
9560 if (!operand_equal_p (t1, t2, 0))
9561 return false;
9563 #ifdef ENABLE_CHECKING
9564 /* Only allow them to compare equal if they also hash equal; otherwise
9565 results are nondeterminate, and we fail bootstrap comparison. */
9566 gcc_assert (hash (p1) == hash (p2));
9567 #endif
9569 return true;