gimplify.c (gimplify_init_constructor <case VECTOR_TYPE>): Use a temporary variable...
[official-gcc.git] / gcc / gimplify.c
blob5df8579913ac37c1c3c2eb9c2355464843923014
1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002, 2003, 2004, 2005, 2006, 2007
4 Free Software Foundation, Inc.
5 Major work done by Sebastian Pop <s.pop@laposte.net>,
6 Diego Novillo <dnovillo@redhat.com> and Jason Merrill <jason@redhat.com>.
8 This file is part of GCC.
10 GCC is free software; you can redistribute it and/or modify it under
11 the terms of the GNU General Public License as published by the Free
12 Software Foundation; either version 2, or (at your option) any later
13 version.
15 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
16 WARRANTY; without even the implied warranty of MERCHANTABILITY or
17 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
18 for more details.
20 You should have received a copy of the GNU General Public License
21 along with GCC; see the file COPYING. If not, write to the Free
22 Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
23 02110-1301, USA. */
25 #include "config.h"
26 #include "system.h"
27 #include "coretypes.h"
28 #include "tm.h"
29 #include "tree.h"
30 #include "rtl.h"
31 #include "varray.h"
32 #include "tree-gimple.h"
33 #include "tree-inline.h"
34 #include "diagnostic.h"
35 #include "langhooks.h"
36 #include "langhooks-def.h"
37 #include "tree-flow.h"
38 #include "cgraph.h"
39 #include "timevar.h"
40 #include "except.h"
41 #include "hashtab.h"
42 #include "flags.h"
43 #include "real.h"
44 #include "function.h"
45 #include "output.h"
46 #include "expr.h"
47 #include "ggc.h"
48 #include "toplev.h"
49 #include "target.h"
50 #include "optabs.h"
51 #include "pointer-set.h"
54 enum gimplify_omp_var_data
56 GOVD_SEEN = 1,
57 GOVD_EXPLICIT = 2,
58 GOVD_SHARED = 4,
59 GOVD_PRIVATE = 8,
60 GOVD_FIRSTPRIVATE = 16,
61 GOVD_LASTPRIVATE = 32,
62 GOVD_REDUCTION = 64,
63 GOVD_LOCAL = 128,
64 GOVD_DEBUG_PRIVATE = 256,
65 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
66 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LOCAL)
69 struct gimplify_omp_ctx
71 struct gimplify_omp_ctx *outer_context;
72 splay_tree variables;
73 struct pointer_set_t *privatized_types;
74 location_t location;
75 enum omp_clause_default_kind default_kind;
76 bool is_parallel;
77 bool is_combined_parallel;
80 struct gimplify_ctx
82 struct gimplify_ctx *prev_context;
84 tree current_bind_expr;
85 tree temps;
86 tree conditional_cleanups;
87 tree exit_label;
88 tree return_temp;
90 VEC(tree,heap) *case_labels;
91 /* The formal temporary table. Should this be persistent? */
92 htab_t temp_htab;
94 int conditions;
95 bool save_stack;
96 bool into_ssa;
99 static struct gimplify_ctx *gimplify_ctxp;
100 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
104 /* Formal (expression) temporary table handling: Multiple occurrences of
105 the same scalar expression are evaluated into the same temporary. */
107 typedef struct gimple_temp_hash_elt
109 tree val; /* Key */
110 tree temp; /* Value */
111 } elt_t;
113 /* Forward declarations. */
114 static enum gimplify_status gimplify_compound_expr (tree *, tree *, bool);
115 #ifdef ENABLE_CHECKING
116 static bool cpt_same_type (tree a, tree b);
117 #endif
120 /* Return a hash value for a formal temporary table entry. */
122 static hashval_t
123 gimple_tree_hash (const void *p)
125 tree t = ((const elt_t *) p)->val;
126 return iterative_hash_expr (t, 0);
129 /* Compare two formal temporary table entries. */
131 static int
132 gimple_tree_eq (const void *p1, const void *p2)
134 tree t1 = ((const elt_t *) p1)->val;
135 tree t2 = ((const elt_t *) p2)->val;
136 enum tree_code code = TREE_CODE (t1);
138 if (TREE_CODE (t2) != code
139 || TREE_TYPE (t1) != TREE_TYPE (t2))
140 return 0;
142 if (!operand_equal_p (t1, t2, 0))
143 return 0;
145 /* Only allow them to compare equal if they also hash equal; otherwise
146 results are nondeterminate, and we fail bootstrap comparison. */
147 gcc_assert (gimple_tree_hash (p1) == gimple_tree_hash (p2));
149 return 1;
152 /* Set up a context for the gimplifier. */
154 void
155 push_gimplify_context (void)
157 struct gimplify_ctx *c;
159 c = (struct gimplify_ctx *) xcalloc (1, sizeof (struct gimplify_ctx));
160 c->prev_context = gimplify_ctxp;
161 if (optimize)
162 c->temp_htab = htab_create (1000, gimple_tree_hash, gimple_tree_eq, free);
164 gimplify_ctxp = c;
167 /* Tear down a context for the gimplifier. If BODY is non-null, then
168 put the temporaries into the outer BIND_EXPR. Otherwise, put them
169 in the unexpanded_var_list. */
171 void
172 pop_gimplify_context (tree body)
174 struct gimplify_ctx *c = gimplify_ctxp;
175 tree t;
177 gcc_assert (c && !c->current_bind_expr);
178 gimplify_ctxp = c->prev_context;
180 for (t = c->temps; t ; t = TREE_CHAIN (t))
181 DECL_GIMPLE_FORMAL_TEMP_P (t) = 0;
183 if (body)
184 declare_vars (c->temps, body, false);
185 else
186 record_vars (c->temps);
188 if (optimize)
189 htab_delete (c->temp_htab);
190 free (c);
193 static void
194 gimple_push_bind_expr (tree bind)
196 TREE_CHAIN (bind) = gimplify_ctxp->current_bind_expr;
197 gimplify_ctxp->current_bind_expr = bind;
200 static void
201 gimple_pop_bind_expr (void)
203 gimplify_ctxp->current_bind_expr
204 = TREE_CHAIN (gimplify_ctxp->current_bind_expr);
207 tree
208 gimple_current_bind_expr (void)
210 return gimplify_ctxp->current_bind_expr;
213 /* Returns true iff there is a COND_EXPR between us and the innermost
214 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
216 static bool
217 gimple_conditional_context (void)
219 return gimplify_ctxp->conditions > 0;
222 /* Note that we've entered a COND_EXPR. */
224 static void
225 gimple_push_condition (void)
227 #ifdef ENABLE_CHECKING
228 if (gimplify_ctxp->conditions == 0)
229 gcc_assert (!gimplify_ctxp->conditional_cleanups);
230 #endif
231 ++(gimplify_ctxp->conditions);
234 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
235 now, add any conditional cleanups we've seen to the prequeue. */
237 static void
238 gimple_pop_condition (tree *pre_p)
240 int conds = --(gimplify_ctxp->conditions);
242 gcc_assert (conds >= 0);
243 if (conds == 0)
245 append_to_statement_list (gimplify_ctxp->conditional_cleanups, pre_p);
246 gimplify_ctxp->conditional_cleanups = NULL_TREE;
250 /* A stable comparison routine for use with splay trees and DECLs. */
252 static int
253 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
255 tree a = (tree) xa;
256 tree b = (tree) xb;
258 return DECL_UID (a) - DECL_UID (b);
261 /* Create a new omp construct that deals with variable remapping. */
263 static struct gimplify_omp_ctx *
264 new_omp_context (bool is_parallel, bool is_combined_parallel)
266 struct gimplify_omp_ctx *c;
268 c = XCNEW (struct gimplify_omp_ctx);
269 c->outer_context = gimplify_omp_ctxp;
270 c->variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
271 c->privatized_types = pointer_set_create ();
272 c->location = input_location;
273 c->is_parallel = is_parallel;
274 c->is_combined_parallel = is_combined_parallel;
275 c->default_kind = OMP_CLAUSE_DEFAULT_SHARED;
277 return c;
280 /* Destroy an omp construct that deals with variable remapping. */
282 static void
283 delete_omp_context (struct gimplify_omp_ctx *c)
285 splay_tree_delete (c->variables);
286 pointer_set_destroy (c->privatized_types);
287 XDELETE (c);
290 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
291 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
293 /* A subroutine of append_to_statement_list{,_force}. T is not NULL. */
295 static void
296 append_to_statement_list_1 (tree t, tree *list_p)
298 tree list = *list_p;
299 tree_stmt_iterator i;
301 if (!list)
303 if (t && TREE_CODE (t) == STATEMENT_LIST)
305 *list_p = t;
306 return;
308 *list_p = list = alloc_stmt_list ();
311 i = tsi_last (list);
312 tsi_link_after (&i, t, TSI_CONTINUE_LINKING);
315 /* Add T to the end of the list container pointed to by LIST_P.
316 If T is an expression with no effects, it is ignored. */
318 void
319 append_to_statement_list (tree t, tree *list_p)
321 if (t && TREE_SIDE_EFFECTS (t))
322 append_to_statement_list_1 (t, list_p);
325 /* Similar, but the statement is always added, regardless of side effects. */
327 void
328 append_to_statement_list_force (tree t, tree *list_p)
330 if (t != NULL_TREE)
331 append_to_statement_list_1 (t, list_p);
334 /* Both gimplify the statement T and append it to LIST_P. */
336 void
337 gimplify_and_add (tree t, tree *list_p)
339 gimplify_stmt (&t);
340 append_to_statement_list (t, list_p);
343 /* Strip off a legitimate source ending from the input string NAME of
344 length LEN. Rather than having to know the names used by all of
345 our front ends, we strip off an ending of a period followed by
346 up to five characters. (Java uses ".class".) */
348 static inline void
349 remove_suffix (char *name, int len)
351 int i;
353 for (i = 2; i < 8 && len > i; i++)
355 if (name[len - i] == '.')
357 name[len - i] = '\0';
358 break;
363 /* Create a nameless artificial label and put it in the current function
364 context. Returns the newly created label. */
366 tree
367 create_artificial_label (void)
369 tree lab = build_decl (LABEL_DECL, NULL_TREE, void_type_node);
371 DECL_ARTIFICIAL (lab) = 1;
372 DECL_IGNORED_P (lab) = 1;
373 DECL_CONTEXT (lab) = current_function_decl;
374 return lab;
377 /* Subroutine for find_single_pointer_decl. */
379 static tree
380 find_single_pointer_decl_1 (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
381 void *data)
383 tree *pdecl = (tree *) data;
385 if (DECL_P (*tp) && POINTER_TYPE_P (TREE_TYPE (*tp)))
387 if (*pdecl)
389 /* We already found a pointer decl; return anything other
390 than NULL_TREE to unwind from walk_tree signalling that
391 we have a duplicate. */
392 return *tp;
394 *pdecl = *tp;
397 return NULL_TREE;
400 /* Find the single DECL of pointer type in the tree T and return it.
401 If there are zero or more than one such DECLs, return NULL. */
403 static tree
404 find_single_pointer_decl (tree t)
406 tree decl = NULL_TREE;
408 if (walk_tree (&t, find_single_pointer_decl_1, &decl, NULL))
410 /* find_single_pointer_decl_1 returns a nonzero value, causing
411 walk_tree to return a nonzero value, to indicate that it
412 found more than one pointer DECL. */
413 return NULL_TREE;
416 return decl;
419 /* Create a new temporary name with PREFIX. Returns an identifier. */
421 static GTY(()) unsigned int tmp_var_id_num;
423 tree
424 create_tmp_var_name (const char *prefix)
426 char *tmp_name;
428 if (prefix)
430 char *preftmp = ASTRDUP (prefix);
432 remove_suffix (preftmp, strlen (preftmp));
433 prefix = preftmp;
436 ASM_FORMAT_PRIVATE_NAME (tmp_name, prefix ? prefix : "T", tmp_var_id_num++);
437 return get_identifier (tmp_name);
441 /* Create a new temporary variable declaration of type TYPE.
442 Does NOT push it into the current binding. */
444 tree
445 create_tmp_var_raw (tree type, const char *prefix)
447 tree tmp_var;
448 tree new_type;
450 /* Make the type of the variable writable. */
451 new_type = build_type_variant (type, 0, 0);
452 TYPE_ATTRIBUTES (new_type) = TYPE_ATTRIBUTES (type);
454 tmp_var = build_decl (VAR_DECL, prefix ? create_tmp_var_name (prefix) : NULL,
455 type);
457 /* The variable was declared by the compiler. */
458 DECL_ARTIFICIAL (tmp_var) = 1;
459 /* And we don't want debug info for it. */
460 DECL_IGNORED_P (tmp_var) = 1;
462 /* Make the variable writable. */
463 TREE_READONLY (tmp_var) = 0;
465 DECL_EXTERNAL (tmp_var) = 0;
466 TREE_STATIC (tmp_var) = 0;
467 TREE_USED (tmp_var) = 1;
469 return tmp_var;
472 /* Create a new temporary variable declaration of type TYPE. DOES push the
473 variable into the current binding. Further, assume that this is called
474 only from gimplification or optimization, at which point the creation of
475 certain types are bugs. */
477 tree
478 create_tmp_var (tree type, const char *prefix)
480 tree tmp_var;
482 /* We don't allow types that are addressable (meaning we can't make copies),
483 or incomplete. We also used to reject every variable size objects here,
484 but now support those for which a constant upper bound can be obtained.
485 The processing for variable sizes is performed in gimple_add_tmp_var,
486 point at which it really matters and possibly reached via paths not going
487 through this function, e.g. after direct calls to create_tmp_var_raw. */
488 gcc_assert (!TREE_ADDRESSABLE (type) && COMPLETE_TYPE_P (type));
490 tmp_var = create_tmp_var_raw (type, prefix);
491 gimple_add_tmp_var (tmp_var);
492 return tmp_var;
495 /* Given a tree, try to return a useful variable name that we can use
496 to prefix a temporary that is being assigned the value of the tree.
497 I.E. given <temp> = &A, return A. */
499 const char *
500 get_name (tree t)
502 tree stripped_decl;
504 stripped_decl = t;
505 STRIP_NOPS (stripped_decl);
506 if (DECL_P (stripped_decl) && DECL_NAME (stripped_decl))
507 return IDENTIFIER_POINTER (DECL_NAME (stripped_decl));
508 else
510 switch (TREE_CODE (stripped_decl))
512 case ADDR_EXPR:
513 return get_name (TREE_OPERAND (stripped_decl, 0));
514 default:
515 return NULL;
520 /* Create a temporary with a name derived from VAL. Subroutine of
521 lookup_tmp_var; nobody else should call this function. */
523 static inline tree
524 create_tmp_from_val (tree val)
526 return create_tmp_var (TYPE_MAIN_VARIANT (TREE_TYPE (val)), get_name (val));
529 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
530 an existing expression temporary. */
532 static tree
533 lookup_tmp_var (tree val, bool is_formal)
535 tree ret;
537 /* If not optimizing, never really reuse a temporary. local-alloc
538 won't allocate any variable that is used in more than one basic
539 block, which means it will go into memory, causing much extra
540 work in reload and final and poorer code generation, outweighing
541 the extra memory allocation here. */
542 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
543 ret = create_tmp_from_val (val);
544 else
546 elt_t elt, *elt_p;
547 void **slot;
549 elt.val = val;
550 slot = htab_find_slot (gimplify_ctxp->temp_htab, (void *)&elt, INSERT);
551 if (*slot == NULL)
553 elt_p = XNEW (elt_t);
554 elt_p->val = val;
555 elt_p->temp = ret = create_tmp_from_val (val);
556 *slot = (void *) elt_p;
558 else
560 elt_p = (elt_t *) *slot;
561 ret = elt_p->temp;
565 if (is_formal)
566 DECL_GIMPLE_FORMAL_TEMP_P (ret) = 1;
568 return ret;
571 /* Returns a formal temporary variable initialized with VAL. PRE_P is as
572 in gimplify_expr. Only use this function if:
574 1) The value of the unfactored expression represented by VAL will not
575 change between the initialization and use of the temporary, and
576 2) The temporary will not be otherwise modified.
578 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
579 and #2 means it is inappropriate for && temps.
581 For other cases, use get_initialized_tmp_var instead. */
583 static tree
584 internal_get_tmp_var (tree val, tree *pre_p, tree *post_p, bool is_formal)
586 tree t, mod;
588 gimplify_expr (&val, pre_p, post_p, is_gimple_formal_tmp_rhs, fb_rvalue);
590 t = lookup_tmp_var (val, is_formal);
592 if (is_formal)
594 tree u = find_single_pointer_decl (val);
596 if (u && TREE_CODE (u) == VAR_DECL && DECL_BASED_ON_RESTRICT_P (u))
597 u = DECL_GET_RESTRICT_BASE (u);
598 if (u && TYPE_RESTRICT (TREE_TYPE (u)))
600 if (DECL_BASED_ON_RESTRICT_P (t))
601 gcc_assert (u == DECL_GET_RESTRICT_BASE (t));
602 else
604 DECL_BASED_ON_RESTRICT_P (t) = 1;
605 SET_DECL_RESTRICT_BASE (t, u);
610 if (TREE_CODE (TREE_TYPE (t)) == COMPLEX_TYPE
611 || TREE_CODE (TREE_TYPE (t)) == VECTOR_TYPE)
612 DECL_GIMPLE_REG_P (t) = 1;
614 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
616 if (EXPR_HAS_LOCATION (val))
617 SET_EXPR_LOCUS (mod, EXPR_LOCUS (val));
618 else
619 SET_EXPR_LOCATION (mod, input_location);
621 /* gimplify_modify_expr might want to reduce this further. */
622 gimplify_and_add (mod, pre_p);
624 /* If we're gimplifying into ssa, gimplify_modify_expr will have
625 given our temporary an ssa name. Find and return it. */
626 if (gimplify_ctxp->into_ssa)
627 t = TREE_OPERAND (mod, 0);
629 return t;
632 /* Returns a formal temporary variable initialized with VAL. PRE_P
633 points to a statement list where side-effects needed to compute VAL
634 should be stored. */
636 tree
637 get_formal_tmp_var (tree val, tree *pre_p)
639 return internal_get_tmp_var (val, pre_p, NULL, true);
642 /* Returns a temporary variable initialized with VAL. PRE_P and POST_P
643 are as in gimplify_expr. */
645 tree
646 get_initialized_tmp_var (tree val, tree *pre_p, tree *post_p)
648 return internal_get_tmp_var (val, pre_p, post_p, false);
651 /* Declares all the variables in VARS in SCOPE. If DEBUG_INFO is
652 true, generate debug info for them; otherwise don't. */
654 void
655 declare_vars (tree vars, tree scope, bool debug_info)
657 tree last = vars;
658 if (last)
660 tree temps, block;
662 /* C99 mode puts the default 'return 0;' for main outside the outer
663 braces. So drill down until we find an actual scope. */
664 while (TREE_CODE (scope) == COMPOUND_EXPR)
665 scope = TREE_OPERAND (scope, 0);
667 gcc_assert (TREE_CODE (scope) == BIND_EXPR);
669 temps = nreverse (last);
671 block = BIND_EXPR_BLOCK (scope);
672 if (!block || !debug_info)
674 TREE_CHAIN (last) = BIND_EXPR_VARS (scope);
675 BIND_EXPR_VARS (scope) = temps;
677 else
679 /* We need to attach the nodes both to the BIND_EXPR and to its
680 associated BLOCK for debugging purposes. The key point here
681 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
682 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
683 if (BLOCK_VARS (block))
684 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
685 else
687 BIND_EXPR_VARS (scope) = chainon (BIND_EXPR_VARS (scope), temps);
688 BLOCK_VARS (block) = temps;
694 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
695 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
696 no such upper bound can be obtained. */
698 static void
699 force_constant_size (tree var)
701 /* The only attempt we make is by querying the maximum size of objects
702 of the variable's type. */
704 HOST_WIDE_INT max_size;
706 gcc_assert (TREE_CODE (var) == VAR_DECL);
708 max_size = max_int_size_in_bytes (TREE_TYPE (var));
710 gcc_assert (max_size >= 0);
712 DECL_SIZE_UNIT (var)
713 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
714 DECL_SIZE (var)
715 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
718 void
719 gimple_add_tmp_var (tree tmp)
721 gcc_assert (!TREE_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
723 /* Later processing assumes that the object size is constant, which might
724 not be true at this point. Force the use of a constant upper bound in
725 this case. */
726 if (!host_integerp (DECL_SIZE_UNIT (tmp), 1))
727 force_constant_size (tmp);
729 DECL_CONTEXT (tmp) = current_function_decl;
730 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
732 if (gimplify_ctxp)
734 TREE_CHAIN (tmp) = gimplify_ctxp->temps;
735 gimplify_ctxp->temps = tmp;
737 /* Mark temporaries local within the nearest enclosing parallel. */
738 if (gimplify_omp_ctxp)
740 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
741 while (ctx && !ctx->is_parallel)
742 ctx = ctx->outer_context;
743 if (ctx)
744 omp_add_variable (ctx, tmp, GOVD_LOCAL | GOVD_SEEN);
747 else if (cfun)
748 record_vars (tmp);
749 else
750 declare_vars (tmp, DECL_SAVED_TREE (current_function_decl), false);
753 /* Determines whether to assign a locus to the statement STMT. */
755 static bool
756 should_carry_locus_p (tree stmt)
758 /* Don't emit a line note for a label. We particularly don't want to
759 emit one for the break label, since it doesn't actually correspond
760 to the beginning of the loop/switch. */
761 if (TREE_CODE (stmt) == LABEL_EXPR)
762 return false;
764 /* Do not annotate empty statements, since it confuses gcov. */
765 if (!TREE_SIDE_EFFECTS (stmt))
766 return false;
768 return true;
771 static void
772 annotate_one_with_locus (tree t, location_t locus)
774 if (CAN_HAVE_LOCATION_P (t)
775 && ! EXPR_HAS_LOCATION (t) && should_carry_locus_p (t))
776 SET_EXPR_LOCATION (t, locus);
779 void
780 annotate_all_with_locus (tree *stmt_p, location_t locus)
782 tree_stmt_iterator i;
784 if (!*stmt_p)
785 return;
787 for (i = tsi_start (*stmt_p); !tsi_end_p (i); tsi_next (&i))
789 tree t = tsi_stmt (i);
791 /* Assuming we've already been gimplified, we shouldn't
792 see nested chaining constructs anymore. */
793 gcc_assert (TREE_CODE (t) != STATEMENT_LIST
794 && TREE_CODE (t) != COMPOUND_EXPR);
796 annotate_one_with_locus (t, locus);
800 /* Similar to copy_tree_r() but do not copy SAVE_EXPR or TARGET_EXPR nodes.
801 These nodes model computations that should only be done once. If we
802 were to unshare something like SAVE_EXPR(i++), the gimplification
803 process would create wrong code. */
805 static tree
806 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
808 enum tree_code code = TREE_CODE (*tp);
809 /* Don't unshare types, decls, constants and SAVE_EXPR nodes. */
810 if (TREE_CODE_CLASS (code) == tcc_type
811 || TREE_CODE_CLASS (code) == tcc_declaration
812 || TREE_CODE_CLASS (code) == tcc_constant
813 || code == SAVE_EXPR || code == TARGET_EXPR
814 /* We can't do anything sensible with a BLOCK used as an expression,
815 but we also can't just die when we see it because of non-expression
816 uses. So just avert our eyes and cross our fingers. Silly Java. */
817 || code == BLOCK)
818 *walk_subtrees = 0;
819 else
821 gcc_assert (code != BIND_EXPR);
822 copy_tree_r (tp, walk_subtrees, data);
825 return NULL_TREE;
828 /* Callback for walk_tree to unshare most of the shared trees rooted at
829 *TP. If *TP has been visited already (i.e., TREE_VISITED (*TP) == 1),
830 then *TP is deep copied by calling copy_tree_r.
832 This unshares the same trees as copy_tree_r with the exception of
833 SAVE_EXPR nodes. These nodes model computations that should only be
834 done once. If we were to unshare something like SAVE_EXPR(i++), the
835 gimplification process would create wrong code. */
837 static tree
838 copy_if_shared_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
839 void *data ATTRIBUTE_UNUSED)
841 tree t = *tp;
842 enum tree_code code = TREE_CODE (t);
844 /* Skip types, decls, and constants. But we do want to look at their
845 types and the bounds of types. Mark them as visited so we properly
846 unmark their subtrees on the unmark pass. If we've already seen them,
847 don't look down further. */
848 if (TREE_CODE_CLASS (code) == tcc_type
849 || TREE_CODE_CLASS (code) == tcc_declaration
850 || TREE_CODE_CLASS (code) == tcc_constant)
852 if (TREE_VISITED (t))
853 *walk_subtrees = 0;
854 else
855 TREE_VISITED (t) = 1;
858 /* If this node has been visited already, unshare it and don't look
859 any deeper. */
860 else if (TREE_VISITED (t))
862 walk_tree (tp, mostly_copy_tree_r, NULL, NULL);
863 *walk_subtrees = 0;
866 /* Otherwise, mark the tree as visited and keep looking. */
867 else
868 TREE_VISITED (t) = 1;
870 return NULL_TREE;
873 static tree
874 unmark_visited_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
875 void *data ATTRIBUTE_UNUSED)
877 if (TREE_VISITED (*tp))
878 TREE_VISITED (*tp) = 0;
879 else
880 *walk_subtrees = 0;
882 return NULL_TREE;
885 /* Unshare all the trees in BODY_P, a pointer into the body of FNDECL, and the
886 bodies of any nested functions if we are unsharing the entire body of
887 FNDECL. */
889 static void
890 unshare_body (tree *body_p, tree fndecl)
892 struct cgraph_node *cgn = cgraph_node (fndecl);
894 walk_tree (body_p, copy_if_shared_r, NULL, NULL);
895 if (body_p == &DECL_SAVED_TREE (fndecl))
896 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
897 unshare_body (&DECL_SAVED_TREE (cgn->decl), cgn->decl);
900 /* Likewise, but mark all trees as not visited. */
902 static void
903 unvisit_body (tree *body_p, tree fndecl)
905 struct cgraph_node *cgn = cgraph_node (fndecl);
907 walk_tree (body_p, unmark_visited_r, NULL, NULL);
908 if (body_p == &DECL_SAVED_TREE (fndecl))
909 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
910 unvisit_body (&DECL_SAVED_TREE (cgn->decl), cgn->decl);
913 /* Unshare T and all the trees reached from T via TREE_CHAIN. */
915 static void
916 unshare_all_trees (tree t)
918 walk_tree (&t, copy_if_shared_r, NULL, NULL);
919 walk_tree (&t, unmark_visited_r, NULL, NULL);
922 /* Unconditionally make an unshared copy of EXPR. This is used when using
923 stored expressions which span multiple functions, such as BINFO_VTABLE,
924 as the normal unsharing process can't tell that they're shared. */
926 tree
927 unshare_expr (tree expr)
929 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
930 return expr;
933 /* A terser interface for building a representation of an exception
934 specification. */
936 tree
937 gimple_build_eh_filter (tree body, tree allowed, tree failure)
939 tree t;
941 /* FIXME should the allowed types go in TREE_TYPE? */
942 t = build2 (EH_FILTER_EXPR, void_type_node, allowed, NULL_TREE);
943 append_to_statement_list (failure, &EH_FILTER_FAILURE (t));
945 t = build2 (TRY_CATCH_EXPR, void_type_node, NULL_TREE, t);
946 append_to_statement_list (body, &TREE_OPERAND (t, 0));
948 return t;
952 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
953 contain statements and have a value. Assign its value to a temporary
954 and give it void_type_node. Returns the temporary, or NULL_TREE if
955 WRAPPER was already void. */
957 tree
958 voidify_wrapper_expr (tree wrapper, tree temp)
960 tree type = TREE_TYPE (wrapper);
961 if (type && !VOID_TYPE_P (type))
963 tree *p;
965 /* Set p to point to the body of the wrapper. Loop until we find
966 something that isn't a wrapper. */
967 for (p = &wrapper; p && *p; )
969 switch (TREE_CODE (*p))
971 case BIND_EXPR:
972 TREE_SIDE_EFFECTS (*p) = 1;
973 TREE_TYPE (*p) = void_type_node;
974 /* For a BIND_EXPR, the body is operand 1. */
975 p = &BIND_EXPR_BODY (*p);
976 break;
978 case CLEANUP_POINT_EXPR:
979 case TRY_FINALLY_EXPR:
980 case TRY_CATCH_EXPR:
981 TREE_SIDE_EFFECTS (*p) = 1;
982 TREE_TYPE (*p) = void_type_node;
983 p = &TREE_OPERAND (*p, 0);
984 break;
986 case STATEMENT_LIST:
988 tree_stmt_iterator i = tsi_last (*p);
989 TREE_SIDE_EFFECTS (*p) = 1;
990 TREE_TYPE (*p) = void_type_node;
991 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
993 break;
995 case COMPOUND_EXPR:
996 /* Advance to the last statement. Set all container types to void. */
997 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
999 TREE_SIDE_EFFECTS (*p) = 1;
1000 TREE_TYPE (*p) = void_type_node;
1002 break;
1004 default:
1005 goto out;
1009 out:
1010 if (p == NULL || IS_EMPTY_STMT (*p))
1011 temp = NULL_TREE;
1012 else if (temp)
1014 /* The wrapper is on the RHS of an assignment that we're pushing
1015 down. */
1016 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1017 || TREE_CODE (temp) == MODIFY_EXPR);
1018 TREE_OPERAND (temp, 1) = *p;
1019 *p = temp;
1021 else
1023 temp = create_tmp_var (type, "retval");
1024 *p = build2 (INIT_EXPR, type, temp, *p);
1027 return temp;
1030 return NULL_TREE;
1033 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1034 a temporary through which they communicate. */
1036 static void
1037 build_stack_save_restore (tree *save, tree *restore)
1039 tree save_call, tmp_var;
1041 save_call =
1042 build_function_call_expr (implicit_built_in_decls[BUILT_IN_STACK_SAVE],
1043 NULL_TREE);
1044 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1046 *save = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, tmp_var, save_call);
1047 *restore =
1048 build_function_call_expr (implicit_built_in_decls[BUILT_IN_STACK_RESTORE],
1049 tree_cons (NULL_TREE, tmp_var, NULL_TREE));
1052 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1054 static enum gimplify_status
1055 gimplify_bind_expr (tree *expr_p, tree *pre_p)
1057 tree bind_expr = *expr_p;
1058 bool old_save_stack = gimplify_ctxp->save_stack;
1059 tree t;
1061 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1063 /* Mark variables seen in this bind expr. */
1064 for (t = BIND_EXPR_VARS (bind_expr); t ; t = TREE_CHAIN (t))
1066 if (TREE_CODE (t) == VAR_DECL)
1068 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1070 /* Mark variable as local. */
1071 if (ctx && !is_global_var (t)
1072 && (! DECL_SEEN_IN_BIND_EXPR_P (t)
1073 || splay_tree_lookup (ctx->variables,
1074 (splay_tree_key) t) == NULL))
1075 omp_add_variable (gimplify_omp_ctxp, t, GOVD_LOCAL | GOVD_SEEN);
1077 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1080 /* Preliminarily mark non-addressed complex variables as eligible
1081 for promotion to gimple registers. We'll transform their uses
1082 as we find them. */
1083 if ((TREE_CODE (TREE_TYPE (t)) == COMPLEX_TYPE
1084 || TREE_CODE (TREE_TYPE (t)) == VECTOR_TYPE)
1085 && !TREE_THIS_VOLATILE (t)
1086 && (TREE_CODE (t) == VAR_DECL && !DECL_HARD_REGISTER (t))
1087 && !needs_to_live_in_memory (t))
1088 DECL_GIMPLE_REG_P (t) = 1;
1091 gimple_push_bind_expr (bind_expr);
1092 gimplify_ctxp->save_stack = false;
1094 gimplify_to_stmt_list (&BIND_EXPR_BODY (bind_expr));
1096 if (gimplify_ctxp->save_stack)
1098 tree stack_save, stack_restore;
1100 /* Save stack on entry and restore it on exit. Add a try_finally
1101 block to achieve this. Note that mudflap depends on the
1102 format of the emitted code: see mx_register_decls(). */
1103 build_stack_save_restore (&stack_save, &stack_restore);
1105 t = build2 (TRY_FINALLY_EXPR, void_type_node,
1106 BIND_EXPR_BODY (bind_expr), NULL_TREE);
1107 append_to_statement_list (stack_restore, &TREE_OPERAND (t, 1));
1109 BIND_EXPR_BODY (bind_expr) = NULL_TREE;
1110 append_to_statement_list (stack_save, &BIND_EXPR_BODY (bind_expr));
1111 append_to_statement_list (t, &BIND_EXPR_BODY (bind_expr));
1114 gimplify_ctxp->save_stack = old_save_stack;
1115 gimple_pop_bind_expr ();
1117 if (temp)
1119 *expr_p = temp;
1120 append_to_statement_list (bind_expr, pre_p);
1121 return GS_OK;
1123 else
1124 return GS_ALL_DONE;
1127 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1128 GIMPLE value, it is assigned to a new temporary and the statement is
1129 re-written to return the temporary.
1131 PRE_P points to the list where side effects that must happen before
1132 STMT should be stored. */
1134 static enum gimplify_status
1135 gimplify_return_expr (tree stmt, tree *pre_p)
1137 tree ret_expr = TREE_OPERAND (stmt, 0);
1138 tree result_decl, result;
1140 if (!ret_expr || TREE_CODE (ret_expr) == RESULT_DECL
1141 || ret_expr == error_mark_node)
1142 return GS_ALL_DONE;
1144 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1145 result_decl = NULL_TREE;
1146 else
1148 result_decl = GENERIC_TREE_OPERAND (ret_expr, 0);
1149 if (TREE_CODE (result_decl) == INDIRECT_REF)
1150 /* See through a return by reference. */
1151 result_decl = TREE_OPERAND (result_decl, 0);
1153 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1154 || TREE_CODE (ret_expr) == GIMPLE_MODIFY_STMT
1155 || TREE_CODE (ret_expr) == INIT_EXPR)
1156 && TREE_CODE (result_decl) == RESULT_DECL);
1159 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1160 Recall that aggregate_value_p is FALSE for any aggregate type that is
1161 returned in registers. If we're returning values in registers, then
1162 we don't want to extend the lifetime of the RESULT_DECL, particularly
1163 across another call. In addition, for those aggregates for which
1164 hard_function_value generates a PARALLEL, we'll die during normal
1165 expansion of structure assignments; there's special code in expand_return
1166 to handle this case that does not exist in expand_expr. */
1167 if (!result_decl
1168 || aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1169 result = result_decl;
1170 else if (gimplify_ctxp->return_temp)
1171 result = gimplify_ctxp->return_temp;
1172 else
1174 result = create_tmp_var (TREE_TYPE (result_decl), NULL);
1175 if (TREE_CODE (TREE_TYPE (result)) == COMPLEX_TYPE
1176 || TREE_CODE (TREE_TYPE (result)) == VECTOR_TYPE)
1177 DECL_GIMPLE_REG_P (result) = 1;
1179 /* ??? With complex control flow (usually involving abnormal edges),
1180 we can wind up warning about an uninitialized value for this. Due
1181 to how this variable is constructed and initialized, this is never
1182 true. Give up and never warn. */
1183 TREE_NO_WARNING (result) = 1;
1185 gimplify_ctxp->return_temp = result;
1188 /* Smash the lhs of the GIMPLE_MODIFY_STMT to the temporary we plan to use.
1189 Then gimplify the whole thing. */
1190 if (result != result_decl)
1191 GENERIC_TREE_OPERAND (ret_expr, 0) = result;
1193 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1195 /* If we didn't use a temporary, then the result is just the result_decl.
1196 Otherwise we need a simple copy. This should already be gimple. */
1197 if (result == result_decl)
1198 ret_expr = result;
1199 else
1200 ret_expr = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (result), result_decl,
1201 result);
1202 TREE_OPERAND (stmt, 0) = ret_expr;
1204 return GS_ALL_DONE;
1207 /* Gimplifies a DECL_EXPR node *STMT_P by making any necessary allocation
1208 and initialization explicit. */
1210 static enum gimplify_status
1211 gimplify_decl_expr (tree *stmt_p)
1213 tree stmt = *stmt_p;
1214 tree decl = DECL_EXPR_DECL (stmt);
1216 *stmt_p = NULL_TREE;
1218 if (TREE_TYPE (decl) == error_mark_node)
1219 return GS_ERROR;
1221 if ((TREE_CODE (decl) == TYPE_DECL
1222 || TREE_CODE (decl) == VAR_DECL)
1223 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1224 gimplify_type_sizes (TREE_TYPE (decl), stmt_p);
1226 if (TREE_CODE (decl) == VAR_DECL && !DECL_EXTERNAL (decl))
1228 tree init = DECL_INITIAL (decl);
1230 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
1232 /* This is a variable-sized decl. Simplify its size and mark it
1233 for deferred expansion. Note that mudflap depends on the format
1234 of the emitted code: see mx_register_decls(). */
1235 tree t, args, addr, ptr_type;
1237 gimplify_one_sizepos (&DECL_SIZE (decl), stmt_p);
1238 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), stmt_p);
1240 /* All occurrences of this decl in final gimplified code will be
1241 replaced by indirection. Setting DECL_VALUE_EXPR does two
1242 things: First, it lets the rest of the gimplifier know what
1243 replacement to use. Second, it lets the debug info know
1244 where to find the value. */
1245 ptr_type = build_pointer_type (TREE_TYPE (decl));
1246 addr = create_tmp_var (ptr_type, get_name (decl));
1247 DECL_IGNORED_P (addr) = 0;
1248 t = build_fold_indirect_ref (addr);
1249 SET_DECL_VALUE_EXPR (decl, t);
1250 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1252 args = tree_cons (NULL, DECL_SIZE_UNIT (decl), NULL);
1253 t = built_in_decls[BUILT_IN_ALLOCA];
1254 t = build_function_call_expr (t, args);
1255 t = fold_convert (ptr_type, t);
1256 t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
1258 gimplify_and_add (t, stmt_p);
1260 /* Indicate that we need to restore the stack level when the
1261 enclosing BIND_EXPR is exited. */
1262 gimplify_ctxp->save_stack = true;
1265 if (init && init != error_mark_node)
1267 if (!TREE_STATIC (decl))
1269 DECL_INITIAL (decl) = NULL_TREE;
1270 init = build2 (INIT_EXPR, void_type_node, decl, init);
1271 gimplify_and_add (init, stmt_p);
1273 else
1274 /* We must still examine initializers for static variables
1275 as they may contain a label address. */
1276 walk_tree (&init, force_labels_r, NULL, NULL);
1279 /* Some front ends do not explicitly declare all anonymous
1280 artificial variables. We compensate here by declaring the
1281 variables, though it would be better if the front ends would
1282 explicitly declare them. */
1283 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1284 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1285 gimple_add_tmp_var (decl);
1288 return GS_ALL_DONE;
1291 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1292 and replacing the LOOP_EXPR with goto, but if the loop contains an
1293 EXIT_EXPR, we need to append a label for it to jump to. */
1295 static enum gimplify_status
1296 gimplify_loop_expr (tree *expr_p, tree *pre_p)
1298 tree saved_label = gimplify_ctxp->exit_label;
1299 tree start_label = build1 (LABEL_EXPR, void_type_node, NULL_TREE);
1300 tree jump_stmt = build_and_jump (&LABEL_EXPR_LABEL (start_label));
1302 append_to_statement_list (start_label, pre_p);
1304 gimplify_ctxp->exit_label = NULL_TREE;
1306 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1308 if (gimplify_ctxp->exit_label)
1310 append_to_statement_list (jump_stmt, pre_p);
1311 *expr_p = build1 (LABEL_EXPR, void_type_node, gimplify_ctxp->exit_label);
1313 else
1314 *expr_p = jump_stmt;
1316 gimplify_ctxp->exit_label = saved_label;
1318 return GS_ALL_DONE;
1321 /* Compare two case labels. Because the front end should already have
1322 made sure that case ranges do not overlap, it is enough to only compare
1323 the CASE_LOW values of each case label. */
1325 static int
1326 compare_case_labels (const void *p1, const void *p2)
1328 tree case1 = *(tree *)p1;
1329 tree case2 = *(tree *)p2;
1331 return tree_int_cst_compare (CASE_LOW (case1), CASE_LOW (case2));
1334 /* Sort the case labels in LABEL_VEC in place in ascending order. */
1336 void
1337 sort_case_labels (tree label_vec)
1339 size_t len = TREE_VEC_LENGTH (label_vec);
1340 tree default_case = TREE_VEC_ELT (label_vec, len - 1);
1342 if (CASE_LOW (default_case))
1344 size_t i;
1346 /* The last label in the vector should be the default case
1347 but it is not. */
1348 for (i = 0; i < len; ++i)
1350 tree t = TREE_VEC_ELT (label_vec, i);
1351 if (!CASE_LOW (t))
1353 default_case = t;
1354 TREE_VEC_ELT (label_vec, i) = TREE_VEC_ELT (label_vec, len - 1);
1355 TREE_VEC_ELT (label_vec, len - 1) = default_case;
1356 break;
1361 qsort (&TREE_VEC_ELT (label_vec, 0), len - 1, sizeof (tree),
1362 compare_case_labels);
1365 /* Gimplify a SWITCH_EXPR, and collect a TREE_VEC of the labels it can
1366 branch to. */
1368 static enum gimplify_status
1369 gimplify_switch_expr (tree *expr_p, tree *pre_p)
1371 tree switch_expr = *expr_p;
1372 enum gimplify_status ret;
1374 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL,
1375 is_gimple_val, fb_rvalue);
1377 if (SWITCH_BODY (switch_expr))
1379 VEC(tree,heap) *labels, *saved_labels;
1380 tree label_vec, default_case = NULL_TREE;
1381 size_t i, len;
1383 /* If someone can be bothered to fill in the labels, they can
1384 be bothered to null out the body too. */
1385 gcc_assert (!SWITCH_LABELS (switch_expr));
1387 saved_labels = gimplify_ctxp->case_labels;
1388 gimplify_ctxp->case_labels = VEC_alloc (tree, heap, 8);
1390 gimplify_to_stmt_list (&SWITCH_BODY (switch_expr));
1392 labels = gimplify_ctxp->case_labels;
1393 gimplify_ctxp->case_labels = saved_labels;
1395 i = 0;
1396 while (i < VEC_length (tree, labels))
1398 tree elt = VEC_index (tree, labels, i);
1399 tree low = CASE_LOW (elt);
1400 bool remove_element = FALSE;
1402 if (low)
1404 /* Discard empty ranges. */
1405 tree high = CASE_HIGH (elt);
1406 if (high && INT_CST_LT (high, low))
1407 remove_element = TRUE;
1409 else
1411 /* The default case must be the last label in the list. */
1412 gcc_assert (!default_case);
1413 default_case = elt;
1414 remove_element = TRUE;
1417 if (remove_element)
1418 VEC_ordered_remove (tree, labels, i);
1419 else
1420 i++;
1422 len = i;
1424 label_vec = make_tree_vec (len + 1);
1425 SWITCH_LABELS (*expr_p) = label_vec;
1426 append_to_statement_list (switch_expr, pre_p);
1428 if (! default_case)
1430 /* If the switch has no default label, add one, so that we jump
1431 around the switch body. */
1432 default_case = build3 (CASE_LABEL_EXPR, void_type_node, NULL_TREE,
1433 NULL_TREE, create_artificial_label ());
1434 append_to_statement_list (SWITCH_BODY (switch_expr), pre_p);
1435 *expr_p = build1 (LABEL_EXPR, void_type_node,
1436 CASE_LABEL (default_case));
1438 else
1439 *expr_p = SWITCH_BODY (switch_expr);
1441 for (i = 0; i < len; ++i)
1442 TREE_VEC_ELT (label_vec, i) = VEC_index (tree, labels, i);
1443 TREE_VEC_ELT (label_vec, len) = default_case;
1445 VEC_free (tree, heap, labels);
1447 sort_case_labels (label_vec);
1449 SWITCH_BODY (switch_expr) = NULL;
1451 else
1452 gcc_assert (SWITCH_LABELS (switch_expr));
1454 return ret;
1457 static enum gimplify_status
1458 gimplify_case_label_expr (tree *expr_p)
1460 tree expr = *expr_p;
1461 struct gimplify_ctx *ctxp;
1463 /* Invalid OpenMP programs can play Duff's Device type games with
1464 #pragma omp parallel. At least in the C front end, we don't
1465 detect such invalid branches until after gimplification. */
1466 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
1467 if (ctxp->case_labels)
1468 break;
1470 VEC_safe_push (tree, heap, ctxp->case_labels, expr);
1471 *expr_p = build1 (LABEL_EXPR, void_type_node, CASE_LABEL (expr));
1472 return GS_ALL_DONE;
1475 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
1476 if necessary. */
1478 tree
1479 build_and_jump (tree *label_p)
1481 if (label_p == NULL)
1482 /* If there's nowhere to jump, just fall through. */
1483 return NULL_TREE;
1485 if (*label_p == NULL_TREE)
1487 tree label = create_artificial_label ();
1488 *label_p = label;
1491 return build1 (GOTO_EXPR, void_type_node, *label_p);
1494 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
1495 This also involves building a label to jump to and communicating it to
1496 gimplify_loop_expr through gimplify_ctxp->exit_label. */
1498 static enum gimplify_status
1499 gimplify_exit_expr (tree *expr_p)
1501 tree cond = TREE_OPERAND (*expr_p, 0);
1502 tree expr;
1504 expr = build_and_jump (&gimplify_ctxp->exit_label);
1505 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
1506 *expr_p = expr;
1508 return GS_OK;
1511 /* A helper function to be called via walk_tree. Mark all labels under *TP
1512 as being forced. To be called for DECL_INITIAL of static variables. */
1514 tree
1515 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1517 if (TYPE_P (*tp))
1518 *walk_subtrees = 0;
1519 if (TREE_CODE (*tp) == LABEL_DECL)
1520 FORCED_LABEL (*tp) = 1;
1522 return NULL_TREE;
1525 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
1526 different from its canonical type, wrap the whole thing inside a
1527 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
1528 type.
1530 The canonical type of a COMPONENT_REF is the type of the field being
1531 referenced--unless the field is a bit-field which can be read directly
1532 in a smaller mode, in which case the canonical type is the
1533 sign-appropriate type corresponding to that mode. */
1535 static void
1536 canonicalize_component_ref (tree *expr_p)
1538 tree expr = *expr_p;
1539 tree type;
1541 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
1543 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
1544 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
1545 else
1546 type = TREE_TYPE (TREE_OPERAND (expr, 1));
1548 if (TREE_TYPE (expr) != type)
1550 tree old_type = TREE_TYPE (expr);
1552 /* Set the type of the COMPONENT_REF to the underlying type. */
1553 TREE_TYPE (expr) = type;
1555 /* And wrap the whole thing inside a NOP_EXPR. */
1556 expr = build1 (NOP_EXPR, old_type, expr);
1558 *expr_p = expr;
1562 /* If a NOP conversion is changing a pointer to array of foo to a pointer
1563 to foo, embed that change in the ADDR_EXPR by converting
1564 T array[U];
1565 (T *)&array
1567 &array[L]
1568 where L is the lower bound. For simplicity, only do this for constant
1569 lower bound. */
1571 static void
1572 canonicalize_addr_expr (tree *expr_p)
1574 tree expr = *expr_p;
1575 tree ctype = TREE_TYPE (expr);
1576 tree addr_expr = TREE_OPERAND (expr, 0);
1577 tree atype = TREE_TYPE (addr_expr);
1578 tree dctype, datype, ddatype, otype, obj_expr;
1580 /* Both cast and addr_expr types should be pointers. */
1581 if (!POINTER_TYPE_P (ctype) || !POINTER_TYPE_P (atype))
1582 return;
1584 /* The addr_expr type should be a pointer to an array. */
1585 datype = TREE_TYPE (atype);
1586 if (TREE_CODE (datype) != ARRAY_TYPE)
1587 return;
1589 /* Both cast and addr_expr types should address the same object type. */
1590 dctype = TREE_TYPE (ctype);
1591 ddatype = TREE_TYPE (datype);
1592 if (!lang_hooks.types_compatible_p (ddatype, dctype))
1593 return;
1595 /* The addr_expr and the object type should match. */
1596 obj_expr = TREE_OPERAND (addr_expr, 0);
1597 otype = TREE_TYPE (obj_expr);
1598 if (!lang_hooks.types_compatible_p (otype, datype))
1599 return;
1601 /* The lower bound and element sizes must be constant. */
1602 if (!TYPE_SIZE_UNIT (dctype)
1603 || TREE_CODE (TYPE_SIZE_UNIT (dctype)) != INTEGER_CST
1604 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
1605 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
1606 return;
1608 /* All checks succeeded. Build a new node to merge the cast. */
1609 *expr_p = build4 (ARRAY_REF, dctype, obj_expr,
1610 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
1611 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
1612 size_binop (EXACT_DIV_EXPR, TYPE_SIZE_UNIT (dctype),
1613 size_int (TYPE_ALIGN_UNIT (dctype))));
1614 *expr_p = build1 (ADDR_EXPR, ctype, *expr_p);
1617 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
1618 underneath as appropriate. */
1620 static enum gimplify_status
1621 gimplify_conversion (tree *expr_p)
1623 gcc_assert (TREE_CODE (*expr_p) == NOP_EXPR
1624 || TREE_CODE (*expr_p) == CONVERT_EXPR);
1626 /* Then strip away all but the outermost conversion. */
1627 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
1629 /* And remove the outermost conversion if it's useless. */
1630 if (tree_ssa_useless_type_conversion (*expr_p))
1631 *expr_p = TREE_OPERAND (*expr_p, 0);
1633 /* If we still have a conversion at the toplevel,
1634 then canonicalize some constructs. */
1635 if (TREE_CODE (*expr_p) == NOP_EXPR || TREE_CODE (*expr_p) == CONVERT_EXPR)
1637 tree sub = TREE_OPERAND (*expr_p, 0);
1639 /* If a NOP conversion is changing the type of a COMPONENT_REF
1640 expression, then canonicalize its type now in order to expose more
1641 redundant conversions. */
1642 if (TREE_CODE (sub) == COMPONENT_REF)
1643 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
1645 /* If a NOP conversion is changing a pointer to array of foo
1646 to a pointer to foo, embed that change in the ADDR_EXPR. */
1647 else if (TREE_CODE (sub) == ADDR_EXPR)
1648 canonicalize_addr_expr (expr_p);
1651 return GS_OK;
1654 /* Gimplify a VAR_DECL or PARM_DECL. Returns GS_OK if we expanded a
1655 DECL_VALUE_EXPR, and it's worth re-examining things. */
1657 static enum gimplify_status
1658 gimplify_var_or_parm_decl (tree *expr_p)
1660 tree decl = *expr_p;
1662 /* ??? If this is a local variable, and it has not been seen in any
1663 outer BIND_EXPR, then it's probably the result of a duplicate
1664 declaration, for which we've already issued an error. It would
1665 be really nice if the front end wouldn't leak these at all.
1666 Currently the only known culprit is C++ destructors, as seen
1667 in g++.old-deja/g++.jason/binding.C. */
1668 if (TREE_CODE (decl) == VAR_DECL
1669 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
1670 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
1671 && decl_function_context (decl) == current_function_decl)
1673 gcc_assert (errorcount || sorrycount);
1674 return GS_ERROR;
1677 /* When within an OpenMP context, notice uses of variables. */
1678 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
1679 return GS_ALL_DONE;
1681 /* If the decl is an alias for another expression, substitute it now. */
1682 if (DECL_HAS_VALUE_EXPR_P (decl))
1684 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
1685 return GS_OK;
1688 return GS_ALL_DONE;
1692 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
1693 node pointed to by EXPR_P.
1695 compound_lval
1696 : min_lval '[' val ']'
1697 | min_lval '.' ID
1698 | compound_lval '[' val ']'
1699 | compound_lval '.' ID
1701 This is not part of the original SIMPLE definition, which separates
1702 array and member references, but it seems reasonable to handle them
1703 together. Also, this way we don't run into problems with union
1704 aliasing; gcc requires that for accesses through a union to alias, the
1705 union reference must be explicit, which was not always the case when we
1706 were splitting up array and member refs.
1708 PRE_P points to the list where side effects that must happen before
1709 *EXPR_P should be stored.
1711 POST_P points to the list where side effects that must happen after
1712 *EXPR_P should be stored. */
1714 static enum gimplify_status
1715 gimplify_compound_lval (tree *expr_p, tree *pre_p,
1716 tree *post_p, fallback_t fallback)
1718 tree *p;
1719 VEC(tree,heap) *stack;
1720 enum gimplify_status ret = GS_OK, tret;
1721 int i;
1723 /* Create a stack of the subexpressions so later we can walk them in
1724 order from inner to outer. */
1725 stack = VEC_alloc (tree, heap, 10);
1727 /* We can handle anything that get_inner_reference can deal with. */
1728 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
1730 restart:
1731 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
1732 if (TREE_CODE (*p) == INDIRECT_REF)
1733 *p = fold_indirect_ref (*p);
1735 if (handled_component_p (*p))
1737 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
1738 additional COMPONENT_REFs. */
1739 else if ((TREE_CODE (*p) == VAR_DECL || TREE_CODE (*p) == PARM_DECL)
1740 && gimplify_var_or_parm_decl (p) == GS_OK)
1741 goto restart;
1742 else
1743 break;
1745 VEC_safe_push (tree, heap, stack, *p);
1748 gcc_assert (VEC_length (tree, stack));
1750 /* Now STACK is a stack of pointers to all the refs we've walked through
1751 and P points to the innermost expression.
1753 Java requires that we elaborated nodes in source order. That
1754 means we must gimplify the inner expression followed by each of
1755 the indices, in order. But we can't gimplify the inner
1756 expression until we deal with any variable bounds, sizes, or
1757 positions in order to deal with PLACEHOLDER_EXPRs.
1759 So we do this in three steps. First we deal with the annotations
1760 for any variables in the components, then we gimplify the base,
1761 then we gimplify any indices, from left to right. */
1762 for (i = VEC_length (tree, stack) - 1; i >= 0; i--)
1764 tree t = VEC_index (tree, stack, i);
1766 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
1768 /* Gimplify the low bound and element type size and put them into
1769 the ARRAY_REF. If these values are set, they have already been
1770 gimplified. */
1771 if (!TREE_OPERAND (t, 2))
1773 tree low = unshare_expr (array_ref_low_bound (t));
1774 if (!is_gimple_min_invariant (low))
1776 TREE_OPERAND (t, 2) = low;
1777 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1778 is_gimple_formal_tmp_reg, fb_rvalue);
1779 ret = MIN (ret, tret);
1783 if (!TREE_OPERAND (t, 3))
1785 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
1786 tree elmt_size = unshare_expr (array_ref_element_size (t));
1787 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
1789 /* Divide the element size by the alignment of the element
1790 type (above). */
1791 elmt_size = size_binop (EXACT_DIV_EXPR, elmt_size, factor);
1793 if (!is_gimple_min_invariant (elmt_size))
1795 TREE_OPERAND (t, 3) = elmt_size;
1796 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
1797 is_gimple_formal_tmp_reg, fb_rvalue);
1798 ret = MIN (ret, tret);
1802 else if (TREE_CODE (t) == COMPONENT_REF)
1804 /* Set the field offset into T and gimplify it. */
1805 if (!TREE_OPERAND (t, 2))
1807 tree offset = unshare_expr (component_ref_field_offset (t));
1808 tree field = TREE_OPERAND (t, 1);
1809 tree factor
1810 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
1812 /* Divide the offset by its alignment. */
1813 offset = size_binop (EXACT_DIV_EXPR, offset, factor);
1815 if (!is_gimple_min_invariant (offset))
1817 TREE_OPERAND (t, 2) = offset;
1818 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1819 is_gimple_formal_tmp_reg, fb_rvalue);
1820 ret = MIN (ret, tret);
1826 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
1827 so as to match the min_lval predicate. Failure to do so may result
1828 in the creation of large aggregate temporaries. */
1829 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
1830 fallback | fb_lvalue);
1831 ret = MIN (ret, tret);
1833 /* And finally, the indices and operands to BIT_FIELD_REF. During this
1834 loop we also remove any useless conversions. */
1835 for (; VEC_length (tree, stack) > 0; )
1837 tree t = VEC_pop (tree, stack);
1839 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
1841 /* Gimplify the dimension.
1842 Temporary fix for gcc.c-torture/execute/20040313-1.c.
1843 Gimplify non-constant array indices into a temporary
1844 variable.
1845 FIXME - The real fix is to gimplify post-modify
1846 expressions into a minimal gimple lvalue. However, that
1847 exposes bugs in alias analysis. The alias analyzer does
1848 not handle &PTR->FIELD very well. Will fix after the
1849 branch is merged into mainline (dnovillo 2004-05-03). */
1850 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
1852 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
1853 is_gimple_formal_tmp_reg, fb_rvalue);
1854 ret = MIN (ret, tret);
1857 else if (TREE_CODE (t) == BIT_FIELD_REF)
1859 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
1860 is_gimple_val, fb_rvalue);
1861 ret = MIN (ret, tret);
1862 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1863 is_gimple_val, fb_rvalue);
1864 ret = MIN (ret, tret);
1867 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
1869 /* The innermost expression P may have originally had TREE_SIDE_EFFECTS
1870 set which would have caused all the outer expressions in EXPR_P
1871 leading to P to also have had TREE_SIDE_EFFECTS set. */
1872 recalculate_side_effects (t);
1875 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval, fallback);
1876 ret = MIN (ret, tret);
1878 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
1879 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
1881 canonicalize_component_ref (expr_p);
1882 ret = MIN (ret, GS_OK);
1885 VEC_free (tree, heap, stack);
1887 return ret;
1890 /* Gimplify the self modifying expression pointed to by EXPR_P
1891 (++, --, +=, -=).
1893 PRE_P points to the list where side effects that must happen before
1894 *EXPR_P should be stored.
1896 POST_P points to the list where side effects that must happen after
1897 *EXPR_P should be stored.
1899 WANT_VALUE is nonzero iff we want to use the value of this expression
1900 in another expression. */
1902 static enum gimplify_status
1903 gimplify_self_mod_expr (tree *expr_p, tree *pre_p, tree *post_p,
1904 bool want_value)
1906 enum tree_code code;
1907 tree lhs, lvalue, rhs, t1, post = NULL, *orig_post_p = post_p;
1908 bool postfix;
1909 enum tree_code arith_code;
1910 enum gimplify_status ret;
1912 code = TREE_CODE (*expr_p);
1914 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
1915 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
1917 /* Prefix or postfix? */
1918 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
1919 /* Faster to treat as prefix if result is not used. */
1920 postfix = want_value;
1921 else
1922 postfix = false;
1924 /* For postfix, make sure the inner expression's post side effects
1925 are executed after side effects from this expression. */
1926 if (postfix)
1927 post_p = &post;
1929 /* Add or subtract? */
1930 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
1931 arith_code = PLUS_EXPR;
1932 else
1933 arith_code = MINUS_EXPR;
1935 /* Gimplify the LHS into a GIMPLE lvalue. */
1936 lvalue = TREE_OPERAND (*expr_p, 0);
1937 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
1938 if (ret == GS_ERROR)
1939 return ret;
1941 /* Extract the operands to the arithmetic operation. */
1942 lhs = lvalue;
1943 rhs = TREE_OPERAND (*expr_p, 1);
1945 /* For postfix operator, we evaluate the LHS to an rvalue and then use
1946 that as the result value and in the postqueue operation. */
1947 if (postfix)
1949 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
1950 if (ret == GS_ERROR)
1951 return ret;
1954 t1 = build2 (arith_code, TREE_TYPE (*expr_p), lhs, rhs);
1955 t1 = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (lvalue), lvalue, t1);
1957 if (postfix)
1959 gimplify_and_add (t1, orig_post_p);
1960 append_to_statement_list (post, orig_post_p);
1961 *expr_p = lhs;
1962 return GS_ALL_DONE;
1964 else
1966 *expr_p = t1;
1967 return GS_OK;
1971 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
1973 static void
1974 maybe_with_size_expr (tree *expr_p)
1976 tree expr = *expr_p;
1977 tree type = TREE_TYPE (expr);
1978 tree size;
1980 /* If we've already wrapped this or the type is error_mark_node, we can't do
1981 anything. */
1982 if (TREE_CODE (expr) == WITH_SIZE_EXPR
1983 || type == error_mark_node)
1984 return;
1986 /* If the size isn't known or is a constant, we have nothing to do. */
1987 size = TYPE_SIZE_UNIT (type);
1988 if (!size || TREE_CODE (size) == INTEGER_CST)
1989 return;
1991 /* Otherwise, make a WITH_SIZE_EXPR. */
1992 size = unshare_expr (size);
1993 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
1994 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
1997 /* Subroutine of gimplify_call_expr: Gimplify a single argument. */
1999 static enum gimplify_status
2000 gimplify_arg (tree *expr_p, tree *pre_p)
2002 bool (*test) (tree);
2003 fallback_t fb;
2005 /* In general, we allow lvalues for function arguments to avoid
2006 extra overhead of copying large aggregates out of even larger
2007 aggregates into temporaries only to copy the temporaries to
2008 the argument list. Make optimizers happy by pulling out to
2009 temporaries those types that fit in registers. */
2010 if (is_gimple_reg_type (TREE_TYPE (*expr_p)))
2011 test = is_gimple_val, fb = fb_rvalue;
2012 else
2013 test = is_gimple_lvalue, fb = fb_either;
2015 /* If this is a variable sized type, we must remember the size. */
2016 maybe_with_size_expr (expr_p);
2018 /* There is a sequence point before a function call. Side effects in
2019 the argument list must occur before the actual call. So, when
2020 gimplifying arguments, force gimplify_expr to use an internal
2021 post queue which is then appended to the end of PRE_P. */
2022 return gimplify_expr (expr_p, pre_p, NULL, test, fb);
2025 /* Gimplify the CALL_EXPR node pointed to by EXPR_P. PRE_P points to the
2026 list where side effects that must happen before *EXPR_P should be stored.
2027 WANT_VALUE is true if the result of the call is desired. */
2029 static enum gimplify_status
2030 gimplify_call_expr (tree *expr_p, tree *pre_p, bool want_value)
2032 tree decl;
2033 tree arglist;
2034 enum gimplify_status ret;
2036 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
2038 /* For reliable diagnostics during inlining, it is necessary that
2039 every call_expr be annotated with file and line. */
2040 if (! EXPR_HAS_LOCATION (*expr_p))
2041 SET_EXPR_LOCATION (*expr_p, input_location);
2043 /* This may be a call to a builtin function.
2045 Builtin function calls may be transformed into different
2046 (and more efficient) builtin function calls under certain
2047 circumstances. Unfortunately, gimplification can muck things
2048 up enough that the builtin expanders are not aware that certain
2049 transformations are still valid.
2051 So we attempt transformation/gimplification of the call before
2052 we gimplify the CALL_EXPR. At this time we do not manage to
2053 transform all calls in the same manner as the expanders do, but
2054 we do transform most of them. */
2055 decl = get_callee_fndecl (*expr_p);
2056 if (decl && DECL_BUILT_IN (decl))
2058 tree arglist = TREE_OPERAND (*expr_p, 1);
2059 tree new = fold_builtin (decl, arglist, !want_value);
2061 if (new && new != *expr_p)
2063 /* There was a transformation of this call which computes the
2064 same value, but in a more efficient way. Return and try
2065 again. */
2066 *expr_p = new;
2067 return GS_OK;
2070 if (DECL_BUILT_IN_CLASS (decl) == BUILT_IN_NORMAL
2071 && DECL_FUNCTION_CODE (decl) == BUILT_IN_VA_START)
2073 if (!arglist || !TREE_CHAIN (arglist))
2075 error ("too few arguments to function %<va_start%>");
2076 *expr_p = build_empty_stmt ();
2077 return GS_OK;
2080 if (fold_builtin_next_arg (TREE_CHAIN (arglist)))
2082 *expr_p = build_empty_stmt ();
2083 return GS_OK;
2085 /* Avoid gimplifying the second argument to va_start, which needs
2086 to be the plain PARM_DECL. */
2087 return gimplify_arg (&TREE_VALUE (TREE_OPERAND (*expr_p, 1)), pre_p);
2091 /* There is a sequence point before the call, so any side effects in
2092 the calling expression must occur before the actual call. Force
2093 gimplify_expr to use an internal post queue. */
2094 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, NULL,
2095 is_gimple_call_addr, fb_rvalue);
2097 if (PUSH_ARGS_REVERSED)
2098 TREE_OPERAND (*expr_p, 1) = nreverse (TREE_OPERAND (*expr_p, 1));
2099 for (arglist = TREE_OPERAND (*expr_p, 1); arglist;
2100 arglist = TREE_CHAIN (arglist))
2102 enum gimplify_status t;
2104 t = gimplify_arg (&TREE_VALUE (arglist), pre_p);
2106 if (t == GS_ERROR)
2107 ret = GS_ERROR;
2109 if (PUSH_ARGS_REVERSED)
2110 TREE_OPERAND (*expr_p, 1) = nreverse (TREE_OPERAND (*expr_p, 1));
2112 /* Try this again in case gimplification exposed something. */
2113 if (ret != GS_ERROR)
2115 decl = get_callee_fndecl (*expr_p);
2116 if (decl && DECL_BUILT_IN (decl))
2118 tree arglist = TREE_OPERAND (*expr_p, 1);
2119 tree new = fold_builtin (decl, arglist, !want_value);
2121 if (new && new != *expr_p)
2123 /* There was a transformation of this call which computes the
2124 same value, but in a more efficient way. Return and try
2125 again. */
2126 *expr_p = new;
2127 return GS_OK;
2132 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
2133 decl. This allows us to eliminate redundant or useless
2134 calls to "const" functions. */
2135 if (TREE_CODE (*expr_p) == CALL_EXPR
2136 && (call_expr_flags (*expr_p) & (ECF_CONST | ECF_PURE)))
2137 TREE_SIDE_EFFECTS (*expr_p) = 0;
2139 return ret;
2142 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
2143 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
2145 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
2146 condition is true or false, respectively. If null, we should generate
2147 our own to skip over the evaluation of this specific expression.
2149 This function is the tree equivalent of do_jump.
2151 shortcut_cond_r should only be called by shortcut_cond_expr. */
2153 static tree
2154 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p)
2156 tree local_label = NULL_TREE;
2157 tree t, expr = NULL;
2159 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
2160 retain the shortcut semantics. Just insert the gotos here;
2161 shortcut_cond_expr will append the real blocks later. */
2162 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
2164 /* Turn if (a && b) into
2166 if (a); else goto no;
2167 if (b) goto yes; else goto no;
2168 (no:) */
2170 if (false_label_p == NULL)
2171 false_label_p = &local_label;
2173 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p);
2174 append_to_statement_list (t, &expr);
2176 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
2177 false_label_p);
2178 append_to_statement_list (t, &expr);
2180 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
2182 /* Turn if (a || b) into
2184 if (a) goto yes;
2185 if (b) goto yes; else goto no;
2186 (yes:) */
2188 if (true_label_p == NULL)
2189 true_label_p = &local_label;
2191 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL);
2192 append_to_statement_list (t, &expr);
2194 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
2195 false_label_p);
2196 append_to_statement_list (t, &expr);
2198 else if (TREE_CODE (pred) == COND_EXPR)
2200 /* As long as we're messing with gotos, turn if (a ? b : c) into
2201 if (a)
2202 if (b) goto yes; else goto no;
2203 else
2204 if (c) goto yes; else goto no; */
2205 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
2206 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
2207 false_label_p),
2208 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
2209 false_label_p));
2211 else
2213 expr = build3 (COND_EXPR, void_type_node, pred,
2214 build_and_jump (true_label_p),
2215 build_and_jump (false_label_p));
2218 if (local_label)
2220 t = build1 (LABEL_EXPR, void_type_node, local_label);
2221 append_to_statement_list (t, &expr);
2224 return expr;
2227 static tree
2228 shortcut_cond_expr (tree expr)
2230 tree pred = TREE_OPERAND (expr, 0);
2231 tree then_ = TREE_OPERAND (expr, 1);
2232 tree else_ = TREE_OPERAND (expr, 2);
2233 tree true_label, false_label, end_label, t;
2234 tree *true_label_p;
2235 tree *false_label_p;
2236 bool emit_end, emit_false, jump_over_else;
2237 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
2238 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
2240 /* First do simple transformations. */
2241 if (!else_se)
2243 /* If there is no 'else', turn (a && b) into if (a) if (b). */
2244 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
2246 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
2247 then_ = shortcut_cond_expr (expr);
2248 then_se = then_ && TREE_SIDE_EFFECTS (then_);
2249 pred = TREE_OPERAND (pred, 0);
2250 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
2253 if (!then_se)
2255 /* If there is no 'then', turn
2256 if (a || b); else d
2257 into
2258 if (a); else if (b); else d. */
2259 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
2261 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
2262 else_ = shortcut_cond_expr (expr);
2263 else_se = else_ && TREE_SIDE_EFFECTS (else_);
2264 pred = TREE_OPERAND (pred, 0);
2265 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
2269 /* If we're done, great. */
2270 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
2271 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
2272 return expr;
2274 /* Otherwise we need to mess with gotos. Change
2275 if (a) c; else d;
2277 if (a); else goto no;
2278 c; goto end;
2279 no: d; end:
2280 and recursively gimplify the condition. */
2282 true_label = false_label = end_label = NULL_TREE;
2284 /* If our arms just jump somewhere, hijack those labels so we don't
2285 generate jumps to jumps. */
2287 if (then_
2288 && TREE_CODE (then_) == GOTO_EXPR
2289 && TREE_CODE (GOTO_DESTINATION (then_)) == LABEL_DECL)
2291 true_label = GOTO_DESTINATION (then_);
2292 then_ = NULL;
2293 then_se = false;
2296 if (else_
2297 && TREE_CODE (else_) == GOTO_EXPR
2298 && TREE_CODE (GOTO_DESTINATION (else_)) == LABEL_DECL)
2300 false_label = GOTO_DESTINATION (else_);
2301 else_ = NULL;
2302 else_se = false;
2305 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
2306 if (true_label)
2307 true_label_p = &true_label;
2308 else
2309 true_label_p = NULL;
2311 /* The 'else' branch also needs a label if it contains interesting code. */
2312 if (false_label || else_se)
2313 false_label_p = &false_label;
2314 else
2315 false_label_p = NULL;
2317 /* If there was nothing else in our arms, just forward the label(s). */
2318 if (!then_se && !else_se)
2319 return shortcut_cond_r (pred, true_label_p, false_label_p);
2321 /* If our last subexpression already has a terminal label, reuse it. */
2322 if (else_se)
2323 expr = expr_last (else_);
2324 else if (then_se)
2325 expr = expr_last (then_);
2326 else
2327 expr = NULL;
2328 if (expr && TREE_CODE (expr) == LABEL_EXPR)
2329 end_label = LABEL_EXPR_LABEL (expr);
2331 /* If we don't care about jumping to the 'else' branch, jump to the end
2332 if the condition is false. */
2333 if (!false_label_p)
2334 false_label_p = &end_label;
2336 /* We only want to emit these labels if we aren't hijacking them. */
2337 emit_end = (end_label == NULL_TREE);
2338 emit_false = (false_label == NULL_TREE);
2340 /* We only emit the jump over the else clause if we have to--if the
2341 then clause may fall through. Otherwise we can wind up with a
2342 useless jump and a useless label at the end of gimplified code,
2343 which will cause us to think that this conditional as a whole
2344 falls through even if it doesn't. If we then inline a function
2345 which ends with such a condition, that can cause us to issue an
2346 inappropriate warning about control reaching the end of a
2347 non-void function. */
2348 jump_over_else = block_may_fallthru (then_);
2350 pred = shortcut_cond_r (pred, true_label_p, false_label_p);
2352 expr = NULL;
2353 append_to_statement_list (pred, &expr);
2355 append_to_statement_list (then_, &expr);
2356 if (else_se)
2358 if (jump_over_else)
2360 t = build_and_jump (&end_label);
2361 append_to_statement_list (t, &expr);
2363 if (emit_false)
2365 t = build1 (LABEL_EXPR, void_type_node, false_label);
2366 append_to_statement_list (t, &expr);
2368 append_to_statement_list (else_, &expr);
2370 if (emit_end && end_label)
2372 t = build1 (LABEL_EXPR, void_type_node, end_label);
2373 append_to_statement_list (t, &expr);
2376 return expr;
2379 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
2381 tree
2382 gimple_boolify (tree expr)
2384 tree type = TREE_TYPE (expr);
2386 if (TREE_CODE (type) == BOOLEAN_TYPE)
2387 return expr;
2389 switch (TREE_CODE (expr))
2391 case TRUTH_AND_EXPR:
2392 case TRUTH_OR_EXPR:
2393 case TRUTH_XOR_EXPR:
2394 case TRUTH_ANDIF_EXPR:
2395 case TRUTH_ORIF_EXPR:
2396 /* Also boolify the arguments of truth exprs. */
2397 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
2398 /* FALLTHRU */
2400 case TRUTH_NOT_EXPR:
2401 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2402 /* FALLTHRU */
2404 case EQ_EXPR: case NE_EXPR:
2405 case LE_EXPR: case GE_EXPR: case LT_EXPR: case GT_EXPR:
2406 /* These expressions always produce boolean results. */
2407 TREE_TYPE (expr) = boolean_type_node;
2408 return expr;
2410 default:
2411 /* Other expressions that get here must have boolean values, but
2412 might need to be converted to the appropriate mode. */
2413 return fold_convert (boolean_type_node, expr);
2417 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
2418 into
2420 if (p) if (p)
2421 t1 = a; a;
2422 else or else
2423 t1 = b; b;
2426 The second form is used when *EXPR_P is of type void.
2428 TARGET is the tree for T1 above.
2430 PRE_P points to the list where side effects that must happen before
2431 *EXPR_P should be stored. */
2433 static enum gimplify_status
2434 gimplify_cond_expr (tree *expr_p, tree *pre_p, fallback_t fallback)
2436 tree expr = *expr_p;
2437 tree tmp, tmp2, type;
2438 enum gimplify_status ret;
2440 type = TREE_TYPE (expr);
2442 /* If this COND_EXPR has a value, copy the values into a temporary within
2443 the arms. */
2444 if (! VOID_TYPE_P (type))
2446 tree result;
2448 if ((fallback & fb_lvalue) == 0)
2450 result = tmp2 = tmp = create_tmp_var (TREE_TYPE (expr), "iftmp");
2451 ret = GS_ALL_DONE;
2453 else
2455 tree type = build_pointer_type (TREE_TYPE (expr));
2457 if (TREE_TYPE (TREE_OPERAND (expr, 1)) != void_type_node)
2458 TREE_OPERAND (expr, 1) =
2459 build_fold_addr_expr (TREE_OPERAND (expr, 1));
2461 if (TREE_TYPE (TREE_OPERAND (expr, 2)) != void_type_node)
2462 TREE_OPERAND (expr, 2) =
2463 build_fold_addr_expr (TREE_OPERAND (expr, 2));
2465 tmp2 = tmp = create_tmp_var (type, "iftmp");
2467 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (expr, 0),
2468 TREE_OPERAND (expr, 1), TREE_OPERAND (expr, 2));
2470 result = build_fold_indirect_ref (tmp);
2471 ret = GS_ALL_DONE;
2474 /* Build the then clause, 't1 = a;'. But don't build an assignment
2475 if this branch is void; in C++ it can be, if it's a throw. */
2476 if (TREE_TYPE (TREE_OPERAND (expr, 1)) != void_type_node)
2477 TREE_OPERAND (expr, 1)
2478 = build2 (GIMPLE_MODIFY_STMT, void_type_node, tmp,
2479 TREE_OPERAND (expr, 1));
2481 /* Build the else clause, 't1 = b;'. */
2482 if (TREE_TYPE (TREE_OPERAND (expr, 2)) != void_type_node)
2483 TREE_OPERAND (expr, 2)
2484 = build2 (GIMPLE_MODIFY_STMT, void_type_node, tmp2,
2485 TREE_OPERAND (expr, 2));
2487 TREE_TYPE (expr) = void_type_node;
2488 recalculate_side_effects (expr);
2490 /* Move the COND_EXPR to the prequeue. */
2491 gimplify_and_add (expr, pre_p);
2493 *expr_p = result;
2494 return ret;
2497 /* Make sure the condition has BOOLEAN_TYPE. */
2498 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2500 /* Break apart && and || conditions. */
2501 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
2502 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
2504 expr = shortcut_cond_expr (expr);
2506 if (expr != *expr_p)
2508 *expr_p = expr;
2510 /* We can't rely on gimplify_expr to re-gimplify the expanded
2511 form properly, as cleanups might cause the target labels to be
2512 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
2513 set up a conditional context. */
2514 gimple_push_condition ();
2515 gimplify_stmt (expr_p);
2516 gimple_pop_condition (pre_p);
2518 return GS_ALL_DONE;
2522 /* Now do the normal gimplification. */
2523 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
2524 is_gimple_condexpr, fb_rvalue);
2526 gimple_push_condition ();
2528 gimplify_to_stmt_list (&TREE_OPERAND (expr, 1));
2529 gimplify_to_stmt_list (&TREE_OPERAND (expr, 2));
2530 recalculate_side_effects (expr);
2532 gimple_pop_condition (pre_p);
2534 if (ret == GS_ERROR)
2536 else if (TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 1)))
2537 ret = GS_ALL_DONE;
2538 else if (TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 2)))
2539 /* Rewrite "if (a); else b" to "if (!a) b" */
2541 TREE_OPERAND (expr, 0) = invert_truthvalue (TREE_OPERAND (expr, 0));
2542 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
2543 is_gimple_condexpr, fb_rvalue);
2545 tmp = TREE_OPERAND (expr, 1);
2546 TREE_OPERAND (expr, 1) = TREE_OPERAND (expr, 2);
2547 TREE_OPERAND (expr, 2) = tmp;
2549 else
2550 /* Both arms are empty; replace the COND_EXPR with its predicate. */
2551 expr = TREE_OPERAND (expr, 0);
2553 *expr_p = expr;
2554 return ret;
2557 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
2558 a call to __builtin_memcpy. */
2560 static enum gimplify_status
2561 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value)
2563 tree args, t, to, to_ptr, from;
2565 to = GENERIC_TREE_OPERAND (*expr_p, 0);
2566 from = GENERIC_TREE_OPERAND (*expr_p, 1);
2568 args = tree_cons (NULL, size, NULL);
2570 t = build_fold_addr_expr (from);
2571 args = tree_cons (NULL, t, args);
2573 to_ptr = build_fold_addr_expr (to);
2574 args = tree_cons (NULL, to_ptr, args);
2575 t = implicit_built_in_decls[BUILT_IN_MEMCPY];
2576 t = build_function_call_expr (t, args);
2578 if (want_value)
2580 t = build1 (NOP_EXPR, TREE_TYPE (to_ptr), t);
2581 t = build1 (INDIRECT_REF, TREE_TYPE (to), t);
2584 *expr_p = t;
2585 return GS_OK;
2588 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
2589 a call to __builtin_memset. In this case we know that the RHS is
2590 a CONSTRUCTOR with an empty element list. */
2592 static enum gimplify_status
2593 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value)
2595 tree args, t, to, to_ptr;
2597 to = GENERIC_TREE_OPERAND (*expr_p, 0);
2599 args = tree_cons (NULL, size, NULL);
2601 args = tree_cons (NULL, integer_zero_node, args);
2603 to_ptr = build_fold_addr_expr (to);
2604 args = tree_cons (NULL, to_ptr, args);
2605 t = implicit_built_in_decls[BUILT_IN_MEMSET];
2606 t = build_function_call_expr (t, args);
2608 if (want_value)
2610 t = build1 (NOP_EXPR, TREE_TYPE (to_ptr), t);
2611 t = build1 (INDIRECT_REF, TREE_TYPE (to), t);
2614 *expr_p = t;
2615 return GS_OK;
2618 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
2619 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
2620 assignment. Returns non-null if we detect a potential overlap. */
2622 struct gimplify_init_ctor_preeval_data
2624 /* The base decl of the lhs object. May be NULL, in which case we
2625 have to assume the lhs is indirect. */
2626 tree lhs_base_decl;
2628 /* The alias set of the lhs object. */
2629 int lhs_alias_set;
2632 static tree
2633 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
2635 struct gimplify_init_ctor_preeval_data *data
2636 = (struct gimplify_init_ctor_preeval_data *) xdata;
2637 tree t = *tp;
2639 /* If we find the base object, obviously we have overlap. */
2640 if (data->lhs_base_decl == t)
2641 return t;
2643 /* If the constructor component is indirect, determine if we have a
2644 potential overlap with the lhs. The only bits of information we
2645 have to go on at this point are addressability and alias sets. */
2646 if (TREE_CODE (t) == INDIRECT_REF
2647 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
2648 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
2649 return t;
2651 if (IS_TYPE_OR_DECL_P (t))
2652 *walk_subtrees = 0;
2653 return NULL;
2656 /* A subroutine of gimplify_init_constructor. Pre-evaluate *EXPR_P,
2657 force values that overlap with the lhs (as described by *DATA)
2658 into temporaries. */
2660 static void
2661 gimplify_init_ctor_preeval (tree *expr_p, tree *pre_p, tree *post_p,
2662 struct gimplify_init_ctor_preeval_data *data)
2664 enum gimplify_status one;
2666 /* If the value is invariant, then there's nothing to pre-evaluate.
2667 But ensure it doesn't have any side-effects since a SAVE_EXPR is
2668 invariant but has side effects and might contain a reference to
2669 the object we're initializing. */
2670 if (TREE_INVARIANT (*expr_p) && !TREE_SIDE_EFFECTS (*expr_p))
2671 return;
2673 /* If the type has non-trivial constructors, we can't pre-evaluate. */
2674 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
2675 return;
2677 /* Recurse for nested constructors. */
2678 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
2680 unsigned HOST_WIDE_INT ix;
2681 constructor_elt *ce;
2682 VEC(constructor_elt,gc) *v = CONSTRUCTOR_ELTS (*expr_p);
2684 for (ix = 0; VEC_iterate (constructor_elt, v, ix, ce); ix++)
2685 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
2686 return;
2689 /* If this is a variable sized type, we must remember the size. */
2690 maybe_with_size_expr (expr_p);
2692 /* Gimplify the constructor element to something appropriate for the rhs
2693 of a MODIFY_EXPR. Given that we know the lhs is an aggregate, we know
2694 the gimplifier will consider this a store to memory. Doing this
2695 gimplification now means that we won't have to deal with complicated
2696 language-specific trees, nor trees like SAVE_EXPR that can induce
2697 exponential search behavior. */
2698 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
2699 if (one == GS_ERROR)
2701 *expr_p = NULL;
2702 return;
2705 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
2706 with the lhs, since "a = { .x=a }" doesn't make sense. This will
2707 always be true for all scalars, since is_gimple_mem_rhs insists on a
2708 temporary variable for them. */
2709 if (DECL_P (*expr_p))
2710 return;
2712 /* If this is of variable size, we have no choice but to assume it doesn't
2713 overlap since we can't make a temporary for it. */
2714 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
2715 return;
2717 /* Otherwise, we must search for overlap ... */
2718 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
2719 return;
2721 /* ... and if found, force the value into a temporary. */
2722 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
2725 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
2726 a RANGE_EXPR in a CONSTRUCTOR for an array.
2728 var = lower;
2729 loop_entry:
2730 object[var] = value;
2731 if (var == upper)
2732 goto loop_exit;
2733 var = var + 1;
2734 goto loop_entry;
2735 loop_exit:
2737 We increment var _after_ the loop exit check because we might otherwise
2738 fail if upper == TYPE_MAX_VALUE (type for upper).
2740 Note that we never have to deal with SAVE_EXPRs here, because this has
2741 already been taken care of for us, in gimplify_init_ctor_preeval(). */
2743 static void gimplify_init_ctor_eval (tree, VEC(constructor_elt,gc) *,
2744 tree *, bool);
2746 static void
2747 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
2748 tree value, tree array_elt_type,
2749 tree *pre_p, bool cleared)
2751 tree loop_entry_label, loop_exit_label;
2752 tree var, var_type, cref;
2754 loop_entry_label = create_artificial_label ();
2755 loop_exit_label = create_artificial_label ();
2757 /* Create and initialize the index variable. */
2758 var_type = TREE_TYPE (upper);
2759 var = create_tmp_var (var_type, NULL);
2760 append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, var_type, var, lower),
2761 pre_p);
2763 /* Add the loop entry label. */
2764 append_to_statement_list (build1 (LABEL_EXPR,
2765 void_type_node,
2766 loop_entry_label),
2767 pre_p);
2769 /* Build the reference. */
2770 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
2771 var, NULL_TREE, NULL_TREE);
2773 /* If we are a constructor, just call gimplify_init_ctor_eval to do
2774 the store. Otherwise just assign value to the reference. */
2776 if (TREE_CODE (value) == CONSTRUCTOR)
2777 /* NB we might have to call ourself recursively through
2778 gimplify_init_ctor_eval if the value is a constructor. */
2779 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
2780 pre_p, cleared);
2781 else
2782 append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (cref),
2783 cref, value),
2784 pre_p);
2786 /* We exit the loop when the index var is equal to the upper bound. */
2787 gimplify_and_add (build3 (COND_EXPR, void_type_node,
2788 build2 (EQ_EXPR, boolean_type_node,
2789 var, upper),
2790 build1 (GOTO_EXPR,
2791 void_type_node,
2792 loop_exit_label),
2793 NULL_TREE),
2794 pre_p);
2796 /* Otherwise, increment the index var... */
2797 append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, var_type, var,
2798 build2 (PLUS_EXPR, var_type, var,
2799 fold_convert (var_type,
2800 integer_one_node))),
2801 pre_p);
2803 /* ...and jump back to the loop entry. */
2804 append_to_statement_list (build1 (GOTO_EXPR,
2805 void_type_node,
2806 loop_entry_label),
2807 pre_p);
2809 /* Add the loop exit label. */
2810 append_to_statement_list (build1 (LABEL_EXPR,
2811 void_type_node,
2812 loop_exit_label),
2813 pre_p);
2816 /* Return true if FDECL is accessing a field that is zero sized. */
2818 static bool
2819 zero_sized_field_decl (tree fdecl)
2821 if (TREE_CODE (fdecl) == FIELD_DECL && DECL_SIZE (fdecl)
2822 && integer_zerop (DECL_SIZE (fdecl)))
2823 return true;
2824 return false;
2827 /* Return true if TYPE is zero sized. */
2829 static bool
2830 zero_sized_type (tree type)
2832 if (AGGREGATE_TYPE_P (type) && TYPE_SIZE (type)
2833 && integer_zerop (TYPE_SIZE (type)))
2834 return true;
2835 return false;
2838 /* A subroutine of gimplify_init_constructor. Generate individual
2839 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
2840 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
2841 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
2842 zeroed first. */
2844 static void
2845 gimplify_init_ctor_eval (tree object, VEC(constructor_elt,gc) *elts,
2846 tree *pre_p, bool cleared)
2848 tree array_elt_type = NULL;
2849 unsigned HOST_WIDE_INT ix;
2850 tree purpose, value;
2852 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
2853 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
2855 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
2857 tree cref, init;
2859 /* NULL values are created above for gimplification errors. */
2860 if (value == NULL)
2861 continue;
2863 if (cleared && initializer_zerop (value))
2864 continue;
2866 /* ??? Here's to hoping the front end fills in all of the indices,
2867 so we don't have to figure out what's missing ourselves. */
2868 gcc_assert (purpose);
2870 /* Skip zero-sized fields, unless value has side-effects. This can
2871 happen with calls to functions returning a zero-sized type, which
2872 we shouldn't discard. As a number of downstream passes don't
2873 expect sets of zero-sized fields, we rely on the gimplification of
2874 the MODIFY_EXPR we make below to drop the assignment statement. */
2875 if (! TREE_SIDE_EFFECTS (value) && zero_sized_field_decl (purpose))
2876 continue;
2878 /* If we have a RANGE_EXPR, we have to build a loop to assign the
2879 whole range. */
2880 if (TREE_CODE (purpose) == RANGE_EXPR)
2882 tree lower = TREE_OPERAND (purpose, 0);
2883 tree upper = TREE_OPERAND (purpose, 1);
2885 /* If the lower bound is equal to upper, just treat it as if
2886 upper was the index. */
2887 if (simple_cst_equal (lower, upper))
2888 purpose = upper;
2889 else
2891 gimplify_init_ctor_eval_range (object, lower, upper, value,
2892 array_elt_type, pre_p, cleared);
2893 continue;
2897 if (array_elt_type)
2899 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
2900 purpose, NULL_TREE, NULL_TREE);
2902 else
2904 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
2905 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
2906 unshare_expr (object), purpose, NULL_TREE);
2909 if (TREE_CODE (value) == CONSTRUCTOR
2910 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
2911 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
2912 pre_p, cleared);
2913 else
2915 init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
2916 gimplify_and_add (init, pre_p);
2921 /* A subroutine of gimplify_modify_expr. Break out elements of a
2922 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
2924 Note that we still need to clear any elements that don't have explicit
2925 initializers, so if not all elements are initialized we keep the
2926 original MODIFY_EXPR, we just remove all of the constructor elements. */
2928 static enum gimplify_status
2929 gimplify_init_constructor (tree *expr_p, tree *pre_p,
2930 tree *post_p, bool want_value)
2932 tree object;
2933 tree ctor = GENERIC_TREE_OPERAND (*expr_p, 1);
2934 tree type = TREE_TYPE (ctor);
2935 enum gimplify_status ret;
2936 VEC(constructor_elt,gc) *elts;
2938 if (TREE_CODE (ctor) != CONSTRUCTOR)
2939 return GS_UNHANDLED;
2941 ret = gimplify_expr (&GENERIC_TREE_OPERAND (*expr_p, 0), pre_p, post_p,
2942 is_gimple_lvalue, fb_lvalue);
2943 if (ret == GS_ERROR)
2944 return ret;
2945 object = GENERIC_TREE_OPERAND (*expr_p, 0);
2947 elts = CONSTRUCTOR_ELTS (ctor);
2949 ret = GS_ALL_DONE;
2950 switch (TREE_CODE (type))
2952 case RECORD_TYPE:
2953 case UNION_TYPE:
2954 case QUAL_UNION_TYPE:
2955 case ARRAY_TYPE:
2957 struct gimplify_init_ctor_preeval_data preeval_data;
2958 HOST_WIDE_INT num_type_elements, num_ctor_elements;
2959 HOST_WIDE_INT num_nonzero_elements;
2960 bool cleared, valid_const_initializer;
2962 /* Aggregate types must lower constructors to initialization of
2963 individual elements. The exception is that a CONSTRUCTOR node
2964 with no elements indicates zero-initialization of the whole. */
2965 if (VEC_empty (constructor_elt, elts))
2966 break;
2968 /* Fetch information about the constructor to direct later processing.
2969 We might want to make static versions of it in various cases, and
2970 can only do so if it known to be a valid constant initializer. */
2971 valid_const_initializer
2972 = categorize_ctor_elements (ctor, &num_nonzero_elements,
2973 &num_ctor_elements, &cleared);
2975 /* If a const aggregate variable is being initialized, then it
2976 should never be a lose to promote the variable to be static. */
2977 if (valid_const_initializer
2978 && num_nonzero_elements > 1
2979 && TREE_READONLY (object)
2980 && TREE_CODE (object) == VAR_DECL)
2982 DECL_INITIAL (object) = ctor;
2983 TREE_STATIC (object) = 1;
2984 if (!DECL_NAME (object))
2985 DECL_NAME (object) = create_tmp_var_name ("C");
2986 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
2988 /* ??? C++ doesn't automatically append a .<number> to the
2989 assembler name, and even when it does, it looks a FE private
2990 data structures to figure out what that number should be,
2991 which are not set for this variable. I suppose this is
2992 important for local statics for inline functions, which aren't
2993 "local" in the object file sense. So in order to get a unique
2994 TU-local symbol, we must invoke the lhd version now. */
2995 lhd_set_decl_assembler_name (object);
2997 *expr_p = NULL_TREE;
2998 break;
3001 /* If there are "lots" of initialized elements, even discounting
3002 those that are not address constants (and thus *must* be
3003 computed at runtime), then partition the constructor into
3004 constant and non-constant parts. Block copy the constant
3005 parts in, then generate code for the non-constant parts. */
3006 /* TODO. There's code in cp/typeck.c to do this. */
3008 num_type_elements = count_type_elements (type, true);
3010 /* If count_type_elements could not determine number of type elements
3011 for a constant-sized object, assume clearing is needed.
3012 Don't do this for variable-sized objects, as store_constructor
3013 will ignore the clearing of variable-sized objects. */
3014 if (num_type_elements < 0 && int_size_in_bytes (type) >= 0)
3015 cleared = true;
3016 /* If there are "lots" of zeros, then block clear the object first. */
3017 else if (num_type_elements - num_nonzero_elements > CLEAR_RATIO
3018 && num_nonzero_elements < num_type_elements/4)
3019 cleared = true;
3020 /* ??? This bit ought not be needed. For any element not present
3021 in the initializer, we should simply set them to zero. Except
3022 we'd need to *find* the elements that are not present, and that
3023 requires trickery to avoid quadratic compile-time behavior in
3024 large cases or excessive memory use in small cases. */
3025 else if (num_ctor_elements < num_type_elements)
3026 cleared = true;
3028 /* If there are "lots" of initialized elements, and all of them
3029 are valid address constants, then the entire initializer can
3030 be dropped to memory, and then memcpy'd out. Don't do this
3031 for sparse arrays, though, as it's more efficient to follow
3032 the standard CONSTRUCTOR behavior of memset followed by
3033 individual element initialization. */
3034 if (valid_const_initializer && !cleared)
3036 HOST_WIDE_INT size = int_size_in_bytes (type);
3037 unsigned int align;
3039 /* ??? We can still get unbounded array types, at least
3040 from the C++ front end. This seems wrong, but attempt
3041 to work around it for now. */
3042 if (size < 0)
3044 size = int_size_in_bytes (TREE_TYPE (object));
3045 if (size >= 0)
3046 TREE_TYPE (ctor) = type = TREE_TYPE (object);
3049 /* Find the maximum alignment we can assume for the object. */
3050 /* ??? Make use of DECL_OFFSET_ALIGN. */
3051 if (DECL_P (object))
3052 align = DECL_ALIGN (object);
3053 else
3054 align = TYPE_ALIGN (type);
3056 if (size > 0 && !can_move_by_pieces (size, align))
3058 tree new = create_tmp_var_raw (type, "C");
3060 gimple_add_tmp_var (new);
3061 TREE_STATIC (new) = 1;
3062 TREE_READONLY (new) = 1;
3063 DECL_INITIAL (new) = ctor;
3064 if (align > DECL_ALIGN (new))
3066 DECL_ALIGN (new) = align;
3067 DECL_USER_ALIGN (new) = 1;
3069 walk_tree (&DECL_INITIAL (new), force_labels_r, NULL, NULL);
3071 GENERIC_TREE_OPERAND (*expr_p, 1) = new;
3073 /* This is no longer an assignment of a CONSTRUCTOR, but
3074 we still may have processing to do on the LHS. So
3075 pretend we didn't do anything here to let that happen. */
3076 return GS_UNHANDLED;
3080 /* If there are nonzero elements, pre-evaluate to capture elements
3081 overlapping with the lhs into temporaries. We must do this before
3082 clearing to fetch the values before they are zeroed-out. */
3083 if (num_nonzero_elements > 0)
3085 preeval_data.lhs_base_decl = get_base_address (object);
3086 if (!DECL_P (preeval_data.lhs_base_decl))
3087 preeval_data.lhs_base_decl = NULL;
3088 preeval_data.lhs_alias_set = get_alias_set (object);
3090 gimplify_init_ctor_preeval (&GENERIC_TREE_OPERAND (*expr_p, 1),
3091 pre_p, post_p, &preeval_data);
3094 if (cleared)
3096 /* Zap the CONSTRUCTOR element list, which simplifies this case.
3097 Note that we still have to gimplify, in order to handle the
3098 case of variable sized types. Avoid shared tree structures. */
3099 CONSTRUCTOR_ELTS (ctor) = NULL;
3100 object = unshare_expr (object);
3101 gimplify_stmt (expr_p);
3102 append_to_statement_list (*expr_p, pre_p);
3105 /* If we have not block cleared the object, or if there are nonzero
3106 elements in the constructor, add assignments to the individual
3107 scalar fields of the object. */
3108 if (!cleared || num_nonzero_elements > 0)
3109 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
3111 *expr_p = NULL_TREE;
3113 break;
3115 case COMPLEX_TYPE:
3117 tree r, i;
3119 /* Extract the real and imaginary parts out of the ctor. */
3120 gcc_assert (VEC_length (constructor_elt, elts) == 2);
3121 r = VEC_index (constructor_elt, elts, 0)->value;
3122 i = VEC_index (constructor_elt, elts, 1)->value;
3123 if (r == NULL || i == NULL)
3125 tree zero = fold_convert (TREE_TYPE (type), integer_zero_node);
3126 if (r == NULL)
3127 r = zero;
3128 if (i == NULL)
3129 i = zero;
3132 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
3133 represent creation of a complex value. */
3134 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
3136 ctor = build_complex (type, r, i);
3137 TREE_OPERAND (*expr_p, 1) = ctor;
3139 else
3141 ctor = build2 (COMPLEX_EXPR, type, r, i);
3142 TREE_OPERAND (*expr_p, 1) = ctor;
3143 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
3144 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
3145 fb_rvalue);
3148 break;
3150 case VECTOR_TYPE:
3152 unsigned HOST_WIDE_INT ix;
3153 constructor_elt *ce;
3155 /* Go ahead and simplify constant constructors to VECTOR_CST. */
3156 if (TREE_CONSTANT (ctor))
3158 bool constant_p = true;
3159 tree value;
3161 /* Even when ctor is constant, it might contain non-*_CST
3162 elements (e.g. { 1.0/0.0 - 1.0/0.0, 0.0 }) and those don't
3163 belong into VECTOR_CST nodes. */
3164 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
3165 if (!CONSTANT_CLASS_P (value))
3167 constant_p = false;
3168 break;
3171 if (constant_p)
3173 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
3174 break;
3177 /* Don't reduce a TREE_CONSTANT vector ctor even if we can't
3178 make a VECTOR_CST. It won't do anything for us, and it'll
3179 prevent us from representing it as a single constant. */
3180 break;
3183 /* Vector types use CONSTRUCTOR all the way through gimple
3184 compilation as a general initializer. */
3185 for (ix = 0; VEC_iterate (constructor_elt, elts, ix, ce); ix++)
3187 enum gimplify_status tret;
3188 tret = gimplify_expr (&ce->value, pre_p, post_p,
3189 is_gimple_val, fb_rvalue);
3190 if (tret == GS_ERROR)
3191 ret = GS_ERROR;
3193 if (!is_gimple_reg (GENERIC_TREE_OPERAND (*expr_p, 0)))
3194 GENERIC_TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
3196 break;
3198 default:
3199 /* So how did we get a CONSTRUCTOR for a scalar type? */
3200 gcc_unreachable ();
3203 if (ret == GS_ERROR)
3204 return GS_ERROR;
3205 else if (want_value)
3207 append_to_statement_list (*expr_p, pre_p);
3208 *expr_p = object;
3209 return GS_OK;
3211 else
3212 return GS_ALL_DONE;
3215 /* Given a pointer value OP0, return a simplified version of an
3216 indirection through OP0, or NULL_TREE if no simplification is
3217 possible. This may only be applied to a rhs of an expression.
3218 Note that the resulting type may be different from the type pointed
3219 to in the sense that it is still compatible from the langhooks
3220 point of view. */
3222 static tree
3223 fold_indirect_ref_rhs (tree t)
3225 tree type = TREE_TYPE (TREE_TYPE (t));
3226 tree sub = t;
3227 tree subtype;
3229 STRIP_USELESS_TYPE_CONVERSION (sub);
3230 subtype = TREE_TYPE (sub);
3231 if (!POINTER_TYPE_P (subtype))
3232 return NULL_TREE;
3234 if (TREE_CODE (sub) == ADDR_EXPR)
3236 tree op = TREE_OPERAND (sub, 0);
3237 tree optype = TREE_TYPE (op);
3238 /* *&p => p */
3239 if (lang_hooks.types_compatible_p (type, optype))
3240 return op;
3241 /* *(foo *)&fooarray => fooarray[0] */
3242 else if (TREE_CODE (optype) == ARRAY_TYPE
3243 && lang_hooks.types_compatible_p (type, TREE_TYPE (optype)))
3245 tree type_domain = TYPE_DOMAIN (optype);
3246 tree min_val = size_zero_node;
3247 if (type_domain && TYPE_MIN_VALUE (type_domain))
3248 min_val = TYPE_MIN_VALUE (type_domain);
3249 return build4 (ARRAY_REF, type, op, min_val, NULL_TREE, NULL_TREE);
3253 /* *(foo *)fooarrptr => (*fooarrptr)[0] */
3254 if (TREE_CODE (TREE_TYPE (subtype)) == ARRAY_TYPE
3255 && lang_hooks.types_compatible_p (type, TREE_TYPE (TREE_TYPE (subtype))))
3257 tree type_domain;
3258 tree min_val = size_zero_node;
3259 tree osub = sub;
3260 sub = fold_indirect_ref_rhs (sub);
3261 if (! sub)
3262 sub = build1 (INDIRECT_REF, TREE_TYPE (subtype), osub);
3263 type_domain = TYPE_DOMAIN (TREE_TYPE (sub));
3264 if (type_domain && TYPE_MIN_VALUE (type_domain))
3265 min_val = TYPE_MIN_VALUE (type_domain);
3266 return build4 (ARRAY_REF, type, sub, min_val, NULL_TREE, NULL_TREE);
3269 return NULL_TREE;
3272 /* Subroutine of gimplify_modify_expr to do simplifications of MODIFY_EXPRs
3273 based on the code of the RHS. We loop for as long as something changes. */
3275 static enum gimplify_status
3276 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p, tree *pre_p,
3277 tree *post_p, bool want_value)
3279 enum gimplify_status ret = GS_OK;
3281 while (ret != GS_UNHANDLED)
3282 switch (TREE_CODE (*from_p))
3284 case INDIRECT_REF:
3286 /* If we have code like
3288 *(const A*)(A*)&x
3290 where the type of "x" is a (possibly cv-qualified variant
3291 of "A"), treat the entire expression as identical to "x".
3292 This kind of code arises in C++ when an object is bound
3293 to a const reference, and if "x" is a TARGET_EXPR we want
3294 to take advantage of the optimization below. */
3295 tree t = fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
3296 if (t)
3298 *from_p = t;
3299 ret = GS_OK;
3301 else
3302 ret = GS_UNHANDLED;
3303 break;
3306 case TARGET_EXPR:
3308 /* If we are initializing something from a TARGET_EXPR, strip the
3309 TARGET_EXPR and initialize it directly, if possible. This can't
3310 be done if the initializer is void, since that implies that the
3311 temporary is set in some non-trivial way.
3313 ??? What about code that pulls out the temp and uses it
3314 elsewhere? I think that such code never uses the TARGET_EXPR as
3315 an initializer. If I'm wrong, we'll die because the temp won't
3316 have any RTL. In that case, I guess we'll need to replace
3317 references somehow. */
3318 tree init = TARGET_EXPR_INITIAL (*from_p);
3320 if (!VOID_TYPE_P (TREE_TYPE (init)))
3322 *from_p = init;
3323 ret = GS_OK;
3325 else
3326 ret = GS_UNHANDLED;
3328 break;
3330 case COMPOUND_EXPR:
3331 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
3332 caught. */
3333 gimplify_compound_expr (from_p, pre_p, true);
3334 ret = GS_OK;
3335 break;
3337 case CONSTRUCTOR:
3338 /* If we're initializing from a CONSTRUCTOR, break this into
3339 individual MODIFY_EXPRs. */
3340 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value);
3342 case COND_EXPR:
3343 /* If we're assigning to a non-register type, push the assignment
3344 down into the branches. This is mandatory for ADDRESSABLE types,
3345 since we cannot generate temporaries for such, but it saves a
3346 copy in other cases as well. */
3347 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
3349 /* This code should mirror the code in gimplify_cond_expr. */
3350 enum tree_code code = TREE_CODE (*expr_p);
3351 tree cond = *from_p;
3352 tree result = *to_p;
3354 ret = gimplify_expr (&result, pre_p, post_p,
3355 is_gimple_min_lval, fb_lvalue);
3356 if (ret != GS_ERROR)
3357 ret = GS_OK;
3359 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
3360 TREE_OPERAND (cond, 1)
3361 = build2 (code, void_type_node, result,
3362 TREE_OPERAND (cond, 1));
3363 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
3364 TREE_OPERAND (cond, 2)
3365 = build2 (code, void_type_node, unshare_expr (result),
3366 TREE_OPERAND (cond, 2));
3368 TREE_TYPE (cond) = void_type_node;
3369 recalculate_side_effects (cond);
3371 if (want_value)
3373 gimplify_and_add (cond, pre_p);
3374 *expr_p = unshare_expr (result);
3376 else
3377 *expr_p = cond;
3378 return ret;
3380 else
3381 ret = GS_UNHANDLED;
3382 break;
3384 case CALL_EXPR:
3385 /* For calls that return in memory, give *to_p as the CALL_EXPR's
3386 return slot so that we don't generate a temporary. */
3387 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
3388 && aggregate_value_p (*from_p, *from_p))
3390 bool use_target;
3392 if (!(rhs_predicate_for (*to_p))(*from_p))
3393 /* If we need a temporary, *to_p isn't accurate. */
3394 use_target = false;
3395 else if (TREE_CODE (*to_p) == RESULT_DECL
3396 && DECL_NAME (*to_p) == NULL_TREE
3397 && needs_to_live_in_memory (*to_p))
3398 /* It's OK to use the return slot directly unless it's an NRV. */
3399 use_target = true;
3400 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
3401 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
3402 /* Don't force regs into memory. */
3403 use_target = false;
3404 else if (TREE_CODE (*to_p) == VAR_DECL
3405 && DECL_GIMPLE_FORMAL_TEMP_P (*to_p))
3406 /* Don't use the original target if it's a formal temp; we
3407 don't want to take their addresses. */
3408 use_target = false;
3409 else if (TREE_CODE (*expr_p) == INIT_EXPR)
3410 /* It's OK to use the target directly if it's being
3411 initialized. */
3412 use_target = true;
3413 else if (!is_gimple_non_addressable (*to_p))
3414 /* Don't use the original target if it's already addressable;
3415 if its address escapes, and the called function uses the
3416 NRV optimization, a conforming program could see *to_p
3417 change before the called function returns; see c++/19317.
3418 When optimizing, the return_slot pass marks more functions
3419 as safe after we have escape info. */
3420 use_target = false;
3421 else
3422 use_target = true;
3424 if (use_target)
3426 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
3427 lang_hooks.mark_addressable (*to_p);
3431 ret = GS_UNHANDLED;
3432 break;
3434 /* If we're initializing from a container, push the initialization
3435 inside it. */
3436 case CLEANUP_POINT_EXPR:
3437 case BIND_EXPR:
3438 case STATEMENT_LIST:
3440 tree wrap = *from_p;
3441 tree t;
3443 ret = gimplify_expr (to_p, pre_p, post_p,
3444 is_gimple_min_lval, fb_lvalue);
3445 if (ret != GS_ERROR)
3446 ret = GS_OK;
3448 t = voidify_wrapper_expr (wrap, *expr_p);
3449 gcc_assert (t == *expr_p);
3451 if (want_value)
3453 gimplify_and_add (wrap, pre_p);
3454 *expr_p = unshare_expr (*to_p);
3456 else
3457 *expr_p = wrap;
3458 return GS_OK;
3461 default:
3462 ret = GS_UNHANDLED;
3463 break;
3466 return ret;
3469 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
3470 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
3471 DECL_GIMPLE_REG_P set. */
3473 static enum gimplify_status
3474 gimplify_modify_expr_complex_part (tree *expr_p, tree *pre_p, bool want_value)
3476 enum tree_code code, ocode;
3477 tree lhs, rhs, new_rhs, other, realpart, imagpart;
3479 lhs = GENERIC_TREE_OPERAND (*expr_p, 0);
3480 rhs = GENERIC_TREE_OPERAND (*expr_p, 1);
3481 code = TREE_CODE (lhs);
3482 lhs = TREE_OPERAND (lhs, 0);
3484 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
3485 other = build1 (ocode, TREE_TYPE (rhs), lhs);
3486 other = get_formal_tmp_var (other, pre_p);
3488 realpart = code == REALPART_EXPR ? rhs : other;
3489 imagpart = code == REALPART_EXPR ? other : rhs;
3491 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
3492 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
3493 else
3494 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
3496 GENERIC_TREE_OPERAND (*expr_p, 0) = lhs;
3497 GENERIC_TREE_OPERAND (*expr_p, 1) = new_rhs;
3499 if (want_value)
3501 append_to_statement_list (*expr_p, pre_p);
3502 *expr_p = rhs;
3505 return GS_ALL_DONE;
3509 /* Destructively convert the TREE pointer in TP into a gimple tuple if
3510 appropriate. */
3512 static void
3513 tree_to_gimple_tuple (tree *tp)
3516 switch (TREE_CODE (*tp))
3518 case GIMPLE_MODIFY_STMT:
3519 return;
3520 case MODIFY_EXPR:
3522 struct gimple_stmt *gs;
3523 tree lhs = TREE_OPERAND (*tp, 0);
3524 bool def_stmt_self_p = false;
3526 if (TREE_CODE (lhs) == SSA_NAME)
3528 if (SSA_NAME_DEF_STMT (lhs) == *tp)
3529 def_stmt_self_p = true;
3532 gs = &make_node (GIMPLE_MODIFY_STMT)->gstmt;
3533 gs->base = (*tp)->base;
3534 /* The set to base above overwrites the CODE. */
3535 TREE_SET_CODE ((tree) gs, GIMPLE_MODIFY_STMT);
3537 gs->locus = EXPR_LOCUS (*tp);
3538 gs->operands[0] = TREE_OPERAND (*tp, 0);
3539 gs->operands[1] = TREE_OPERAND (*tp, 1);
3540 gs->block = TREE_BLOCK (*tp);
3541 *tp = (tree)gs;
3543 /* If we re-gimplify a set to an SSA_NAME, we must change the
3544 SSA name's DEF_STMT link. */
3545 if (def_stmt_self_p)
3546 SSA_NAME_DEF_STMT (GIMPLE_STMT_OPERAND (*tp, 0)) = *tp;
3548 return;
3550 default:
3551 break;
3555 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
3557 modify_expr
3558 : varname '=' rhs
3559 | '*' ID '=' rhs
3561 PRE_P points to the list where side effects that must happen before
3562 *EXPR_P should be stored.
3564 POST_P points to the list where side effects that must happen after
3565 *EXPR_P should be stored.
3567 WANT_VALUE is nonzero iff we want to use the value of this expression
3568 in another expression. */
3570 static enum gimplify_status
3571 gimplify_modify_expr (tree *expr_p, tree *pre_p, tree *post_p, bool want_value)
3573 tree *from_p = &GENERIC_TREE_OPERAND (*expr_p, 1);
3574 tree *to_p = &GENERIC_TREE_OPERAND (*expr_p, 0);
3575 enum gimplify_status ret = GS_UNHANDLED;
3577 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
3578 || TREE_CODE (*expr_p) == GIMPLE_MODIFY_STMT
3579 || TREE_CODE (*expr_p) == INIT_EXPR);
3581 /* For zero sized types only gimplify the left hand side and right hand side
3582 as statements and throw away the assignment. */
3583 if (zero_sized_type (TREE_TYPE (*from_p)))
3585 gimplify_stmt (from_p);
3586 gimplify_stmt (to_p);
3587 append_to_statement_list (*from_p, pre_p);
3588 append_to_statement_list (*to_p, pre_p);
3589 *expr_p = NULL_TREE;
3590 return GS_ALL_DONE;
3593 /* See if any simplifications can be done based on what the RHS is. */
3594 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
3595 want_value);
3596 if (ret != GS_UNHANDLED)
3597 return ret;
3599 /* If the value being copied is of variable width, compute the length
3600 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
3601 before gimplifying any of the operands so that we can resolve any
3602 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
3603 the size of the expression to be copied, not of the destination, so
3604 that is what we must here. */
3605 maybe_with_size_expr (from_p);
3607 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3608 if (ret == GS_ERROR)
3609 return ret;
3611 ret = gimplify_expr (from_p, pre_p, post_p,
3612 rhs_predicate_for (*to_p), fb_rvalue);
3613 if (ret == GS_ERROR)
3614 return ret;
3616 /* Now see if the above changed *from_p to something we handle specially. */
3617 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
3618 want_value);
3619 if (ret != GS_UNHANDLED)
3620 return ret;
3622 /* If we've got a variable sized assignment between two lvalues (i.e. does
3623 not involve a call), then we can make things a bit more straightforward
3624 by converting the assignment to memcpy or memset. */
3625 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
3627 tree from = TREE_OPERAND (*from_p, 0);
3628 tree size = TREE_OPERAND (*from_p, 1);
3630 if (TREE_CODE (from) == CONSTRUCTOR)
3631 return gimplify_modify_expr_to_memset (expr_p, size, want_value);
3632 if (is_gimple_addressable (from))
3634 *from_p = from;
3635 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value);
3639 /* Transform partial stores to non-addressable complex variables into
3640 total stores. This allows us to use real instead of virtual operands
3641 for these variables, which improves optimization. */
3642 if ((TREE_CODE (*to_p) == REALPART_EXPR
3643 || TREE_CODE (*to_p) == IMAGPART_EXPR)
3644 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
3645 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
3647 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
3649 /* If we've somehow already got an SSA_NAME on the LHS, then
3650 we're probably modified it twice. Not good. */
3651 gcc_assert (TREE_CODE (*to_p) != SSA_NAME);
3652 *to_p = make_ssa_name (*to_p, *expr_p);
3655 if (want_value)
3657 tree_to_gimple_tuple (expr_p);
3659 append_to_statement_list (*expr_p, pre_p);
3660 *expr_p = *to_p;
3661 return GS_OK;
3664 return GS_ALL_DONE;
3667 /* Gimplify a comparison between two variable-sized objects. Do this
3668 with a call to BUILT_IN_MEMCMP. */
3670 static enum gimplify_status
3671 gimplify_variable_sized_compare (tree *expr_p)
3673 tree op0 = TREE_OPERAND (*expr_p, 0);
3674 tree op1 = TREE_OPERAND (*expr_p, 1);
3675 tree args, t, dest;
3677 t = TYPE_SIZE_UNIT (TREE_TYPE (op0));
3678 t = unshare_expr (t);
3679 t = SUBSTITUTE_PLACEHOLDER_IN_EXPR (t, op0);
3680 args = tree_cons (NULL, t, NULL);
3681 t = build_fold_addr_expr (op1);
3682 args = tree_cons (NULL, t, args);
3683 dest = build_fold_addr_expr (op0);
3684 args = tree_cons (NULL, dest, args);
3685 t = implicit_built_in_decls[BUILT_IN_MEMCMP];
3686 t = build_function_call_expr (t, args);
3687 *expr_p
3688 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
3690 return GS_OK;
3693 /* Gimplify a comparison between two aggregate objects of integral scalar
3694 mode as a comparison between the bitwise equivalent scalar values. */
3696 static enum gimplify_status
3697 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
3699 tree op0 = TREE_OPERAND (*expr_p, 0);
3700 tree op1 = TREE_OPERAND (*expr_p, 1);
3702 tree type = TREE_TYPE (op0);
3703 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
3705 op0 = fold_build1 (VIEW_CONVERT_EXPR, scalar_type, op0);
3706 op1 = fold_build1 (VIEW_CONVERT_EXPR, scalar_type, op1);
3708 *expr_p
3709 = fold_build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
3711 return GS_OK;
3714 /* Gimplify TRUTH_ANDIF_EXPR and TRUTH_ORIF_EXPR expressions. EXPR_P
3715 points to the expression to gimplify.
3717 Expressions of the form 'a && b' are gimplified to:
3719 a && b ? true : false
3721 gimplify_cond_expr will do the rest.
3723 PRE_P points to the list where side effects that must happen before
3724 *EXPR_P should be stored. */
3726 static enum gimplify_status
3727 gimplify_boolean_expr (tree *expr_p)
3729 /* Preserve the original type of the expression. */
3730 tree type = TREE_TYPE (*expr_p);
3732 *expr_p = build3 (COND_EXPR, type, *expr_p,
3733 fold_convert (type, boolean_true_node),
3734 fold_convert (type, boolean_false_node));
3736 return GS_OK;
3739 /* Gimplifies an expression sequence. This function gimplifies each
3740 expression and re-writes the original expression with the last
3741 expression of the sequence in GIMPLE form.
3743 PRE_P points to the list where the side effects for all the
3744 expressions in the sequence will be emitted.
3746 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
3747 /* ??? Should rearrange to share the pre-queue with all the indirect
3748 invocations of gimplify_expr. Would probably save on creations
3749 of statement_list nodes. */
3751 static enum gimplify_status
3752 gimplify_compound_expr (tree *expr_p, tree *pre_p, bool want_value)
3754 tree t = *expr_p;
3758 tree *sub_p = &TREE_OPERAND (t, 0);
3760 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
3761 gimplify_compound_expr (sub_p, pre_p, false);
3762 else
3763 gimplify_stmt (sub_p);
3764 append_to_statement_list (*sub_p, pre_p);
3766 t = TREE_OPERAND (t, 1);
3768 while (TREE_CODE (t) == COMPOUND_EXPR);
3770 *expr_p = t;
3771 if (want_value)
3772 return GS_OK;
3773 else
3775 gimplify_stmt (expr_p);
3776 return GS_ALL_DONE;
3780 /* Gimplifies a statement list. These may be created either by an
3781 enlightened front-end, or by shortcut_cond_expr. */
3783 static enum gimplify_status
3784 gimplify_statement_list (tree *expr_p, tree *pre_p)
3786 tree temp = voidify_wrapper_expr (*expr_p, NULL);
3788 tree_stmt_iterator i = tsi_start (*expr_p);
3790 while (!tsi_end_p (i))
3792 tree t;
3794 gimplify_stmt (tsi_stmt_ptr (i));
3796 t = tsi_stmt (i);
3797 if (t == NULL)
3798 tsi_delink (&i);
3799 else if (TREE_CODE (t) == STATEMENT_LIST)
3801 tsi_link_before (&i, t, TSI_SAME_STMT);
3802 tsi_delink (&i);
3804 else
3805 tsi_next (&i);
3808 if (temp)
3810 append_to_statement_list (*expr_p, pre_p);
3811 *expr_p = temp;
3812 return GS_OK;
3815 return GS_ALL_DONE;
3818 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
3819 gimplify. After gimplification, EXPR_P will point to a new temporary
3820 that holds the original value of the SAVE_EXPR node.
3822 PRE_P points to the list where side effects that must happen before
3823 *EXPR_P should be stored. */
3825 static enum gimplify_status
3826 gimplify_save_expr (tree *expr_p, tree *pre_p, tree *post_p)
3828 enum gimplify_status ret = GS_ALL_DONE;
3829 tree val;
3831 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
3832 val = TREE_OPERAND (*expr_p, 0);
3834 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
3835 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
3837 /* The operand may be a void-valued expression such as SAVE_EXPRs
3838 generated by the Java frontend for class initialization. It is
3839 being executed only for its side-effects. */
3840 if (TREE_TYPE (val) == void_type_node)
3842 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3843 is_gimple_stmt, fb_none);
3844 append_to_statement_list (TREE_OPERAND (*expr_p, 0), pre_p);
3845 val = NULL;
3847 else
3848 val = get_initialized_tmp_var (val, pre_p, post_p);
3850 TREE_OPERAND (*expr_p, 0) = val;
3851 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
3854 *expr_p = val;
3856 return ret;
3859 /* Re-write the ADDR_EXPR node pointed to by EXPR_P
3861 unary_expr
3862 : ...
3863 | '&' varname
3866 PRE_P points to the list where side effects that must happen before
3867 *EXPR_P should be stored.
3869 POST_P points to the list where side effects that must happen after
3870 *EXPR_P should be stored. */
3872 static enum gimplify_status
3873 gimplify_addr_expr (tree *expr_p, tree *pre_p, tree *post_p)
3875 tree expr = *expr_p;
3876 tree op0 = TREE_OPERAND (expr, 0);
3877 enum gimplify_status ret;
3879 switch (TREE_CODE (op0))
3881 case INDIRECT_REF:
3882 case MISALIGNED_INDIRECT_REF:
3883 do_indirect_ref:
3884 /* Check if we are dealing with an expression of the form '&*ptr'.
3885 While the front end folds away '&*ptr' into 'ptr', these
3886 expressions may be generated internally by the compiler (e.g.,
3887 builtins like __builtin_va_end). */
3888 /* Caution: the silent array decomposition semantics we allow for
3889 ADDR_EXPR means we can't always discard the pair. */
3890 /* Gimplification of the ADDR_EXPR operand may drop
3891 cv-qualification conversions, so make sure we add them if
3892 needed. */
3894 tree op00 = TREE_OPERAND (op0, 0);
3895 tree t_expr = TREE_TYPE (expr);
3896 tree t_op00 = TREE_TYPE (op00);
3898 if (!lang_hooks.types_compatible_p (t_expr, t_op00))
3900 #ifdef ENABLE_CHECKING
3901 tree t_op0 = TREE_TYPE (op0);
3902 gcc_assert (POINTER_TYPE_P (t_expr)
3903 && cpt_same_type (TREE_CODE (t_op0) == ARRAY_TYPE
3904 ? TREE_TYPE (t_op0) : t_op0,
3905 TREE_TYPE (t_expr))
3906 && POINTER_TYPE_P (t_op00)
3907 && cpt_same_type (t_op0, TREE_TYPE (t_op00)));
3908 #endif
3909 op00 = fold_convert (TREE_TYPE (expr), op00);
3911 *expr_p = op00;
3912 ret = GS_OK;
3914 break;
3916 case VIEW_CONVERT_EXPR:
3917 /* Take the address of our operand and then convert it to the type of
3918 this ADDR_EXPR.
3920 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
3921 all clear. The impact of this transformation is even less clear. */
3923 /* If the operand is a useless conversion, look through it. Doing so
3924 guarantees that the ADDR_EXPR and its operand will remain of the
3925 same type. */
3926 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
3927 op0 = TREE_OPERAND (op0, 0);
3929 *expr_p = fold_convert (TREE_TYPE (expr),
3930 build_fold_addr_expr (TREE_OPERAND (op0, 0)));
3931 ret = GS_OK;
3932 break;
3934 default:
3935 /* We use fb_either here because the C frontend sometimes takes
3936 the address of a call that returns a struct; see
3937 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
3938 the implied temporary explicit. */
3939 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
3940 is_gimple_addressable, fb_either);
3941 if (ret != GS_ERROR)
3943 op0 = TREE_OPERAND (expr, 0);
3945 /* For various reasons, the gimplification of the expression
3946 may have made a new INDIRECT_REF. */
3947 if (TREE_CODE (op0) == INDIRECT_REF)
3948 goto do_indirect_ref;
3950 /* Make sure TREE_INVARIANT, TREE_CONSTANT, and TREE_SIDE_EFFECTS
3951 is set properly. */
3952 recompute_tree_invariant_for_addr_expr (expr);
3954 /* Mark the RHS addressable. */
3955 lang_hooks.mark_addressable (TREE_OPERAND (expr, 0));
3957 break;
3960 return ret;
3963 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
3964 value; output operands should be a gimple lvalue. */
3966 static enum gimplify_status
3967 gimplify_asm_expr (tree *expr_p, tree *pre_p, tree *post_p)
3969 tree expr = *expr_p;
3970 int noutputs = list_length (ASM_OUTPUTS (expr));
3971 const char **oconstraints
3972 = (const char **) alloca ((noutputs) * sizeof (const char *));
3973 int i;
3974 tree link;
3975 const char *constraint;
3976 bool allows_mem, allows_reg, is_inout;
3977 enum gimplify_status ret, tret;
3979 ret = GS_ALL_DONE;
3980 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = TREE_CHAIN (link))
3982 size_t constraint_len;
3983 oconstraints[i] = constraint
3984 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
3985 constraint_len = strlen (constraint);
3986 if (constraint_len == 0)
3987 continue;
3989 parse_output_constraint (&constraint, i, 0, 0,
3990 &allows_mem, &allows_reg, &is_inout);
3992 if (!allows_reg && allows_mem)
3993 lang_hooks.mark_addressable (TREE_VALUE (link));
3995 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
3996 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
3997 fb_lvalue | fb_mayfail);
3998 if (tret == GS_ERROR)
4000 error ("invalid lvalue in asm output %d", i);
4001 ret = tret;
4004 if (is_inout)
4006 /* An input/output operand. To give the optimizers more
4007 flexibility, split it into separate input and output
4008 operands. */
4009 tree input;
4010 char buf[10];
4012 /* Turn the in/out constraint into an output constraint. */
4013 char *p = xstrdup (constraint);
4014 p[0] = '=';
4015 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
4017 /* And add a matching input constraint. */
4018 if (allows_reg)
4020 sprintf (buf, "%d", i);
4022 /* If there are multiple alternatives in the constraint,
4023 handle each of them individually. Those that allow register
4024 will be replaced with operand number, the others will stay
4025 unchanged. */
4026 if (strchr (p, ',') != NULL)
4028 size_t len = 0, buflen = strlen (buf);
4029 char *beg, *end, *str, *dst;
4031 for (beg = p + 1;;)
4033 end = strchr (beg, ',');
4034 if (end == NULL)
4035 end = strchr (beg, '\0');
4036 if ((size_t) (end - beg) < buflen)
4037 len += buflen + 1;
4038 else
4039 len += end - beg + 1;
4040 if (*end)
4041 beg = end + 1;
4042 else
4043 break;
4046 str = (char *) alloca (len);
4047 for (beg = p + 1, dst = str;;)
4049 const char *tem;
4050 bool mem_p, reg_p, inout_p;
4052 end = strchr (beg, ',');
4053 if (end)
4054 *end = '\0';
4055 beg[-1] = '=';
4056 tem = beg - 1;
4057 parse_output_constraint (&tem, i, 0, 0,
4058 &mem_p, &reg_p, &inout_p);
4059 if (dst != str)
4060 *dst++ = ',';
4061 if (reg_p)
4063 memcpy (dst, buf, buflen);
4064 dst += buflen;
4066 else
4068 if (end)
4069 len = end - beg;
4070 else
4071 len = strlen (beg);
4072 memcpy (dst, beg, len);
4073 dst += len;
4075 if (end)
4076 beg = end + 1;
4077 else
4078 break;
4080 *dst = '\0';
4081 input = build_string (dst - str, str);
4083 else
4084 input = build_string (strlen (buf), buf);
4086 else
4087 input = build_string (constraint_len - 1, constraint + 1);
4089 free (p);
4091 input = build_tree_list (build_tree_list (NULL_TREE, input),
4092 unshare_expr (TREE_VALUE (link)));
4093 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
4097 for (link = ASM_INPUTS (expr); link; ++i, link = TREE_CHAIN (link))
4099 constraint
4100 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
4101 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
4102 oconstraints, &allows_mem, &allows_reg);
4104 /* If the operand is a memory input, it should be an lvalue. */
4105 if (!allows_reg && allows_mem)
4107 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
4108 is_gimple_lvalue, fb_lvalue | fb_mayfail);
4109 lang_hooks.mark_addressable (TREE_VALUE (link));
4110 if (tret == GS_ERROR)
4112 error ("memory input %d is not directly addressable", i);
4113 ret = tret;
4116 else
4118 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
4119 is_gimple_asm_val, fb_rvalue);
4120 if (tret == GS_ERROR)
4121 ret = tret;
4125 return ret;
4128 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
4129 WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
4130 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
4131 return to this function.
4133 FIXME should we complexify the prequeue handling instead? Or use flags
4134 for all the cleanups and let the optimizer tighten them up? The current
4135 code seems pretty fragile; it will break on a cleanup within any
4136 non-conditional nesting. But any such nesting would be broken, anyway;
4137 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
4138 and continues out of it. We can do that at the RTL level, though, so
4139 having an optimizer to tighten up try/finally regions would be a Good
4140 Thing. */
4142 static enum gimplify_status
4143 gimplify_cleanup_point_expr (tree *expr_p, tree *pre_p)
4145 tree_stmt_iterator iter;
4146 tree body;
4148 tree temp = voidify_wrapper_expr (*expr_p, NULL);
4150 /* We only care about the number of conditions between the innermost
4151 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
4152 any cleanups collected outside the CLEANUP_POINT_EXPR. */
4153 int old_conds = gimplify_ctxp->conditions;
4154 tree old_cleanups = gimplify_ctxp->conditional_cleanups;
4155 gimplify_ctxp->conditions = 0;
4156 gimplify_ctxp->conditional_cleanups = NULL_TREE;
4158 body = TREE_OPERAND (*expr_p, 0);
4159 gimplify_to_stmt_list (&body);
4161 gimplify_ctxp->conditions = old_conds;
4162 gimplify_ctxp->conditional_cleanups = old_cleanups;
4164 for (iter = tsi_start (body); !tsi_end_p (iter); )
4166 tree *wce_p = tsi_stmt_ptr (iter);
4167 tree wce = *wce_p;
4169 if (TREE_CODE (wce) == WITH_CLEANUP_EXPR)
4171 if (tsi_one_before_end_p (iter))
4173 tsi_link_before (&iter, TREE_OPERAND (wce, 0), TSI_SAME_STMT);
4174 tsi_delink (&iter);
4175 break;
4177 else
4179 tree sl, tfe;
4180 enum tree_code code;
4182 if (CLEANUP_EH_ONLY (wce))
4183 code = TRY_CATCH_EXPR;
4184 else
4185 code = TRY_FINALLY_EXPR;
4187 sl = tsi_split_statement_list_after (&iter);
4188 tfe = build2 (code, void_type_node, sl, NULL_TREE);
4189 append_to_statement_list (TREE_OPERAND (wce, 0),
4190 &TREE_OPERAND (tfe, 1));
4191 *wce_p = tfe;
4192 iter = tsi_start (sl);
4195 else
4196 tsi_next (&iter);
4199 if (temp)
4201 *expr_p = temp;
4202 append_to_statement_list (body, pre_p);
4203 return GS_OK;
4205 else
4207 *expr_p = body;
4208 return GS_ALL_DONE;
4212 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
4213 is the cleanup action required. */
4215 static void
4216 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, tree *pre_p)
4218 tree wce;
4220 /* Errors can result in improperly nested cleanups. Which results in
4221 confusion when trying to resolve the WITH_CLEANUP_EXPR. */
4222 if (errorcount || sorrycount)
4223 return;
4225 if (gimple_conditional_context ())
4227 /* If we're in a conditional context, this is more complex. We only
4228 want to run the cleanup if we actually ran the initialization that
4229 necessitates it, but we want to run it after the end of the
4230 conditional context. So we wrap the try/finally around the
4231 condition and use a flag to determine whether or not to actually
4232 run the destructor. Thus
4234 test ? f(A()) : 0
4236 becomes (approximately)
4238 flag = 0;
4239 try {
4240 if (test) { A::A(temp); flag = 1; val = f(temp); }
4241 else { val = 0; }
4242 } finally {
4243 if (flag) A::~A(temp);
4248 tree flag = create_tmp_var (boolean_type_node, "cleanup");
4249 tree ffalse = build2 (GIMPLE_MODIFY_STMT, void_type_node, flag,
4250 boolean_false_node);
4251 tree ftrue = build2 (GIMPLE_MODIFY_STMT, void_type_node, flag,
4252 boolean_true_node);
4253 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
4254 wce = build1 (WITH_CLEANUP_EXPR, void_type_node, cleanup);
4255 append_to_statement_list (ffalse, &gimplify_ctxp->conditional_cleanups);
4256 append_to_statement_list (wce, &gimplify_ctxp->conditional_cleanups);
4257 append_to_statement_list (ftrue, pre_p);
4259 /* Because of this manipulation, and the EH edges that jump
4260 threading cannot redirect, the temporary (VAR) will appear
4261 to be used uninitialized. Don't warn. */
4262 TREE_NO_WARNING (var) = 1;
4264 else
4266 wce = build1 (WITH_CLEANUP_EXPR, void_type_node, cleanup);
4267 CLEANUP_EH_ONLY (wce) = eh_only;
4268 append_to_statement_list (wce, pre_p);
4271 gimplify_stmt (&TREE_OPERAND (wce, 0));
4274 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
4276 static enum gimplify_status
4277 gimplify_target_expr (tree *expr_p, tree *pre_p, tree *post_p)
4279 tree targ = *expr_p;
4280 tree temp = TARGET_EXPR_SLOT (targ);
4281 tree init = TARGET_EXPR_INITIAL (targ);
4282 enum gimplify_status ret;
4284 if (init)
4286 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
4287 to the temps list. */
4288 gimple_add_tmp_var (temp);
4290 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
4291 expression is supposed to initialize the slot. */
4292 if (VOID_TYPE_P (TREE_TYPE (init)))
4293 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
4294 else
4296 init = build2 (INIT_EXPR, void_type_node, temp, init);
4297 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt,
4298 fb_none);
4300 if (ret == GS_ERROR)
4301 return GS_ERROR;
4302 append_to_statement_list (init, pre_p);
4304 /* If needed, push the cleanup for the temp. */
4305 if (TARGET_EXPR_CLEANUP (targ))
4307 gimplify_stmt (&TARGET_EXPR_CLEANUP (targ));
4308 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
4309 CLEANUP_EH_ONLY (targ), pre_p);
4312 /* Only expand this once. */
4313 TREE_OPERAND (targ, 3) = init;
4314 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
4316 else
4317 /* We should have expanded this before. */
4318 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
4320 *expr_p = temp;
4321 return GS_OK;
4324 /* Gimplification of expression trees. */
4326 /* Gimplify an expression which appears at statement context; usually, this
4327 means replacing it with a suitably gimple STATEMENT_LIST. */
4329 void
4330 gimplify_stmt (tree *stmt_p)
4332 gimplify_expr (stmt_p, NULL, NULL, is_gimple_stmt, fb_none);
4335 /* Similarly, but force the result to be a STATEMENT_LIST. */
4337 void
4338 gimplify_to_stmt_list (tree *stmt_p)
4340 gimplify_stmt (stmt_p);
4341 if (!*stmt_p)
4342 *stmt_p = alloc_stmt_list ();
4343 else if (TREE_CODE (*stmt_p) != STATEMENT_LIST)
4345 tree t = *stmt_p;
4346 *stmt_p = alloc_stmt_list ();
4347 append_to_statement_list (t, stmt_p);
4352 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
4353 to CTX. If entries already exist, force them to be some flavor of private.
4354 If there is no enclosing parallel, do nothing. */
4356 void
4357 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
4359 splay_tree_node n;
4361 if (decl == NULL || !DECL_P (decl))
4362 return;
4366 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
4367 if (n != NULL)
4369 if (n->value & GOVD_SHARED)
4370 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
4371 else
4372 return;
4374 else if (ctx->is_parallel)
4375 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
4377 ctx = ctx->outer_context;
4379 while (ctx);
4382 /* Similarly for each of the type sizes of TYPE. */
4384 static void
4385 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
4387 if (type == NULL || type == error_mark_node)
4388 return;
4389 type = TYPE_MAIN_VARIANT (type);
4391 if (pointer_set_insert (ctx->privatized_types, type))
4392 return;
4394 switch (TREE_CODE (type))
4396 case INTEGER_TYPE:
4397 case ENUMERAL_TYPE:
4398 case BOOLEAN_TYPE:
4399 case REAL_TYPE:
4400 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
4401 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
4402 break;
4404 case ARRAY_TYPE:
4405 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
4406 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
4407 break;
4409 case RECORD_TYPE:
4410 case UNION_TYPE:
4411 case QUAL_UNION_TYPE:
4413 tree field;
4414 for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
4415 if (TREE_CODE (field) == FIELD_DECL)
4417 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
4418 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
4421 break;
4423 case POINTER_TYPE:
4424 case REFERENCE_TYPE:
4425 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
4426 break;
4428 default:
4429 break;
4432 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
4433 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
4434 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
4437 /* Add an entry for DECL in the OpenMP context CTX with FLAGS. */
4439 static void
4440 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
4442 splay_tree_node n;
4443 unsigned int nflags;
4444 tree t;
4446 if (decl == error_mark_node || TREE_TYPE (decl) == error_mark_node)
4447 return;
4449 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
4450 there are constructors involved somewhere. */
4451 if (TREE_ADDRESSABLE (TREE_TYPE (decl))
4452 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
4453 flags |= GOVD_SEEN;
4455 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
4456 if (n != NULL)
4458 /* We shouldn't be re-adding the decl with the same data
4459 sharing class. */
4460 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
4461 /* The only combination of data sharing classes we should see is
4462 FIRSTPRIVATE and LASTPRIVATE. */
4463 nflags = n->value | flags;
4464 gcc_assert ((nflags & GOVD_DATA_SHARE_CLASS)
4465 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE));
4466 n->value = nflags;
4467 return;
4470 /* When adding a variable-sized variable, we have to handle all sorts
4471 of additional bits of data: the pointer replacement variable, and
4472 the parameters of the type. */
4473 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
4475 /* Add the pointer replacement variable as PRIVATE if the variable
4476 replacement is private, else FIRSTPRIVATE since we'll need the
4477 address of the original variable either for SHARED, or for the
4478 copy into or out of the context. */
4479 if (!(flags & GOVD_LOCAL))
4481 nflags = flags & GOVD_PRIVATE ? GOVD_PRIVATE : GOVD_FIRSTPRIVATE;
4482 nflags |= flags & GOVD_SEEN;
4483 t = DECL_VALUE_EXPR (decl);
4484 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
4485 t = TREE_OPERAND (t, 0);
4486 gcc_assert (DECL_P (t));
4487 omp_add_variable (ctx, t, nflags);
4490 /* Add all of the variable and type parameters (which should have
4491 been gimplified to a formal temporary) as FIRSTPRIVATE. */
4492 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
4493 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
4494 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
4496 /* The variable-sized variable itself is never SHARED, only some form
4497 of PRIVATE. The sharing would take place via the pointer variable
4498 which we remapped above. */
4499 if (flags & GOVD_SHARED)
4500 flags = GOVD_PRIVATE | GOVD_DEBUG_PRIVATE
4501 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
4503 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
4504 alloca statement we generate for the variable, so make sure it
4505 is available. This isn't automatically needed for the SHARED
4506 case, since we won't be allocating local storage then. */
4507 else
4508 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
4510 else if (lang_hooks.decls.omp_privatize_by_reference (decl))
4512 gcc_assert ((flags & GOVD_LOCAL) == 0);
4513 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
4515 /* Similar to the direct variable sized case above, we'll need the
4516 size of references being privatized. */
4517 if ((flags & GOVD_SHARED) == 0)
4519 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
4520 if (TREE_CODE (t) != INTEGER_CST)
4521 omp_notice_variable (ctx, t, true);
4525 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
4528 /* Record the fact that DECL was used within the OpenMP context CTX.
4529 IN_CODE is true when real code uses DECL, and false when we should
4530 merely emit default(none) errors. Return true if DECL is going to
4531 be remapped and thus DECL shouldn't be gimplified into its
4532 DECL_VALUE_EXPR (if any). */
4534 static bool
4535 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
4537 splay_tree_node n;
4538 unsigned flags = in_code ? GOVD_SEEN : 0;
4539 bool ret = false, shared;
4541 if (decl == error_mark_node || TREE_TYPE (decl) == error_mark_node)
4542 return false;
4544 /* Threadprivate variables are predetermined. */
4545 if (is_global_var (decl))
4547 if (DECL_THREAD_LOCAL_P (decl))
4548 return false;
4550 if (DECL_HAS_VALUE_EXPR_P (decl))
4552 tree value = get_base_address (DECL_VALUE_EXPR (decl));
4554 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
4555 return false;
4559 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
4560 if (n == NULL)
4562 enum omp_clause_default_kind default_kind, kind;
4564 if (!ctx->is_parallel)
4565 goto do_outer;
4567 /* ??? Some compiler-generated variables (like SAVE_EXPRs) could be
4568 remapped firstprivate instead of shared. To some extent this is
4569 addressed in omp_firstprivatize_type_sizes, but not effectively. */
4570 default_kind = ctx->default_kind;
4571 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
4572 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
4573 default_kind = kind;
4575 switch (default_kind)
4577 case OMP_CLAUSE_DEFAULT_NONE:
4578 error ("%qs not specified in enclosing parallel",
4579 IDENTIFIER_POINTER (DECL_NAME (decl)));
4580 error ("%Henclosing parallel", &ctx->location);
4581 /* FALLTHRU */
4582 case OMP_CLAUSE_DEFAULT_SHARED:
4583 flags |= GOVD_SHARED;
4584 break;
4585 case OMP_CLAUSE_DEFAULT_PRIVATE:
4586 flags |= GOVD_PRIVATE;
4587 break;
4588 default:
4589 gcc_unreachable ();
4592 omp_add_variable (ctx, decl, flags);
4594 shared = (flags & GOVD_SHARED) != 0;
4595 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
4596 goto do_outer;
4599 shared = ((flags | n->value) & GOVD_SHARED) != 0;
4600 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
4602 /* If nothing changed, there's nothing left to do. */
4603 if ((n->value & flags) == flags)
4604 return ret;
4605 flags |= n->value;
4606 n->value = flags;
4608 do_outer:
4609 /* If the variable is private in the current context, then we don't
4610 need to propagate anything to an outer context. */
4611 if (flags & GOVD_PRIVATE)
4612 return ret;
4613 if (ctx->outer_context
4614 && omp_notice_variable (ctx->outer_context, decl, in_code))
4615 return true;
4616 return ret;
4619 /* Verify that DECL is private within CTX. If there's specific information
4620 to the contrary in the innermost scope, generate an error. */
4622 static bool
4623 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl)
4625 splay_tree_node n;
4627 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
4628 if (n != NULL)
4630 if (n->value & GOVD_SHARED)
4632 if (ctx == gimplify_omp_ctxp)
4634 error ("iteration variable %qs should be private",
4635 IDENTIFIER_POINTER (DECL_NAME (decl)));
4636 n->value = GOVD_PRIVATE;
4637 return true;
4639 else
4640 return false;
4642 else if ((n->value & GOVD_EXPLICIT) != 0
4643 && (ctx == gimplify_omp_ctxp
4644 || (ctx->is_combined_parallel
4645 && gimplify_omp_ctxp->outer_context == ctx)))
4647 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
4648 error ("iteration variable %qs should not be firstprivate",
4649 IDENTIFIER_POINTER (DECL_NAME (decl)));
4650 else if ((n->value & GOVD_REDUCTION) != 0)
4651 error ("iteration variable %qs should not be reduction",
4652 IDENTIFIER_POINTER (DECL_NAME (decl)));
4654 return true;
4657 if (ctx->is_parallel)
4658 return false;
4659 else if (ctx->outer_context)
4660 return omp_is_private (ctx->outer_context, decl);
4661 else
4662 return !is_global_var (decl);
4665 /* Scan the OpenMP clauses in *LIST_P, installing mappings into a new
4666 and previous omp contexts. */
4668 static void
4669 gimplify_scan_omp_clauses (tree *list_p, tree *pre_p, bool in_parallel,
4670 bool in_combined_parallel)
4672 struct gimplify_omp_ctx *ctx, *outer_ctx;
4673 tree c;
4675 ctx = new_omp_context (in_parallel, in_combined_parallel);
4676 outer_ctx = ctx->outer_context;
4678 while ((c = *list_p) != NULL)
4680 enum gimplify_status gs;
4681 bool remove = false;
4682 bool notice_outer = true;
4683 unsigned int flags;
4684 tree decl;
4686 switch (OMP_CLAUSE_CODE (c))
4688 case OMP_CLAUSE_PRIVATE:
4689 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
4690 notice_outer = false;
4691 goto do_add;
4692 case OMP_CLAUSE_SHARED:
4693 flags = GOVD_SHARED | GOVD_EXPLICIT;
4694 goto do_add;
4695 case OMP_CLAUSE_FIRSTPRIVATE:
4696 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
4697 goto do_add;
4698 case OMP_CLAUSE_LASTPRIVATE:
4699 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
4700 goto do_add;
4701 case OMP_CLAUSE_REDUCTION:
4702 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
4703 goto do_add;
4705 do_add:
4706 decl = OMP_CLAUSE_DECL (c);
4707 if (decl == error_mark_node || TREE_TYPE (decl) == error_mark_node)
4709 remove = true;
4710 break;
4712 /* Handle NRV results passed by reference. */
4713 if (TREE_CODE (decl) == INDIRECT_REF
4714 && TREE_CODE (TREE_OPERAND (decl, 0)) == RESULT_DECL
4715 && DECL_BY_REFERENCE (TREE_OPERAND (decl, 0)))
4716 OMP_CLAUSE_DECL (c) = decl = TREE_OPERAND (decl, 0);
4717 omp_add_variable (ctx, decl, flags);
4718 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
4719 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
4721 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
4722 GOVD_LOCAL | GOVD_SEEN);
4723 gimplify_omp_ctxp = ctx;
4724 push_gimplify_context ();
4725 gimplify_stmt (&OMP_CLAUSE_REDUCTION_INIT (c));
4726 pop_gimplify_context (OMP_CLAUSE_REDUCTION_INIT (c));
4727 push_gimplify_context ();
4728 gimplify_stmt (&OMP_CLAUSE_REDUCTION_MERGE (c));
4729 pop_gimplify_context (OMP_CLAUSE_REDUCTION_MERGE (c));
4730 gimplify_omp_ctxp = outer_ctx;
4732 if (notice_outer)
4733 goto do_notice;
4734 break;
4736 case OMP_CLAUSE_COPYIN:
4737 case OMP_CLAUSE_COPYPRIVATE:
4738 decl = OMP_CLAUSE_DECL (c);
4739 if (decl == error_mark_node || TREE_TYPE (decl) == error_mark_node)
4741 remove = true;
4742 break;
4744 /* Handle NRV results passed by reference. */
4745 if (TREE_CODE (decl) == INDIRECT_REF
4746 && TREE_CODE (TREE_OPERAND (decl, 0)) == RESULT_DECL
4747 && DECL_BY_REFERENCE (TREE_OPERAND (decl, 0)))
4748 OMP_CLAUSE_DECL (c) = decl = TREE_OPERAND (decl, 0);
4749 do_notice:
4750 if (outer_ctx)
4751 omp_notice_variable (outer_ctx, decl, true);
4752 break;
4754 case OMP_CLAUSE_IF:
4755 OMP_CLAUSE_OPERAND (c, 0)
4756 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
4757 /* Fall through. */
4759 case OMP_CLAUSE_SCHEDULE:
4760 case OMP_CLAUSE_NUM_THREADS:
4761 gs = gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
4762 is_gimple_val, fb_rvalue);
4763 if (gs == GS_ERROR)
4764 remove = true;
4765 break;
4767 case OMP_CLAUSE_NOWAIT:
4768 case OMP_CLAUSE_ORDERED:
4769 break;
4771 case OMP_CLAUSE_DEFAULT:
4772 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
4773 break;
4775 default:
4776 gcc_unreachable ();
4779 if (remove)
4780 *list_p = OMP_CLAUSE_CHAIN (c);
4781 else
4782 list_p = &OMP_CLAUSE_CHAIN (c);
4785 gimplify_omp_ctxp = ctx;
4788 /* For all variables that were not actually used within the context,
4789 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
4791 static int
4792 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
4794 tree *list_p = (tree *) data;
4795 tree decl = (tree) n->key;
4796 unsigned flags = n->value;
4797 enum omp_clause_code code;
4798 tree clause;
4799 bool private_debug;
4801 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
4802 return 0;
4803 if ((flags & GOVD_SEEN) == 0)
4804 return 0;
4805 if (flags & GOVD_DEBUG_PRIVATE)
4807 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_PRIVATE);
4808 private_debug = true;
4810 else
4811 private_debug
4812 = lang_hooks.decls.omp_private_debug_clause (decl,
4813 !!(flags & GOVD_SHARED));
4814 if (private_debug)
4815 code = OMP_CLAUSE_PRIVATE;
4816 else if (flags & GOVD_SHARED)
4818 if (is_global_var (decl))
4819 return 0;
4820 code = OMP_CLAUSE_SHARED;
4822 else if (flags & GOVD_PRIVATE)
4823 code = OMP_CLAUSE_PRIVATE;
4824 else if (flags & GOVD_FIRSTPRIVATE)
4825 code = OMP_CLAUSE_FIRSTPRIVATE;
4826 else
4827 gcc_unreachable ();
4829 clause = build_omp_clause (code);
4830 OMP_CLAUSE_DECL (clause) = decl;
4831 OMP_CLAUSE_CHAIN (clause) = *list_p;
4832 if (private_debug)
4833 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
4834 *list_p = clause;
4836 return 0;
4839 static void
4840 gimplify_adjust_omp_clauses (tree *list_p)
4842 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
4843 tree c, decl;
4845 while ((c = *list_p) != NULL)
4847 splay_tree_node n;
4848 bool remove = false;
4850 switch (OMP_CLAUSE_CODE (c))
4852 case OMP_CLAUSE_PRIVATE:
4853 case OMP_CLAUSE_SHARED:
4854 case OMP_CLAUSE_FIRSTPRIVATE:
4855 decl = OMP_CLAUSE_DECL (c);
4856 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
4857 remove = !(n->value & GOVD_SEEN);
4858 if (! remove)
4860 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
4861 if ((n->value & GOVD_DEBUG_PRIVATE)
4862 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
4864 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
4865 || ((n->value & GOVD_DATA_SHARE_CLASS)
4866 == GOVD_PRIVATE));
4867 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
4868 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
4871 break;
4873 case OMP_CLAUSE_LASTPRIVATE:
4874 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
4875 accurately reflect the presence of a FIRSTPRIVATE clause. */
4876 decl = OMP_CLAUSE_DECL (c);
4877 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
4878 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
4879 = (n->value & GOVD_FIRSTPRIVATE) != 0;
4880 break;
4882 case OMP_CLAUSE_REDUCTION:
4883 case OMP_CLAUSE_COPYIN:
4884 case OMP_CLAUSE_COPYPRIVATE:
4885 case OMP_CLAUSE_IF:
4886 case OMP_CLAUSE_NUM_THREADS:
4887 case OMP_CLAUSE_SCHEDULE:
4888 case OMP_CLAUSE_NOWAIT:
4889 case OMP_CLAUSE_ORDERED:
4890 case OMP_CLAUSE_DEFAULT:
4891 break;
4893 default:
4894 gcc_unreachable ();
4897 if (remove)
4898 *list_p = OMP_CLAUSE_CHAIN (c);
4899 else
4900 list_p = &OMP_CLAUSE_CHAIN (c);
4903 /* Add in any implicit data sharing. */
4904 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, list_p);
4906 gimplify_omp_ctxp = ctx->outer_context;
4907 delete_omp_context (ctx);
4910 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
4911 gimplification of the body, as well as scanning the body for used
4912 variables. We need to do this scan now, because variable-sized
4913 decls will be decomposed during gimplification. */
4915 static enum gimplify_status
4916 gimplify_omp_parallel (tree *expr_p, tree *pre_p)
4918 tree expr = *expr_p;
4920 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p, true,
4921 OMP_PARALLEL_COMBINED (expr));
4923 push_gimplify_context ();
4925 gimplify_stmt (&OMP_PARALLEL_BODY (expr));
4927 if (TREE_CODE (OMP_PARALLEL_BODY (expr)) == BIND_EXPR)
4928 pop_gimplify_context (OMP_PARALLEL_BODY (expr));
4929 else
4930 pop_gimplify_context (NULL_TREE);
4932 gimplify_adjust_omp_clauses (&OMP_PARALLEL_CLAUSES (expr));
4934 return GS_ALL_DONE;
4937 /* Gimplify the gross structure of an OMP_FOR statement. */
4939 static enum gimplify_status
4940 gimplify_omp_for (tree *expr_p, tree *pre_p)
4942 tree for_stmt, decl, t;
4943 enum gimplify_status ret = GS_OK;
4945 for_stmt = *expr_p;
4947 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, false, false);
4949 t = OMP_FOR_INIT (for_stmt);
4950 gcc_assert (TREE_CODE (t) == MODIFY_EXPR
4951 || TREE_CODE (t) == GIMPLE_MODIFY_STMT);
4952 decl = GENERIC_TREE_OPERAND (t, 0);
4953 gcc_assert (DECL_P (decl));
4954 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl)));
4956 /* Make sure the iteration variable is private. */
4957 if (omp_is_private (gimplify_omp_ctxp, decl))
4958 omp_notice_variable (gimplify_omp_ctxp, decl, true);
4959 else
4960 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
4962 ret |= gimplify_expr (&GENERIC_TREE_OPERAND (t, 1),
4963 &OMP_FOR_PRE_BODY (for_stmt),
4964 NULL, is_gimple_val, fb_rvalue);
4966 tree_to_gimple_tuple (&OMP_FOR_INIT (for_stmt));
4968 t = OMP_FOR_COND (for_stmt);
4969 gcc_assert (COMPARISON_CLASS_P (t));
4970 gcc_assert (GENERIC_TREE_OPERAND (t, 0) == decl);
4972 ret |= gimplify_expr (&GENERIC_TREE_OPERAND (t, 1),
4973 &OMP_FOR_PRE_BODY (for_stmt),
4974 NULL, is_gimple_val, fb_rvalue);
4976 tree_to_gimple_tuple (&OMP_FOR_INCR (for_stmt));
4977 t = OMP_FOR_INCR (for_stmt);
4978 switch (TREE_CODE (t))
4980 case PREINCREMENT_EXPR:
4981 case POSTINCREMENT_EXPR:
4982 t = build_int_cst (TREE_TYPE (decl), 1);
4983 goto build_modify;
4984 case PREDECREMENT_EXPR:
4985 case POSTDECREMENT_EXPR:
4986 t = build_int_cst (TREE_TYPE (decl), -1);
4987 goto build_modify;
4988 build_modify:
4989 t = build2 (PLUS_EXPR, TREE_TYPE (decl), decl, t);
4990 t = build2 (GIMPLE_MODIFY_STMT, void_type_node, decl, t);
4991 OMP_FOR_INCR (for_stmt) = t;
4992 break;
4994 case GIMPLE_MODIFY_STMT:
4995 gcc_assert (GIMPLE_STMT_OPERAND (t, 0) == decl);
4996 t = GIMPLE_STMT_OPERAND (t, 1);
4997 switch (TREE_CODE (t))
4999 case PLUS_EXPR:
5000 if (TREE_OPERAND (t, 1) == decl)
5002 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
5003 TREE_OPERAND (t, 0) = decl;
5004 break;
5006 case MINUS_EXPR:
5007 gcc_assert (TREE_OPERAND (t, 0) == decl);
5008 break;
5009 default:
5010 gcc_unreachable ();
5013 ret |= gimplify_expr (&TREE_OPERAND (t, 1), &OMP_FOR_PRE_BODY (for_stmt),
5014 NULL, is_gimple_val, fb_rvalue);
5015 break;
5017 default:
5018 gcc_unreachable ();
5021 gimplify_to_stmt_list (&OMP_FOR_BODY (for_stmt));
5022 gimplify_adjust_omp_clauses (&OMP_FOR_CLAUSES (for_stmt));
5024 return ret == GS_ALL_DONE ? GS_ALL_DONE : GS_ERROR;
5027 /* Gimplify the gross structure of other OpenMP worksharing constructs.
5028 In particular, OMP_SECTIONS and OMP_SINGLE. */
5030 static enum gimplify_status
5031 gimplify_omp_workshare (tree *expr_p, tree *pre_p)
5033 tree stmt = *expr_p;
5035 gimplify_scan_omp_clauses (&OMP_CLAUSES (stmt), pre_p, false, false);
5036 gimplify_to_stmt_list (&OMP_BODY (stmt));
5037 gimplify_adjust_omp_clauses (&OMP_CLAUSES (stmt));
5039 return GS_ALL_DONE;
5042 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
5043 stabilized the lhs of the atomic operation as *ADDR. Return true if
5044 EXPR is this stabilized form. */
5046 static bool
5047 goa_lhs_expr_p (tree expr, tree addr)
5049 /* Also include casts to other type variants. The C front end is fond
5050 of adding these for e.g. volatile variables. This is like
5051 STRIP_TYPE_NOPS but includes the main variant lookup. */
5052 while ((TREE_CODE (expr) == NOP_EXPR
5053 || TREE_CODE (expr) == CONVERT_EXPR
5054 || TREE_CODE (expr) == NON_LVALUE_EXPR)
5055 && TREE_OPERAND (expr, 0) != error_mark_node
5056 && (TYPE_MAIN_VARIANT (TREE_TYPE (expr))
5057 == TYPE_MAIN_VARIANT (TREE_TYPE (TREE_OPERAND (expr, 0)))))
5058 expr = TREE_OPERAND (expr, 0);
5060 if (TREE_CODE (expr) == INDIRECT_REF && TREE_OPERAND (expr, 0) == addr)
5061 return true;
5062 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
5063 return true;
5064 return false;
5067 /* A subroutine of gimplify_omp_atomic. Attempt to implement the atomic
5068 operation as a __sync_fetch_and_op builtin. INDEX is log2 of the
5069 size of the data type, and thus usable to find the index of the builtin
5070 decl. Returns GS_UNHANDLED if the expression is not of the proper form. */
5072 static enum gimplify_status
5073 gimplify_omp_atomic_fetch_op (tree *expr_p, tree addr, tree rhs, int index)
5075 enum built_in_function base;
5076 tree decl, args, itype;
5077 enum insn_code *optab;
5079 /* Check for one of the supported fetch-op operations. */
5080 switch (TREE_CODE (rhs))
5082 case PLUS_EXPR:
5083 base = BUILT_IN_FETCH_AND_ADD_N;
5084 optab = sync_add_optab;
5085 break;
5086 case MINUS_EXPR:
5087 base = BUILT_IN_FETCH_AND_SUB_N;
5088 optab = sync_add_optab;
5089 break;
5090 case BIT_AND_EXPR:
5091 base = BUILT_IN_FETCH_AND_AND_N;
5092 optab = sync_and_optab;
5093 break;
5094 case BIT_IOR_EXPR:
5095 base = BUILT_IN_FETCH_AND_OR_N;
5096 optab = sync_ior_optab;
5097 break;
5098 case BIT_XOR_EXPR:
5099 base = BUILT_IN_FETCH_AND_XOR_N;
5100 optab = sync_xor_optab;
5101 break;
5102 default:
5103 return GS_UNHANDLED;
5106 /* Make sure the expression is of the proper form. */
5107 if (goa_lhs_expr_p (TREE_OPERAND (rhs, 0), addr))
5108 rhs = TREE_OPERAND (rhs, 1);
5109 else if (commutative_tree_code (TREE_CODE (rhs))
5110 && goa_lhs_expr_p (TREE_OPERAND (rhs, 1), addr))
5111 rhs = TREE_OPERAND (rhs, 0);
5112 else
5113 return GS_UNHANDLED;
5115 decl = built_in_decls[base + index + 1];
5116 itype = TREE_TYPE (TREE_TYPE (decl));
5118 if (optab[TYPE_MODE (itype)] == CODE_FOR_nothing)
5119 return GS_UNHANDLED;
5121 args = tree_cons (NULL, fold_convert (itype, rhs), NULL);
5122 args = tree_cons (NULL, addr, args);
5123 *expr_p = build_function_call_expr (decl, args);
5124 return GS_OK;
5127 /* A subroutine of gimplify_omp_atomic_pipeline. Walk *EXPR_P and replace
5128 appearances of *LHS_ADDR with LHS_VAR. If an expression does not involve
5129 the lhs, evaluate it into a temporary. Return 1 if the lhs appeared as
5130 a subexpression, 0 if it did not, or -1 if an error was encountered. */
5132 static int
5133 goa_stabilize_expr (tree *expr_p, tree *pre_p, tree lhs_addr, tree lhs_var)
5135 tree expr = *expr_p;
5136 int saw_lhs;
5138 if (goa_lhs_expr_p (expr, lhs_addr))
5140 *expr_p = lhs_var;
5141 return 1;
5143 if (is_gimple_val (expr))
5144 return 0;
5146 saw_lhs = 0;
5147 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
5149 case tcc_binary:
5150 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
5151 lhs_addr, lhs_var);
5152 case tcc_unary:
5153 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
5154 lhs_addr, lhs_var);
5155 break;
5156 default:
5157 break;
5160 if (saw_lhs == 0)
5162 enum gimplify_status gs;
5163 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
5164 if (gs != GS_ALL_DONE)
5165 saw_lhs = -1;
5168 return saw_lhs;
5171 /* A subroutine of gimplify_omp_atomic. Implement the atomic operation as:
5173 oldval = *addr;
5174 repeat:
5175 newval = rhs; // with oldval replacing *addr in rhs
5176 oldval = __sync_val_compare_and_swap (addr, oldval, newval);
5177 if (oldval != newval)
5178 goto repeat;
5180 INDEX is log2 of the size of the data type, and thus usable to find the
5181 index of the builtin decl. */
5183 static enum gimplify_status
5184 gimplify_omp_atomic_pipeline (tree *expr_p, tree *pre_p, tree addr,
5185 tree rhs, int index)
5187 tree oldval, oldival, oldival2, newval, newival, label;
5188 tree type, itype, cmpxchg, args, x, iaddr;
5190 cmpxchg = built_in_decls[BUILT_IN_VAL_COMPARE_AND_SWAP_N + index + 1];
5191 type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
5192 itype = TREE_TYPE (TREE_TYPE (cmpxchg));
5194 if (sync_compare_and_swap[TYPE_MODE (itype)] == CODE_FOR_nothing)
5195 return GS_UNHANDLED;
5197 oldval = create_tmp_var (type, NULL);
5198 newval = create_tmp_var (type, NULL);
5200 /* Precompute as much of RHS as possible. In the same walk, replace
5201 occurrences of the lhs value with our temporary. */
5202 if (goa_stabilize_expr (&rhs, pre_p, addr, oldval) < 0)
5203 return GS_ERROR;
5205 x = build_fold_indirect_ref (addr);
5206 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldval, x);
5207 gimplify_and_add (x, pre_p);
5209 /* For floating-point values, we'll need to view-convert them to integers
5210 so that we can perform the atomic compare and swap. Simplify the
5211 following code by always setting up the "i"ntegral variables. */
5212 if (INTEGRAL_TYPE_P (type) || POINTER_TYPE_P (type))
5214 oldival = oldval;
5215 newival = newval;
5216 iaddr = addr;
5218 else
5220 oldival = create_tmp_var (itype, NULL);
5221 newival = create_tmp_var (itype, NULL);
5223 x = build1 (VIEW_CONVERT_EXPR, itype, oldval);
5224 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival, x);
5225 gimplify_and_add (x, pre_p);
5226 iaddr = fold_convert (build_pointer_type (itype), addr);
5229 oldival2 = create_tmp_var (itype, NULL);
5231 label = create_artificial_label ();
5232 x = build1 (LABEL_EXPR, void_type_node, label);
5233 gimplify_and_add (x, pre_p);
5235 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, newval, rhs);
5236 gimplify_and_add (x, pre_p);
5238 if (newval != newival)
5240 x = build1 (VIEW_CONVERT_EXPR, itype, newval);
5241 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, newival, x);
5242 gimplify_and_add (x, pre_p);
5245 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival2,
5246 fold_convert (itype, oldival));
5247 gimplify_and_add (x, pre_p);
5249 args = tree_cons (NULL, fold_convert (itype, newival), NULL);
5250 args = tree_cons (NULL, fold_convert (itype, oldival), args);
5251 args = tree_cons (NULL, iaddr, args);
5252 x = build_function_call_expr (cmpxchg, args);
5253 if (oldval == oldival)
5254 x = fold_convert (type, x);
5255 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival, x);
5256 gimplify_and_add (x, pre_p);
5258 /* For floating point, be prepared for the loop backedge. */
5259 if (oldval != oldival)
5261 x = build1 (VIEW_CONVERT_EXPR, type, oldival);
5262 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldval, x);
5263 gimplify_and_add (x, pre_p);
5266 /* Note that we always perform the comparison as an integer, even for
5267 floating point. This allows the atomic operation to properly
5268 succeed even with NaNs and -0.0. */
5269 x = build3 (COND_EXPR, void_type_node,
5270 build2 (NE_EXPR, boolean_type_node, oldival, oldival2),
5271 build1 (GOTO_EXPR, void_type_node, label), NULL);
5272 gimplify_and_add (x, pre_p);
5274 *expr_p = NULL;
5275 return GS_ALL_DONE;
5278 /* A subroutine of gimplify_omp_atomic. Implement the atomic operation as:
5280 GOMP_atomic_start ();
5281 *addr = rhs;
5282 GOMP_atomic_end ();
5284 The result is not globally atomic, but works so long as all parallel
5285 references are within #pragma omp atomic directives. According to
5286 responses received from omp@openmp.org, appears to be within spec.
5287 Which makes sense, since that's how several other compilers handle
5288 this situation as well. */
5290 static enum gimplify_status
5291 gimplify_omp_atomic_mutex (tree *expr_p, tree *pre_p, tree addr, tree rhs)
5293 tree t;
5295 t = built_in_decls[BUILT_IN_GOMP_ATOMIC_START];
5296 t = build_function_call_expr (t, NULL);
5297 gimplify_and_add (t, pre_p);
5299 t = build_fold_indirect_ref (addr);
5300 t = build2 (GIMPLE_MODIFY_STMT, void_type_node, t, rhs);
5301 gimplify_and_add (t, pre_p);
5303 t = built_in_decls[BUILT_IN_GOMP_ATOMIC_END];
5304 t = build_function_call_expr (t, NULL);
5305 gimplify_and_add (t, pre_p);
5307 *expr_p = NULL;
5308 return GS_ALL_DONE;
5311 /* Gimplify an OMP_ATOMIC statement. */
5313 static enum gimplify_status
5314 gimplify_omp_atomic (tree *expr_p, tree *pre_p)
5316 tree addr = TREE_OPERAND (*expr_p, 0);
5317 tree rhs = TREE_OPERAND (*expr_p, 1);
5318 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
5319 HOST_WIDE_INT index;
5321 /* Make sure the type is one of the supported sizes. */
5322 index = tree_low_cst (TYPE_SIZE_UNIT (type), 1);
5323 index = exact_log2 (index);
5324 if (index >= 0 && index <= 4)
5326 enum gimplify_status gs;
5327 unsigned int align;
5329 if (DECL_P (TREE_OPERAND (addr, 0)))
5330 align = DECL_ALIGN_UNIT (TREE_OPERAND (addr, 0));
5331 else if (TREE_CODE (TREE_OPERAND (addr, 0)) == COMPONENT_REF
5332 && TREE_CODE (TREE_OPERAND (TREE_OPERAND (addr, 0), 1))
5333 == FIELD_DECL)
5334 align = DECL_ALIGN_UNIT (TREE_OPERAND (TREE_OPERAND (addr, 0), 1));
5335 else
5336 align = TYPE_ALIGN_UNIT (type);
5338 /* __sync builtins require strict data alignment. */
5339 if (exact_log2 (align) >= index)
5341 /* When possible, use specialized atomic update functions. */
5342 if (INTEGRAL_TYPE_P (type) || POINTER_TYPE_P (type))
5344 gs = gimplify_omp_atomic_fetch_op (expr_p, addr, rhs, index);
5345 if (gs != GS_UNHANDLED)
5346 return gs;
5349 /* If we don't have specialized __sync builtins, try and implement
5350 as a compare and swap loop. */
5351 gs = gimplify_omp_atomic_pipeline (expr_p, pre_p, addr, rhs, index);
5352 if (gs != GS_UNHANDLED)
5353 return gs;
5357 /* The ultimate fallback is wrapping the operation in a mutex. */
5358 return gimplify_omp_atomic_mutex (expr_p, pre_p, addr, rhs);
5361 /* Gimplifies the expression tree pointed to by EXPR_P. Return 0 if
5362 gimplification failed.
5364 PRE_P points to the list where side effects that must happen before
5365 EXPR should be stored.
5367 POST_P points to the list where side effects that must happen after
5368 EXPR should be stored, or NULL if there is no suitable list. In
5369 that case, we copy the result to a temporary, emit the
5370 post-effects, and then return the temporary.
5372 GIMPLE_TEST_F points to a function that takes a tree T and
5373 returns nonzero if T is in the GIMPLE form requested by the
5374 caller. The GIMPLE predicates are in tree-gimple.c.
5376 This test is used twice. Before gimplification, the test is
5377 invoked to determine whether *EXPR_P is already gimple enough. If
5378 that fails, *EXPR_P is gimplified according to its code and
5379 GIMPLE_TEST_F is called again. If the test still fails, then a new
5380 temporary variable is created and assigned the value of the
5381 gimplified expression.
5383 FALLBACK tells the function what sort of a temporary we want. If the 1
5384 bit is set, an rvalue is OK. If the 2 bit is set, an lvalue is OK.
5385 If both are set, either is OK, but an lvalue is preferable.
5387 The return value is either GS_ERROR or GS_ALL_DONE, since this function
5388 iterates until solution. */
5390 enum gimplify_status
5391 gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p,
5392 bool (* gimple_test_f) (tree), fallback_t fallback)
5394 tree tmp;
5395 tree internal_pre = NULL_TREE;
5396 tree internal_post = NULL_TREE;
5397 tree save_expr;
5398 int is_statement = (pre_p == NULL);
5399 location_t saved_location;
5400 enum gimplify_status ret;
5402 save_expr = *expr_p;
5403 if (save_expr == NULL_TREE)
5404 return GS_ALL_DONE;
5406 /* We used to check the predicate here and return immediately if it
5407 succeeds. This is wrong; the design is for gimplification to be
5408 idempotent, and for the predicates to only test for valid forms, not
5409 whether they are fully simplified. */
5411 /* Set up our internal queues if needed. */
5412 if (pre_p == NULL)
5413 pre_p = &internal_pre;
5414 if (post_p == NULL)
5415 post_p = &internal_post;
5417 saved_location = input_location;
5418 if (save_expr != error_mark_node
5419 && EXPR_HAS_LOCATION (*expr_p))
5420 input_location = EXPR_LOCATION (*expr_p);
5422 /* Loop over the specific gimplifiers until the toplevel node
5423 remains the same. */
5426 /* Strip away as many useless type conversions as possible
5427 at the toplevel. */
5428 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
5430 /* Remember the expr. */
5431 save_expr = *expr_p;
5433 /* Die, die, die, my darling. */
5434 if (save_expr == error_mark_node
5435 || (!GIMPLE_STMT_P (save_expr)
5436 && TREE_TYPE (save_expr)
5437 && TREE_TYPE (save_expr) == error_mark_node))
5439 ret = GS_ERROR;
5440 break;
5443 /* Do any language-specific gimplification. */
5444 ret = lang_hooks.gimplify_expr (expr_p, pre_p, post_p);
5445 if (ret == GS_OK)
5447 if (*expr_p == NULL_TREE)
5448 break;
5449 if (*expr_p != save_expr)
5450 continue;
5452 else if (ret != GS_UNHANDLED)
5453 break;
5455 ret = GS_OK;
5456 switch (TREE_CODE (*expr_p))
5458 /* First deal with the special cases. */
5460 case POSTINCREMENT_EXPR:
5461 case POSTDECREMENT_EXPR:
5462 case PREINCREMENT_EXPR:
5463 case PREDECREMENT_EXPR:
5464 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
5465 fallback != fb_none);
5466 break;
5468 case ARRAY_REF:
5469 case ARRAY_RANGE_REF:
5470 case REALPART_EXPR:
5471 case IMAGPART_EXPR:
5472 case COMPONENT_REF:
5473 case VIEW_CONVERT_EXPR:
5474 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
5475 fallback ? fallback : fb_rvalue);
5476 break;
5478 case COND_EXPR:
5479 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
5480 /* C99 code may assign to an array in a structure value of a
5481 conditional expression, and this has undefined behavior
5482 only on execution, so create a temporary if an lvalue is
5483 required. */
5484 if (fallback == fb_lvalue)
5486 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
5487 lang_hooks.mark_addressable (*expr_p);
5489 break;
5491 case CALL_EXPR:
5492 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
5493 /* C99 code may assign to an array in a structure returned
5494 from a function, and this has undefined behavior only on
5495 execution, so create a temporary if an lvalue is
5496 required. */
5497 if (fallback == fb_lvalue)
5499 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
5500 lang_hooks.mark_addressable (*expr_p);
5502 break;
5504 case TREE_LIST:
5505 gcc_unreachable ();
5507 case COMPOUND_EXPR:
5508 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
5509 break;
5511 case MODIFY_EXPR:
5512 case GIMPLE_MODIFY_STMT:
5513 case INIT_EXPR:
5514 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
5515 fallback != fb_none);
5517 if (*expr_p)
5519 /* The distinction between MODIFY_EXPR and INIT_EXPR is no longer
5520 useful. */
5521 if (TREE_CODE (*expr_p) == INIT_EXPR)
5522 TREE_SET_CODE (*expr_p, MODIFY_EXPR);
5524 /* Convert MODIFY_EXPR to GIMPLE_MODIFY_STMT. */
5525 if (TREE_CODE (*expr_p) == MODIFY_EXPR)
5526 tree_to_gimple_tuple (expr_p);
5529 break;
5531 case TRUTH_ANDIF_EXPR:
5532 case TRUTH_ORIF_EXPR:
5533 ret = gimplify_boolean_expr (expr_p);
5534 break;
5536 case TRUTH_NOT_EXPR:
5537 TREE_OPERAND (*expr_p, 0)
5538 = gimple_boolify (TREE_OPERAND (*expr_p, 0));
5539 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5540 is_gimple_val, fb_rvalue);
5541 recalculate_side_effects (*expr_p);
5542 break;
5544 case ADDR_EXPR:
5545 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
5546 break;
5548 case VA_ARG_EXPR:
5549 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
5550 break;
5552 case CONVERT_EXPR:
5553 case NOP_EXPR:
5554 if (IS_EMPTY_STMT (*expr_p))
5556 ret = GS_ALL_DONE;
5557 break;
5560 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
5561 || fallback == fb_none)
5563 /* Just strip a conversion to void (or in void context) and
5564 try again. */
5565 *expr_p = TREE_OPERAND (*expr_p, 0);
5566 break;
5569 ret = gimplify_conversion (expr_p);
5570 if (ret == GS_ERROR)
5571 break;
5572 if (*expr_p != save_expr)
5573 break;
5574 /* FALLTHRU */
5576 case FIX_TRUNC_EXPR:
5577 /* unary_expr: ... | '(' cast ')' val | ... */
5578 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5579 is_gimple_val, fb_rvalue);
5580 recalculate_side_effects (*expr_p);
5581 break;
5583 case INDIRECT_REF:
5584 *expr_p = fold_indirect_ref (*expr_p);
5585 if (*expr_p != save_expr)
5586 break;
5587 /* else fall through. */
5588 case ALIGN_INDIRECT_REF:
5589 case MISALIGNED_INDIRECT_REF:
5590 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5591 is_gimple_reg, fb_rvalue);
5592 recalculate_side_effects (*expr_p);
5593 break;
5595 /* Constants need not be gimplified. */
5596 case INTEGER_CST:
5597 case REAL_CST:
5598 case STRING_CST:
5599 case COMPLEX_CST:
5600 case VECTOR_CST:
5601 ret = GS_ALL_DONE;
5602 break;
5604 case CONST_DECL:
5605 /* If we require an lvalue, such as for ADDR_EXPR, retain the
5606 CONST_DECL node. Otherwise the decl is replaceable by its
5607 value. */
5608 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
5609 if (fallback & fb_lvalue)
5610 ret = GS_ALL_DONE;
5611 else
5612 *expr_p = DECL_INITIAL (*expr_p);
5613 break;
5615 case DECL_EXPR:
5616 ret = gimplify_decl_expr (expr_p);
5617 break;
5619 case EXC_PTR_EXPR:
5620 /* FIXME make this a decl. */
5621 ret = GS_ALL_DONE;
5622 break;
5624 case BIND_EXPR:
5625 ret = gimplify_bind_expr (expr_p, pre_p);
5626 break;
5628 case LOOP_EXPR:
5629 ret = gimplify_loop_expr (expr_p, pre_p);
5630 break;
5632 case SWITCH_EXPR:
5633 ret = gimplify_switch_expr (expr_p, pre_p);
5634 break;
5636 case EXIT_EXPR:
5637 ret = gimplify_exit_expr (expr_p);
5638 break;
5640 case GOTO_EXPR:
5641 /* If the target is not LABEL, then it is a computed jump
5642 and the target needs to be gimplified. */
5643 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
5644 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
5645 NULL, is_gimple_val, fb_rvalue);
5646 break;
5648 case LABEL_EXPR:
5649 ret = GS_ALL_DONE;
5650 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
5651 == current_function_decl);
5652 break;
5654 case CASE_LABEL_EXPR:
5655 ret = gimplify_case_label_expr (expr_p);
5656 break;
5658 case RETURN_EXPR:
5659 ret = gimplify_return_expr (*expr_p, pre_p);
5660 break;
5662 case CONSTRUCTOR:
5663 /* Don't reduce this in place; let gimplify_init_constructor work its
5664 magic. Buf if we're just elaborating this for side effects, just
5665 gimplify any element that has side-effects. */
5666 if (fallback == fb_none)
5668 unsigned HOST_WIDE_INT ix;
5669 constructor_elt *ce;
5670 tree temp = NULL_TREE;
5671 for (ix = 0;
5672 VEC_iterate (constructor_elt, CONSTRUCTOR_ELTS (*expr_p),
5673 ix, ce);
5674 ix++)
5675 if (TREE_SIDE_EFFECTS (ce->value))
5676 append_to_statement_list (ce->value, &temp);
5678 *expr_p = temp;
5679 ret = GS_OK;
5681 /* C99 code may assign to an array in a constructed
5682 structure or union, and this has undefined behavior only
5683 on execution, so create a temporary if an lvalue is
5684 required. */
5685 else if (fallback == fb_lvalue)
5687 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
5688 lang_hooks.mark_addressable (*expr_p);
5690 else
5691 ret = GS_ALL_DONE;
5692 break;
5694 /* The following are special cases that are not handled by the
5695 original GIMPLE grammar. */
5697 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
5698 eliminated. */
5699 case SAVE_EXPR:
5700 ret = gimplify_save_expr (expr_p, pre_p, post_p);
5701 break;
5703 case BIT_FIELD_REF:
5705 enum gimplify_status r0, r1, r2;
5707 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5708 is_gimple_lvalue, fb_either);
5709 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
5710 is_gimple_val, fb_rvalue);
5711 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p, post_p,
5712 is_gimple_val, fb_rvalue);
5713 recalculate_side_effects (*expr_p);
5715 ret = MIN (r0, MIN (r1, r2));
5717 break;
5719 case NON_LVALUE_EXPR:
5720 /* This should have been stripped above. */
5721 gcc_unreachable ();
5723 case ASM_EXPR:
5724 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
5725 break;
5727 case TRY_FINALLY_EXPR:
5728 case TRY_CATCH_EXPR:
5729 gimplify_to_stmt_list (&TREE_OPERAND (*expr_p, 0));
5730 gimplify_to_stmt_list (&TREE_OPERAND (*expr_p, 1));
5731 ret = GS_ALL_DONE;
5732 break;
5734 case CLEANUP_POINT_EXPR:
5735 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
5736 break;
5738 case TARGET_EXPR:
5739 ret = gimplify_target_expr (expr_p, pre_p, post_p);
5740 break;
5742 case CATCH_EXPR:
5743 gimplify_to_stmt_list (&CATCH_BODY (*expr_p));
5744 ret = GS_ALL_DONE;
5745 break;
5747 case EH_FILTER_EXPR:
5748 gimplify_to_stmt_list (&EH_FILTER_FAILURE (*expr_p));
5749 ret = GS_ALL_DONE;
5750 break;
5752 case OBJ_TYPE_REF:
5754 enum gimplify_status r0, r1;
5755 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p, post_p,
5756 is_gimple_val, fb_rvalue);
5757 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p, post_p,
5758 is_gimple_val, fb_rvalue);
5759 ret = MIN (r0, r1);
5761 break;
5763 case LABEL_DECL:
5764 /* We get here when taking the address of a label. We mark
5765 the label as "forced"; meaning it can never be removed and
5766 it is a potential target for any computed goto. */
5767 FORCED_LABEL (*expr_p) = 1;
5768 ret = GS_ALL_DONE;
5769 break;
5771 case STATEMENT_LIST:
5772 ret = gimplify_statement_list (expr_p, pre_p);
5773 break;
5775 case WITH_SIZE_EXPR:
5777 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
5778 post_p == &internal_post ? NULL : post_p,
5779 gimple_test_f, fallback);
5780 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
5781 is_gimple_val, fb_rvalue);
5783 break;
5785 case VAR_DECL:
5786 case PARM_DECL:
5787 ret = gimplify_var_or_parm_decl (expr_p);
5788 break;
5790 case RESULT_DECL:
5791 /* When within an OpenMP context, notice uses of variables. */
5792 if (gimplify_omp_ctxp)
5793 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
5794 ret = GS_ALL_DONE;
5795 break;
5797 case SSA_NAME:
5798 /* Allow callbacks into the gimplifier during optimization. */
5799 ret = GS_ALL_DONE;
5800 break;
5802 case OMP_PARALLEL:
5803 ret = gimplify_omp_parallel (expr_p, pre_p);
5804 break;
5806 case OMP_FOR:
5807 ret = gimplify_omp_for (expr_p, pre_p);
5808 break;
5810 case OMP_SECTIONS:
5811 case OMP_SINGLE:
5812 ret = gimplify_omp_workshare (expr_p, pre_p);
5813 break;
5815 case OMP_SECTION:
5816 case OMP_MASTER:
5817 case OMP_ORDERED:
5818 case OMP_CRITICAL:
5819 gimplify_to_stmt_list (&OMP_BODY (*expr_p));
5820 break;
5822 case OMP_ATOMIC:
5823 ret = gimplify_omp_atomic (expr_p, pre_p);
5824 break;
5826 case OMP_RETURN:
5827 case OMP_CONTINUE:
5828 ret = GS_ALL_DONE;
5829 break;
5831 default:
5832 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
5834 case tcc_comparison:
5835 /* Handle comparison of objects of non scalar mode aggregates
5836 with a call to memcmp. It would be nice to only have to do
5837 this for variable-sized objects, but then we'd have to allow
5838 the same nest of reference nodes we allow for MODIFY_EXPR and
5839 that's too complex.
5841 Compare scalar mode aggregates as scalar mode values. Using
5842 memcmp for them would be very inefficient at best, and is
5843 plain wrong if bitfields are involved. */
5846 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
5848 if (!AGGREGATE_TYPE_P (type))
5849 goto expr_2;
5850 else if (TYPE_MODE (type) != BLKmode)
5851 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
5852 else
5853 ret = gimplify_variable_sized_compare (expr_p);
5855 break;
5858 /* If *EXPR_P does not need to be special-cased, handle it
5859 according to its class. */
5860 case tcc_unary:
5861 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
5862 post_p, is_gimple_val, fb_rvalue);
5863 break;
5865 case tcc_binary:
5866 expr_2:
5868 enum gimplify_status r0, r1;
5870 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
5871 post_p, is_gimple_val, fb_rvalue);
5872 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
5873 post_p, is_gimple_val, fb_rvalue);
5875 ret = MIN (r0, r1);
5876 break;
5879 case tcc_declaration:
5880 case tcc_constant:
5881 ret = GS_ALL_DONE;
5882 goto dont_recalculate;
5884 default:
5885 gcc_assert (TREE_CODE (*expr_p) == TRUTH_AND_EXPR
5886 || TREE_CODE (*expr_p) == TRUTH_OR_EXPR
5887 || TREE_CODE (*expr_p) == TRUTH_XOR_EXPR);
5888 goto expr_2;
5891 recalculate_side_effects (*expr_p);
5892 dont_recalculate:
5893 break;
5896 /* If we replaced *expr_p, gimplify again. */
5897 if (ret == GS_OK && (*expr_p == NULL || *expr_p == save_expr))
5898 ret = GS_ALL_DONE;
5900 while (ret == GS_OK);
5902 /* If we encountered an error_mark somewhere nested inside, either
5903 stub out the statement or propagate the error back out. */
5904 if (ret == GS_ERROR)
5906 if (is_statement)
5907 *expr_p = NULL;
5908 goto out;
5911 /* This was only valid as a return value from the langhook, which
5912 we handled. Make sure it doesn't escape from any other context. */
5913 gcc_assert (ret != GS_UNHANDLED);
5915 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
5917 /* We aren't looking for a value, and we don't have a valid
5918 statement. If it doesn't have side-effects, throw it away. */
5919 if (!TREE_SIDE_EFFECTS (*expr_p))
5920 *expr_p = NULL;
5921 else if (!TREE_THIS_VOLATILE (*expr_p))
5923 /* This is probably a _REF that contains something nested that
5924 has side effects. Recurse through the operands to find it. */
5925 enum tree_code code = TREE_CODE (*expr_p);
5927 switch (code)
5929 case COMPONENT_REF:
5930 case REALPART_EXPR:
5931 case IMAGPART_EXPR:
5932 case VIEW_CONVERT_EXPR:
5933 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5934 gimple_test_f, fallback);
5935 break;
5937 case ARRAY_REF:
5938 case ARRAY_RANGE_REF:
5939 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5940 gimple_test_f, fallback);
5941 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
5942 gimple_test_f, fallback);
5943 break;
5945 default:
5946 /* Anything else with side-effects must be converted to
5947 a valid statement before we get here. */
5948 gcc_unreachable ();
5951 *expr_p = NULL;
5953 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
5954 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
5956 /* Historically, the compiler has treated a bare reference
5957 to a non-BLKmode volatile lvalue as forcing a load. */
5958 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
5959 /* Normally, we do not want to create a temporary for a
5960 TREE_ADDRESSABLE type because such a type should not be
5961 copied by bitwise-assignment. However, we make an
5962 exception here, as all we are doing here is ensuring that
5963 we read the bytes that make up the type. We use
5964 create_tmp_var_raw because create_tmp_var will abort when
5965 given a TREE_ADDRESSABLE type. */
5966 tree tmp = create_tmp_var_raw (type, "vol");
5967 gimple_add_tmp_var (tmp);
5968 *expr_p = build2 (GIMPLE_MODIFY_STMT, type, tmp, *expr_p);
5970 else
5971 /* We can't do anything useful with a volatile reference to
5972 an incomplete type, so just throw it away. Likewise for
5973 a BLKmode type, since any implicit inner load should
5974 already have been turned into an explicit one by the
5975 gimplification process. */
5976 *expr_p = NULL;
5979 /* If we are gimplifying at the statement level, we're done. Tack
5980 everything together and replace the original statement with the
5981 gimplified form. */
5982 if (fallback == fb_none || is_statement)
5984 if (internal_pre || internal_post)
5986 append_to_statement_list (*expr_p, &internal_pre);
5987 append_to_statement_list (internal_post, &internal_pre);
5988 annotate_all_with_locus (&internal_pre, input_location);
5989 *expr_p = internal_pre;
5991 else if (!*expr_p)
5993 else if (TREE_CODE (*expr_p) == STATEMENT_LIST)
5994 annotate_all_with_locus (expr_p, input_location);
5995 else
5996 annotate_one_with_locus (*expr_p, input_location);
5997 goto out;
6000 /* Otherwise we're gimplifying a subexpression, so the resulting value is
6001 interesting. */
6003 /* If it's sufficiently simple already, we're done. Unless we are
6004 handling some post-effects internally; if that's the case, we need to
6005 copy into a temp before adding the post-effects to the tree. */
6006 if (!internal_post && (*gimple_test_f) (*expr_p))
6007 goto out;
6009 /* Otherwise, we need to create a new temporary for the gimplified
6010 expression. */
6012 /* We can't return an lvalue if we have an internal postqueue. The
6013 object the lvalue refers to would (probably) be modified by the
6014 postqueue; we need to copy the value out first, which means an
6015 rvalue. */
6016 if ((fallback & fb_lvalue) && !internal_post
6017 && is_gimple_addressable (*expr_p))
6019 /* An lvalue will do. Take the address of the expression, store it
6020 in a temporary, and replace the expression with an INDIRECT_REF of
6021 that temporary. */
6022 tmp = build_fold_addr_expr (*expr_p);
6023 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
6024 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (TREE_TYPE (tmp)), tmp);
6026 else if ((fallback & fb_rvalue) && is_gimple_formal_tmp_rhs (*expr_p))
6028 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
6030 /* An rvalue will do. Assign the gimplified expression into a new
6031 temporary TMP and replace the original expression with TMP. */
6033 if (internal_post || (fallback & fb_lvalue))
6034 /* The postqueue might change the value of the expression between
6035 the initialization and use of the temporary, so we can't use a
6036 formal temp. FIXME do we care? */
6037 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
6038 else
6039 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
6041 if (TREE_CODE (*expr_p) != SSA_NAME)
6042 DECL_GIMPLE_FORMAL_TEMP_P (*expr_p) = 1;
6044 else
6046 #ifdef ENABLE_CHECKING
6047 if (!(fallback & fb_mayfail))
6049 fprintf (stderr, "gimplification failed:\n");
6050 print_generic_expr (stderr, *expr_p, 0);
6051 debug_tree (*expr_p);
6052 internal_error ("gimplification failed");
6054 #endif
6055 gcc_assert (fallback & fb_mayfail);
6056 /* If this is an asm statement, and the user asked for the
6057 impossible, don't die. Fail and let gimplify_asm_expr
6058 issue an error. */
6059 ret = GS_ERROR;
6060 goto out;
6063 /* Make sure the temporary matches our predicate. */
6064 gcc_assert ((*gimple_test_f) (*expr_p));
6066 if (internal_post)
6068 annotate_all_with_locus (&internal_post, input_location);
6069 append_to_statement_list (internal_post, pre_p);
6072 out:
6073 input_location = saved_location;
6074 return ret;
6077 /* Look through TYPE for variable-sized objects and gimplify each such
6078 size that we find. Add to LIST_P any statements generated. */
6080 void
6081 gimplify_type_sizes (tree type, tree *list_p)
6083 tree field, t;
6085 if (type == NULL || type == error_mark_node)
6086 return;
6088 /* We first do the main variant, then copy into any other variants. */
6089 type = TYPE_MAIN_VARIANT (type);
6091 /* Avoid infinite recursion. */
6092 if (TYPE_SIZES_GIMPLIFIED (type))
6093 return;
6095 TYPE_SIZES_GIMPLIFIED (type) = 1;
6097 switch (TREE_CODE (type))
6099 case INTEGER_TYPE:
6100 case ENUMERAL_TYPE:
6101 case BOOLEAN_TYPE:
6102 case REAL_TYPE:
6103 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
6104 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
6106 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
6108 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
6109 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
6111 break;
6113 case ARRAY_TYPE:
6114 /* These types may not have declarations, so handle them here. */
6115 gimplify_type_sizes (TREE_TYPE (type), list_p);
6116 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
6117 break;
6119 case RECORD_TYPE:
6120 case UNION_TYPE:
6121 case QUAL_UNION_TYPE:
6122 for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
6123 if (TREE_CODE (field) == FIELD_DECL)
6125 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
6126 gimplify_type_sizes (TREE_TYPE (field), list_p);
6128 break;
6130 case POINTER_TYPE:
6131 case REFERENCE_TYPE:
6132 /* We used to recurse on the pointed-to type here, which turned out to
6133 be incorrect because its definition might refer to variables not
6134 yet initialized at this point if a forward declaration is involved.
6136 It was actually useful for anonymous pointed-to types to ensure
6137 that the sizes evaluation dominates every possible later use of the
6138 values. Restricting to such types here would be safe since there
6139 is no possible forward declaration around, but would introduce an
6140 undesirable middle-end semantic to anonymity. We then defer to
6141 front-ends the responsibility of ensuring that the sizes are
6142 evaluated both early and late enough, e.g. by attaching artificial
6143 type declarations to the tree. */
6144 break;
6146 default:
6147 break;
6150 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
6151 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
6153 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
6155 TYPE_SIZE (t) = TYPE_SIZE (type);
6156 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
6157 TYPE_SIZES_GIMPLIFIED (t) = 1;
6161 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
6162 a size or position, has had all of its SAVE_EXPRs evaluated.
6163 We add any required statements to STMT_P. */
6165 void
6166 gimplify_one_sizepos (tree *expr_p, tree *stmt_p)
6168 tree type, expr = *expr_p;
6170 /* We don't do anything if the value isn't there, is constant, or contains
6171 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
6172 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
6173 will want to replace it with a new variable, but that will cause problems
6174 if this type is from outside the function. It's OK to have that here. */
6175 if (expr == NULL_TREE || TREE_CONSTANT (expr)
6176 || TREE_CODE (expr) == VAR_DECL
6177 || CONTAINS_PLACEHOLDER_P (expr))
6178 return;
6180 type = TREE_TYPE (expr);
6181 *expr_p = unshare_expr (expr);
6183 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue);
6184 expr = *expr_p;
6186 /* Verify that we've an exact type match with the original expression.
6187 In particular, we do not wish to drop a "sizetype" in favour of a
6188 type of similar dimensions. We don't want to pollute the generic
6189 type-stripping code with this knowledge because it doesn't matter
6190 for the bulk of GENERIC/GIMPLE. It only matters that TYPE_SIZE_UNIT
6191 and friends retain their "sizetype-ness". */
6192 if (TREE_TYPE (expr) != type
6193 && TREE_CODE (type) == INTEGER_TYPE
6194 && TYPE_IS_SIZETYPE (type))
6196 tree tmp;
6198 *expr_p = create_tmp_var (type, NULL);
6199 tmp = build1 (NOP_EXPR, type, expr);
6200 tmp = build2 (GIMPLE_MODIFY_STMT, type, *expr_p, tmp);
6201 if (EXPR_HAS_LOCATION (expr))
6202 SET_EXPR_LOCUS (tmp, EXPR_LOCUS (expr));
6203 else
6204 SET_EXPR_LOCATION (tmp, input_location);
6206 gimplify_and_add (tmp, stmt_p);
6210 #ifdef ENABLE_CHECKING
6211 /* Compare types A and B for a "close enough" match. */
6213 static bool
6214 cpt_same_type (tree a, tree b)
6216 if (lang_hooks.types_compatible_p (a, b))
6217 return true;
6219 /* ??? The C++ FE decomposes METHOD_TYPES to FUNCTION_TYPES and doesn't
6220 link them together. This routine is intended to catch type errors
6221 that will affect the optimizers, and the optimizers don't add new
6222 dereferences of function pointers, so ignore it. */
6223 if ((TREE_CODE (a) == FUNCTION_TYPE || TREE_CODE (a) == METHOD_TYPE)
6224 && (TREE_CODE (b) == FUNCTION_TYPE || TREE_CODE (b) == METHOD_TYPE))
6225 return true;
6227 /* ??? The C FE pushes type qualifiers after the fact into the type of
6228 the element from the type of the array. See build_unary_op's handling
6229 of ADDR_EXPR. This seems wrong -- if we were going to do this, we
6230 should have done it when creating the variable in the first place.
6231 Alternately, why aren't the two array types made variants? */
6232 if (TREE_CODE (a) == ARRAY_TYPE && TREE_CODE (b) == ARRAY_TYPE)
6233 return cpt_same_type (TREE_TYPE (a), TREE_TYPE (b));
6235 /* And because of those, we have to recurse down through pointers. */
6236 if (POINTER_TYPE_P (a) && POINTER_TYPE_P (b))
6237 return cpt_same_type (TREE_TYPE (a), TREE_TYPE (b));
6239 return false;
6242 /* Check for some cases of the front end missing cast expressions.
6243 The type of a dereference should correspond to the pointer type;
6244 similarly the type of an address should match its object. */
6246 static tree
6247 check_pointer_types_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
6248 void *data ATTRIBUTE_UNUSED)
6250 tree t = *tp;
6251 tree ptype, otype, dtype;
6253 switch (TREE_CODE (t))
6255 case INDIRECT_REF:
6256 case ARRAY_REF:
6257 otype = TREE_TYPE (t);
6258 ptype = TREE_TYPE (TREE_OPERAND (t, 0));
6259 dtype = TREE_TYPE (ptype);
6260 gcc_assert (cpt_same_type (otype, dtype));
6261 break;
6263 case ADDR_EXPR:
6264 ptype = TREE_TYPE (t);
6265 otype = TREE_TYPE (TREE_OPERAND (t, 0));
6266 dtype = TREE_TYPE (ptype);
6267 if (!cpt_same_type (otype, dtype))
6269 /* &array is allowed to produce a pointer to the element, rather than
6270 a pointer to the array type. We must allow this in order to
6271 properly represent assigning the address of an array in C into
6272 pointer to the element type. */
6273 gcc_assert (TREE_CODE (otype) == ARRAY_TYPE
6274 && POINTER_TYPE_P (ptype)
6275 && cpt_same_type (TREE_TYPE (otype), dtype));
6276 break;
6278 break;
6280 default:
6281 return NULL_TREE;
6285 return NULL_TREE;
6287 #endif
6289 /* Gimplify the body of statements pointed to by BODY_P. FNDECL is the
6290 function decl containing BODY. */
6292 void
6293 gimplify_body (tree *body_p, tree fndecl, bool do_parms)
6295 location_t saved_location = input_location;
6296 tree body, parm_stmts;
6298 timevar_push (TV_TREE_GIMPLIFY);
6300 gcc_assert (gimplify_ctxp == NULL);
6301 push_gimplify_context ();
6303 /* Unshare most shared trees in the body and in that of any nested functions.
6304 It would seem we don't have to do this for nested functions because
6305 they are supposed to be output and then the outer function gimplified
6306 first, but the g++ front end doesn't always do it that way. */
6307 unshare_body (body_p, fndecl);
6308 unvisit_body (body_p, fndecl);
6310 /* Make sure input_location isn't set to something wierd. */
6311 input_location = DECL_SOURCE_LOCATION (fndecl);
6313 /* Resolve callee-copies. This has to be done before processing
6314 the body so that DECL_VALUE_EXPR gets processed correctly. */
6315 parm_stmts = do_parms ? gimplify_parameters () : NULL;
6317 /* Gimplify the function's body. */
6318 gimplify_stmt (body_p);
6319 body = *body_p;
6321 if (!body)
6322 body = alloc_stmt_list ();
6323 else if (TREE_CODE (body) == STATEMENT_LIST)
6325 tree t = expr_only (*body_p);
6326 if (t)
6327 body = t;
6330 /* If there isn't an outer BIND_EXPR, add one. */
6331 if (TREE_CODE (body) != BIND_EXPR)
6333 tree b = build3 (BIND_EXPR, void_type_node, NULL_TREE,
6334 NULL_TREE, NULL_TREE);
6335 TREE_SIDE_EFFECTS (b) = 1;
6336 append_to_statement_list_force (body, &BIND_EXPR_BODY (b));
6337 body = b;
6340 /* If we had callee-copies statements, insert them at the beginning
6341 of the function. */
6342 if (parm_stmts)
6344 append_to_statement_list_force (BIND_EXPR_BODY (body), &parm_stmts);
6345 BIND_EXPR_BODY (body) = parm_stmts;
6348 /* Unshare again, in case gimplification was sloppy. */
6349 unshare_all_trees (body);
6351 *body_p = body;
6353 pop_gimplify_context (body);
6354 gcc_assert (gimplify_ctxp == NULL);
6356 #ifdef ENABLE_CHECKING
6357 walk_tree (body_p, check_pointer_types_r, NULL, NULL);
6358 #endif
6360 timevar_pop (TV_TREE_GIMPLIFY);
6361 input_location = saved_location;
6364 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
6365 node for the function we want to gimplify. */
6367 void
6368 gimplify_function_tree (tree fndecl)
6370 tree oldfn, parm, ret;
6372 oldfn = current_function_decl;
6373 current_function_decl = fndecl;
6374 cfun = DECL_STRUCT_FUNCTION (fndecl);
6375 if (cfun == NULL)
6376 allocate_struct_function (fndecl);
6378 for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = TREE_CHAIN (parm))
6380 /* Preliminarily mark non-addressed complex variables as eligible
6381 for promotion to gimple registers. We'll transform their uses
6382 as we find them. */
6383 if ((TREE_CODE (TREE_TYPE (parm)) == COMPLEX_TYPE
6384 || TREE_CODE (TREE_TYPE (parm)) == VECTOR_TYPE)
6385 && !TREE_THIS_VOLATILE (parm)
6386 && !needs_to_live_in_memory (parm))
6387 DECL_GIMPLE_REG_P (parm) = 1;
6390 ret = DECL_RESULT (fndecl);
6391 if ((TREE_CODE (TREE_TYPE (ret)) == COMPLEX_TYPE
6392 || TREE_CODE (TREE_TYPE (ret)) == VECTOR_TYPE)
6393 && !needs_to_live_in_memory (ret))
6394 DECL_GIMPLE_REG_P (ret) = 1;
6396 gimplify_body (&DECL_SAVED_TREE (fndecl), fndecl, true);
6398 /* If we're instrumenting function entry/exit, then prepend the call to
6399 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
6400 catch the exit hook. */
6401 /* ??? Add some way to ignore exceptions for this TFE. */
6402 if (flag_instrument_function_entry_exit
6403 && ! DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl))
6405 tree tf, x, bind;
6407 tf = build2 (TRY_FINALLY_EXPR, void_type_node, NULL, NULL);
6408 TREE_SIDE_EFFECTS (tf) = 1;
6409 x = DECL_SAVED_TREE (fndecl);
6410 append_to_statement_list (x, &TREE_OPERAND (tf, 0));
6411 x = implicit_built_in_decls[BUILT_IN_PROFILE_FUNC_EXIT];
6412 x = build_function_call_expr (x, NULL);
6413 append_to_statement_list (x, &TREE_OPERAND (tf, 1));
6415 bind = build3 (BIND_EXPR, void_type_node, NULL, NULL, NULL);
6416 TREE_SIDE_EFFECTS (bind) = 1;
6417 x = implicit_built_in_decls[BUILT_IN_PROFILE_FUNC_ENTER];
6418 x = build_function_call_expr (x, NULL);
6419 append_to_statement_list (x, &BIND_EXPR_BODY (bind));
6420 append_to_statement_list (tf, &BIND_EXPR_BODY (bind));
6422 DECL_SAVED_TREE (fndecl) = bind;
6425 cfun->gimplified = true;
6426 current_function_decl = oldfn;
6427 cfun = oldfn ? DECL_STRUCT_FUNCTION (oldfn) : NULL;
6430 /* Expands EXPR to list of gimple statements STMTS. If SIMPLE is true,
6431 force the result to be either ssa_name or an invariant, otherwise
6432 just force it to be a rhs expression. If VAR is not NULL, make the
6433 base variable of the final destination be VAR if suitable. */
6435 tree
6436 force_gimple_operand (tree expr, tree *stmts, bool simple, tree var)
6438 tree t;
6439 enum gimplify_status ret;
6440 gimple_predicate gimple_test_f;
6442 *stmts = NULL_TREE;
6444 if (is_gimple_val (expr))
6445 return expr;
6447 gimple_test_f = simple ? is_gimple_val : is_gimple_reg_rhs;
6449 push_gimplify_context ();
6450 gimplify_ctxp->into_ssa = gimple_in_ssa_p (cfun);
6452 if (var)
6453 expr = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (var), var, expr);
6455 ret = gimplify_expr (&expr, stmts, NULL,
6456 gimple_test_f, fb_rvalue);
6457 gcc_assert (ret != GS_ERROR);
6459 if (gimple_referenced_vars (cfun))
6461 for (t = gimplify_ctxp->temps; t ; t = TREE_CHAIN (t))
6462 add_referenced_var (t);
6465 pop_gimplify_context (NULL);
6467 return expr;
6470 /* Invokes force_gimple_operand for EXPR with parameters SIMPLE_P and VAR. If
6471 some statements are produced, emits them before BSI. */
6473 tree
6474 force_gimple_operand_bsi (block_stmt_iterator *bsi, tree expr,
6475 bool simple_p, tree var)
6477 tree stmts;
6479 expr = force_gimple_operand (expr, &stmts, simple_p, var);
6480 if (stmts)
6481 bsi_insert_before (bsi, stmts, BSI_SAME_STMT);
6483 return expr;
6486 #include "gt-gimplify.h"