Replace enum omp_clause_map_kind with enum gomp_map_kind.
[official-gcc.git] / gcc / gimplify.c
blobcbbb9a7525ec6bce63c5dde834ab38050f3997b7
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 "hash-set.h"
27 #include "machmode.h"
28 #include "vec.h"
29 #include "double-int.h"
30 #include "input.h"
31 #include "alias.h"
32 #include "symtab.h"
33 #include "options.h"
34 #include "wide-int.h"
35 #include "inchash.h"
36 #include "tree.h"
37 #include "fold-const.h"
38 #include "expr.h"
39 #include "predict.h"
40 #include "tm.h"
41 #include "hard-reg-set.h"
42 #include "input.h"
43 #include "function.h"
44 #include "basic-block.h"
45 #include "tree-ssa-alias.h"
46 #include "internal-fn.h"
47 #include "gimple-fold.h"
48 #include "tree-eh.h"
49 #include "gimple-expr.h"
50 #include "is-a.h"
51 #include "gimple.h"
52 #include "gimplify.h"
53 #include "gimple-iterator.h"
54 #include "stringpool.h"
55 #include "calls.h"
56 #include "varasm.h"
57 #include "stor-layout.h"
58 #include "stmt.h"
59 #include "print-tree.h"
60 #include "tree-iterator.h"
61 #include "tree-inline.h"
62 #include "tree-pretty-print.h"
63 #include "langhooks.h"
64 #include "bitmap.h"
65 #include "gimple-ssa.h"
66 #include "hash-map.h"
67 #include "plugin-api.h"
68 #include "ipa-ref.h"
69 #include "cgraph.h"
70 #include "tree-cfg.h"
71 #include "tree-ssanames.h"
72 #include "tree-ssa.h"
73 #include "diagnostic-core.h"
74 #include "target.h"
75 #include "splay-tree.h"
76 #include "omp-low.h"
77 #include "gimple-low.h"
78 #include "cilk.h"
79 #include "gomp-constants.h"
81 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
82 #include "tree-pass.h" /* FIXME: only for PROP_gimple_any */
83 #include "builtins.h"
85 enum gimplify_omp_var_data
87 GOVD_SEEN = 1,
88 GOVD_EXPLICIT = 2,
89 GOVD_SHARED = 4,
90 GOVD_PRIVATE = 8,
91 GOVD_FIRSTPRIVATE = 16,
92 GOVD_LASTPRIVATE = 32,
93 GOVD_REDUCTION = 64,
94 GOVD_LOCAL = 128,
95 GOVD_MAP = 256,
96 GOVD_DEBUG_PRIVATE = 512,
97 GOVD_PRIVATE_OUTER_REF = 1024,
98 GOVD_LINEAR = 2048,
99 GOVD_ALIGNED = 4096,
101 /* Flag for GOVD_MAP: don't copy back. */
102 GOVD_MAP_TO_ONLY = 8192,
104 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
105 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
106 | GOVD_LOCAL)
110 enum omp_region_type
112 ORT_WORKSHARE = 0,
113 ORT_SIMD = 1,
114 ORT_PARALLEL = 2,
115 ORT_COMBINED_PARALLEL = 3,
116 ORT_TASK = 4,
117 ORT_UNTIED_TASK = 5,
118 ORT_TEAMS = 8,
119 /* Data region. */
120 ORT_TARGET_DATA = 16,
121 /* Data region with offloading. */
122 ORT_TARGET = 32
125 /* Gimplify hashtable helper. */
127 struct gimplify_hasher : typed_free_remove <elt_t>
129 typedef elt_t value_type;
130 typedef elt_t compare_type;
131 static inline hashval_t hash (const value_type *);
132 static inline bool equal (const value_type *, const compare_type *);
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 if (cleared)
3989 /* Zap the CONSTRUCTOR element list, which simplifies this case.
3990 Note that we still have to gimplify, in order to handle the
3991 case of variable sized types. Avoid shared tree structures. */
3992 CONSTRUCTOR_ELTS (ctor) = NULL;
3993 TREE_SIDE_EFFECTS (ctor) = 0;
3994 object = unshare_expr (object);
3995 gimplify_stmt (expr_p, pre_p);
3998 /* If we have not block cleared the object, or if there are nonzero
3999 elements in the constructor, add assignments to the individual
4000 scalar fields of the object. */
4001 if (!cleared || num_nonzero_elements > 0)
4002 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
4004 *expr_p = NULL_TREE;
4006 break;
4008 case COMPLEX_TYPE:
4010 tree r, i;
4012 if (notify_temp_creation)
4013 return GS_OK;
4015 /* Extract the real and imaginary parts out of the ctor. */
4016 gcc_assert (elts->length () == 2);
4017 r = (*elts)[0].value;
4018 i = (*elts)[1].value;
4019 if (r == NULL || i == NULL)
4021 tree zero = build_zero_cst (TREE_TYPE (type));
4022 if (r == NULL)
4023 r = zero;
4024 if (i == NULL)
4025 i = zero;
4028 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
4029 represent creation of a complex value. */
4030 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
4032 ctor = build_complex (type, r, i);
4033 TREE_OPERAND (*expr_p, 1) = ctor;
4035 else
4037 ctor = build2 (COMPLEX_EXPR, type, r, i);
4038 TREE_OPERAND (*expr_p, 1) = ctor;
4039 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
4040 pre_p,
4041 post_p,
4042 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
4043 fb_rvalue);
4046 break;
4048 case VECTOR_TYPE:
4050 unsigned HOST_WIDE_INT ix;
4051 constructor_elt *ce;
4053 if (notify_temp_creation)
4054 return GS_OK;
4056 /* Go ahead and simplify constant constructors to VECTOR_CST. */
4057 if (TREE_CONSTANT (ctor))
4059 bool constant_p = true;
4060 tree value;
4062 /* Even when ctor is constant, it might contain non-*_CST
4063 elements, such as addresses or trapping values like
4064 1.0/0.0 - 1.0/0.0. Such expressions don't belong
4065 in VECTOR_CST nodes. */
4066 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
4067 if (!CONSTANT_CLASS_P (value))
4069 constant_p = false;
4070 break;
4073 if (constant_p)
4075 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
4076 break;
4079 TREE_CONSTANT (ctor) = 0;
4082 /* Vector types use CONSTRUCTOR all the way through gimple
4083 compilation as a general initializer. */
4084 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
4086 enum gimplify_status tret;
4087 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
4088 fb_rvalue);
4089 if (tret == GS_ERROR)
4090 ret = GS_ERROR;
4092 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
4093 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
4095 break;
4097 default:
4098 /* So how did we get a CONSTRUCTOR for a scalar type? */
4099 gcc_unreachable ();
4102 if (ret == GS_ERROR)
4103 return GS_ERROR;
4104 else if (want_value)
4106 *expr_p = object;
4107 return GS_OK;
4109 else
4111 /* If we have gimplified both sides of the initializer but have
4112 not emitted an assignment, do so now. */
4113 if (*expr_p)
4115 tree lhs = TREE_OPERAND (*expr_p, 0);
4116 tree rhs = TREE_OPERAND (*expr_p, 1);
4117 gassign *init = gimple_build_assign (lhs, rhs);
4118 gimplify_seq_add_stmt (pre_p, init);
4119 *expr_p = NULL;
4122 return GS_ALL_DONE;
4126 /* Given a pointer value OP0, return a simplified version of an
4127 indirection through OP0, or NULL_TREE if no simplification is
4128 possible. This may only be applied to a rhs of an expression.
4129 Note that the resulting type may be different from the type pointed
4130 to in the sense that it is still compatible from the langhooks
4131 point of view. */
4133 static tree
4134 gimple_fold_indirect_ref_rhs (tree t)
4136 return gimple_fold_indirect_ref (t);
4139 /* Subroutine of gimplify_modify_expr to do simplifications of
4140 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
4141 something changes. */
4143 static enum gimplify_status
4144 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
4145 gimple_seq *pre_p, gimple_seq *post_p,
4146 bool want_value)
4148 enum gimplify_status ret = GS_UNHANDLED;
4149 bool changed;
4153 changed = false;
4154 switch (TREE_CODE (*from_p))
4156 case VAR_DECL:
4157 /* If we're assigning from a read-only variable initialized with
4158 a constructor, do the direct assignment from the constructor,
4159 but only if neither source nor target are volatile since this
4160 latter assignment might end up being done on a per-field basis. */
4161 if (DECL_INITIAL (*from_p)
4162 && TREE_READONLY (*from_p)
4163 && !TREE_THIS_VOLATILE (*from_p)
4164 && !TREE_THIS_VOLATILE (*to_p)
4165 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR)
4167 tree old_from = *from_p;
4168 enum gimplify_status subret;
4170 /* Move the constructor into the RHS. */
4171 *from_p = unshare_expr (DECL_INITIAL (*from_p));
4173 /* Let's see if gimplify_init_constructor will need to put
4174 it in memory. */
4175 subret = gimplify_init_constructor (expr_p, NULL, NULL,
4176 false, true);
4177 if (subret == GS_ERROR)
4179 /* If so, revert the change. */
4180 *from_p = old_from;
4182 else
4184 ret = GS_OK;
4185 changed = true;
4188 break;
4189 case INDIRECT_REF:
4191 /* If we have code like
4193 *(const A*)(A*)&x
4195 where the type of "x" is a (possibly cv-qualified variant
4196 of "A"), treat the entire expression as identical to "x".
4197 This kind of code arises in C++ when an object is bound
4198 to a const reference, and if "x" is a TARGET_EXPR we want
4199 to take advantage of the optimization below. */
4200 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
4201 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
4202 if (t)
4204 if (TREE_THIS_VOLATILE (t) != volatile_p)
4206 if (TREE_CODE_CLASS (TREE_CODE (t)) == tcc_declaration)
4207 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
4208 build_fold_addr_expr (t));
4209 if (REFERENCE_CLASS_P (t))
4210 TREE_THIS_VOLATILE (t) = volatile_p;
4212 *from_p = t;
4213 ret = GS_OK;
4214 changed = true;
4216 break;
4219 case TARGET_EXPR:
4221 /* If we are initializing something from a TARGET_EXPR, strip the
4222 TARGET_EXPR and initialize it directly, if possible. This can't
4223 be done if the initializer is void, since that implies that the
4224 temporary is set in some non-trivial way.
4226 ??? What about code that pulls out the temp and uses it
4227 elsewhere? I think that such code never uses the TARGET_EXPR as
4228 an initializer. If I'm wrong, we'll die because the temp won't
4229 have any RTL. In that case, I guess we'll need to replace
4230 references somehow. */
4231 tree init = TARGET_EXPR_INITIAL (*from_p);
4233 if (init
4234 && !VOID_TYPE_P (TREE_TYPE (init)))
4236 *from_p = init;
4237 ret = GS_OK;
4238 changed = true;
4241 break;
4243 case COMPOUND_EXPR:
4244 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
4245 caught. */
4246 gimplify_compound_expr (from_p, pre_p, true);
4247 ret = GS_OK;
4248 changed = true;
4249 break;
4251 case CONSTRUCTOR:
4252 /* If we already made some changes, let the front end have a
4253 crack at this before we break it down. */
4254 if (ret != GS_UNHANDLED)
4255 break;
4256 /* If we're initializing from a CONSTRUCTOR, break this into
4257 individual MODIFY_EXPRs. */
4258 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
4259 false);
4261 case COND_EXPR:
4262 /* If we're assigning to a non-register type, push the assignment
4263 down into the branches. This is mandatory for ADDRESSABLE types,
4264 since we cannot generate temporaries for such, but it saves a
4265 copy in other cases as well. */
4266 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
4268 /* This code should mirror the code in gimplify_cond_expr. */
4269 enum tree_code code = TREE_CODE (*expr_p);
4270 tree cond = *from_p;
4271 tree result = *to_p;
4273 ret = gimplify_expr (&result, pre_p, post_p,
4274 is_gimple_lvalue, fb_lvalue);
4275 if (ret != GS_ERROR)
4276 ret = GS_OK;
4278 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
4279 TREE_OPERAND (cond, 1)
4280 = build2 (code, void_type_node, result,
4281 TREE_OPERAND (cond, 1));
4282 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
4283 TREE_OPERAND (cond, 2)
4284 = build2 (code, void_type_node, unshare_expr (result),
4285 TREE_OPERAND (cond, 2));
4287 TREE_TYPE (cond) = void_type_node;
4288 recalculate_side_effects (cond);
4290 if (want_value)
4292 gimplify_and_add (cond, pre_p);
4293 *expr_p = unshare_expr (result);
4295 else
4296 *expr_p = cond;
4297 return ret;
4299 break;
4301 case CALL_EXPR:
4302 /* For calls that return in memory, give *to_p as the CALL_EXPR's
4303 return slot so that we don't generate a temporary. */
4304 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
4305 && aggregate_value_p (*from_p, *from_p))
4307 bool use_target;
4309 if (!(rhs_predicate_for (*to_p))(*from_p))
4310 /* If we need a temporary, *to_p isn't accurate. */
4311 use_target = false;
4312 /* It's OK to use the return slot directly unless it's an NRV. */
4313 else if (TREE_CODE (*to_p) == RESULT_DECL
4314 && DECL_NAME (*to_p) == NULL_TREE
4315 && needs_to_live_in_memory (*to_p))
4316 use_target = true;
4317 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
4318 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
4319 /* Don't force regs into memory. */
4320 use_target = false;
4321 else if (TREE_CODE (*expr_p) == INIT_EXPR)
4322 /* It's OK to use the target directly if it's being
4323 initialized. */
4324 use_target = true;
4325 else if (variably_modified_type_p (TREE_TYPE (*to_p), NULL_TREE))
4326 /* Always use the target and thus RSO for variable-sized types.
4327 GIMPLE cannot deal with a variable-sized assignment
4328 embedded in a call statement. */
4329 use_target = true;
4330 else if (TREE_CODE (*to_p) != SSA_NAME
4331 && (!is_gimple_variable (*to_p)
4332 || needs_to_live_in_memory (*to_p)))
4333 /* Don't use the original target if it's already addressable;
4334 if its address escapes, and the called function uses the
4335 NRV optimization, a conforming program could see *to_p
4336 change before the called function returns; see c++/19317.
4337 When optimizing, the return_slot pass marks more functions
4338 as safe after we have escape info. */
4339 use_target = false;
4340 else
4341 use_target = true;
4343 if (use_target)
4345 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
4346 mark_addressable (*to_p);
4349 break;
4351 case WITH_SIZE_EXPR:
4352 /* Likewise for calls that return an aggregate of non-constant size,
4353 since we would not be able to generate a temporary at all. */
4354 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
4356 *from_p = TREE_OPERAND (*from_p, 0);
4357 /* We don't change ret in this case because the
4358 WITH_SIZE_EXPR might have been added in
4359 gimplify_modify_expr, so returning GS_OK would lead to an
4360 infinite loop. */
4361 changed = true;
4363 break;
4365 /* If we're initializing from a container, push the initialization
4366 inside it. */
4367 case CLEANUP_POINT_EXPR:
4368 case BIND_EXPR:
4369 case STATEMENT_LIST:
4371 tree wrap = *from_p;
4372 tree t;
4374 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
4375 fb_lvalue);
4376 if (ret != GS_ERROR)
4377 ret = GS_OK;
4379 t = voidify_wrapper_expr (wrap, *expr_p);
4380 gcc_assert (t == *expr_p);
4382 if (want_value)
4384 gimplify_and_add (wrap, pre_p);
4385 *expr_p = unshare_expr (*to_p);
4387 else
4388 *expr_p = wrap;
4389 return GS_OK;
4392 case COMPOUND_LITERAL_EXPR:
4394 tree complit = TREE_OPERAND (*expr_p, 1);
4395 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
4396 tree decl = DECL_EXPR_DECL (decl_s);
4397 tree init = DECL_INITIAL (decl);
4399 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
4400 into struct T x = { 0, 1, 2 } if the address of the
4401 compound literal has never been taken. */
4402 if (!TREE_ADDRESSABLE (complit)
4403 && !TREE_ADDRESSABLE (decl)
4404 && init)
4406 *expr_p = copy_node (*expr_p);
4407 TREE_OPERAND (*expr_p, 1) = init;
4408 return GS_OK;
4412 default:
4413 break;
4416 while (changed);
4418 return ret;
4422 /* Return true if T looks like a valid GIMPLE statement. */
4424 static bool
4425 is_gimple_stmt (tree t)
4427 const enum tree_code code = TREE_CODE (t);
4429 switch (code)
4431 case NOP_EXPR:
4432 /* The only valid NOP_EXPR is the empty statement. */
4433 return IS_EMPTY_STMT (t);
4435 case BIND_EXPR:
4436 case COND_EXPR:
4437 /* These are only valid if they're void. */
4438 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
4440 case SWITCH_EXPR:
4441 case GOTO_EXPR:
4442 case RETURN_EXPR:
4443 case LABEL_EXPR:
4444 case CASE_LABEL_EXPR:
4445 case TRY_CATCH_EXPR:
4446 case TRY_FINALLY_EXPR:
4447 case EH_FILTER_EXPR:
4448 case CATCH_EXPR:
4449 case ASM_EXPR:
4450 case STATEMENT_LIST:
4451 case OACC_PARALLEL:
4452 case OACC_KERNELS:
4453 case OACC_DATA:
4454 case OACC_HOST_DATA:
4455 case OACC_DECLARE:
4456 case OACC_UPDATE:
4457 case OACC_ENTER_DATA:
4458 case OACC_EXIT_DATA:
4459 case OACC_CACHE:
4460 case OMP_PARALLEL:
4461 case OMP_FOR:
4462 case OMP_SIMD:
4463 case CILK_SIMD:
4464 case OMP_DISTRIBUTE:
4465 case OACC_LOOP:
4466 case OMP_SECTIONS:
4467 case OMP_SECTION:
4468 case OMP_SINGLE:
4469 case OMP_MASTER:
4470 case OMP_TASKGROUP:
4471 case OMP_ORDERED:
4472 case OMP_CRITICAL:
4473 case OMP_TASK:
4474 /* These are always void. */
4475 return true;
4477 case CALL_EXPR:
4478 case MODIFY_EXPR:
4479 case PREDICT_EXPR:
4480 /* These are valid regardless of their type. */
4481 return true;
4483 default:
4484 return false;
4489 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
4490 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
4491 DECL_GIMPLE_REG_P set.
4493 IMPORTANT NOTE: This promotion is performed by introducing a load of the
4494 other, unmodified part of the complex object just before the total store.
4495 As a consequence, if the object is still uninitialized, an undefined value
4496 will be loaded into a register, which may result in a spurious exception
4497 if the register is floating-point and the value happens to be a signaling
4498 NaN for example. Then the fully-fledged complex operations lowering pass
4499 followed by a DCE pass are necessary in order to fix things up. */
4501 static enum gimplify_status
4502 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
4503 bool want_value)
4505 enum tree_code code, ocode;
4506 tree lhs, rhs, new_rhs, other, realpart, imagpart;
4508 lhs = TREE_OPERAND (*expr_p, 0);
4509 rhs = TREE_OPERAND (*expr_p, 1);
4510 code = TREE_CODE (lhs);
4511 lhs = TREE_OPERAND (lhs, 0);
4513 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
4514 other = build1 (ocode, TREE_TYPE (rhs), lhs);
4515 TREE_NO_WARNING (other) = 1;
4516 other = get_formal_tmp_var (other, pre_p);
4518 realpart = code == REALPART_EXPR ? rhs : other;
4519 imagpart = code == REALPART_EXPR ? other : rhs;
4521 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
4522 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
4523 else
4524 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
4526 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
4527 *expr_p = (want_value) ? rhs : NULL_TREE;
4529 return GS_ALL_DONE;
4532 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
4534 modify_expr
4535 : varname '=' rhs
4536 | '*' ID '=' rhs
4538 PRE_P points to the list where side effects that must happen before
4539 *EXPR_P should be stored.
4541 POST_P points to the list where side effects that must happen after
4542 *EXPR_P should be stored.
4544 WANT_VALUE is nonzero iff we want to use the value of this expression
4545 in another expression. */
4547 static enum gimplify_status
4548 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4549 bool want_value)
4551 tree *from_p = &TREE_OPERAND (*expr_p, 1);
4552 tree *to_p = &TREE_OPERAND (*expr_p, 0);
4553 enum gimplify_status ret = GS_UNHANDLED;
4554 gimple assign;
4555 location_t loc = EXPR_LOCATION (*expr_p);
4556 gimple_stmt_iterator gsi;
4558 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
4559 || TREE_CODE (*expr_p) == INIT_EXPR);
4561 /* Trying to simplify a clobber using normal logic doesn't work,
4562 so handle it here. */
4563 if (TREE_CLOBBER_P (*from_p))
4565 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
4566 if (ret == GS_ERROR)
4567 return ret;
4568 gcc_assert (!want_value
4569 && (TREE_CODE (*to_p) == VAR_DECL
4570 || TREE_CODE (*to_p) == MEM_REF));
4571 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
4572 *expr_p = NULL;
4573 return GS_ALL_DONE;
4576 /* Insert pointer conversions required by the middle-end that are not
4577 required by the frontend. This fixes middle-end type checking for
4578 for example gcc.dg/redecl-6.c. */
4579 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
4581 STRIP_USELESS_TYPE_CONVERSION (*from_p);
4582 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
4583 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
4586 /* See if any simplifications can be done based on what the RHS is. */
4587 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
4588 want_value);
4589 if (ret != GS_UNHANDLED)
4590 return ret;
4592 /* For zero sized types only gimplify the left hand side and right hand
4593 side as statements and throw away the assignment. Do this after
4594 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
4595 types properly. */
4596 if (zero_sized_type (TREE_TYPE (*from_p)) && !want_value)
4598 gimplify_stmt (from_p, pre_p);
4599 gimplify_stmt (to_p, pre_p);
4600 *expr_p = NULL_TREE;
4601 return GS_ALL_DONE;
4604 /* If the value being copied is of variable width, compute the length
4605 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
4606 before gimplifying any of the operands so that we can resolve any
4607 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
4608 the size of the expression to be copied, not of the destination, so
4609 that is what we must do here. */
4610 maybe_with_size_expr (from_p);
4612 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
4613 if (ret == GS_ERROR)
4614 return ret;
4616 /* As a special case, we have to temporarily allow for assignments
4617 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
4618 a toplevel statement, when gimplifying the GENERIC expression
4619 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
4620 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
4622 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
4623 prevent gimplify_expr from trying to create a new temporary for
4624 foo's LHS, we tell it that it should only gimplify until it
4625 reaches the CALL_EXPR. On return from gimplify_expr, the newly
4626 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
4627 and all we need to do here is set 'a' to be its LHS. */
4628 ret = gimplify_expr (from_p, pre_p, post_p, rhs_predicate_for (*to_p),
4629 fb_rvalue);
4630 if (ret == GS_ERROR)
4631 return ret;
4633 /* Now see if the above changed *from_p to something we handle specially. */
4634 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
4635 want_value);
4636 if (ret != GS_UNHANDLED)
4637 return ret;
4639 /* If we've got a variable sized assignment between two lvalues (i.e. does
4640 not involve a call), then we can make things a bit more straightforward
4641 by converting the assignment to memcpy or memset. */
4642 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
4644 tree from = TREE_OPERAND (*from_p, 0);
4645 tree size = TREE_OPERAND (*from_p, 1);
4647 if (TREE_CODE (from) == CONSTRUCTOR)
4648 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
4650 if (is_gimple_addressable (from))
4652 *from_p = from;
4653 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
4654 pre_p);
4658 /* Transform partial stores to non-addressable complex variables into
4659 total stores. This allows us to use real instead of virtual operands
4660 for these variables, which improves optimization. */
4661 if ((TREE_CODE (*to_p) == REALPART_EXPR
4662 || TREE_CODE (*to_p) == IMAGPART_EXPR)
4663 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
4664 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
4666 /* Try to alleviate the effects of the gimplification creating artificial
4667 temporaries (see for example is_gimple_reg_rhs) on the debug info. */
4668 if (!gimplify_ctxp->into_ssa
4669 && TREE_CODE (*from_p) == VAR_DECL
4670 && DECL_IGNORED_P (*from_p)
4671 && DECL_P (*to_p)
4672 && !DECL_IGNORED_P (*to_p))
4674 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
4675 DECL_NAME (*from_p)
4676 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
4677 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
4678 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
4681 if (want_value && TREE_THIS_VOLATILE (*to_p))
4682 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
4684 if (TREE_CODE (*from_p) == CALL_EXPR)
4686 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
4687 instead of a GIMPLE_ASSIGN. */
4688 gcall *call_stmt;
4689 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
4691 /* Gimplify internal functions created in the FEs. */
4692 int nargs = call_expr_nargs (*from_p), i;
4693 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
4694 auto_vec<tree> vargs (nargs);
4696 for (i = 0; i < nargs; i++)
4698 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
4699 EXPR_LOCATION (*from_p));
4700 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
4702 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
4703 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
4705 else
4707 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
4708 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
4709 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
4710 tree fndecl = get_callee_fndecl (*from_p);
4711 if (fndecl
4712 && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL
4713 && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_EXPECT
4714 && call_expr_nargs (*from_p) == 3)
4715 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
4716 CALL_EXPR_ARG (*from_p, 0),
4717 CALL_EXPR_ARG (*from_p, 1),
4718 CALL_EXPR_ARG (*from_p, 2));
4719 else
4721 call_stmt = gimple_build_call_from_tree (*from_p);
4722 gimple_call_set_fntype (call_stmt, TREE_TYPE (fnptrtype));
4725 notice_special_calls (call_stmt);
4726 if (!gimple_call_noreturn_p (call_stmt))
4727 gimple_call_set_lhs (call_stmt, *to_p);
4728 assign = call_stmt;
4730 else
4732 assign = gimple_build_assign (*to_p, *from_p);
4733 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
4736 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
4738 /* We should have got an SSA name from the start. */
4739 gcc_assert (TREE_CODE (*to_p) == SSA_NAME);
4742 gimplify_seq_add_stmt (pre_p, assign);
4743 gsi = gsi_last (*pre_p);
4744 maybe_fold_stmt (&gsi);
4746 if (want_value)
4748 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
4749 return GS_OK;
4751 else
4752 *expr_p = NULL;
4754 return GS_ALL_DONE;
4757 /* Gimplify a comparison between two variable-sized objects. Do this
4758 with a call to BUILT_IN_MEMCMP. */
4760 static enum gimplify_status
4761 gimplify_variable_sized_compare (tree *expr_p)
4763 location_t loc = EXPR_LOCATION (*expr_p);
4764 tree op0 = TREE_OPERAND (*expr_p, 0);
4765 tree op1 = TREE_OPERAND (*expr_p, 1);
4766 tree t, arg, dest, src, expr;
4768 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
4769 arg = unshare_expr (arg);
4770 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
4771 src = build_fold_addr_expr_loc (loc, op1);
4772 dest = build_fold_addr_expr_loc (loc, op0);
4773 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
4774 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
4776 expr
4777 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
4778 SET_EXPR_LOCATION (expr, loc);
4779 *expr_p = expr;
4781 return GS_OK;
4784 /* Gimplify a comparison between two aggregate objects of integral scalar
4785 mode as a comparison between the bitwise equivalent scalar values. */
4787 static enum gimplify_status
4788 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
4790 location_t loc = EXPR_LOCATION (*expr_p);
4791 tree op0 = TREE_OPERAND (*expr_p, 0);
4792 tree op1 = TREE_OPERAND (*expr_p, 1);
4794 tree type = TREE_TYPE (op0);
4795 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
4797 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
4798 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
4800 *expr_p
4801 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
4803 return GS_OK;
4806 /* Gimplify an expression sequence. This function gimplifies each
4807 expression and rewrites the original expression with the last
4808 expression of the sequence in GIMPLE form.
4810 PRE_P points to the list where the side effects for all the
4811 expressions in the sequence will be emitted.
4813 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
4815 static enum gimplify_status
4816 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
4818 tree t = *expr_p;
4822 tree *sub_p = &TREE_OPERAND (t, 0);
4824 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
4825 gimplify_compound_expr (sub_p, pre_p, false);
4826 else
4827 gimplify_stmt (sub_p, pre_p);
4829 t = TREE_OPERAND (t, 1);
4831 while (TREE_CODE (t) == COMPOUND_EXPR);
4833 *expr_p = t;
4834 if (want_value)
4835 return GS_OK;
4836 else
4838 gimplify_stmt (expr_p, pre_p);
4839 return GS_ALL_DONE;
4843 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
4844 gimplify. After gimplification, EXPR_P will point to a new temporary
4845 that holds the original value of the SAVE_EXPR node.
4847 PRE_P points to the list where side effects that must happen before
4848 *EXPR_P should be stored. */
4850 static enum gimplify_status
4851 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
4853 enum gimplify_status ret = GS_ALL_DONE;
4854 tree val;
4856 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
4857 val = TREE_OPERAND (*expr_p, 0);
4859 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
4860 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
4862 /* The operand may be a void-valued expression such as SAVE_EXPRs
4863 generated by the Java frontend for class initialization. It is
4864 being executed only for its side-effects. */
4865 if (TREE_TYPE (val) == void_type_node)
4867 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
4868 is_gimple_stmt, fb_none);
4869 val = NULL;
4871 else
4872 val = get_initialized_tmp_var (val, pre_p, post_p);
4874 TREE_OPERAND (*expr_p, 0) = val;
4875 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
4878 *expr_p = val;
4880 return ret;
4883 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
4885 unary_expr
4886 : ...
4887 | '&' varname
4890 PRE_P points to the list where side effects that must happen before
4891 *EXPR_P should be stored.
4893 POST_P points to the list where side effects that must happen after
4894 *EXPR_P should be stored. */
4896 static enum gimplify_status
4897 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
4899 tree expr = *expr_p;
4900 tree op0 = TREE_OPERAND (expr, 0);
4901 enum gimplify_status ret;
4902 location_t loc = EXPR_LOCATION (*expr_p);
4904 switch (TREE_CODE (op0))
4906 case INDIRECT_REF:
4907 do_indirect_ref:
4908 /* Check if we are dealing with an expression of the form '&*ptr'.
4909 While the front end folds away '&*ptr' into 'ptr', these
4910 expressions may be generated internally by the compiler (e.g.,
4911 builtins like __builtin_va_end). */
4912 /* Caution: the silent array decomposition semantics we allow for
4913 ADDR_EXPR means we can't always discard the pair. */
4914 /* Gimplification of the ADDR_EXPR operand may drop
4915 cv-qualification conversions, so make sure we add them if
4916 needed. */
4918 tree op00 = TREE_OPERAND (op0, 0);
4919 tree t_expr = TREE_TYPE (expr);
4920 tree t_op00 = TREE_TYPE (op00);
4922 if (!useless_type_conversion_p (t_expr, t_op00))
4923 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
4924 *expr_p = op00;
4925 ret = GS_OK;
4927 break;
4929 case VIEW_CONVERT_EXPR:
4930 /* Take the address of our operand and then convert it to the type of
4931 this ADDR_EXPR.
4933 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
4934 all clear. The impact of this transformation is even less clear. */
4936 /* If the operand is a useless conversion, look through it. Doing so
4937 guarantees that the ADDR_EXPR and its operand will remain of the
4938 same type. */
4939 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
4940 op0 = TREE_OPERAND (op0, 0);
4942 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
4943 build_fold_addr_expr_loc (loc,
4944 TREE_OPERAND (op0, 0)));
4945 ret = GS_OK;
4946 break;
4948 default:
4949 /* We use fb_either here because the C frontend sometimes takes
4950 the address of a call that returns a struct; see
4951 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
4952 the implied temporary explicit. */
4954 /* Make the operand addressable. */
4955 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
4956 is_gimple_addressable, fb_either);
4957 if (ret == GS_ERROR)
4958 break;
4960 /* Then mark it. Beware that it may not be possible to do so directly
4961 if a temporary has been created by the gimplification. */
4962 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
4964 op0 = TREE_OPERAND (expr, 0);
4966 /* For various reasons, the gimplification of the expression
4967 may have made a new INDIRECT_REF. */
4968 if (TREE_CODE (op0) == INDIRECT_REF)
4969 goto do_indirect_ref;
4971 mark_addressable (TREE_OPERAND (expr, 0));
4973 /* The FEs may end up building ADDR_EXPRs early on a decl with
4974 an incomplete type. Re-build ADDR_EXPRs in canonical form
4975 here. */
4976 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
4977 *expr_p = build_fold_addr_expr (op0);
4979 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
4980 recompute_tree_invariant_for_addr_expr (*expr_p);
4982 /* If we re-built the ADDR_EXPR add a conversion to the original type
4983 if required. */
4984 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
4985 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
4987 break;
4990 return ret;
4993 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
4994 value; output operands should be a gimple lvalue. */
4996 static enum gimplify_status
4997 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
4999 tree expr;
5000 int noutputs;
5001 const char **oconstraints;
5002 int i;
5003 tree link;
5004 const char *constraint;
5005 bool allows_mem, allows_reg, is_inout;
5006 enum gimplify_status ret, tret;
5007 gasm *stmt;
5008 vec<tree, va_gc> *inputs;
5009 vec<tree, va_gc> *outputs;
5010 vec<tree, va_gc> *clobbers;
5011 vec<tree, va_gc> *labels;
5012 tree link_next;
5014 expr = *expr_p;
5015 noutputs = list_length (ASM_OUTPUTS (expr));
5016 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
5018 inputs = NULL;
5019 outputs = NULL;
5020 clobbers = NULL;
5021 labels = NULL;
5023 ret = GS_ALL_DONE;
5024 link_next = NULL_TREE;
5025 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
5027 bool ok;
5028 size_t constraint_len;
5030 link_next = TREE_CHAIN (link);
5032 oconstraints[i]
5033 = constraint
5034 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
5035 constraint_len = strlen (constraint);
5036 if (constraint_len == 0)
5037 continue;
5039 ok = parse_output_constraint (&constraint, i, 0, 0,
5040 &allows_mem, &allows_reg, &is_inout);
5041 if (!ok)
5043 ret = GS_ERROR;
5044 is_inout = false;
5047 if (!allows_reg && allows_mem)
5048 mark_addressable (TREE_VALUE (link));
5050 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5051 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
5052 fb_lvalue | fb_mayfail);
5053 if (tret == GS_ERROR)
5055 error ("invalid lvalue in asm output %d", i);
5056 ret = tret;
5059 vec_safe_push (outputs, link);
5060 TREE_CHAIN (link) = NULL_TREE;
5062 if (is_inout)
5064 /* An input/output operand. To give the optimizers more
5065 flexibility, split it into separate input and output
5066 operands. */
5067 tree input;
5068 char buf[10];
5070 /* Turn the in/out constraint into an output constraint. */
5071 char *p = xstrdup (constraint);
5072 p[0] = '=';
5073 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
5075 /* And add a matching input constraint. */
5076 if (allows_reg)
5078 sprintf (buf, "%d", i);
5080 /* If there are multiple alternatives in the constraint,
5081 handle each of them individually. Those that allow register
5082 will be replaced with operand number, the others will stay
5083 unchanged. */
5084 if (strchr (p, ',') != NULL)
5086 size_t len = 0, buflen = strlen (buf);
5087 char *beg, *end, *str, *dst;
5089 for (beg = p + 1;;)
5091 end = strchr (beg, ',');
5092 if (end == NULL)
5093 end = strchr (beg, '\0');
5094 if ((size_t) (end - beg) < buflen)
5095 len += buflen + 1;
5096 else
5097 len += end - beg + 1;
5098 if (*end)
5099 beg = end + 1;
5100 else
5101 break;
5104 str = (char *) alloca (len);
5105 for (beg = p + 1, dst = str;;)
5107 const char *tem;
5108 bool mem_p, reg_p, inout_p;
5110 end = strchr (beg, ',');
5111 if (end)
5112 *end = '\0';
5113 beg[-1] = '=';
5114 tem = beg - 1;
5115 parse_output_constraint (&tem, i, 0, 0,
5116 &mem_p, &reg_p, &inout_p);
5117 if (dst != str)
5118 *dst++ = ',';
5119 if (reg_p)
5121 memcpy (dst, buf, buflen);
5122 dst += buflen;
5124 else
5126 if (end)
5127 len = end - beg;
5128 else
5129 len = strlen (beg);
5130 memcpy (dst, beg, len);
5131 dst += len;
5133 if (end)
5134 beg = end + 1;
5135 else
5136 break;
5138 *dst = '\0';
5139 input = build_string (dst - str, str);
5141 else
5142 input = build_string (strlen (buf), buf);
5144 else
5145 input = build_string (constraint_len - 1, constraint + 1);
5147 free (p);
5149 input = build_tree_list (build_tree_list (NULL_TREE, input),
5150 unshare_expr (TREE_VALUE (link)));
5151 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
5155 link_next = NULL_TREE;
5156 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
5158 link_next = TREE_CHAIN (link);
5159 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
5160 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
5161 oconstraints, &allows_mem, &allows_reg);
5163 /* If we can't make copies, we can only accept memory. */
5164 if (TREE_ADDRESSABLE (TREE_TYPE (TREE_VALUE (link))))
5166 if (allows_mem)
5167 allows_reg = 0;
5168 else
5170 error ("impossible constraint in %<asm%>");
5171 error ("non-memory input %d must stay in memory", i);
5172 return GS_ERROR;
5176 /* If the operand is a memory input, it should be an lvalue. */
5177 if (!allows_reg && allows_mem)
5179 tree inputv = TREE_VALUE (link);
5180 STRIP_NOPS (inputv);
5181 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
5182 || TREE_CODE (inputv) == PREINCREMENT_EXPR
5183 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
5184 || TREE_CODE (inputv) == POSTINCREMENT_EXPR)
5185 TREE_VALUE (link) = error_mark_node;
5186 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5187 is_gimple_lvalue, fb_lvalue | fb_mayfail);
5188 mark_addressable (TREE_VALUE (link));
5189 if (tret == GS_ERROR)
5191 if (EXPR_HAS_LOCATION (TREE_VALUE (link)))
5192 input_location = EXPR_LOCATION (TREE_VALUE (link));
5193 error ("memory input %d is not directly addressable", i);
5194 ret = tret;
5197 else
5199 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
5200 is_gimple_asm_val, fb_rvalue);
5201 if (tret == GS_ERROR)
5202 ret = tret;
5205 TREE_CHAIN (link) = NULL_TREE;
5206 vec_safe_push (inputs, link);
5209 link_next = NULL_TREE;
5210 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
5212 link_next = TREE_CHAIN (link);
5213 TREE_CHAIN (link) = NULL_TREE;
5214 vec_safe_push (clobbers, link);
5217 link_next = NULL_TREE;
5218 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
5220 link_next = TREE_CHAIN (link);
5221 TREE_CHAIN (link) = NULL_TREE;
5222 vec_safe_push (labels, link);
5225 /* Do not add ASMs with errors to the gimple IL stream. */
5226 if (ret != GS_ERROR)
5228 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
5229 inputs, outputs, clobbers, labels);
5231 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr));
5232 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
5234 gimplify_seq_add_stmt (pre_p, stmt);
5237 return ret;
5240 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
5241 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
5242 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
5243 return to this function.
5245 FIXME should we complexify the prequeue handling instead? Or use flags
5246 for all the cleanups and let the optimizer tighten them up? The current
5247 code seems pretty fragile; it will break on a cleanup within any
5248 non-conditional nesting. But any such nesting would be broken, anyway;
5249 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
5250 and continues out of it. We can do that at the RTL level, though, so
5251 having an optimizer to tighten up try/finally regions would be a Good
5252 Thing. */
5254 static enum gimplify_status
5255 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
5257 gimple_stmt_iterator iter;
5258 gimple_seq body_sequence = NULL;
5260 tree temp = voidify_wrapper_expr (*expr_p, NULL);
5262 /* We only care about the number of conditions between the innermost
5263 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
5264 any cleanups collected outside the CLEANUP_POINT_EXPR. */
5265 int old_conds = gimplify_ctxp->conditions;
5266 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
5267 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
5268 gimplify_ctxp->conditions = 0;
5269 gimplify_ctxp->conditional_cleanups = NULL;
5270 gimplify_ctxp->in_cleanup_point_expr = true;
5272 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
5274 gimplify_ctxp->conditions = old_conds;
5275 gimplify_ctxp->conditional_cleanups = old_cleanups;
5276 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
5278 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
5280 gimple wce = gsi_stmt (iter);
5282 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
5284 if (gsi_one_before_end_p (iter))
5286 /* Note that gsi_insert_seq_before and gsi_remove do not
5287 scan operands, unlike some other sequence mutators. */
5288 if (!gimple_wce_cleanup_eh_only (wce))
5289 gsi_insert_seq_before_without_update (&iter,
5290 gimple_wce_cleanup (wce),
5291 GSI_SAME_STMT);
5292 gsi_remove (&iter, true);
5293 break;
5295 else
5297 gtry *gtry;
5298 gimple_seq seq;
5299 enum gimple_try_flags kind;
5301 if (gimple_wce_cleanup_eh_only (wce))
5302 kind = GIMPLE_TRY_CATCH;
5303 else
5304 kind = GIMPLE_TRY_FINALLY;
5305 seq = gsi_split_seq_after (iter);
5307 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
5308 /* Do not use gsi_replace here, as it may scan operands.
5309 We want to do a simple structural modification only. */
5310 gsi_set_stmt (&iter, gtry);
5311 iter = gsi_start (gtry->eval);
5314 else
5315 gsi_next (&iter);
5318 gimplify_seq_add_seq (pre_p, body_sequence);
5319 if (temp)
5321 *expr_p = temp;
5322 return GS_OK;
5324 else
5326 *expr_p = NULL;
5327 return GS_ALL_DONE;
5331 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
5332 is the cleanup action required. EH_ONLY is true if the cleanup should
5333 only be executed if an exception is thrown, not on normal exit. */
5335 static void
5336 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p)
5338 gimple wce;
5339 gimple_seq cleanup_stmts = NULL;
5341 /* Errors can result in improperly nested cleanups. Which results in
5342 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
5343 if (seen_error ())
5344 return;
5346 if (gimple_conditional_context ())
5348 /* If we're in a conditional context, this is more complex. We only
5349 want to run the cleanup if we actually ran the initialization that
5350 necessitates it, but we want to run it after the end of the
5351 conditional context. So we wrap the try/finally around the
5352 condition and use a flag to determine whether or not to actually
5353 run the destructor. Thus
5355 test ? f(A()) : 0
5357 becomes (approximately)
5359 flag = 0;
5360 try {
5361 if (test) { A::A(temp); flag = 1; val = f(temp); }
5362 else { val = 0; }
5363 } finally {
5364 if (flag) A::~A(temp);
5368 tree flag = create_tmp_var (boolean_type_node, "cleanup");
5369 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
5370 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
5372 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
5373 gimplify_stmt (&cleanup, &cleanup_stmts);
5374 wce = gimple_build_wce (cleanup_stmts);
5376 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
5377 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
5378 gimplify_seq_add_stmt (pre_p, ftrue);
5380 /* Because of this manipulation, and the EH edges that jump
5381 threading cannot redirect, the temporary (VAR) will appear
5382 to be used uninitialized. Don't warn. */
5383 TREE_NO_WARNING (var) = 1;
5385 else
5387 gimplify_stmt (&cleanup, &cleanup_stmts);
5388 wce = gimple_build_wce (cleanup_stmts);
5389 gimple_wce_set_cleanup_eh_only (wce, eh_only);
5390 gimplify_seq_add_stmt (pre_p, wce);
5394 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
5396 static enum gimplify_status
5397 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
5399 tree targ = *expr_p;
5400 tree temp = TARGET_EXPR_SLOT (targ);
5401 tree init = TARGET_EXPR_INITIAL (targ);
5402 enum gimplify_status ret;
5404 if (init)
5406 tree cleanup = NULL_TREE;
5408 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
5409 to the temps list. Handle also variable length TARGET_EXPRs. */
5410 if (TREE_CODE (DECL_SIZE (temp)) != INTEGER_CST)
5412 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
5413 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
5414 gimplify_vla_decl (temp, pre_p);
5416 else
5417 gimple_add_tmp_var (temp);
5419 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
5420 expression is supposed to initialize the slot. */
5421 if (VOID_TYPE_P (TREE_TYPE (init)))
5422 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
5423 else
5425 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
5426 init = init_expr;
5427 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
5428 init = NULL;
5429 ggc_free (init_expr);
5431 if (ret == GS_ERROR)
5433 /* PR c++/28266 Make sure this is expanded only once. */
5434 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
5435 return GS_ERROR;
5437 if (init)
5438 gimplify_and_add (init, pre_p);
5440 /* If needed, push the cleanup for the temp. */
5441 if (TARGET_EXPR_CLEANUP (targ))
5443 if (CLEANUP_EH_ONLY (targ))
5444 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
5445 CLEANUP_EH_ONLY (targ), pre_p);
5446 else
5447 cleanup = TARGET_EXPR_CLEANUP (targ);
5450 /* Add a clobber for the temporary going out of scope, like
5451 gimplify_bind_expr. */
5452 if (gimplify_ctxp->in_cleanup_point_expr
5453 && needs_to_live_in_memory (temp)
5454 && flag_stack_reuse == SR_ALL)
5456 tree clobber = build_constructor (TREE_TYPE (temp),
5457 NULL);
5458 TREE_THIS_VOLATILE (clobber) = true;
5459 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
5460 if (cleanup)
5461 cleanup = build2 (COMPOUND_EXPR, void_type_node, cleanup,
5462 clobber);
5463 else
5464 cleanup = clobber;
5467 if (cleanup)
5468 gimple_push_cleanup (temp, cleanup, false, pre_p);
5470 /* Only expand this once. */
5471 TREE_OPERAND (targ, 3) = init;
5472 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
5474 else
5475 /* We should have expanded this before. */
5476 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
5478 *expr_p = temp;
5479 return GS_OK;
5482 /* Gimplification of expression trees. */
5484 /* Gimplify an expression which appears at statement context. The
5485 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
5486 NULL, a new sequence is allocated.
5488 Return true if we actually added a statement to the queue. */
5490 bool
5491 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
5493 gimple_seq_node last;
5495 last = gimple_seq_last (*seq_p);
5496 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
5497 return last != gimple_seq_last (*seq_p);
5500 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
5501 to CTX. If entries already exist, force them to be some flavor of private.
5502 If there is no enclosing parallel, do nothing. */
5504 void
5505 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
5507 splay_tree_node n;
5509 if (decl == NULL || !DECL_P (decl))
5510 return;
5514 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5515 if (n != NULL)
5517 if (n->value & GOVD_SHARED)
5518 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
5519 else if (n->value & GOVD_MAP)
5520 n->value |= GOVD_MAP_TO_ONLY;
5521 else
5522 return;
5524 else if (ctx->region_type == ORT_TARGET)
5525 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
5526 else if (ctx->region_type != ORT_WORKSHARE
5527 && ctx->region_type != ORT_SIMD
5528 && ctx->region_type != ORT_TARGET_DATA)
5529 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
5531 ctx = ctx->outer_context;
5533 while (ctx);
5536 /* Similarly for each of the type sizes of TYPE. */
5538 static void
5539 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
5541 if (type == NULL || type == error_mark_node)
5542 return;
5543 type = TYPE_MAIN_VARIANT (type);
5545 if (ctx->privatized_types->add (type))
5546 return;
5548 switch (TREE_CODE (type))
5550 case INTEGER_TYPE:
5551 case ENUMERAL_TYPE:
5552 case BOOLEAN_TYPE:
5553 case REAL_TYPE:
5554 case FIXED_POINT_TYPE:
5555 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
5556 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
5557 break;
5559 case ARRAY_TYPE:
5560 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
5561 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
5562 break;
5564 case RECORD_TYPE:
5565 case UNION_TYPE:
5566 case QUAL_UNION_TYPE:
5568 tree field;
5569 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
5570 if (TREE_CODE (field) == FIELD_DECL)
5572 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
5573 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
5576 break;
5578 case POINTER_TYPE:
5579 case REFERENCE_TYPE:
5580 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
5581 break;
5583 default:
5584 break;
5587 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
5588 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
5589 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
5592 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
5594 static void
5595 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
5597 splay_tree_node n;
5598 unsigned int nflags;
5599 tree t;
5601 if (error_operand_p (decl))
5602 return;
5604 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
5605 there are constructors involved somewhere. */
5606 if (TREE_ADDRESSABLE (TREE_TYPE (decl))
5607 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
5608 flags |= GOVD_SEEN;
5610 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5611 if (n != NULL && n->value != GOVD_ALIGNED)
5613 /* We shouldn't be re-adding the decl with the same data
5614 sharing class. */
5615 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
5616 /* The only combination of data sharing classes we should see is
5617 FIRSTPRIVATE and LASTPRIVATE. */
5618 nflags = n->value | flags;
5619 gcc_assert ((nflags & GOVD_DATA_SHARE_CLASS)
5620 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE)
5621 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
5622 n->value = nflags;
5623 return;
5626 /* When adding a variable-sized variable, we have to handle all sorts
5627 of additional bits of data: the pointer replacement variable, and
5628 the parameters of the type. */
5629 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
5631 /* Add the pointer replacement variable as PRIVATE if the variable
5632 replacement is private, else FIRSTPRIVATE since we'll need the
5633 address of the original variable either for SHARED, or for the
5634 copy into or out of the context. */
5635 if (!(flags & GOVD_LOCAL))
5637 if (flags & GOVD_MAP)
5638 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
5639 else if (flags & GOVD_PRIVATE)
5640 nflags = GOVD_PRIVATE;
5641 else
5642 nflags = GOVD_FIRSTPRIVATE;
5643 nflags |= flags & GOVD_SEEN;
5644 t = DECL_VALUE_EXPR (decl);
5645 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
5646 t = TREE_OPERAND (t, 0);
5647 gcc_assert (DECL_P (t));
5648 omp_add_variable (ctx, t, nflags);
5651 /* Add all of the variable and type parameters (which should have
5652 been gimplified to a formal temporary) as FIRSTPRIVATE. */
5653 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
5654 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
5655 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
5657 /* The variable-sized variable itself is never SHARED, only some form
5658 of PRIVATE. The sharing would take place via the pointer variable
5659 which we remapped above. */
5660 if (flags & GOVD_SHARED)
5661 flags = GOVD_PRIVATE | GOVD_DEBUG_PRIVATE
5662 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
5664 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
5665 alloca statement we generate for the variable, so make sure it
5666 is available. This isn't automatically needed for the SHARED
5667 case, since we won't be allocating local storage then.
5668 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
5669 in this case omp_notice_variable will be called later
5670 on when it is gimplified. */
5671 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
5672 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
5673 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
5675 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
5676 && lang_hooks.decls.omp_privatize_by_reference (decl))
5678 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
5680 /* Similar to the direct variable sized case above, we'll need the
5681 size of references being privatized. */
5682 if ((flags & GOVD_SHARED) == 0)
5684 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
5685 if (TREE_CODE (t) != INTEGER_CST)
5686 omp_notice_variable (ctx, t, true);
5690 if (n != NULL)
5691 n->value |= flags;
5692 else
5693 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
5696 /* Notice a threadprivate variable DECL used in OMP context CTX.
5697 This just prints out diagnostics about threadprivate variable uses
5698 in untied tasks. If DECL2 is non-NULL, prevent this warning
5699 on that variable. */
5701 static bool
5702 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
5703 tree decl2)
5705 splay_tree_node n;
5706 struct gimplify_omp_ctx *octx;
5708 for (octx = ctx; octx; octx = octx->outer_context)
5709 if (octx->region_type == ORT_TARGET)
5711 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
5712 if (n == NULL)
5714 error ("threadprivate variable %qE used in target region",
5715 DECL_NAME (decl));
5716 error_at (octx->location, "enclosing target region");
5717 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
5719 if (decl2)
5720 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
5723 if (ctx->region_type != ORT_UNTIED_TASK)
5724 return false;
5725 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5726 if (n == NULL)
5728 error ("threadprivate variable %qE used in untied task",
5729 DECL_NAME (decl));
5730 error_at (ctx->location, "enclosing task");
5731 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
5733 if (decl2)
5734 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
5735 return false;
5738 /* Record the fact that DECL was used within the OMP context CTX.
5739 IN_CODE is true when real code uses DECL, and false when we should
5740 merely emit default(none) errors. Return true if DECL is going to
5741 be remapped and thus DECL shouldn't be gimplified into its
5742 DECL_VALUE_EXPR (if any). */
5744 static bool
5745 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
5747 splay_tree_node n;
5748 unsigned flags = in_code ? GOVD_SEEN : 0;
5749 bool ret = false, shared;
5751 if (error_operand_p (decl))
5752 return false;
5754 /* Threadprivate variables are predetermined. */
5755 if (is_global_var (decl))
5757 if (DECL_THREAD_LOCAL_P (decl))
5758 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
5760 if (DECL_HAS_VALUE_EXPR_P (decl))
5762 tree value = get_base_address (DECL_VALUE_EXPR (decl));
5764 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
5765 return omp_notice_threadprivate_variable (ctx, decl, value);
5769 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5770 if (ctx->region_type == ORT_TARGET)
5772 ret = lang_hooks.decls.omp_disregard_value_expr (decl, true);
5773 if (n == NULL)
5775 if (!lang_hooks.types.omp_mappable_type (TREE_TYPE (decl)))
5777 error ("%qD referenced in target region does not have "
5778 "a mappable type", decl);
5779 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_EXPLICIT | flags);
5781 else
5782 omp_add_variable (ctx, decl, GOVD_MAP | flags);
5784 else
5786 /* If nothing changed, there's nothing left to do. */
5787 if ((n->value & flags) == flags)
5788 return ret;
5789 n->value |= flags;
5791 goto do_outer;
5794 if (n == NULL)
5796 enum omp_clause_default_kind default_kind, kind;
5797 struct gimplify_omp_ctx *octx;
5799 if (ctx->region_type == ORT_WORKSHARE
5800 || ctx->region_type == ORT_SIMD
5801 || ctx->region_type == ORT_TARGET_DATA)
5802 goto do_outer;
5804 /* ??? Some compiler-generated variables (like SAVE_EXPRs) could be
5805 remapped firstprivate instead of shared. To some extent this is
5806 addressed in omp_firstprivatize_type_sizes, but not effectively. */
5807 default_kind = ctx->default_kind;
5808 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
5809 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
5810 default_kind = kind;
5812 switch (default_kind)
5814 case OMP_CLAUSE_DEFAULT_NONE:
5815 if ((ctx->region_type & ORT_PARALLEL) != 0)
5817 error ("%qE not specified in enclosing parallel",
5818 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5819 error_at (ctx->location, "enclosing parallel");
5821 else if ((ctx->region_type & ORT_TASK) != 0)
5823 error ("%qE not specified in enclosing task",
5824 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5825 error_at (ctx->location, "enclosing task");
5827 else if (ctx->region_type == ORT_TEAMS)
5829 error ("%qE not specified in enclosing teams construct",
5830 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)));
5831 error_at (ctx->location, "enclosing teams construct");
5833 else
5834 gcc_unreachable ();
5835 /* FALLTHRU */
5836 case OMP_CLAUSE_DEFAULT_SHARED:
5837 flags |= GOVD_SHARED;
5838 break;
5839 case OMP_CLAUSE_DEFAULT_PRIVATE:
5840 flags |= GOVD_PRIVATE;
5841 break;
5842 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
5843 flags |= GOVD_FIRSTPRIVATE;
5844 break;
5845 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
5846 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
5847 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
5848 if (ctx->outer_context)
5849 omp_notice_variable (ctx->outer_context, decl, in_code);
5850 for (octx = ctx->outer_context; octx; octx = octx->outer_context)
5852 splay_tree_node n2;
5854 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0)
5855 continue;
5856 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
5857 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
5859 flags |= GOVD_FIRSTPRIVATE;
5860 break;
5862 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
5863 break;
5865 if (flags & GOVD_FIRSTPRIVATE)
5866 break;
5867 if (octx == NULL
5868 && (TREE_CODE (decl) == PARM_DECL
5869 || (!is_global_var (decl)
5870 && DECL_CONTEXT (decl) == current_function_decl)))
5872 flags |= GOVD_FIRSTPRIVATE;
5873 break;
5875 flags |= GOVD_SHARED;
5876 break;
5877 default:
5878 gcc_unreachable ();
5881 if ((flags & GOVD_PRIVATE)
5882 && lang_hooks.decls.omp_private_outer_ref (decl))
5883 flags |= GOVD_PRIVATE_OUTER_REF;
5885 omp_add_variable (ctx, decl, flags);
5887 shared = (flags & GOVD_SHARED) != 0;
5888 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
5889 goto do_outer;
5892 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
5893 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
5894 && DECL_SIZE (decl)
5895 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
5897 splay_tree_node n2;
5898 tree t = DECL_VALUE_EXPR (decl);
5899 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
5900 t = TREE_OPERAND (t, 0);
5901 gcc_assert (DECL_P (t));
5902 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
5903 n2->value |= GOVD_SEEN;
5906 shared = ((flags | n->value) & GOVD_SHARED) != 0;
5907 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
5909 /* If nothing changed, there's nothing left to do. */
5910 if ((n->value & flags) == flags)
5911 return ret;
5912 flags |= n->value;
5913 n->value = flags;
5915 do_outer:
5916 /* If the variable is private in the current context, then we don't
5917 need to propagate anything to an outer context. */
5918 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
5919 return ret;
5920 if (ctx->outer_context
5921 && omp_notice_variable (ctx->outer_context, decl, in_code))
5922 return true;
5923 return ret;
5926 /* Verify that DECL is private within CTX. If there's specific information
5927 to the contrary in the innermost scope, generate an error. */
5929 static bool
5930 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
5932 splay_tree_node n;
5934 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
5935 if (n != NULL)
5937 if (n->value & GOVD_SHARED)
5939 if (ctx == gimplify_omp_ctxp)
5941 if (simd)
5942 error ("iteration variable %qE is predetermined linear",
5943 DECL_NAME (decl));
5944 else
5945 error ("iteration variable %qE should be private",
5946 DECL_NAME (decl));
5947 n->value = GOVD_PRIVATE;
5948 return true;
5950 else
5951 return false;
5953 else if ((n->value & GOVD_EXPLICIT) != 0
5954 && (ctx == gimplify_omp_ctxp
5955 || (ctx->region_type == ORT_COMBINED_PARALLEL
5956 && gimplify_omp_ctxp->outer_context == ctx)))
5958 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
5959 error ("iteration variable %qE should not be firstprivate",
5960 DECL_NAME (decl));
5961 else if ((n->value & GOVD_REDUCTION) != 0)
5962 error ("iteration variable %qE should not be reduction",
5963 DECL_NAME (decl));
5964 else if (simd == 1 && (n->value & GOVD_LASTPRIVATE) != 0)
5965 error ("iteration variable %qE should not be lastprivate",
5966 DECL_NAME (decl));
5967 else if (simd && (n->value & GOVD_PRIVATE) != 0)
5968 error ("iteration variable %qE should not be private",
5969 DECL_NAME (decl));
5970 else if (simd == 2 && (n->value & GOVD_LINEAR) != 0)
5971 error ("iteration variable %qE is predetermined linear",
5972 DECL_NAME (decl));
5974 return (ctx == gimplify_omp_ctxp
5975 || (ctx->region_type == ORT_COMBINED_PARALLEL
5976 && gimplify_omp_ctxp->outer_context == ctx));
5979 if (ctx->region_type != ORT_WORKSHARE
5980 && ctx->region_type != ORT_SIMD)
5981 return false;
5982 else if (ctx->outer_context)
5983 return omp_is_private (ctx->outer_context, decl, simd);
5984 return false;
5987 /* Return true if DECL is private within a parallel region
5988 that binds to the current construct's context or in parallel
5989 region's REDUCTION clause. */
5991 static bool
5992 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
5994 splay_tree_node n;
5998 ctx = ctx->outer_context;
5999 if (ctx == NULL)
6000 return !(is_global_var (decl)
6001 /* References might be private, but might be shared too,
6002 when checking for copyprivate, assume they might be
6003 private, otherwise assume they might be shared. */
6004 || (!copyprivate
6005 && lang_hooks.decls.omp_privatize_by_reference (decl)));
6007 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0)
6008 continue;
6010 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6011 if (n != NULL)
6012 return (n->value & GOVD_SHARED) == 0;
6014 while (ctx->region_type == ORT_WORKSHARE
6015 || ctx->region_type == ORT_SIMD);
6016 return false;
6019 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
6020 and previous omp contexts. */
6022 static void
6023 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
6024 enum omp_region_type region_type)
6026 struct gimplify_omp_ctx *ctx, *outer_ctx;
6027 tree c;
6029 ctx = new_omp_context (region_type);
6030 outer_ctx = ctx->outer_context;
6032 while ((c = *list_p) != NULL)
6034 bool remove = false;
6035 bool notice_outer = true;
6036 const char *check_non_private = NULL;
6037 unsigned int flags;
6038 tree decl;
6040 switch (OMP_CLAUSE_CODE (c))
6042 case OMP_CLAUSE_PRIVATE:
6043 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
6044 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
6046 flags |= GOVD_PRIVATE_OUTER_REF;
6047 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
6049 else
6050 notice_outer = false;
6051 goto do_add;
6052 case OMP_CLAUSE_SHARED:
6053 flags = GOVD_SHARED | GOVD_EXPLICIT;
6054 goto do_add;
6055 case OMP_CLAUSE_FIRSTPRIVATE:
6056 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
6057 check_non_private = "firstprivate";
6058 goto do_add;
6059 case OMP_CLAUSE_LASTPRIVATE:
6060 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
6061 check_non_private = "lastprivate";
6062 goto do_add;
6063 case OMP_CLAUSE_REDUCTION:
6064 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
6065 check_non_private = "reduction";
6066 goto do_add;
6067 case OMP_CLAUSE_LINEAR:
6068 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
6069 is_gimple_val, fb_rvalue) == GS_ERROR)
6071 remove = true;
6072 break;
6074 flags = GOVD_LINEAR | GOVD_EXPLICIT;
6075 goto do_add;
6077 case OMP_CLAUSE_MAP:
6078 decl = OMP_CLAUSE_DECL (c);
6079 if (error_operand_p (decl))
6081 remove = true;
6082 break;
6084 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6085 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
6086 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
6087 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
6088 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
6090 remove = true;
6091 break;
6093 if (!DECL_P (decl))
6095 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
6096 NULL, is_gimple_lvalue, fb_lvalue)
6097 == GS_ERROR)
6099 remove = true;
6100 break;
6102 break;
6104 flags = GOVD_MAP | GOVD_EXPLICIT;
6105 goto do_add;
6107 case OMP_CLAUSE_DEPEND:
6108 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
6110 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
6111 NULL, is_gimple_val, fb_rvalue);
6112 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
6114 if (error_operand_p (OMP_CLAUSE_DECL (c)))
6116 remove = true;
6117 break;
6119 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
6120 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
6121 is_gimple_val, fb_rvalue) == GS_ERROR)
6123 remove = true;
6124 break;
6126 break;
6128 case OMP_CLAUSE_TO:
6129 case OMP_CLAUSE_FROM:
6130 case OMP_CLAUSE__CACHE_:
6131 decl = OMP_CLAUSE_DECL (c);
6132 if (error_operand_p (decl))
6134 remove = true;
6135 break;
6137 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6138 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
6139 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
6140 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
6141 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
6143 remove = true;
6144 break;
6146 if (!DECL_P (decl))
6148 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
6149 NULL, is_gimple_lvalue, fb_lvalue)
6150 == GS_ERROR)
6152 remove = true;
6153 break;
6155 break;
6157 goto do_notice;
6159 do_add:
6160 decl = OMP_CLAUSE_DECL (c);
6161 if (error_operand_p (decl))
6163 remove = true;
6164 break;
6166 omp_add_variable (ctx, decl, flags);
6167 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
6168 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
6170 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
6171 GOVD_LOCAL | GOVD_SEEN);
6172 gimplify_omp_ctxp = ctx;
6173 push_gimplify_context ();
6175 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
6176 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
6178 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
6179 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
6180 pop_gimplify_context
6181 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
6182 push_gimplify_context ();
6183 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
6184 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
6185 pop_gimplify_context
6186 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
6187 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
6188 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
6190 gimplify_omp_ctxp = outer_ctx;
6192 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
6193 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
6195 gimplify_omp_ctxp = ctx;
6196 push_gimplify_context ();
6197 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
6199 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
6200 NULL, NULL);
6201 TREE_SIDE_EFFECTS (bind) = 1;
6202 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
6203 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
6205 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
6206 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
6207 pop_gimplify_context
6208 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
6209 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
6211 gimplify_omp_ctxp = outer_ctx;
6213 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
6214 && OMP_CLAUSE_LINEAR_STMT (c))
6216 gimplify_omp_ctxp = ctx;
6217 push_gimplify_context ();
6218 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
6220 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
6221 NULL, NULL);
6222 TREE_SIDE_EFFECTS (bind) = 1;
6223 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
6224 OMP_CLAUSE_LINEAR_STMT (c) = bind;
6226 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
6227 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
6228 pop_gimplify_context
6229 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
6230 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
6232 gimplify_omp_ctxp = outer_ctx;
6234 if (notice_outer)
6235 goto do_notice;
6236 break;
6238 case OMP_CLAUSE_COPYIN:
6239 case OMP_CLAUSE_COPYPRIVATE:
6240 decl = OMP_CLAUSE_DECL (c);
6241 if (error_operand_p (decl))
6243 remove = true;
6244 break;
6246 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
6247 && !remove
6248 && !omp_check_private (ctx, decl, true))
6250 remove = true;
6251 if (is_global_var (decl))
6253 if (DECL_THREAD_LOCAL_P (decl))
6254 remove = false;
6255 else if (DECL_HAS_VALUE_EXPR_P (decl))
6257 tree value = get_base_address (DECL_VALUE_EXPR (decl));
6259 if (value
6260 && DECL_P (value)
6261 && DECL_THREAD_LOCAL_P (value))
6262 remove = false;
6265 if (remove)
6266 error_at (OMP_CLAUSE_LOCATION (c),
6267 "copyprivate variable %qE is not threadprivate"
6268 " or private in outer context", DECL_NAME (decl));
6270 do_notice:
6271 if (outer_ctx)
6272 omp_notice_variable (outer_ctx, decl, true);
6273 if (check_non_private
6274 && region_type == ORT_WORKSHARE
6275 && omp_check_private (ctx, decl, false))
6277 error ("%s variable %qE is private in outer context",
6278 check_non_private, DECL_NAME (decl));
6279 remove = true;
6281 break;
6283 case OMP_CLAUSE_FINAL:
6284 case OMP_CLAUSE_IF:
6285 OMP_CLAUSE_OPERAND (c, 0)
6286 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
6287 /* Fall through. */
6289 case OMP_CLAUSE_SCHEDULE:
6290 case OMP_CLAUSE_NUM_THREADS:
6291 case OMP_CLAUSE_NUM_TEAMS:
6292 case OMP_CLAUSE_THREAD_LIMIT:
6293 case OMP_CLAUSE_DIST_SCHEDULE:
6294 case OMP_CLAUSE_DEVICE:
6295 case OMP_CLAUSE__CILK_FOR_COUNT_:
6296 case OMP_CLAUSE_ASYNC:
6297 case OMP_CLAUSE_WAIT:
6298 case OMP_CLAUSE_NUM_GANGS:
6299 case OMP_CLAUSE_NUM_WORKERS:
6300 case OMP_CLAUSE_VECTOR_LENGTH:
6301 case OMP_CLAUSE_GANG:
6302 case OMP_CLAUSE_WORKER:
6303 case OMP_CLAUSE_VECTOR:
6304 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
6305 is_gimple_val, fb_rvalue) == GS_ERROR)
6306 remove = true;
6307 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_GANG
6308 && gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
6309 is_gimple_val, fb_rvalue) == GS_ERROR)
6310 remove = true;
6311 break;
6313 case OMP_CLAUSE_DEVICE_RESIDENT:
6314 case OMP_CLAUSE_USE_DEVICE:
6315 case OMP_CLAUSE_INDEPENDENT:
6316 remove = true;
6317 break;
6319 case OMP_CLAUSE_NOWAIT:
6320 case OMP_CLAUSE_ORDERED:
6321 case OMP_CLAUSE_UNTIED:
6322 case OMP_CLAUSE_COLLAPSE:
6323 case OMP_CLAUSE_AUTO:
6324 case OMP_CLAUSE_SEQ:
6325 case OMP_CLAUSE_MERGEABLE:
6326 case OMP_CLAUSE_PROC_BIND:
6327 case OMP_CLAUSE_SAFELEN:
6328 break;
6330 case OMP_CLAUSE_ALIGNED:
6331 decl = OMP_CLAUSE_DECL (c);
6332 if (error_operand_p (decl))
6334 remove = true;
6335 break;
6337 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
6338 is_gimple_val, fb_rvalue) == GS_ERROR)
6340 remove = true;
6341 break;
6343 if (!is_global_var (decl)
6344 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
6345 omp_add_variable (ctx, decl, GOVD_ALIGNED);
6346 break;
6348 case OMP_CLAUSE_DEFAULT:
6349 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
6350 break;
6352 default:
6353 gcc_unreachable ();
6356 if (remove)
6357 *list_p = OMP_CLAUSE_CHAIN (c);
6358 else
6359 list_p = &OMP_CLAUSE_CHAIN (c);
6362 gimplify_omp_ctxp = ctx;
6365 struct gimplify_adjust_omp_clauses_data
6367 tree *list_p;
6368 gimple_seq *pre_p;
6371 /* For all variables that were not actually used within the context,
6372 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
6374 static int
6375 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
6377 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
6378 gimple_seq *pre_p
6379 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
6380 tree decl = (tree) n->key;
6381 unsigned flags = n->value;
6382 enum omp_clause_code code;
6383 tree clause;
6384 bool private_debug;
6386 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
6387 return 0;
6388 if ((flags & GOVD_SEEN) == 0)
6389 return 0;
6390 if (flags & GOVD_DEBUG_PRIVATE)
6392 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_PRIVATE);
6393 private_debug = true;
6395 else if (flags & GOVD_MAP)
6396 private_debug = false;
6397 else
6398 private_debug
6399 = lang_hooks.decls.omp_private_debug_clause (decl,
6400 !!(flags & GOVD_SHARED));
6401 if (private_debug)
6402 code = OMP_CLAUSE_PRIVATE;
6403 else if (flags & GOVD_MAP)
6404 code = OMP_CLAUSE_MAP;
6405 else if (flags & GOVD_SHARED)
6407 if (is_global_var (decl))
6409 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
6410 while (ctx != NULL)
6412 splay_tree_node on
6413 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6414 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
6415 | GOVD_PRIVATE | GOVD_REDUCTION
6416 | GOVD_LINEAR | GOVD_MAP)) != 0)
6417 break;
6418 ctx = ctx->outer_context;
6420 if (ctx == NULL)
6421 return 0;
6423 code = OMP_CLAUSE_SHARED;
6425 else if (flags & GOVD_PRIVATE)
6426 code = OMP_CLAUSE_PRIVATE;
6427 else if (flags & GOVD_FIRSTPRIVATE)
6428 code = OMP_CLAUSE_FIRSTPRIVATE;
6429 else if (flags & GOVD_LASTPRIVATE)
6430 code = OMP_CLAUSE_LASTPRIVATE;
6431 else if (flags & GOVD_ALIGNED)
6432 return 0;
6433 else
6434 gcc_unreachable ();
6436 clause = build_omp_clause (input_location, code);
6437 OMP_CLAUSE_DECL (clause) = decl;
6438 OMP_CLAUSE_CHAIN (clause) = *list_p;
6439 if (private_debug)
6440 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
6441 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
6442 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
6443 else if (code == OMP_CLAUSE_MAP)
6445 OMP_CLAUSE_MAP_KIND (clause) = flags & GOVD_MAP_TO_ONLY
6446 ? GOMP_MAP_TO
6447 : GOMP_MAP_TOFROM;
6448 if (DECL_SIZE (decl)
6449 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
6451 tree decl2 = DECL_VALUE_EXPR (decl);
6452 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6453 decl2 = TREE_OPERAND (decl2, 0);
6454 gcc_assert (DECL_P (decl2));
6455 tree mem = build_simple_mem_ref (decl2);
6456 OMP_CLAUSE_DECL (clause) = mem;
6457 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6458 if (gimplify_omp_ctxp->outer_context)
6460 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
6461 omp_notice_variable (ctx, decl2, true);
6462 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
6464 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
6465 OMP_CLAUSE_MAP);
6466 OMP_CLAUSE_DECL (nc) = decl;
6467 OMP_CLAUSE_SIZE (nc) = size_zero_node;
6468 OMP_CLAUSE_MAP_KIND (nc) = GOMP_MAP_POINTER;
6469 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
6470 OMP_CLAUSE_CHAIN (clause) = nc;
6472 else
6473 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
6475 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
6477 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
6478 OMP_CLAUSE_DECL (nc) = decl;
6479 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
6480 OMP_CLAUSE_CHAIN (nc) = *list_p;
6481 OMP_CLAUSE_CHAIN (clause) = nc;
6482 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6483 gimplify_omp_ctxp = ctx->outer_context;
6484 lang_hooks.decls.omp_finish_clause (nc, pre_p);
6485 gimplify_omp_ctxp = ctx;
6487 *list_p = clause;
6488 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6489 gimplify_omp_ctxp = ctx->outer_context;
6490 lang_hooks.decls.omp_finish_clause (clause, pre_p);
6491 gimplify_omp_ctxp = ctx;
6492 return 0;
6495 static void
6496 gimplify_adjust_omp_clauses (gimple_seq *pre_p, tree *list_p)
6498 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
6499 tree c, decl;
6501 while ((c = *list_p) != NULL)
6503 splay_tree_node n;
6504 bool remove = false;
6506 switch (OMP_CLAUSE_CODE (c))
6508 case OMP_CLAUSE_PRIVATE:
6509 case OMP_CLAUSE_SHARED:
6510 case OMP_CLAUSE_FIRSTPRIVATE:
6511 case OMP_CLAUSE_LINEAR:
6512 decl = OMP_CLAUSE_DECL (c);
6513 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6514 remove = !(n->value & GOVD_SEEN);
6515 if (! remove)
6517 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
6518 if ((n->value & GOVD_DEBUG_PRIVATE)
6519 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
6521 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
6522 || ((n->value & GOVD_DATA_SHARE_CLASS)
6523 == GOVD_PRIVATE));
6524 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
6525 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
6527 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
6528 && ctx->outer_context
6529 && !(OMP_CLAUSE_LINEAR_NO_COPYIN (c)
6530 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
6532 if (ctx->outer_context->combined_loop
6533 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
6535 n = splay_tree_lookup (ctx->outer_context->variables,
6536 (splay_tree_key) decl);
6537 if (n == NULL
6538 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
6540 int flags = GOVD_FIRSTPRIVATE;
6541 /* #pragma omp distribute does not allow
6542 lastprivate clause. */
6543 if (!ctx->outer_context->distribute)
6544 flags |= GOVD_LASTPRIVATE;
6545 if (n == NULL)
6546 omp_add_variable (ctx->outer_context, decl,
6547 flags | GOVD_SEEN);
6548 else
6549 n->value |= flags | GOVD_SEEN;
6552 else if (!is_global_var (decl))
6553 omp_notice_variable (ctx->outer_context, decl, true);
6556 break;
6558 case OMP_CLAUSE_LASTPRIVATE:
6559 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
6560 accurately reflect the presence of a FIRSTPRIVATE clause. */
6561 decl = OMP_CLAUSE_DECL (c);
6562 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6563 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
6564 = (n->value & GOVD_FIRSTPRIVATE) != 0;
6565 break;
6567 case OMP_CLAUSE_ALIGNED:
6568 decl = OMP_CLAUSE_DECL (c);
6569 if (!is_global_var (decl))
6571 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6572 remove = n == NULL || !(n->value & GOVD_SEEN);
6573 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
6575 struct gimplify_omp_ctx *octx;
6576 if (n != NULL
6577 && (n->value & (GOVD_DATA_SHARE_CLASS
6578 & ~GOVD_FIRSTPRIVATE)))
6579 remove = true;
6580 else
6581 for (octx = ctx->outer_context; octx;
6582 octx = octx->outer_context)
6584 n = splay_tree_lookup (octx->variables,
6585 (splay_tree_key) decl);
6586 if (n == NULL)
6587 continue;
6588 if (n->value & GOVD_LOCAL)
6589 break;
6590 /* We have to avoid assigning a shared variable
6591 to itself when trying to add
6592 __builtin_assume_aligned. */
6593 if (n->value & GOVD_SHARED)
6595 remove = true;
6596 break;
6601 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
6603 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6604 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
6605 remove = true;
6607 break;
6609 case OMP_CLAUSE_MAP:
6610 decl = OMP_CLAUSE_DECL (c);
6611 if (!DECL_P (decl))
6612 break;
6613 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
6614 if (ctx->region_type == ORT_TARGET && !(n->value & GOVD_SEEN))
6615 remove = true;
6616 else if (DECL_SIZE (decl)
6617 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
6618 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER)
6620 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
6621 for these, TREE_CODE (DECL_SIZE (decl)) will always be
6622 INTEGER_CST. */
6623 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
6625 tree decl2 = DECL_VALUE_EXPR (decl);
6626 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6627 decl2 = TREE_OPERAND (decl2, 0);
6628 gcc_assert (DECL_P (decl2));
6629 tree mem = build_simple_mem_ref (decl2);
6630 OMP_CLAUSE_DECL (c) = mem;
6631 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6632 if (ctx->outer_context)
6634 omp_notice_variable (ctx->outer_context, decl2, true);
6635 omp_notice_variable (ctx->outer_context,
6636 OMP_CLAUSE_SIZE (c), true);
6638 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
6639 OMP_CLAUSE_MAP);
6640 OMP_CLAUSE_DECL (nc) = decl;
6641 OMP_CLAUSE_SIZE (nc) = size_zero_node;
6642 OMP_CLAUSE_MAP_KIND (nc) = GOMP_MAP_POINTER;
6643 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
6644 OMP_CLAUSE_CHAIN (c) = nc;
6645 c = nc;
6647 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6648 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
6649 break;
6651 case OMP_CLAUSE_TO:
6652 case OMP_CLAUSE_FROM:
6653 case OMP_CLAUSE__CACHE_:
6654 decl = OMP_CLAUSE_DECL (c);
6655 if (!DECL_P (decl))
6656 break;
6657 if (DECL_SIZE (decl)
6658 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
6660 tree decl2 = DECL_VALUE_EXPR (decl);
6661 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
6662 decl2 = TREE_OPERAND (decl2, 0);
6663 gcc_assert (DECL_P (decl2));
6664 tree mem = build_simple_mem_ref (decl2);
6665 OMP_CLAUSE_DECL (c) = mem;
6666 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
6667 if (ctx->outer_context)
6669 omp_notice_variable (ctx->outer_context, decl2, true);
6670 omp_notice_variable (ctx->outer_context,
6671 OMP_CLAUSE_SIZE (c), true);
6674 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
6675 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
6676 break;
6678 case OMP_CLAUSE_REDUCTION:
6679 case OMP_CLAUSE_COPYIN:
6680 case OMP_CLAUSE_COPYPRIVATE:
6681 case OMP_CLAUSE_IF:
6682 case OMP_CLAUSE_NUM_THREADS:
6683 case OMP_CLAUSE_NUM_TEAMS:
6684 case OMP_CLAUSE_THREAD_LIMIT:
6685 case OMP_CLAUSE_DIST_SCHEDULE:
6686 case OMP_CLAUSE_DEVICE:
6687 case OMP_CLAUSE_SCHEDULE:
6688 case OMP_CLAUSE_NOWAIT:
6689 case OMP_CLAUSE_ORDERED:
6690 case OMP_CLAUSE_DEFAULT:
6691 case OMP_CLAUSE_UNTIED:
6692 case OMP_CLAUSE_COLLAPSE:
6693 case OMP_CLAUSE_FINAL:
6694 case OMP_CLAUSE_MERGEABLE:
6695 case OMP_CLAUSE_PROC_BIND:
6696 case OMP_CLAUSE_SAFELEN:
6697 case OMP_CLAUSE_DEPEND:
6698 case OMP_CLAUSE__CILK_FOR_COUNT_:
6699 case OMP_CLAUSE_ASYNC:
6700 case OMP_CLAUSE_WAIT:
6701 case OMP_CLAUSE_DEVICE_RESIDENT:
6702 case OMP_CLAUSE_USE_DEVICE:
6703 case OMP_CLAUSE_INDEPENDENT:
6704 case OMP_CLAUSE_NUM_GANGS:
6705 case OMP_CLAUSE_NUM_WORKERS:
6706 case OMP_CLAUSE_VECTOR_LENGTH:
6707 case OMP_CLAUSE_GANG:
6708 case OMP_CLAUSE_WORKER:
6709 case OMP_CLAUSE_VECTOR:
6710 case OMP_CLAUSE_AUTO:
6711 case OMP_CLAUSE_SEQ:
6712 break;
6714 default:
6715 gcc_unreachable ();
6718 if (remove)
6719 *list_p = OMP_CLAUSE_CHAIN (c);
6720 else
6721 list_p = &OMP_CLAUSE_CHAIN (c);
6724 /* Add in any implicit data sharing. */
6725 struct gimplify_adjust_omp_clauses_data data;
6726 data.list_p = list_p;
6727 data.pre_p = pre_p;
6728 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
6730 gimplify_omp_ctxp = ctx->outer_context;
6731 delete_omp_context (ctx);
6734 /* Gimplify OACC_CACHE. */
6736 static void
6737 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
6739 tree expr = *expr_p;
6741 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_WORKSHARE);
6742 gimplify_adjust_omp_clauses (pre_p, &OACC_CACHE_CLAUSES (expr));
6744 /* TODO: Do something sensible with this information. */
6746 *expr_p = NULL_TREE;
6749 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
6750 gimplification of the body, as well as scanning the body for used
6751 variables. We need to do this scan now, because variable-sized
6752 decls will be decomposed during gimplification. */
6754 static void
6755 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
6757 tree expr = *expr_p;
6758 gimple g;
6759 gimple_seq body = NULL;
6761 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
6762 OMP_PARALLEL_COMBINED (expr)
6763 ? ORT_COMBINED_PARALLEL
6764 : ORT_PARALLEL);
6766 push_gimplify_context ();
6768 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
6769 if (gimple_code (g) == GIMPLE_BIND)
6770 pop_gimplify_context (g);
6771 else
6772 pop_gimplify_context (NULL);
6774 gimplify_adjust_omp_clauses (pre_p, &OMP_PARALLEL_CLAUSES (expr));
6776 g = gimple_build_omp_parallel (body,
6777 OMP_PARALLEL_CLAUSES (expr),
6778 NULL_TREE, NULL_TREE);
6779 if (OMP_PARALLEL_COMBINED (expr))
6780 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
6781 gimplify_seq_add_stmt (pre_p, g);
6782 *expr_p = NULL_TREE;
6785 /* Gimplify the contents of an OMP_TASK statement. This involves
6786 gimplification of the body, as well as scanning the body for used
6787 variables. We need to do this scan now, because variable-sized
6788 decls will be decomposed during gimplification. */
6790 static void
6791 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
6793 tree expr = *expr_p;
6794 gimple g;
6795 gimple_seq body = NULL;
6797 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
6798 find_omp_clause (OMP_TASK_CLAUSES (expr),
6799 OMP_CLAUSE_UNTIED)
6800 ? ORT_UNTIED_TASK : ORT_TASK);
6802 push_gimplify_context ();
6804 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
6805 if (gimple_code (g) == GIMPLE_BIND)
6806 pop_gimplify_context (g);
6807 else
6808 pop_gimplify_context (NULL);
6810 gimplify_adjust_omp_clauses (pre_p, &OMP_TASK_CLAUSES (expr));
6812 g = gimple_build_omp_task (body,
6813 OMP_TASK_CLAUSES (expr),
6814 NULL_TREE, NULL_TREE,
6815 NULL_TREE, NULL_TREE, NULL_TREE);
6816 gimplify_seq_add_stmt (pre_p, g);
6817 *expr_p = NULL_TREE;
6820 /* Helper function of gimplify_omp_for, find OMP_FOR resp. OMP_SIMD
6821 with non-NULL OMP_FOR_INIT. */
6823 static tree
6824 find_combined_omp_for (tree *tp, int *walk_subtrees, void *)
6826 *walk_subtrees = 0;
6827 switch (TREE_CODE (*tp))
6829 case OMP_FOR:
6830 *walk_subtrees = 1;
6831 /* FALLTHRU */
6832 case OMP_SIMD:
6833 if (OMP_FOR_INIT (*tp) != NULL_TREE)
6834 return *tp;
6835 break;
6836 case BIND_EXPR:
6837 case STATEMENT_LIST:
6838 case OMP_PARALLEL:
6839 *walk_subtrees = 1;
6840 break;
6841 default:
6842 break;
6844 return NULL_TREE;
6847 /* Gimplify the gross structure of an OMP_FOR statement. */
6849 static enum gimplify_status
6850 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
6852 tree for_stmt, orig_for_stmt, decl, var, t;
6853 enum gimplify_status ret = GS_ALL_DONE;
6854 enum gimplify_status tret;
6855 gomp_for *gfor;
6856 gimple_seq for_body, for_pre_body;
6857 int i;
6858 bool simd;
6859 bitmap has_decl_expr = NULL;
6861 orig_for_stmt = for_stmt = *expr_p;
6863 switch (TREE_CODE (for_stmt))
6865 case OMP_FOR:
6866 case CILK_FOR:
6867 case OMP_DISTRIBUTE:
6868 case OACC_LOOP:
6869 simd = false;
6870 break;
6871 case OMP_SIMD:
6872 case CILK_SIMD:
6873 simd = true;
6874 break;
6875 default:
6876 gcc_unreachable ();
6879 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p,
6880 simd ? ORT_SIMD : ORT_WORKSHARE);
6881 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
6882 gimplify_omp_ctxp->distribute = true;
6884 /* Handle OMP_FOR_INIT. */
6885 for_pre_body = NULL;
6886 if (simd && OMP_FOR_PRE_BODY (for_stmt))
6888 has_decl_expr = BITMAP_ALLOC (NULL);
6889 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
6890 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
6891 == VAR_DECL)
6893 t = OMP_FOR_PRE_BODY (for_stmt);
6894 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
6896 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
6898 tree_stmt_iterator si;
6899 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
6900 tsi_next (&si))
6902 t = tsi_stmt (si);
6903 if (TREE_CODE (t) == DECL_EXPR
6904 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
6905 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
6909 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
6910 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
6912 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
6914 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
6915 for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt), find_combined_omp_for,
6916 NULL, NULL);
6917 gcc_assert (for_stmt != NULL_TREE);
6918 gimplify_omp_ctxp->combined_loop = true;
6921 for_body = NULL;
6922 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
6923 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
6924 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
6925 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
6926 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
6928 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
6929 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
6930 decl = TREE_OPERAND (t, 0);
6931 gcc_assert (DECL_P (decl));
6932 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
6933 || POINTER_TYPE_P (TREE_TYPE (decl)));
6935 /* Make sure the iteration variable is private. */
6936 tree c = NULL_TREE;
6937 tree c2 = NULL_TREE;
6938 if (orig_for_stmt != for_stmt)
6939 /* Do this only on innermost construct for combined ones. */;
6940 else if (simd)
6942 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
6943 (splay_tree_key)decl);
6944 omp_is_private (gimplify_omp_ctxp, decl,
6945 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
6946 != 1));
6947 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
6948 omp_notice_variable (gimplify_omp_ctxp, decl, true);
6949 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
6951 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
6952 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
6953 if (has_decl_expr
6954 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
6955 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
6956 OMP_CLAUSE_DECL (c) = decl;
6957 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
6958 OMP_FOR_CLAUSES (for_stmt) = c;
6959 omp_add_variable (gimplify_omp_ctxp, decl,
6960 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
6962 else
6964 bool lastprivate
6965 = (!has_decl_expr
6966 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
6967 if (lastprivate
6968 && gimplify_omp_ctxp->outer_context
6969 && gimplify_omp_ctxp->outer_context->region_type
6970 == ORT_WORKSHARE
6971 && gimplify_omp_ctxp->outer_context->combined_loop
6972 && !gimplify_omp_ctxp->outer_context->distribute)
6974 struct gimplify_omp_ctx *outer
6975 = gimplify_omp_ctxp->outer_context;
6976 n = splay_tree_lookup (outer->variables,
6977 (splay_tree_key) decl);
6978 if (n != NULL
6979 && (n->value & GOVD_DATA_SHARE_CLASS) == GOVD_LOCAL)
6980 lastprivate = false;
6981 else if (omp_check_private (outer, decl, false))
6982 error ("lastprivate variable %qE is private in outer "
6983 "context", DECL_NAME (decl));
6984 else
6986 omp_add_variable (outer, decl,
6987 GOVD_LASTPRIVATE | GOVD_SEEN);
6988 if (outer->outer_context)
6989 omp_notice_variable (outer->outer_context, decl, true);
6992 c = build_omp_clause (input_location,
6993 lastprivate ? OMP_CLAUSE_LASTPRIVATE
6994 : OMP_CLAUSE_PRIVATE);
6995 OMP_CLAUSE_DECL (c) = decl;
6996 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
6997 OMP_FOR_CLAUSES (for_stmt) = c;
6998 omp_add_variable (gimplify_omp_ctxp, decl,
6999 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
7000 | GOVD_EXPLICIT | GOVD_SEEN);
7001 c = NULL_TREE;
7004 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
7005 omp_notice_variable (gimplify_omp_ctxp, decl, true);
7006 else
7007 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
7009 /* If DECL is not a gimple register, create a temporary variable to act
7010 as an iteration counter. This is valid, since DECL cannot be
7011 modified in the body of the loop. Similarly for any iteration vars
7012 in simd with collapse > 1 where the iterator vars must be
7013 lastprivate. */
7014 if (orig_for_stmt != for_stmt)
7015 var = decl;
7016 else if (!is_gimple_reg (decl)
7017 || (simd && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1))
7019 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
7020 TREE_OPERAND (t, 0) = var;
7022 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
7024 if (simd && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
7026 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
7027 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
7028 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
7029 OMP_CLAUSE_DECL (c2) = var;
7030 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
7031 OMP_FOR_CLAUSES (for_stmt) = c2;
7032 omp_add_variable (gimplify_omp_ctxp, var,
7033 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
7034 if (c == NULL_TREE)
7036 c = c2;
7037 c2 = NULL_TREE;
7040 else
7041 omp_add_variable (gimplify_omp_ctxp, var,
7042 GOVD_PRIVATE | GOVD_SEEN);
7044 else
7045 var = decl;
7047 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7048 is_gimple_val, fb_rvalue);
7049 ret = MIN (ret, tret);
7050 if (ret == GS_ERROR)
7051 return ret;
7053 /* Handle OMP_FOR_COND. */
7054 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
7055 gcc_assert (COMPARISON_CLASS_P (t));
7056 gcc_assert (TREE_OPERAND (t, 0) == decl);
7058 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7059 is_gimple_val, fb_rvalue);
7060 ret = MIN (ret, tret);
7062 /* Handle OMP_FOR_INCR. */
7063 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7064 switch (TREE_CODE (t))
7066 case PREINCREMENT_EXPR:
7067 case POSTINCREMENT_EXPR:
7069 tree decl = TREE_OPERAND (t, 0);
7070 /* c_omp_for_incr_canonicalize_ptr() should have been
7071 called to massage things appropriately. */
7072 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
7074 if (orig_for_stmt != for_stmt)
7075 break;
7076 t = build_int_cst (TREE_TYPE (decl), 1);
7077 if (c)
7078 OMP_CLAUSE_LINEAR_STEP (c) = t;
7079 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
7080 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
7081 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
7082 break;
7085 case PREDECREMENT_EXPR:
7086 case POSTDECREMENT_EXPR:
7087 /* c_omp_for_incr_canonicalize_ptr() should have been
7088 called to massage things appropriately. */
7089 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
7090 if (orig_for_stmt != for_stmt)
7091 break;
7092 t = build_int_cst (TREE_TYPE (decl), -1);
7093 if (c)
7094 OMP_CLAUSE_LINEAR_STEP (c) = t;
7095 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
7096 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
7097 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
7098 break;
7100 case MODIFY_EXPR:
7101 gcc_assert (TREE_OPERAND (t, 0) == decl);
7102 TREE_OPERAND (t, 0) = var;
7104 t = TREE_OPERAND (t, 1);
7105 switch (TREE_CODE (t))
7107 case PLUS_EXPR:
7108 if (TREE_OPERAND (t, 1) == decl)
7110 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
7111 TREE_OPERAND (t, 0) = var;
7112 break;
7115 /* Fallthru. */
7116 case MINUS_EXPR:
7117 case POINTER_PLUS_EXPR:
7118 gcc_assert (TREE_OPERAND (t, 0) == decl);
7119 TREE_OPERAND (t, 0) = var;
7120 break;
7121 default:
7122 gcc_unreachable ();
7125 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
7126 is_gimple_val, fb_rvalue);
7127 ret = MIN (ret, tret);
7128 if (c)
7130 tree step = TREE_OPERAND (t, 1);
7131 tree stept = TREE_TYPE (decl);
7132 if (POINTER_TYPE_P (stept))
7133 stept = sizetype;
7134 step = fold_convert (stept, step);
7135 if (TREE_CODE (t) == MINUS_EXPR)
7136 step = fold_build1 (NEGATE_EXPR, stept, step);
7137 OMP_CLAUSE_LINEAR_STEP (c) = step;
7138 if (step != TREE_OPERAND (t, 1))
7140 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
7141 &for_pre_body, NULL,
7142 is_gimple_val, fb_rvalue);
7143 ret = MIN (ret, tret);
7146 break;
7148 default:
7149 gcc_unreachable ();
7152 if (c2)
7154 gcc_assert (c);
7155 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
7158 if ((var != decl || TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
7159 && orig_for_stmt == for_stmt)
7161 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
7162 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
7163 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
7164 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
7165 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
7166 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
7167 && OMP_CLAUSE_DECL (c) == decl)
7169 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7170 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
7171 gcc_assert (TREE_OPERAND (t, 0) == var);
7172 t = TREE_OPERAND (t, 1);
7173 gcc_assert (TREE_CODE (t) == PLUS_EXPR
7174 || TREE_CODE (t) == MINUS_EXPR
7175 || TREE_CODE (t) == POINTER_PLUS_EXPR);
7176 gcc_assert (TREE_OPERAND (t, 0) == var);
7177 t = build2 (TREE_CODE (t), TREE_TYPE (decl), decl,
7178 TREE_OPERAND (t, 1));
7179 gimple_seq *seq;
7180 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
7181 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
7182 else
7183 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
7184 gimplify_assign (decl, t, seq);
7189 BITMAP_FREE (has_decl_expr);
7191 gimplify_and_add (OMP_FOR_BODY (orig_for_stmt), &for_body);
7193 if (orig_for_stmt != for_stmt)
7194 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
7196 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
7197 decl = TREE_OPERAND (t, 0);
7198 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
7199 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
7200 TREE_OPERAND (t, 0) = var;
7201 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7202 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
7203 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
7206 gimplify_adjust_omp_clauses (pre_p, &OMP_FOR_CLAUSES (orig_for_stmt));
7208 int kind;
7209 switch (TREE_CODE (orig_for_stmt))
7211 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
7212 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
7213 case CILK_SIMD: kind = GF_OMP_FOR_KIND_CILKSIMD; break;
7214 case CILK_FOR: kind = GF_OMP_FOR_KIND_CILKFOR; break;
7215 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
7216 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
7217 default:
7218 gcc_unreachable ();
7220 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
7221 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
7222 for_pre_body);
7223 if (orig_for_stmt != for_stmt)
7224 gimple_omp_for_set_combined_p (gfor, true);
7225 if (gimplify_omp_ctxp
7226 && (gimplify_omp_ctxp->combined_loop
7227 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
7228 && gimplify_omp_ctxp->outer_context
7229 && gimplify_omp_ctxp->outer_context->combined_loop)))
7231 gimple_omp_for_set_combined_into_p (gfor, true);
7232 if (gimplify_omp_ctxp->combined_loop)
7233 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
7234 else
7235 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
7238 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
7240 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
7241 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
7242 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
7243 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
7244 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
7245 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
7246 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
7247 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
7250 gimplify_seq_add_stmt (pre_p, gfor);
7251 if (ret != GS_ALL_DONE)
7252 return GS_ERROR;
7253 *expr_p = NULL_TREE;
7254 return GS_ALL_DONE;
7257 /* Gimplify the gross structure of several OMP constructs. */
7259 static void
7260 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
7262 tree expr = *expr_p;
7263 gimple stmt;
7264 gimple_seq body = NULL;
7265 enum omp_region_type ort;
7267 switch (TREE_CODE (expr))
7269 case OMP_SECTIONS:
7270 case OMP_SINGLE:
7271 ort = ORT_WORKSHARE;
7272 break;
7273 case OACC_KERNELS:
7274 case OACC_PARALLEL:
7275 case OMP_TARGET:
7276 ort = ORT_TARGET;
7277 break;
7278 case OACC_DATA:
7279 case OMP_TARGET_DATA:
7280 ort = ORT_TARGET_DATA;
7281 break;
7282 case OMP_TEAMS:
7283 ort = ORT_TEAMS;
7284 break;
7285 default:
7286 gcc_unreachable ();
7288 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort);
7289 if (ort == ORT_TARGET || ort == ORT_TARGET_DATA)
7291 push_gimplify_context ();
7292 gimple g = gimplify_and_return_first (OMP_BODY (expr), &body);
7293 if (gimple_code (g) == GIMPLE_BIND)
7294 pop_gimplify_context (g);
7295 else
7296 pop_gimplify_context (NULL);
7297 if (ort == ORT_TARGET_DATA)
7299 enum built_in_function end_ix;
7300 switch (TREE_CODE (expr))
7302 case OACC_DATA:
7303 end_ix = BUILT_IN_GOACC_DATA_END;
7304 break;
7305 case OMP_TARGET_DATA:
7306 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
7307 break;
7308 default:
7309 gcc_unreachable ();
7311 tree fn = builtin_decl_explicit (end_ix);
7312 g = gimple_build_call (fn, 0);
7313 gimple_seq cleanup = NULL;
7314 gimple_seq_add_stmt (&cleanup, g);
7315 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
7316 body = NULL;
7317 gimple_seq_add_stmt (&body, g);
7320 else
7321 gimplify_and_add (OMP_BODY (expr), &body);
7322 gimplify_adjust_omp_clauses (pre_p, &OMP_CLAUSES (expr));
7324 switch (TREE_CODE (expr))
7326 case OACC_DATA:
7327 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
7328 OMP_CLAUSES (expr));
7329 break;
7330 case OACC_KERNELS:
7331 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
7332 OMP_CLAUSES (expr));
7333 break;
7334 case OACC_PARALLEL:
7335 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
7336 OMP_CLAUSES (expr));
7337 break;
7338 case OMP_SECTIONS:
7339 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
7340 break;
7341 case OMP_SINGLE:
7342 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
7343 break;
7344 case OMP_TARGET:
7345 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
7346 OMP_CLAUSES (expr));
7347 break;
7348 case OMP_TARGET_DATA:
7349 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
7350 OMP_CLAUSES (expr));
7351 break;
7352 case OMP_TEAMS:
7353 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
7354 break;
7355 default:
7356 gcc_unreachable ();
7359 gimplify_seq_add_stmt (pre_p, stmt);
7360 *expr_p = NULL_TREE;
7363 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
7364 target update constructs. */
7366 static void
7367 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
7369 tree expr = *expr_p, clauses;
7370 int kind;
7371 gomp_target *stmt;
7373 switch (TREE_CODE (expr))
7375 case OACC_ENTER_DATA:
7376 clauses = OACC_ENTER_DATA_CLAUSES (expr);
7377 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
7378 break;
7379 case OACC_EXIT_DATA:
7380 clauses = OACC_EXIT_DATA_CLAUSES (expr);
7381 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
7382 break;
7383 case OACC_UPDATE:
7384 clauses = OACC_UPDATE_CLAUSES (expr);
7385 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
7386 break;
7387 case OMP_TARGET_UPDATE:
7388 clauses = OMP_TARGET_UPDATE_CLAUSES (expr);
7389 kind = GF_OMP_TARGET_KIND_UPDATE;
7390 break;
7391 default:
7392 gcc_unreachable ();
7394 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_WORKSHARE);
7395 gimplify_adjust_omp_clauses (pre_p, &clauses);
7396 stmt = gimple_build_omp_target (NULL, kind, clauses);
7398 gimplify_seq_add_stmt (pre_p, stmt);
7399 *expr_p = NULL_TREE;
7402 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
7403 stabilized the lhs of the atomic operation as *ADDR. Return true if
7404 EXPR is this stabilized form. */
7406 static bool
7407 goa_lhs_expr_p (tree expr, tree addr)
7409 /* Also include casts to other type variants. The C front end is fond
7410 of adding these for e.g. volatile variables. This is like
7411 STRIP_TYPE_NOPS but includes the main variant lookup. */
7412 STRIP_USELESS_TYPE_CONVERSION (expr);
7414 if (TREE_CODE (expr) == INDIRECT_REF)
7416 expr = TREE_OPERAND (expr, 0);
7417 while (expr != addr
7418 && (CONVERT_EXPR_P (expr)
7419 || TREE_CODE (expr) == NON_LVALUE_EXPR)
7420 && TREE_CODE (expr) == TREE_CODE (addr)
7421 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
7423 expr = TREE_OPERAND (expr, 0);
7424 addr = TREE_OPERAND (addr, 0);
7426 if (expr == addr)
7427 return true;
7428 return (TREE_CODE (addr) == ADDR_EXPR
7429 && TREE_CODE (expr) == ADDR_EXPR
7430 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
7432 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
7433 return true;
7434 return false;
7437 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
7438 expression does not involve the lhs, evaluate it into a temporary.
7439 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
7440 or -1 if an error was encountered. */
7442 static int
7443 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
7444 tree lhs_var)
7446 tree expr = *expr_p;
7447 int saw_lhs;
7449 if (goa_lhs_expr_p (expr, lhs_addr))
7451 *expr_p = lhs_var;
7452 return 1;
7454 if (is_gimple_val (expr))
7455 return 0;
7457 saw_lhs = 0;
7458 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
7460 case tcc_binary:
7461 case tcc_comparison:
7462 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
7463 lhs_var);
7464 case tcc_unary:
7465 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
7466 lhs_var);
7467 break;
7468 case tcc_expression:
7469 switch (TREE_CODE (expr))
7471 case TRUTH_ANDIF_EXPR:
7472 case TRUTH_ORIF_EXPR:
7473 case TRUTH_AND_EXPR:
7474 case TRUTH_OR_EXPR:
7475 case TRUTH_XOR_EXPR:
7476 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
7477 lhs_addr, lhs_var);
7478 case TRUTH_NOT_EXPR:
7479 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
7480 lhs_addr, lhs_var);
7481 break;
7482 case COMPOUND_EXPR:
7483 /* Break out any preevaluations from cp_build_modify_expr. */
7484 for (; TREE_CODE (expr) == COMPOUND_EXPR;
7485 expr = TREE_OPERAND (expr, 1))
7486 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
7487 *expr_p = expr;
7488 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var);
7489 default:
7490 break;
7492 break;
7493 default:
7494 break;
7497 if (saw_lhs == 0)
7499 enum gimplify_status gs;
7500 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
7501 if (gs != GS_ALL_DONE)
7502 saw_lhs = -1;
7505 return saw_lhs;
7508 /* Gimplify an OMP_ATOMIC statement. */
7510 static enum gimplify_status
7511 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
7513 tree addr = TREE_OPERAND (*expr_p, 0);
7514 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
7515 ? NULL : TREE_OPERAND (*expr_p, 1);
7516 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
7517 tree tmp_load;
7518 gomp_atomic_load *loadstmt;
7519 gomp_atomic_store *storestmt;
7521 tmp_load = create_tmp_reg (type);
7522 if (rhs && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load) < 0)
7523 return GS_ERROR;
7525 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
7526 != GS_ALL_DONE)
7527 return GS_ERROR;
7529 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr);
7530 gimplify_seq_add_stmt (pre_p, loadstmt);
7531 if (rhs && gimplify_expr (&rhs, pre_p, NULL, is_gimple_val, fb_rvalue)
7532 != GS_ALL_DONE)
7533 return GS_ERROR;
7535 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
7536 rhs = tmp_load;
7537 storestmt = gimple_build_omp_atomic_store (rhs);
7538 gimplify_seq_add_stmt (pre_p, storestmt);
7539 if (OMP_ATOMIC_SEQ_CST (*expr_p))
7541 gimple_omp_atomic_set_seq_cst (loadstmt);
7542 gimple_omp_atomic_set_seq_cst (storestmt);
7544 switch (TREE_CODE (*expr_p))
7546 case OMP_ATOMIC_READ:
7547 case OMP_ATOMIC_CAPTURE_OLD:
7548 *expr_p = tmp_load;
7549 gimple_omp_atomic_set_need_value (loadstmt);
7550 break;
7551 case OMP_ATOMIC_CAPTURE_NEW:
7552 *expr_p = rhs;
7553 gimple_omp_atomic_set_need_value (storestmt);
7554 break;
7555 default:
7556 *expr_p = NULL;
7557 break;
7560 return GS_ALL_DONE;
7563 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
7564 body, and adding some EH bits. */
7566 static enum gimplify_status
7567 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
7569 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
7570 gimple body_stmt;
7571 gtransaction *trans_stmt;
7572 gimple_seq body = NULL;
7573 int subcode = 0;
7575 /* Wrap the transaction body in a BIND_EXPR so we have a context
7576 where to put decls for OMP. */
7577 if (TREE_CODE (tbody) != BIND_EXPR)
7579 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
7580 TREE_SIDE_EFFECTS (bind) = 1;
7581 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
7582 TRANSACTION_EXPR_BODY (expr) = bind;
7585 push_gimplify_context ();
7586 temp = voidify_wrapper_expr (*expr_p, NULL);
7588 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
7589 pop_gimplify_context (body_stmt);
7591 trans_stmt = gimple_build_transaction (body, NULL);
7592 if (TRANSACTION_EXPR_OUTER (expr))
7593 subcode = GTMA_IS_OUTER;
7594 else if (TRANSACTION_EXPR_RELAXED (expr))
7595 subcode = GTMA_IS_RELAXED;
7596 gimple_transaction_set_subcode (trans_stmt, subcode);
7598 gimplify_seq_add_stmt (pre_p, trans_stmt);
7600 if (temp)
7602 *expr_p = temp;
7603 return GS_OK;
7606 *expr_p = NULL_TREE;
7607 return GS_ALL_DONE;
7610 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
7611 expression produces a value to be used as an operand inside a GIMPLE
7612 statement, the value will be stored back in *EXPR_P. This value will
7613 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
7614 an SSA_NAME. The corresponding sequence of GIMPLE statements is
7615 emitted in PRE_P and POST_P.
7617 Additionally, this process may overwrite parts of the input
7618 expression during gimplification. Ideally, it should be
7619 possible to do non-destructive gimplification.
7621 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
7622 the expression needs to evaluate to a value to be used as
7623 an operand in a GIMPLE statement, this value will be stored in
7624 *EXPR_P on exit. This happens when the caller specifies one
7625 of fb_lvalue or fb_rvalue fallback flags.
7627 PRE_P will contain the sequence of GIMPLE statements corresponding
7628 to the evaluation of EXPR and all the side-effects that must
7629 be executed before the main expression. On exit, the last
7630 statement of PRE_P is the core statement being gimplified. For
7631 instance, when gimplifying 'if (++a)' the last statement in
7632 PRE_P will be 'if (t.1)' where t.1 is the result of
7633 pre-incrementing 'a'.
7635 POST_P will contain the sequence of GIMPLE statements corresponding
7636 to the evaluation of all the side-effects that must be executed
7637 after the main expression. If this is NULL, the post
7638 side-effects are stored at the end of PRE_P.
7640 The reason why the output is split in two is to handle post
7641 side-effects explicitly. In some cases, an expression may have
7642 inner and outer post side-effects which need to be emitted in
7643 an order different from the one given by the recursive
7644 traversal. For instance, for the expression (*p--)++ the post
7645 side-effects of '--' must actually occur *after* the post
7646 side-effects of '++'. However, gimplification will first visit
7647 the inner expression, so if a separate POST sequence was not
7648 used, the resulting sequence would be:
7650 1 t.1 = *p
7651 2 p = p - 1
7652 3 t.2 = t.1 + 1
7653 4 *p = t.2
7655 However, the post-decrement operation in line #2 must not be
7656 evaluated until after the store to *p at line #4, so the
7657 correct sequence should be:
7659 1 t.1 = *p
7660 2 t.2 = t.1 + 1
7661 3 *p = t.2
7662 4 p = p - 1
7664 So, by specifying a separate post queue, it is possible
7665 to emit the post side-effects in the correct order.
7666 If POST_P is NULL, an internal queue will be used. Before
7667 returning to the caller, the sequence POST_P is appended to
7668 the main output sequence PRE_P.
7670 GIMPLE_TEST_F points to a function that takes a tree T and
7671 returns nonzero if T is in the GIMPLE form requested by the
7672 caller. The GIMPLE predicates are in gimple.c.
7674 FALLBACK tells the function what sort of a temporary we want if
7675 gimplification cannot produce an expression that complies with
7676 GIMPLE_TEST_F.
7678 fb_none means that no temporary should be generated
7679 fb_rvalue means that an rvalue is OK to generate
7680 fb_lvalue means that an lvalue is OK to generate
7681 fb_either means that either is OK, but an lvalue is preferable.
7682 fb_mayfail means that gimplification may fail (in which case
7683 GS_ERROR will be returned)
7685 The return value is either GS_ERROR or GS_ALL_DONE, since this
7686 function iterates until EXPR is completely gimplified or an error
7687 occurs. */
7689 enum gimplify_status
7690 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
7691 bool (*gimple_test_f) (tree), fallback_t fallback)
7693 tree tmp;
7694 gimple_seq internal_pre = NULL;
7695 gimple_seq internal_post = NULL;
7696 tree save_expr;
7697 bool is_statement;
7698 location_t saved_location;
7699 enum gimplify_status ret;
7700 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
7702 save_expr = *expr_p;
7703 if (save_expr == NULL_TREE)
7704 return GS_ALL_DONE;
7706 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
7707 is_statement = gimple_test_f == is_gimple_stmt;
7708 if (is_statement)
7709 gcc_assert (pre_p);
7711 /* Consistency checks. */
7712 if (gimple_test_f == is_gimple_reg)
7713 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
7714 else if (gimple_test_f == is_gimple_val
7715 || gimple_test_f == is_gimple_call_addr
7716 || gimple_test_f == is_gimple_condexpr
7717 || gimple_test_f == is_gimple_mem_rhs
7718 || gimple_test_f == is_gimple_mem_rhs_or_call
7719 || gimple_test_f == is_gimple_reg_rhs
7720 || gimple_test_f == is_gimple_reg_rhs_or_call
7721 || gimple_test_f == is_gimple_asm_val
7722 || gimple_test_f == is_gimple_mem_ref_addr)
7723 gcc_assert (fallback & fb_rvalue);
7724 else if (gimple_test_f == is_gimple_min_lval
7725 || gimple_test_f == is_gimple_lvalue)
7726 gcc_assert (fallback & fb_lvalue);
7727 else if (gimple_test_f == is_gimple_addressable)
7728 gcc_assert (fallback & fb_either);
7729 else if (gimple_test_f == is_gimple_stmt)
7730 gcc_assert (fallback == fb_none);
7731 else
7733 /* We should have recognized the GIMPLE_TEST_F predicate to
7734 know what kind of fallback to use in case a temporary is
7735 needed to hold the value or address of *EXPR_P. */
7736 gcc_unreachable ();
7739 /* We used to check the predicate here and return immediately if it
7740 succeeds. This is wrong; the design is for gimplification to be
7741 idempotent, and for the predicates to only test for valid forms, not
7742 whether they are fully simplified. */
7743 if (pre_p == NULL)
7744 pre_p = &internal_pre;
7746 if (post_p == NULL)
7747 post_p = &internal_post;
7749 /* Remember the last statements added to PRE_P and POST_P. Every
7750 new statement added by the gimplification helpers needs to be
7751 annotated with location information. To centralize the
7752 responsibility, we remember the last statement that had been
7753 added to both queues before gimplifying *EXPR_P. If
7754 gimplification produces new statements in PRE_P and POST_P, those
7755 statements will be annotated with the same location information
7756 as *EXPR_P. */
7757 pre_last_gsi = gsi_last (*pre_p);
7758 post_last_gsi = gsi_last (*post_p);
7760 saved_location = input_location;
7761 if (save_expr != error_mark_node
7762 && EXPR_HAS_LOCATION (*expr_p))
7763 input_location = EXPR_LOCATION (*expr_p);
7765 /* Loop over the specific gimplifiers until the toplevel node
7766 remains the same. */
7769 /* Strip away as many useless type conversions as possible
7770 at the toplevel. */
7771 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
7773 /* Remember the expr. */
7774 save_expr = *expr_p;
7776 /* Die, die, die, my darling. */
7777 if (save_expr == error_mark_node
7778 || (TREE_TYPE (save_expr)
7779 && TREE_TYPE (save_expr) == error_mark_node))
7781 ret = GS_ERROR;
7782 break;
7785 /* Do any language-specific gimplification. */
7786 ret = ((enum gimplify_status)
7787 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
7788 if (ret == GS_OK)
7790 if (*expr_p == NULL_TREE)
7791 break;
7792 if (*expr_p != save_expr)
7793 continue;
7795 else if (ret != GS_UNHANDLED)
7796 break;
7798 /* Make sure that all the cases set 'ret' appropriately. */
7799 ret = GS_UNHANDLED;
7800 switch (TREE_CODE (*expr_p))
7802 /* First deal with the special cases. */
7804 case POSTINCREMENT_EXPR:
7805 case POSTDECREMENT_EXPR:
7806 case PREINCREMENT_EXPR:
7807 case PREDECREMENT_EXPR:
7808 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
7809 fallback != fb_none,
7810 TREE_TYPE (*expr_p));
7811 break;
7813 case VIEW_CONVERT_EXPR:
7814 if (is_gimple_reg_type (TREE_TYPE (*expr_p))
7815 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
7817 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
7818 post_p, is_gimple_val, fb_rvalue);
7819 recalculate_side_effects (*expr_p);
7820 break;
7822 /* Fallthru. */
7824 case ARRAY_REF:
7825 case ARRAY_RANGE_REF:
7826 case REALPART_EXPR:
7827 case IMAGPART_EXPR:
7828 case COMPONENT_REF:
7829 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
7830 fallback ? fallback : fb_rvalue);
7831 break;
7833 case COND_EXPR:
7834 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
7836 /* C99 code may assign to an array in a structure value of a
7837 conditional expression, and this has undefined behavior
7838 only on execution, so create a temporary if an lvalue is
7839 required. */
7840 if (fallback == fb_lvalue)
7842 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
7843 mark_addressable (*expr_p);
7844 ret = GS_OK;
7846 break;
7848 case CALL_EXPR:
7849 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
7851 /* C99 code may assign to an array in a structure returned
7852 from a function, and this has undefined behavior only on
7853 execution, so create a temporary if an lvalue is
7854 required. */
7855 if (fallback == fb_lvalue)
7857 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
7858 mark_addressable (*expr_p);
7859 ret = GS_OK;
7861 break;
7863 case TREE_LIST:
7864 gcc_unreachable ();
7866 case COMPOUND_EXPR:
7867 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
7868 break;
7870 case COMPOUND_LITERAL_EXPR:
7871 ret = gimplify_compound_literal_expr (expr_p, pre_p,
7872 gimple_test_f, fallback);
7873 break;
7875 case MODIFY_EXPR:
7876 case INIT_EXPR:
7877 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
7878 fallback != fb_none);
7879 break;
7881 case TRUTH_ANDIF_EXPR:
7882 case TRUTH_ORIF_EXPR:
7884 /* Preserve the original type of the expression and the
7885 source location of the outer expression. */
7886 tree org_type = TREE_TYPE (*expr_p);
7887 *expr_p = gimple_boolify (*expr_p);
7888 *expr_p = build3_loc (input_location, COND_EXPR,
7889 org_type, *expr_p,
7890 fold_convert_loc
7891 (input_location,
7892 org_type, boolean_true_node),
7893 fold_convert_loc
7894 (input_location,
7895 org_type, boolean_false_node));
7896 ret = GS_OK;
7897 break;
7900 case TRUTH_NOT_EXPR:
7902 tree type = TREE_TYPE (*expr_p);
7903 /* The parsers are careful to generate TRUTH_NOT_EXPR
7904 only with operands that are always zero or one.
7905 We do not fold here but handle the only interesting case
7906 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
7907 *expr_p = gimple_boolify (*expr_p);
7908 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
7909 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
7910 TREE_TYPE (*expr_p),
7911 TREE_OPERAND (*expr_p, 0));
7912 else
7913 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
7914 TREE_TYPE (*expr_p),
7915 TREE_OPERAND (*expr_p, 0),
7916 build_int_cst (TREE_TYPE (*expr_p), 1));
7917 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
7918 *expr_p = fold_convert_loc (input_location, type, *expr_p);
7919 ret = GS_OK;
7920 break;
7923 case ADDR_EXPR:
7924 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
7925 break;
7927 case ANNOTATE_EXPR:
7929 tree cond = TREE_OPERAND (*expr_p, 0);
7930 tree kind = TREE_OPERAND (*expr_p, 1);
7931 tree type = TREE_TYPE (cond);
7932 if (!INTEGRAL_TYPE_P (type))
7934 *expr_p = cond;
7935 ret = GS_OK;
7936 break;
7938 tree tmp = create_tmp_var (type);
7939 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
7940 gcall *call
7941 = gimple_build_call_internal (IFN_ANNOTATE, 2, cond, kind);
7942 gimple_call_set_lhs (call, tmp);
7943 gimplify_seq_add_stmt (pre_p, call);
7944 *expr_p = tmp;
7945 ret = GS_ALL_DONE;
7946 break;
7949 case VA_ARG_EXPR:
7950 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
7951 break;
7953 CASE_CONVERT:
7954 if (IS_EMPTY_STMT (*expr_p))
7956 ret = GS_ALL_DONE;
7957 break;
7960 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
7961 || fallback == fb_none)
7963 /* Just strip a conversion to void (or in void context) and
7964 try again. */
7965 *expr_p = TREE_OPERAND (*expr_p, 0);
7966 ret = GS_OK;
7967 break;
7970 ret = gimplify_conversion (expr_p);
7971 if (ret == GS_ERROR)
7972 break;
7973 if (*expr_p != save_expr)
7974 break;
7975 /* FALLTHRU */
7977 case FIX_TRUNC_EXPR:
7978 /* unary_expr: ... | '(' cast ')' val | ... */
7979 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
7980 is_gimple_val, fb_rvalue);
7981 recalculate_side_effects (*expr_p);
7982 break;
7984 case INDIRECT_REF:
7986 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
7987 bool notrap = TREE_THIS_NOTRAP (*expr_p);
7988 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
7990 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
7991 if (*expr_p != save_expr)
7993 ret = GS_OK;
7994 break;
7997 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
7998 is_gimple_reg, fb_rvalue);
7999 if (ret == GS_ERROR)
8000 break;
8002 recalculate_side_effects (*expr_p);
8003 *expr_p = fold_build2_loc (input_location, MEM_REF,
8004 TREE_TYPE (*expr_p),
8005 TREE_OPERAND (*expr_p, 0),
8006 build_int_cst (saved_ptr_type, 0));
8007 TREE_THIS_VOLATILE (*expr_p) = volatilep;
8008 TREE_THIS_NOTRAP (*expr_p) = notrap;
8009 ret = GS_OK;
8010 break;
8013 /* We arrive here through the various re-gimplifcation paths. */
8014 case MEM_REF:
8015 /* First try re-folding the whole thing. */
8016 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
8017 TREE_OPERAND (*expr_p, 0),
8018 TREE_OPERAND (*expr_p, 1));
8019 if (tmp)
8021 *expr_p = tmp;
8022 recalculate_side_effects (*expr_p);
8023 ret = GS_OK;
8024 break;
8026 /* Avoid re-gimplifying the address operand if it is already
8027 in suitable form. Re-gimplifying would mark the address
8028 operand addressable. Always gimplify when not in SSA form
8029 as we still may have to gimplify decls with value-exprs. */
8030 if (!gimplify_ctxp || !gimplify_ctxp->into_ssa
8031 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
8033 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8034 is_gimple_mem_ref_addr, fb_rvalue);
8035 if (ret == GS_ERROR)
8036 break;
8038 recalculate_side_effects (*expr_p);
8039 ret = GS_ALL_DONE;
8040 break;
8042 /* Constants need not be gimplified. */
8043 case INTEGER_CST:
8044 case REAL_CST:
8045 case FIXED_CST:
8046 case STRING_CST:
8047 case COMPLEX_CST:
8048 case VECTOR_CST:
8049 /* Drop the overflow flag on constants, we do not want
8050 that in the GIMPLE IL. */
8051 if (TREE_OVERFLOW_P (*expr_p))
8052 *expr_p = drop_tree_overflow (*expr_p);
8053 ret = GS_ALL_DONE;
8054 break;
8056 case CONST_DECL:
8057 /* If we require an lvalue, such as for ADDR_EXPR, retain the
8058 CONST_DECL node. Otherwise the decl is replaceable by its
8059 value. */
8060 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
8061 if (fallback & fb_lvalue)
8062 ret = GS_ALL_DONE;
8063 else
8065 *expr_p = DECL_INITIAL (*expr_p);
8066 ret = GS_OK;
8068 break;
8070 case DECL_EXPR:
8071 ret = gimplify_decl_expr (expr_p, pre_p);
8072 break;
8074 case BIND_EXPR:
8075 ret = gimplify_bind_expr (expr_p, pre_p);
8076 break;
8078 case LOOP_EXPR:
8079 ret = gimplify_loop_expr (expr_p, pre_p);
8080 break;
8082 case SWITCH_EXPR:
8083 ret = gimplify_switch_expr (expr_p, pre_p);
8084 break;
8086 case EXIT_EXPR:
8087 ret = gimplify_exit_expr (expr_p);
8088 break;
8090 case GOTO_EXPR:
8091 /* If the target is not LABEL, then it is a computed jump
8092 and the target needs to be gimplified. */
8093 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
8095 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
8096 NULL, is_gimple_val, fb_rvalue);
8097 if (ret == GS_ERROR)
8098 break;
8100 gimplify_seq_add_stmt (pre_p,
8101 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
8102 ret = GS_ALL_DONE;
8103 break;
8105 case PREDICT_EXPR:
8106 gimplify_seq_add_stmt (pre_p,
8107 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
8108 PREDICT_EXPR_OUTCOME (*expr_p)));
8109 ret = GS_ALL_DONE;
8110 break;
8112 case LABEL_EXPR:
8113 ret = GS_ALL_DONE;
8114 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
8115 == current_function_decl);
8116 gimplify_seq_add_stmt (pre_p,
8117 gimple_build_label (LABEL_EXPR_LABEL (*expr_p)));
8118 break;
8120 case CASE_LABEL_EXPR:
8121 ret = gimplify_case_label_expr (expr_p, pre_p);
8122 break;
8124 case RETURN_EXPR:
8125 ret = gimplify_return_expr (*expr_p, pre_p);
8126 break;
8128 case CONSTRUCTOR:
8129 /* Don't reduce this in place; let gimplify_init_constructor work its
8130 magic. Buf if we're just elaborating this for side effects, just
8131 gimplify any element that has side-effects. */
8132 if (fallback == fb_none)
8134 unsigned HOST_WIDE_INT ix;
8135 tree val;
8136 tree temp = NULL_TREE;
8137 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
8138 if (TREE_SIDE_EFFECTS (val))
8139 append_to_statement_list (val, &temp);
8141 *expr_p = temp;
8142 ret = temp ? GS_OK : GS_ALL_DONE;
8144 /* C99 code may assign to an array in a constructed
8145 structure or union, and this has undefined behavior only
8146 on execution, so create a temporary if an lvalue is
8147 required. */
8148 else if (fallback == fb_lvalue)
8150 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
8151 mark_addressable (*expr_p);
8152 ret = GS_OK;
8154 else
8155 ret = GS_ALL_DONE;
8156 break;
8158 /* The following are special cases that are not handled by the
8159 original GIMPLE grammar. */
8161 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
8162 eliminated. */
8163 case SAVE_EXPR:
8164 ret = gimplify_save_expr (expr_p, pre_p, post_p);
8165 break;
8167 case BIT_FIELD_REF:
8168 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8169 post_p, is_gimple_lvalue, fb_either);
8170 recalculate_side_effects (*expr_p);
8171 break;
8173 case TARGET_MEM_REF:
8175 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
8177 if (TMR_BASE (*expr_p))
8178 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
8179 post_p, is_gimple_mem_ref_addr, fb_either);
8180 if (TMR_INDEX (*expr_p))
8181 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
8182 post_p, is_gimple_val, fb_rvalue);
8183 if (TMR_INDEX2 (*expr_p))
8184 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
8185 post_p, is_gimple_val, fb_rvalue);
8186 /* TMR_STEP and TMR_OFFSET are always integer constants. */
8187 ret = MIN (r0, r1);
8189 break;
8191 case NON_LVALUE_EXPR:
8192 /* This should have been stripped above. */
8193 gcc_unreachable ();
8195 case ASM_EXPR:
8196 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
8197 break;
8199 case TRY_FINALLY_EXPR:
8200 case TRY_CATCH_EXPR:
8202 gimple_seq eval, cleanup;
8203 gtry *try_;
8205 /* Calls to destructors are generated automatically in FINALLY/CATCH
8206 block. They should have location as UNKNOWN_LOCATION. However,
8207 gimplify_call_expr will reset these call stmts to input_location
8208 if it finds stmt's location is unknown. To prevent resetting for
8209 destructors, we set the input_location to unknown.
8210 Note that this only affects the destructor calls in FINALLY/CATCH
8211 block, and will automatically reset to its original value by the
8212 end of gimplify_expr. */
8213 input_location = UNKNOWN_LOCATION;
8214 eval = cleanup = NULL;
8215 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
8216 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
8217 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
8218 if (gimple_seq_empty_p (cleanup))
8220 gimple_seq_add_seq (pre_p, eval);
8221 ret = GS_ALL_DONE;
8222 break;
8224 try_ = gimple_build_try (eval, cleanup,
8225 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
8226 ? GIMPLE_TRY_FINALLY
8227 : GIMPLE_TRY_CATCH);
8228 if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
8229 gimple_set_location (try_, saved_location);
8230 else
8231 gimple_set_location (try_, EXPR_LOCATION (save_expr));
8232 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
8233 gimple_try_set_catch_is_cleanup (try_,
8234 TRY_CATCH_IS_CLEANUP (*expr_p));
8235 gimplify_seq_add_stmt (pre_p, try_);
8236 ret = GS_ALL_DONE;
8237 break;
8240 case CLEANUP_POINT_EXPR:
8241 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
8242 break;
8244 case TARGET_EXPR:
8245 ret = gimplify_target_expr (expr_p, pre_p, post_p);
8246 break;
8248 case CATCH_EXPR:
8250 gimple c;
8251 gimple_seq handler = NULL;
8252 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
8253 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
8254 gimplify_seq_add_stmt (pre_p, c);
8255 ret = GS_ALL_DONE;
8256 break;
8259 case EH_FILTER_EXPR:
8261 gimple ehf;
8262 gimple_seq failure = NULL;
8264 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
8265 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
8266 gimple_set_no_warning (ehf, TREE_NO_WARNING (*expr_p));
8267 gimplify_seq_add_stmt (pre_p, ehf);
8268 ret = GS_ALL_DONE;
8269 break;
8272 case OBJ_TYPE_REF:
8274 enum gimplify_status r0, r1;
8275 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
8276 post_p, is_gimple_val, fb_rvalue);
8277 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
8278 post_p, is_gimple_val, fb_rvalue);
8279 TREE_SIDE_EFFECTS (*expr_p) = 0;
8280 ret = MIN (r0, r1);
8282 break;
8284 case LABEL_DECL:
8285 /* We get here when taking the address of a label. We mark
8286 the label as "forced"; meaning it can never be removed and
8287 it is a potential target for any computed goto. */
8288 FORCED_LABEL (*expr_p) = 1;
8289 ret = GS_ALL_DONE;
8290 break;
8292 case STATEMENT_LIST:
8293 ret = gimplify_statement_list (expr_p, pre_p);
8294 break;
8296 case WITH_SIZE_EXPR:
8298 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8299 post_p == &internal_post ? NULL : post_p,
8300 gimple_test_f, fallback);
8301 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
8302 is_gimple_val, fb_rvalue);
8303 ret = GS_ALL_DONE;
8305 break;
8307 case VAR_DECL:
8308 case PARM_DECL:
8309 ret = gimplify_var_or_parm_decl (expr_p);
8310 break;
8312 case RESULT_DECL:
8313 /* When within an OMP context, notice uses of variables. */
8314 if (gimplify_omp_ctxp)
8315 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
8316 ret = GS_ALL_DONE;
8317 break;
8319 case SSA_NAME:
8320 /* Allow callbacks into the gimplifier during optimization. */
8321 ret = GS_ALL_DONE;
8322 break;
8324 case OMP_PARALLEL:
8325 gimplify_omp_parallel (expr_p, pre_p);
8326 ret = GS_ALL_DONE;
8327 break;
8329 case OMP_TASK:
8330 gimplify_omp_task (expr_p, pre_p);
8331 ret = GS_ALL_DONE;
8332 break;
8334 case OMP_FOR:
8335 case OMP_SIMD:
8336 case CILK_SIMD:
8337 case CILK_FOR:
8338 case OMP_DISTRIBUTE:
8339 case OACC_LOOP:
8340 ret = gimplify_omp_for (expr_p, pre_p);
8341 break;
8343 case OACC_CACHE:
8344 gimplify_oacc_cache (expr_p, pre_p);
8345 ret = GS_ALL_DONE;
8346 break;
8348 case OACC_HOST_DATA:
8349 case OACC_DECLARE:
8350 sorry ("directive not yet implemented");
8351 ret = GS_ALL_DONE;
8352 break;
8354 case OACC_KERNELS:
8355 if (OACC_KERNELS_COMBINED (*expr_p))
8356 sorry ("directive not yet implemented");
8357 else
8358 gimplify_omp_workshare (expr_p, pre_p);
8359 ret = GS_ALL_DONE;
8360 break;
8362 case OACC_PARALLEL:
8363 if (OACC_PARALLEL_COMBINED (*expr_p))
8364 sorry ("directive not yet implemented");
8365 else
8366 gimplify_omp_workshare (expr_p, pre_p);
8367 ret = GS_ALL_DONE;
8368 break;
8370 case OACC_DATA:
8371 case OMP_SECTIONS:
8372 case OMP_SINGLE:
8373 case OMP_TARGET:
8374 case OMP_TARGET_DATA:
8375 case OMP_TEAMS:
8376 gimplify_omp_workshare (expr_p, pre_p);
8377 ret = GS_ALL_DONE;
8378 break;
8380 case OACC_ENTER_DATA:
8381 case OACC_EXIT_DATA:
8382 case OACC_UPDATE:
8383 case OMP_TARGET_UPDATE:
8384 gimplify_omp_target_update (expr_p, pre_p);
8385 ret = GS_ALL_DONE;
8386 break;
8388 case OMP_SECTION:
8389 case OMP_MASTER:
8390 case OMP_TASKGROUP:
8391 case OMP_ORDERED:
8392 case OMP_CRITICAL:
8394 gimple_seq body = NULL;
8395 gimple g;
8397 gimplify_and_add (OMP_BODY (*expr_p), &body);
8398 switch (TREE_CODE (*expr_p))
8400 case OMP_SECTION:
8401 g = gimple_build_omp_section (body);
8402 break;
8403 case OMP_MASTER:
8404 g = gimple_build_omp_master (body);
8405 break;
8406 case OMP_TASKGROUP:
8408 gimple_seq cleanup = NULL;
8409 tree fn
8410 = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
8411 g = gimple_build_call (fn, 0);
8412 gimple_seq_add_stmt (&cleanup, g);
8413 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
8414 body = NULL;
8415 gimple_seq_add_stmt (&body, g);
8416 g = gimple_build_omp_taskgroup (body);
8418 break;
8419 case OMP_ORDERED:
8420 g = gimple_build_omp_ordered (body);
8421 break;
8422 case OMP_CRITICAL:
8423 g = gimple_build_omp_critical (body,
8424 OMP_CRITICAL_NAME (*expr_p));
8425 break;
8426 default:
8427 gcc_unreachable ();
8429 gimplify_seq_add_stmt (pre_p, g);
8430 ret = GS_ALL_DONE;
8431 break;
8434 case OMP_ATOMIC:
8435 case OMP_ATOMIC_READ:
8436 case OMP_ATOMIC_CAPTURE_OLD:
8437 case OMP_ATOMIC_CAPTURE_NEW:
8438 ret = gimplify_omp_atomic (expr_p, pre_p);
8439 break;
8441 case TRANSACTION_EXPR:
8442 ret = gimplify_transaction (expr_p, pre_p);
8443 break;
8445 case TRUTH_AND_EXPR:
8446 case TRUTH_OR_EXPR:
8447 case TRUTH_XOR_EXPR:
8449 tree orig_type = TREE_TYPE (*expr_p);
8450 tree new_type, xop0, xop1;
8451 *expr_p = gimple_boolify (*expr_p);
8452 new_type = TREE_TYPE (*expr_p);
8453 if (!useless_type_conversion_p (orig_type, new_type))
8455 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
8456 ret = GS_OK;
8457 break;
8460 /* Boolified binary truth expressions are semantically equivalent
8461 to bitwise binary expressions. Canonicalize them to the
8462 bitwise variant. */
8463 switch (TREE_CODE (*expr_p))
8465 case TRUTH_AND_EXPR:
8466 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
8467 break;
8468 case TRUTH_OR_EXPR:
8469 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
8470 break;
8471 case TRUTH_XOR_EXPR:
8472 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
8473 break;
8474 default:
8475 break;
8477 /* Now make sure that operands have compatible type to
8478 expression's new_type. */
8479 xop0 = TREE_OPERAND (*expr_p, 0);
8480 xop1 = TREE_OPERAND (*expr_p, 1);
8481 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
8482 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
8483 new_type,
8484 xop0);
8485 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
8486 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
8487 new_type,
8488 xop1);
8489 /* Continue classified as tcc_binary. */
8490 goto expr_2;
8493 case FMA_EXPR:
8494 case VEC_COND_EXPR:
8495 case VEC_PERM_EXPR:
8496 /* Classified as tcc_expression. */
8497 goto expr_3;
8499 case POINTER_PLUS_EXPR:
8501 enum gimplify_status r0, r1;
8502 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8503 post_p, is_gimple_val, fb_rvalue);
8504 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8505 post_p, is_gimple_val, fb_rvalue);
8506 recalculate_side_effects (*expr_p);
8507 ret = MIN (r0, r1);
8508 /* Convert &X + CST to invariant &MEM[&X, CST]. Do this
8509 after gimplifying operands - this is similar to how
8510 it would be folding all gimplified stmts on creation
8511 to have them canonicalized, which is what we eventually
8512 should do anyway. */
8513 if (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == INTEGER_CST
8514 && is_gimple_min_invariant (TREE_OPERAND (*expr_p, 0)))
8516 *expr_p = build_fold_addr_expr_with_type_loc
8517 (input_location,
8518 fold_build2 (MEM_REF, TREE_TYPE (TREE_TYPE (*expr_p)),
8519 TREE_OPERAND (*expr_p, 0),
8520 fold_convert (ptr_type_node,
8521 TREE_OPERAND (*expr_p, 1))),
8522 TREE_TYPE (*expr_p));
8523 ret = MIN (ret, GS_OK);
8525 break;
8528 case CILK_SYNC_STMT:
8530 if (!fn_contains_cilk_spawn_p (cfun))
8532 error_at (EXPR_LOCATION (*expr_p),
8533 "expected %<_Cilk_spawn%> before %<_Cilk_sync%>");
8534 ret = GS_ERROR;
8536 else
8538 gimplify_cilk_sync (expr_p, pre_p);
8539 ret = GS_ALL_DONE;
8541 break;
8544 default:
8545 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
8547 case tcc_comparison:
8548 /* Handle comparison of objects of non scalar mode aggregates
8549 with a call to memcmp. It would be nice to only have to do
8550 this for variable-sized objects, but then we'd have to allow
8551 the same nest of reference nodes we allow for MODIFY_EXPR and
8552 that's too complex.
8554 Compare scalar mode aggregates as scalar mode values. Using
8555 memcmp for them would be very inefficient at best, and is
8556 plain wrong if bitfields are involved. */
8558 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
8560 /* Vector comparisons need no boolification. */
8561 if (TREE_CODE (type) == VECTOR_TYPE)
8562 goto expr_2;
8563 else if (!AGGREGATE_TYPE_P (type))
8565 tree org_type = TREE_TYPE (*expr_p);
8566 *expr_p = gimple_boolify (*expr_p);
8567 if (!useless_type_conversion_p (org_type,
8568 TREE_TYPE (*expr_p)))
8570 *expr_p = fold_convert_loc (input_location,
8571 org_type, *expr_p);
8572 ret = GS_OK;
8574 else
8575 goto expr_2;
8577 else if (TYPE_MODE (type) != BLKmode)
8578 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
8579 else
8580 ret = gimplify_variable_sized_compare (expr_p);
8582 break;
8585 /* If *EXPR_P does not need to be special-cased, handle it
8586 according to its class. */
8587 case tcc_unary:
8588 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8589 post_p, is_gimple_val, fb_rvalue);
8590 break;
8592 case tcc_binary:
8593 expr_2:
8595 enum gimplify_status r0, r1;
8597 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8598 post_p, is_gimple_val, fb_rvalue);
8599 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8600 post_p, is_gimple_val, fb_rvalue);
8602 ret = MIN (r0, r1);
8603 break;
8606 expr_3:
8608 enum gimplify_status r0, r1, r2;
8610 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
8611 post_p, is_gimple_val, fb_rvalue);
8612 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
8613 post_p, is_gimple_val, fb_rvalue);
8614 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
8615 post_p, is_gimple_val, fb_rvalue);
8617 ret = MIN (MIN (r0, r1), r2);
8618 break;
8621 case tcc_declaration:
8622 case tcc_constant:
8623 ret = GS_ALL_DONE;
8624 goto dont_recalculate;
8626 default:
8627 gcc_unreachable ();
8630 recalculate_side_effects (*expr_p);
8632 dont_recalculate:
8633 break;
8636 gcc_assert (*expr_p || ret != GS_OK);
8638 while (ret == GS_OK);
8640 /* If we encountered an error_mark somewhere nested inside, either
8641 stub out the statement or propagate the error back out. */
8642 if (ret == GS_ERROR)
8644 if (is_statement)
8645 *expr_p = NULL;
8646 goto out;
8649 /* This was only valid as a return value from the langhook, which
8650 we handled. Make sure it doesn't escape from any other context. */
8651 gcc_assert (ret != GS_UNHANDLED);
8653 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
8655 /* We aren't looking for a value, and we don't have a valid
8656 statement. If it doesn't have side-effects, throw it away. */
8657 if (!TREE_SIDE_EFFECTS (*expr_p))
8658 *expr_p = NULL;
8659 else if (!TREE_THIS_VOLATILE (*expr_p))
8661 /* This is probably a _REF that contains something nested that
8662 has side effects. Recurse through the operands to find it. */
8663 enum tree_code code = TREE_CODE (*expr_p);
8665 switch (code)
8667 case COMPONENT_REF:
8668 case REALPART_EXPR:
8669 case IMAGPART_EXPR:
8670 case VIEW_CONVERT_EXPR:
8671 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8672 gimple_test_f, fallback);
8673 break;
8675 case ARRAY_REF:
8676 case ARRAY_RANGE_REF:
8677 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
8678 gimple_test_f, fallback);
8679 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
8680 gimple_test_f, fallback);
8681 break;
8683 default:
8684 /* Anything else with side-effects must be converted to
8685 a valid statement before we get here. */
8686 gcc_unreachable ();
8689 *expr_p = NULL;
8691 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
8692 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
8694 /* Historically, the compiler has treated a bare reference
8695 to a non-BLKmode volatile lvalue as forcing a load. */
8696 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
8698 /* Normally, we do not want to create a temporary for a
8699 TREE_ADDRESSABLE type because such a type should not be
8700 copied by bitwise-assignment. However, we make an
8701 exception here, as all we are doing here is ensuring that
8702 we read the bytes that make up the type. We use
8703 create_tmp_var_raw because create_tmp_var will abort when
8704 given a TREE_ADDRESSABLE type. */
8705 tree tmp = create_tmp_var_raw (type, "vol");
8706 gimple_add_tmp_var (tmp);
8707 gimplify_assign (tmp, *expr_p, pre_p);
8708 *expr_p = NULL;
8710 else
8711 /* We can't do anything useful with a volatile reference to
8712 an incomplete type, so just throw it away. Likewise for
8713 a BLKmode type, since any implicit inner load should
8714 already have been turned into an explicit one by the
8715 gimplification process. */
8716 *expr_p = NULL;
8719 /* If we are gimplifying at the statement level, we're done. Tack
8720 everything together and return. */
8721 if (fallback == fb_none || is_statement)
8723 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
8724 it out for GC to reclaim it. */
8725 *expr_p = NULL_TREE;
8727 if (!gimple_seq_empty_p (internal_pre)
8728 || !gimple_seq_empty_p (internal_post))
8730 gimplify_seq_add_seq (&internal_pre, internal_post);
8731 gimplify_seq_add_seq (pre_p, internal_pre);
8734 /* The result of gimplifying *EXPR_P is going to be the last few
8735 statements in *PRE_P and *POST_P. Add location information
8736 to all the statements that were added by the gimplification
8737 helpers. */
8738 if (!gimple_seq_empty_p (*pre_p))
8739 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
8741 if (!gimple_seq_empty_p (*post_p))
8742 annotate_all_with_location_after (*post_p, post_last_gsi,
8743 input_location);
8745 goto out;
8748 #ifdef ENABLE_GIMPLE_CHECKING
8749 if (*expr_p)
8751 enum tree_code code = TREE_CODE (*expr_p);
8752 /* These expressions should already be in gimple IR form. */
8753 gcc_assert (code != MODIFY_EXPR
8754 && code != ASM_EXPR
8755 && code != BIND_EXPR
8756 && code != CATCH_EXPR
8757 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
8758 && code != EH_FILTER_EXPR
8759 && code != GOTO_EXPR
8760 && code != LABEL_EXPR
8761 && code != LOOP_EXPR
8762 && code != SWITCH_EXPR
8763 && code != TRY_FINALLY_EXPR
8764 && code != OACC_PARALLEL
8765 && code != OACC_KERNELS
8766 && code != OACC_DATA
8767 && code != OACC_HOST_DATA
8768 && code != OACC_DECLARE
8769 && code != OACC_UPDATE
8770 && code != OACC_ENTER_DATA
8771 && code != OACC_EXIT_DATA
8772 && code != OACC_CACHE
8773 && code != OMP_CRITICAL
8774 && code != OMP_FOR
8775 && code != OACC_LOOP
8776 && code != OMP_MASTER
8777 && code != OMP_TASKGROUP
8778 && code != OMP_ORDERED
8779 && code != OMP_PARALLEL
8780 && code != OMP_SECTIONS
8781 && code != OMP_SECTION
8782 && code != OMP_SINGLE);
8784 #endif
8786 /* Otherwise we're gimplifying a subexpression, so the resulting
8787 value is interesting. If it's a valid operand that matches
8788 GIMPLE_TEST_F, we're done. Unless we are handling some
8789 post-effects internally; if that's the case, we need to copy into
8790 a temporary before adding the post-effects to POST_P. */
8791 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
8792 goto out;
8794 /* Otherwise, we need to create a new temporary for the gimplified
8795 expression. */
8797 /* We can't return an lvalue if we have an internal postqueue. The
8798 object the lvalue refers to would (probably) be modified by the
8799 postqueue; we need to copy the value out first, which means an
8800 rvalue. */
8801 if ((fallback & fb_lvalue)
8802 && gimple_seq_empty_p (internal_post)
8803 && is_gimple_addressable (*expr_p))
8805 /* An lvalue will do. Take the address of the expression, store it
8806 in a temporary, and replace the expression with an INDIRECT_REF of
8807 that temporary. */
8808 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
8809 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
8810 *expr_p = build_simple_mem_ref (tmp);
8812 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
8814 /* An rvalue will do. Assign the gimplified expression into a
8815 new temporary TMP and replace the original expression with
8816 TMP. First, make sure that the expression has a type so that
8817 it can be assigned into a temporary. */
8818 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
8819 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
8821 else
8823 #ifdef ENABLE_GIMPLE_CHECKING
8824 if (!(fallback & fb_mayfail))
8826 fprintf (stderr, "gimplification failed:\n");
8827 print_generic_expr (stderr, *expr_p, 0);
8828 debug_tree (*expr_p);
8829 internal_error ("gimplification failed");
8831 #endif
8832 gcc_assert (fallback & fb_mayfail);
8834 /* If this is an asm statement, and the user asked for the
8835 impossible, don't die. Fail and let gimplify_asm_expr
8836 issue an error. */
8837 ret = GS_ERROR;
8838 goto out;
8841 /* Make sure the temporary matches our predicate. */
8842 gcc_assert ((*gimple_test_f) (*expr_p));
8844 if (!gimple_seq_empty_p (internal_post))
8846 annotate_all_with_location (internal_post, input_location);
8847 gimplify_seq_add_seq (pre_p, internal_post);
8850 out:
8851 input_location = saved_location;
8852 return ret;
8855 /* Look through TYPE for variable-sized objects and gimplify each such
8856 size that we find. Add to LIST_P any statements generated. */
8858 void
8859 gimplify_type_sizes (tree type, gimple_seq *list_p)
8861 tree field, t;
8863 if (type == NULL || type == error_mark_node)
8864 return;
8866 /* We first do the main variant, then copy into any other variants. */
8867 type = TYPE_MAIN_VARIANT (type);
8869 /* Avoid infinite recursion. */
8870 if (TYPE_SIZES_GIMPLIFIED (type))
8871 return;
8873 TYPE_SIZES_GIMPLIFIED (type) = 1;
8875 switch (TREE_CODE (type))
8877 case INTEGER_TYPE:
8878 case ENUMERAL_TYPE:
8879 case BOOLEAN_TYPE:
8880 case REAL_TYPE:
8881 case FIXED_POINT_TYPE:
8882 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
8883 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
8885 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
8887 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
8888 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
8890 break;
8892 case ARRAY_TYPE:
8893 /* These types may not have declarations, so handle them here. */
8894 gimplify_type_sizes (TREE_TYPE (type), list_p);
8895 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
8896 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
8897 with assigned stack slots, for -O1+ -g they should be tracked
8898 by VTA. */
8899 if (!(TYPE_NAME (type)
8900 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
8901 && DECL_IGNORED_P (TYPE_NAME (type)))
8902 && TYPE_DOMAIN (type)
8903 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
8905 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
8906 if (t && TREE_CODE (t) == VAR_DECL && DECL_ARTIFICIAL (t))
8907 DECL_IGNORED_P (t) = 0;
8908 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
8909 if (t && TREE_CODE (t) == VAR_DECL && DECL_ARTIFICIAL (t))
8910 DECL_IGNORED_P (t) = 0;
8912 break;
8914 case RECORD_TYPE:
8915 case UNION_TYPE:
8916 case QUAL_UNION_TYPE:
8917 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
8918 if (TREE_CODE (field) == FIELD_DECL)
8920 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
8921 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
8922 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
8923 gimplify_type_sizes (TREE_TYPE (field), list_p);
8925 break;
8927 case POINTER_TYPE:
8928 case REFERENCE_TYPE:
8929 /* We used to recurse on the pointed-to type here, which turned out to
8930 be incorrect because its definition might refer to variables not
8931 yet initialized at this point if a forward declaration is involved.
8933 It was actually useful for anonymous pointed-to types to ensure
8934 that the sizes evaluation dominates every possible later use of the
8935 values. Restricting to such types here would be safe since there
8936 is no possible forward declaration around, but would introduce an
8937 undesirable middle-end semantic to anonymity. We then defer to
8938 front-ends the responsibility of ensuring that the sizes are
8939 evaluated both early and late enough, e.g. by attaching artificial
8940 type declarations to the tree. */
8941 break;
8943 default:
8944 break;
8947 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
8948 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
8950 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
8952 TYPE_SIZE (t) = TYPE_SIZE (type);
8953 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
8954 TYPE_SIZES_GIMPLIFIED (t) = 1;
8958 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
8959 a size or position, has had all of its SAVE_EXPRs evaluated.
8960 We add any required statements to *STMT_P. */
8962 void
8963 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
8965 tree expr = *expr_p;
8967 /* We don't do anything if the value isn't there, is constant, or contains
8968 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
8969 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
8970 will want to replace it with a new variable, but that will cause problems
8971 if this type is from outside the function. It's OK to have that here. */
8972 if (is_gimple_sizepos (expr))
8973 return;
8975 *expr_p = unshare_expr (expr);
8977 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue);
8980 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
8981 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
8982 is true, also gimplify the parameters. */
8984 gbind *
8985 gimplify_body (tree fndecl, bool do_parms)
8987 location_t saved_location = input_location;
8988 gimple_seq parm_stmts, seq;
8989 gimple outer_stmt;
8990 gbind *outer_bind;
8991 struct cgraph_node *cgn;
8993 timevar_push (TV_TREE_GIMPLIFY);
8995 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
8996 gimplification. */
8997 default_rtl_profile ();
8999 gcc_assert (gimplify_ctxp == NULL);
9000 push_gimplify_context ();
9002 if (flag_openacc || flag_openmp)
9004 gcc_assert (gimplify_omp_ctxp == NULL);
9005 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
9006 gimplify_omp_ctxp = new_omp_context (ORT_TARGET);
9009 /* Unshare most shared trees in the body and in that of any nested functions.
9010 It would seem we don't have to do this for nested functions because
9011 they are supposed to be output and then the outer function gimplified
9012 first, but the g++ front end doesn't always do it that way. */
9013 unshare_body (fndecl);
9014 unvisit_body (fndecl);
9016 cgn = cgraph_node::get (fndecl);
9017 if (cgn && cgn->origin)
9018 nonlocal_vlas = new hash_set<tree>;
9020 /* Make sure input_location isn't set to something weird. */
9021 input_location = DECL_SOURCE_LOCATION (fndecl);
9023 /* Resolve callee-copies. This has to be done before processing
9024 the body so that DECL_VALUE_EXPR gets processed correctly. */
9025 parm_stmts = do_parms ? gimplify_parameters () : NULL;
9027 /* Gimplify the function's body. */
9028 seq = NULL;
9029 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
9030 outer_stmt = gimple_seq_first_stmt (seq);
9031 if (!outer_stmt)
9033 outer_stmt = gimple_build_nop ();
9034 gimplify_seq_add_stmt (&seq, outer_stmt);
9037 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
9038 not the case, wrap everything in a GIMPLE_BIND to make it so. */
9039 if (gimple_code (outer_stmt) == GIMPLE_BIND
9040 && gimple_seq_first (seq) == gimple_seq_last (seq))
9041 outer_bind = as_a <gbind *> (outer_stmt);
9042 else
9043 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
9045 DECL_SAVED_TREE (fndecl) = NULL_TREE;
9047 /* If we had callee-copies statements, insert them at the beginning
9048 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
9049 if (!gimple_seq_empty_p (parm_stmts))
9051 tree parm;
9053 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
9054 gimple_bind_set_body (outer_bind, parm_stmts);
9056 for (parm = DECL_ARGUMENTS (current_function_decl);
9057 parm; parm = DECL_CHAIN (parm))
9058 if (DECL_HAS_VALUE_EXPR_P (parm))
9060 DECL_HAS_VALUE_EXPR_P (parm) = 0;
9061 DECL_IGNORED_P (parm) = 0;
9065 if (nonlocal_vlas)
9067 if (nonlocal_vla_vars)
9069 /* tree-nested.c may later on call declare_vars (..., true);
9070 which relies on BLOCK_VARS chain to be the tail of the
9071 gimple_bind_vars chain. Ensure we don't violate that
9072 assumption. */
9073 if (gimple_bind_block (outer_bind)
9074 == DECL_INITIAL (current_function_decl))
9075 declare_vars (nonlocal_vla_vars, outer_bind, true);
9076 else
9077 BLOCK_VARS (DECL_INITIAL (current_function_decl))
9078 = chainon (BLOCK_VARS (DECL_INITIAL (current_function_decl)),
9079 nonlocal_vla_vars);
9080 nonlocal_vla_vars = NULL_TREE;
9082 delete nonlocal_vlas;
9083 nonlocal_vlas = NULL;
9086 if ((flag_openacc || flag_openmp || flag_openmp_simd)
9087 && gimplify_omp_ctxp)
9089 delete_omp_context (gimplify_omp_ctxp);
9090 gimplify_omp_ctxp = NULL;
9093 pop_gimplify_context (outer_bind);
9094 gcc_assert (gimplify_ctxp == NULL);
9096 #ifdef ENABLE_CHECKING
9097 if (!seen_error ())
9098 verify_gimple_in_seq (gimple_bind_body (outer_bind));
9099 #endif
9101 timevar_pop (TV_TREE_GIMPLIFY);
9102 input_location = saved_location;
9104 return outer_bind;
9107 typedef char *char_p; /* For DEF_VEC_P. */
9109 /* Return whether we should exclude FNDECL from instrumentation. */
9111 static bool
9112 flag_instrument_functions_exclude_p (tree fndecl)
9114 vec<char_p> *v;
9116 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
9117 if (v && v->length () > 0)
9119 const char *name;
9120 int i;
9121 char *s;
9123 name = lang_hooks.decl_printable_name (fndecl, 0);
9124 FOR_EACH_VEC_ELT (*v, i, s)
9125 if (strstr (name, s) != NULL)
9126 return true;
9129 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
9130 if (v && v->length () > 0)
9132 const char *name;
9133 int i;
9134 char *s;
9136 name = DECL_SOURCE_FILE (fndecl);
9137 FOR_EACH_VEC_ELT (*v, i, s)
9138 if (strstr (name, s) != NULL)
9139 return true;
9142 return false;
9145 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
9146 node for the function we want to gimplify.
9148 Return the sequence of GIMPLE statements corresponding to the body
9149 of FNDECL. */
9151 void
9152 gimplify_function_tree (tree fndecl)
9154 tree parm, ret;
9155 gimple_seq seq;
9156 gbind *bind;
9158 gcc_assert (!gimple_body (fndecl));
9160 if (DECL_STRUCT_FUNCTION (fndecl))
9161 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
9162 else
9163 push_struct_function (fndecl);
9165 for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = DECL_CHAIN (parm))
9167 /* Preliminarily mark non-addressed complex variables as eligible
9168 for promotion to gimple registers. We'll transform their uses
9169 as we find them. */
9170 if ((TREE_CODE (TREE_TYPE (parm)) == COMPLEX_TYPE
9171 || TREE_CODE (TREE_TYPE (parm)) == VECTOR_TYPE)
9172 && !TREE_THIS_VOLATILE (parm)
9173 && !needs_to_live_in_memory (parm))
9174 DECL_GIMPLE_REG_P (parm) = 1;
9177 ret = DECL_RESULT (fndecl);
9178 if ((TREE_CODE (TREE_TYPE (ret)) == COMPLEX_TYPE
9179 || TREE_CODE (TREE_TYPE (ret)) == VECTOR_TYPE)
9180 && !needs_to_live_in_memory (ret))
9181 DECL_GIMPLE_REG_P (ret) = 1;
9183 bind = gimplify_body (fndecl, true);
9185 /* The tree body of the function is no longer needed, replace it
9186 with the new GIMPLE body. */
9187 seq = NULL;
9188 gimple_seq_add_stmt (&seq, bind);
9189 gimple_set_body (fndecl, seq);
9191 /* If we're instrumenting function entry/exit, then prepend the call to
9192 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
9193 catch the exit hook. */
9194 /* ??? Add some way to ignore exceptions for this TFE. */
9195 if (flag_instrument_function_entry_exit
9196 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
9197 && !flag_instrument_functions_exclude_p (fndecl))
9199 tree x;
9200 gbind *new_bind;
9201 gimple tf;
9202 gimple_seq cleanup = NULL, body = NULL;
9203 tree tmp_var;
9204 gcall *call;
9206 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
9207 call = gimple_build_call (x, 1, integer_zero_node);
9208 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
9209 gimple_call_set_lhs (call, tmp_var);
9210 gimplify_seq_add_stmt (&cleanup, call);
9211 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
9212 call = gimple_build_call (x, 2,
9213 build_fold_addr_expr (current_function_decl),
9214 tmp_var);
9215 gimplify_seq_add_stmt (&cleanup, call);
9216 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
9218 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
9219 call = gimple_build_call (x, 1, integer_zero_node);
9220 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
9221 gimple_call_set_lhs (call, tmp_var);
9222 gimplify_seq_add_stmt (&body, call);
9223 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
9224 call = gimple_build_call (x, 2,
9225 build_fold_addr_expr (current_function_decl),
9226 tmp_var);
9227 gimplify_seq_add_stmt (&body, call);
9228 gimplify_seq_add_stmt (&body, tf);
9229 new_bind = gimple_build_bind (NULL, body, gimple_bind_block (bind));
9230 /* Clear the block for BIND, since it is no longer directly inside
9231 the function, but within a try block. */
9232 gimple_bind_set_block (bind, NULL);
9234 /* Replace the current function body with the body
9235 wrapped in the try/finally TF. */
9236 seq = NULL;
9237 gimple_seq_add_stmt (&seq, new_bind);
9238 gimple_set_body (fndecl, seq);
9239 bind = new_bind;
9242 if (flag_sanitize & SANITIZE_THREAD)
9244 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
9245 gimple tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
9246 gbind *new_bind = gimple_build_bind (NULL, tf, gimple_bind_block (bind));
9247 /* Clear the block for BIND, since it is no longer directly inside
9248 the function, but within a try block. */
9249 gimple_bind_set_block (bind, NULL);
9250 /* Replace the current function body with the body
9251 wrapped in the try/finally TF. */
9252 seq = NULL;
9253 gimple_seq_add_stmt (&seq, new_bind);
9254 gimple_set_body (fndecl, seq);
9257 DECL_SAVED_TREE (fndecl) = NULL_TREE;
9258 cfun->curr_properties = PROP_gimple_any;
9260 pop_cfun ();
9263 /* Return a dummy expression of type TYPE in order to keep going after an
9264 error. */
9266 static tree
9267 dummy_object (tree type)
9269 tree t = build_int_cst (build_pointer_type (type), 0);
9270 return build2 (MEM_REF, type, t, t);
9273 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
9274 builtin function, but a very special sort of operator. */
9276 enum gimplify_status
9277 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
9279 tree promoted_type, have_va_type;
9280 tree valist = TREE_OPERAND (*expr_p, 0);
9281 tree type = TREE_TYPE (*expr_p);
9282 tree t;
9283 location_t loc = EXPR_LOCATION (*expr_p);
9285 /* Verify that valist is of the proper type. */
9286 have_va_type = TREE_TYPE (valist);
9287 if (have_va_type == error_mark_node)
9288 return GS_ERROR;
9289 have_va_type = targetm.canonical_va_list_type (have_va_type);
9291 if (have_va_type == NULL_TREE)
9293 error_at (loc, "first argument to %<va_arg%> not of type %<va_list%>");
9294 return GS_ERROR;
9297 /* Generate a diagnostic for requesting data of a type that cannot
9298 be passed through `...' due to type promotion at the call site. */
9299 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
9300 != type)
9302 static bool gave_help;
9303 bool warned;
9305 /* Unfortunately, this is merely undefined, rather than a constraint
9306 violation, so we cannot make this an error. If this call is never
9307 executed, the program is still strictly conforming. */
9308 warned = warning_at (loc, 0,
9309 "%qT is promoted to %qT when passed through %<...%>",
9310 type, promoted_type);
9311 if (!gave_help && warned)
9313 gave_help = true;
9314 inform (loc, "(so you should pass %qT not %qT to %<va_arg%>)",
9315 promoted_type, type);
9318 /* We can, however, treat "undefined" any way we please.
9319 Call abort to encourage the user to fix the program. */
9320 if (warned)
9321 inform (loc, "if this code is reached, the program will abort");
9322 /* Before the abort, allow the evaluation of the va_list
9323 expression to exit or longjmp. */
9324 gimplify_and_add (valist, pre_p);
9325 t = build_call_expr_loc (loc,
9326 builtin_decl_implicit (BUILT_IN_TRAP), 0);
9327 gimplify_and_add (t, pre_p);
9329 /* This is dead code, but go ahead and finish so that the
9330 mode of the result comes out right. */
9331 *expr_p = dummy_object (type);
9332 return GS_ALL_DONE;
9334 else
9336 /* Make it easier for the backends by protecting the valist argument
9337 from multiple evaluations. */
9338 if (TREE_CODE (have_va_type) == ARRAY_TYPE)
9340 /* For this case, the backends will be expecting a pointer to
9341 TREE_TYPE (abi), but it's possible we've
9342 actually been given an array (an actual TARGET_FN_ABI_VA_LIST).
9343 So fix it. */
9344 if (TREE_CODE (TREE_TYPE (valist)) == ARRAY_TYPE)
9346 tree p1 = build_pointer_type (TREE_TYPE (have_va_type));
9347 valist = fold_convert_loc (loc, p1,
9348 build_fold_addr_expr_loc (loc, valist));
9351 gimplify_expr (&valist, pre_p, post_p, is_gimple_val, fb_rvalue);
9353 else
9354 gimplify_expr (&valist, pre_p, post_p, is_gimple_min_lval, fb_lvalue);
9356 if (!targetm.gimplify_va_arg_expr)
9357 /* FIXME: Once most targets are converted we should merely
9358 assert this is non-null. */
9359 return GS_ALL_DONE;
9361 *expr_p = targetm.gimplify_va_arg_expr (valist, type, pre_p, post_p);
9362 return GS_OK;
9366 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
9368 DST/SRC are the destination and source respectively. You can pass
9369 ungimplified trees in DST or SRC, in which case they will be
9370 converted to a gimple operand if necessary.
9372 This function returns the newly created GIMPLE_ASSIGN tuple. */
9374 gimple
9375 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
9377 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
9378 gimplify_and_add (t, seq_p);
9379 ggc_free (t);
9380 return gimple_seq_last_stmt (*seq_p);
9383 inline hashval_t
9384 gimplify_hasher::hash (const value_type *p)
9386 tree t = p->val;
9387 return iterative_hash_expr (t, 0);
9390 inline bool
9391 gimplify_hasher::equal (const value_type *p1, const compare_type *p2)
9393 tree t1 = p1->val;
9394 tree t2 = p2->val;
9395 enum tree_code code = TREE_CODE (t1);
9397 if (TREE_CODE (t2) != code
9398 || TREE_TYPE (t1) != TREE_TYPE (t2))
9399 return false;
9401 if (!operand_equal_p (t1, t2, 0))
9402 return false;
9404 #ifdef ENABLE_CHECKING
9405 /* Only allow them to compare equal if they also hash equal; otherwise
9406 results are nondeterminate, and we fail bootstrap comparison. */
9407 gcc_assert (hash (p1) == hash (p2));
9408 #endif
9410 return true;