* sched-deps.c (find_insn_list): Remove.
[official-gcc.git] / gcc / gimplify.c
blob2d02617ccb404e3657b076c4a3ffc72932432c0f
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) == GIMPLE_MODIFY_STMT
1018 || TREE_CODE (temp) == MODIFY_EXPR);
1019 GENERIC_TREE_OPERAND (temp, 1) = *p;
1020 *p = temp;
1022 else
1024 temp = create_tmp_var (type, "retval");
1025 *p = build2 (INIT_EXPR, type, temp, *p);
1028 return temp;
1031 return NULL_TREE;
1034 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1035 a temporary through which they communicate. */
1037 static void
1038 build_stack_save_restore (tree *save, tree *restore)
1040 tree save_call, tmp_var;
1042 save_call =
1043 build_call_expr (implicit_built_in_decls[BUILT_IN_STACK_SAVE], 0);
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_call_expr (implicit_built_in_decls[BUILT_IN_STACK_RESTORE],
1049 1, tmp_var);
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, 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 t = built_in_decls[BUILT_IN_ALLOCA];
1253 t = build_call_expr (t, 1, DECL_SIZE_UNIT (decl));
1254 t = fold_convert (ptr_type, t);
1255 t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
1257 gimplify_and_add (t, stmt_p);
1259 /* Indicate that we need to restore the stack level when the
1260 enclosing BIND_EXPR is exited. */
1261 gimplify_ctxp->save_stack = true;
1264 if (init && init != error_mark_node)
1266 if (!TREE_STATIC (decl))
1268 DECL_INITIAL (decl) = NULL_TREE;
1269 init = build2 (INIT_EXPR, void_type_node, decl, init);
1270 gimplify_and_add (init, stmt_p);
1272 else
1273 /* We must still examine initializers for static variables
1274 as they may contain a label address. */
1275 walk_tree (&init, force_labels_r, NULL, NULL);
1278 /* Some front ends do not explicitly declare all anonymous
1279 artificial variables. We compensate here by declaring the
1280 variables, though it would be better if the front ends would
1281 explicitly declare them. */
1282 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1283 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1284 gimple_add_tmp_var (decl);
1287 return GS_ALL_DONE;
1290 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1291 and replacing the LOOP_EXPR with goto, but if the loop contains an
1292 EXIT_EXPR, we need to append a label for it to jump to. */
1294 static enum gimplify_status
1295 gimplify_loop_expr (tree *expr_p, tree *pre_p)
1297 tree saved_label = gimplify_ctxp->exit_label;
1298 tree start_label = build1 (LABEL_EXPR, void_type_node, NULL_TREE);
1299 tree jump_stmt = build_and_jump (&LABEL_EXPR_LABEL (start_label));
1301 append_to_statement_list (start_label, pre_p);
1303 gimplify_ctxp->exit_label = NULL_TREE;
1305 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1307 if (gimplify_ctxp->exit_label)
1309 append_to_statement_list (jump_stmt, pre_p);
1310 *expr_p = build1 (LABEL_EXPR, void_type_node, gimplify_ctxp->exit_label);
1312 else
1313 *expr_p = jump_stmt;
1315 gimplify_ctxp->exit_label = saved_label;
1317 return GS_ALL_DONE;
1320 /* Compare two case labels. Because the front end should already have
1321 made sure that case ranges do not overlap, it is enough to only compare
1322 the CASE_LOW values of each case label. */
1324 static int
1325 compare_case_labels (const void *p1, const void *p2)
1327 tree case1 = *(tree *)p1;
1328 tree case2 = *(tree *)p2;
1330 return tree_int_cst_compare (CASE_LOW (case1), CASE_LOW (case2));
1333 /* Sort the case labels in LABEL_VEC in place in ascending order. */
1335 void
1336 sort_case_labels (tree label_vec)
1338 size_t len = TREE_VEC_LENGTH (label_vec);
1339 tree default_case = TREE_VEC_ELT (label_vec, len - 1);
1341 if (CASE_LOW (default_case))
1343 size_t i;
1345 /* The last label in the vector should be the default case
1346 but it is not. */
1347 for (i = 0; i < len; ++i)
1349 tree t = TREE_VEC_ELT (label_vec, i);
1350 if (!CASE_LOW (t))
1352 default_case = t;
1353 TREE_VEC_ELT (label_vec, i) = TREE_VEC_ELT (label_vec, len - 1);
1354 TREE_VEC_ELT (label_vec, len - 1) = default_case;
1355 break;
1360 qsort (&TREE_VEC_ELT (label_vec, 0), len - 1, sizeof (tree),
1361 compare_case_labels);
1364 /* Gimplify a SWITCH_EXPR, and collect a TREE_VEC of the labels it can
1365 branch to. */
1367 static enum gimplify_status
1368 gimplify_switch_expr (tree *expr_p, tree *pre_p)
1370 tree switch_expr = *expr_p;
1371 enum gimplify_status ret;
1373 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL,
1374 is_gimple_val, fb_rvalue);
1376 if (SWITCH_BODY (switch_expr))
1378 VEC(tree,heap) *labels, *saved_labels;
1379 tree label_vec, default_case = NULL_TREE;
1380 size_t i, len;
1382 /* If someone can be bothered to fill in the labels, they can
1383 be bothered to null out the body too. */
1384 gcc_assert (!SWITCH_LABELS (switch_expr));
1386 saved_labels = gimplify_ctxp->case_labels;
1387 gimplify_ctxp->case_labels = VEC_alloc (tree, heap, 8);
1389 gimplify_to_stmt_list (&SWITCH_BODY (switch_expr));
1391 labels = gimplify_ctxp->case_labels;
1392 gimplify_ctxp->case_labels = saved_labels;
1394 i = 0;
1395 while (i < VEC_length (tree, labels))
1397 tree elt = VEC_index (tree, labels, i);
1398 tree low = CASE_LOW (elt);
1399 bool remove_element = FALSE;
1401 if (low)
1403 /* Discard empty ranges. */
1404 tree high = CASE_HIGH (elt);
1405 if (high && INT_CST_LT (high, low))
1406 remove_element = TRUE;
1408 else
1410 /* The default case must be the last label in the list. */
1411 gcc_assert (!default_case);
1412 default_case = elt;
1413 remove_element = TRUE;
1416 if (remove_element)
1417 VEC_ordered_remove (tree, labels, i);
1418 else
1419 i++;
1421 len = i;
1423 label_vec = make_tree_vec (len + 1);
1424 SWITCH_LABELS (*expr_p) = label_vec;
1425 append_to_statement_list (switch_expr, pre_p);
1427 if (! default_case)
1429 /* If the switch has no default label, add one, so that we jump
1430 around the switch body. */
1431 default_case = build3 (CASE_LABEL_EXPR, void_type_node, NULL_TREE,
1432 NULL_TREE, create_artificial_label ());
1433 append_to_statement_list (SWITCH_BODY (switch_expr), pre_p);
1434 *expr_p = build1 (LABEL_EXPR, void_type_node,
1435 CASE_LABEL (default_case));
1437 else
1438 *expr_p = SWITCH_BODY (switch_expr);
1440 for (i = 0; i < len; ++i)
1441 TREE_VEC_ELT (label_vec, i) = VEC_index (tree, labels, i);
1442 TREE_VEC_ELT (label_vec, len) = default_case;
1444 VEC_free (tree, heap, labels);
1446 sort_case_labels (label_vec);
1448 SWITCH_BODY (switch_expr) = NULL;
1450 else
1451 gcc_assert (SWITCH_LABELS (switch_expr));
1453 return ret;
1456 static enum gimplify_status
1457 gimplify_case_label_expr (tree *expr_p)
1459 tree expr = *expr_p;
1460 struct gimplify_ctx *ctxp;
1462 /* Invalid OpenMP programs can play Duff's Device type games with
1463 #pragma omp parallel. At least in the C front end, we don't
1464 detect such invalid branches until after gimplification. */
1465 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
1466 if (ctxp->case_labels)
1467 break;
1469 VEC_safe_push (tree, heap, ctxp->case_labels, expr);
1470 *expr_p = build1 (LABEL_EXPR, void_type_node, CASE_LABEL (expr));
1471 return GS_ALL_DONE;
1474 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
1475 if necessary. */
1477 tree
1478 build_and_jump (tree *label_p)
1480 if (label_p == NULL)
1481 /* If there's nowhere to jump, just fall through. */
1482 return NULL_TREE;
1484 if (*label_p == NULL_TREE)
1486 tree label = create_artificial_label ();
1487 *label_p = label;
1490 return build1 (GOTO_EXPR, void_type_node, *label_p);
1493 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
1494 This also involves building a label to jump to and communicating it to
1495 gimplify_loop_expr through gimplify_ctxp->exit_label. */
1497 static enum gimplify_status
1498 gimplify_exit_expr (tree *expr_p)
1500 tree cond = TREE_OPERAND (*expr_p, 0);
1501 tree expr;
1503 expr = build_and_jump (&gimplify_ctxp->exit_label);
1504 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
1505 *expr_p = expr;
1507 return GS_OK;
1510 /* A helper function to be called via walk_tree. Mark all labels under *TP
1511 as being forced. To be called for DECL_INITIAL of static variables. */
1513 tree
1514 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1516 if (TYPE_P (*tp))
1517 *walk_subtrees = 0;
1518 if (TREE_CODE (*tp) == LABEL_DECL)
1519 FORCED_LABEL (*tp) = 1;
1521 return NULL_TREE;
1524 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
1525 different from its canonical type, wrap the whole thing inside a
1526 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
1527 type.
1529 The canonical type of a COMPONENT_REF is the type of the field being
1530 referenced--unless the field is a bit-field which can be read directly
1531 in a smaller mode, in which case the canonical type is the
1532 sign-appropriate type corresponding to that mode. */
1534 static void
1535 canonicalize_component_ref (tree *expr_p)
1537 tree expr = *expr_p;
1538 tree type;
1540 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
1542 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
1543 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
1544 else
1545 type = TREE_TYPE (TREE_OPERAND (expr, 1));
1547 if (TREE_TYPE (expr) != type)
1549 tree old_type = TREE_TYPE (expr);
1551 /* Set the type of the COMPONENT_REF to the underlying type. */
1552 TREE_TYPE (expr) = type;
1554 /* And wrap the whole thing inside a NOP_EXPR. */
1555 expr = build1 (NOP_EXPR, old_type, expr);
1557 *expr_p = expr;
1561 /* If a NOP conversion is changing a pointer to array of foo to a pointer
1562 to foo, embed that change in the ADDR_EXPR by converting
1563 T array[U];
1564 (T *)&array
1566 &array[L]
1567 where L is the lower bound. For simplicity, only do this for constant
1568 lower bound. */
1570 static void
1571 canonicalize_addr_expr (tree *expr_p)
1573 tree expr = *expr_p;
1574 tree ctype = TREE_TYPE (expr);
1575 tree addr_expr = TREE_OPERAND (expr, 0);
1576 tree atype = TREE_TYPE (addr_expr);
1577 tree dctype, datype, ddatype, otype, obj_expr;
1579 /* Both cast and addr_expr types should be pointers. */
1580 if (!POINTER_TYPE_P (ctype) || !POINTER_TYPE_P (atype))
1581 return;
1583 /* The addr_expr type should be a pointer to an array. */
1584 datype = TREE_TYPE (atype);
1585 if (TREE_CODE (datype) != ARRAY_TYPE)
1586 return;
1588 /* Both cast and addr_expr types should address the same object type. */
1589 dctype = TREE_TYPE (ctype);
1590 ddatype = TREE_TYPE (datype);
1591 if (!lang_hooks.types_compatible_p (ddatype, dctype))
1592 return;
1594 /* The addr_expr and the object type should match. */
1595 obj_expr = TREE_OPERAND (addr_expr, 0);
1596 otype = TREE_TYPE (obj_expr);
1597 if (!lang_hooks.types_compatible_p (otype, datype))
1598 return;
1600 /* The lower bound and element sizes must be constant. */
1601 if (!TYPE_SIZE_UNIT (dctype)
1602 || TREE_CODE (TYPE_SIZE_UNIT (dctype)) != INTEGER_CST
1603 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
1604 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
1605 return;
1607 /* All checks succeeded. Build a new node to merge the cast. */
1608 *expr_p = build4 (ARRAY_REF, dctype, obj_expr,
1609 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
1610 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
1611 size_binop (EXACT_DIV_EXPR, TYPE_SIZE_UNIT (dctype),
1612 size_int (TYPE_ALIGN_UNIT (dctype))));
1613 *expr_p = build1 (ADDR_EXPR, ctype, *expr_p);
1616 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
1617 underneath as appropriate. */
1619 static enum gimplify_status
1620 gimplify_conversion (tree *expr_p)
1622 gcc_assert (TREE_CODE (*expr_p) == NOP_EXPR
1623 || TREE_CODE (*expr_p) == CONVERT_EXPR);
1625 /* Then strip away all but the outermost conversion. */
1626 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
1628 /* And remove the outermost conversion if it's useless. */
1629 if (tree_ssa_useless_type_conversion (*expr_p))
1630 *expr_p = TREE_OPERAND (*expr_p, 0);
1632 /* If we still have a conversion at the toplevel,
1633 then canonicalize some constructs. */
1634 if (TREE_CODE (*expr_p) == NOP_EXPR || TREE_CODE (*expr_p) == CONVERT_EXPR)
1636 tree sub = TREE_OPERAND (*expr_p, 0);
1638 /* If a NOP conversion is changing the type of a COMPONENT_REF
1639 expression, then canonicalize its type now in order to expose more
1640 redundant conversions. */
1641 if (TREE_CODE (sub) == COMPONENT_REF)
1642 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
1644 /* If a NOP conversion is changing a pointer to array of foo
1645 to a pointer to foo, embed that change in the ADDR_EXPR. */
1646 else if (TREE_CODE (sub) == ADDR_EXPR)
1647 canonicalize_addr_expr (expr_p);
1650 return GS_OK;
1653 /* Gimplify a VAR_DECL or PARM_DECL. Returns GS_OK if we expanded a
1654 DECL_VALUE_EXPR, and it's worth re-examining things. */
1656 static enum gimplify_status
1657 gimplify_var_or_parm_decl (tree *expr_p)
1659 tree decl = *expr_p;
1661 /* ??? If this is a local variable, and it has not been seen in any
1662 outer BIND_EXPR, then it's probably the result of a duplicate
1663 declaration, for which we've already issued an error. It would
1664 be really nice if the front end wouldn't leak these at all.
1665 Currently the only known culprit is C++ destructors, as seen
1666 in g++.old-deja/g++.jason/binding.C. */
1667 if (TREE_CODE (decl) == VAR_DECL
1668 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
1669 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
1670 && decl_function_context (decl) == current_function_decl)
1672 gcc_assert (errorcount || sorrycount);
1673 return GS_ERROR;
1676 /* When within an OpenMP context, notice uses of variables. */
1677 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
1678 return GS_ALL_DONE;
1680 /* If the decl is an alias for another expression, substitute it now. */
1681 if (DECL_HAS_VALUE_EXPR_P (decl))
1683 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
1684 return GS_OK;
1687 return GS_ALL_DONE;
1691 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
1692 node pointed to by EXPR_P.
1694 compound_lval
1695 : min_lval '[' val ']'
1696 | min_lval '.' ID
1697 | compound_lval '[' val ']'
1698 | compound_lval '.' ID
1700 This is not part of the original SIMPLE definition, which separates
1701 array and member references, but it seems reasonable to handle them
1702 together. Also, this way we don't run into problems with union
1703 aliasing; gcc requires that for accesses through a union to alias, the
1704 union reference must be explicit, which was not always the case when we
1705 were splitting up array and member refs.
1707 PRE_P points to the list where side effects that must happen before
1708 *EXPR_P should be stored.
1710 POST_P points to the list where side effects that must happen after
1711 *EXPR_P should be stored. */
1713 static enum gimplify_status
1714 gimplify_compound_lval (tree *expr_p, tree *pre_p,
1715 tree *post_p, fallback_t fallback)
1717 tree *p;
1718 VEC(tree,heap) *stack;
1719 enum gimplify_status ret = GS_OK, tret;
1720 int i;
1722 /* Create a stack of the subexpressions so later we can walk them in
1723 order from inner to outer. */
1724 stack = VEC_alloc (tree, heap, 10);
1726 /* We can handle anything that get_inner_reference can deal with. */
1727 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
1729 restart:
1730 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
1731 if (TREE_CODE (*p) == INDIRECT_REF)
1732 *p = fold_indirect_ref (*p);
1734 if (handled_component_p (*p))
1736 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
1737 additional COMPONENT_REFs. */
1738 else if ((TREE_CODE (*p) == VAR_DECL || TREE_CODE (*p) == PARM_DECL)
1739 && gimplify_var_or_parm_decl (p) == GS_OK)
1740 goto restart;
1741 else
1742 break;
1744 VEC_safe_push (tree, heap, stack, *p);
1747 gcc_assert (VEC_length (tree, stack));
1749 /* Now STACK is a stack of pointers to all the refs we've walked through
1750 and P points to the innermost expression.
1752 Java requires that we elaborated nodes in source order. That
1753 means we must gimplify the inner expression followed by each of
1754 the indices, in order. But we can't gimplify the inner
1755 expression until we deal with any variable bounds, sizes, or
1756 positions in order to deal with PLACEHOLDER_EXPRs.
1758 So we do this in three steps. First we deal with the annotations
1759 for any variables in the components, then we gimplify the base,
1760 then we gimplify any indices, from left to right. */
1761 for (i = VEC_length (tree, stack) - 1; i >= 0; i--)
1763 tree t = VEC_index (tree, stack, i);
1765 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
1767 /* Gimplify the low bound and element type size and put them into
1768 the ARRAY_REF. If these values are set, they have already been
1769 gimplified. */
1770 if (!TREE_OPERAND (t, 2))
1772 tree low = unshare_expr (array_ref_low_bound (t));
1773 if (!is_gimple_min_invariant (low))
1775 TREE_OPERAND (t, 2) = low;
1776 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1777 is_gimple_formal_tmp_reg, fb_rvalue);
1778 ret = MIN (ret, tret);
1782 if (!TREE_OPERAND (t, 3))
1784 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
1785 tree elmt_size = unshare_expr (array_ref_element_size (t));
1786 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
1788 /* Divide the element size by the alignment of the element
1789 type (above). */
1790 elmt_size = size_binop (EXACT_DIV_EXPR, elmt_size, factor);
1792 if (!is_gimple_min_invariant (elmt_size))
1794 TREE_OPERAND (t, 3) = elmt_size;
1795 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
1796 is_gimple_formal_tmp_reg, fb_rvalue);
1797 ret = MIN (ret, tret);
1801 else if (TREE_CODE (t) == COMPONENT_REF)
1803 /* Set the field offset into T and gimplify it. */
1804 if (!TREE_OPERAND (t, 2))
1806 tree offset = unshare_expr (component_ref_field_offset (t));
1807 tree field = TREE_OPERAND (t, 1);
1808 tree factor
1809 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
1811 /* Divide the offset by its alignment. */
1812 offset = size_binop (EXACT_DIV_EXPR, offset, factor);
1814 if (!is_gimple_min_invariant (offset))
1816 TREE_OPERAND (t, 2) = offset;
1817 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1818 is_gimple_formal_tmp_reg, fb_rvalue);
1819 ret = MIN (ret, tret);
1825 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
1826 so as to match the min_lval predicate. Failure to do so may result
1827 in the creation of large aggregate temporaries. */
1828 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
1829 fallback | fb_lvalue);
1830 ret = MIN (ret, tret);
1832 /* And finally, the indices and operands to BIT_FIELD_REF. During this
1833 loop we also remove any useless conversions. */
1834 for (; VEC_length (tree, stack) > 0; )
1836 tree t = VEC_pop (tree, stack);
1838 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
1840 /* Gimplify the dimension.
1841 Temporary fix for gcc.c-torture/execute/20040313-1.c.
1842 Gimplify non-constant array indices into a temporary
1843 variable.
1844 FIXME - The real fix is to gimplify post-modify
1845 expressions into a minimal gimple lvalue. However, that
1846 exposes bugs in alias analysis. The alias analyzer does
1847 not handle &PTR->FIELD very well. Will fix after the
1848 branch is merged into mainline (dnovillo 2004-05-03). */
1849 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
1851 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
1852 is_gimple_formal_tmp_reg, fb_rvalue);
1853 ret = MIN (ret, tret);
1856 else if (TREE_CODE (t) == BIT_FIELD_REF)
1858 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
1859 is_gimple_val, fb_rvalue);
1860 ret = MIN (ret, tret);
1861 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1862 is_gimple_val, fb_rvalue);
1863 ret = MIN (ret, tret);
1866 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
1868 /* The innermost expression P may have originally had TREE_SIDE_EFFECTS
1869 set which would have caused all the outer expressions in EXPR_P
1870 leading to P to also have had TREE_SIDE_EFFECTS set. */
1871 recalculate_side_effects (t);
1874 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval, fallback);
1875 ret = MIN (ret, tret);
1877 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
1878 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
1880 canonicalize_component_ref (expr_p);
1881 ret = MIN (ret, GS_OK);
1884 VEC_free (tree, heap, stack);
1886 return ret;
1889 /* Gimplify the self modifying expression pointed to by EXPR_P
1890 (++, --, +=, -=).
1892 PRE_P points to the list where side effects that must happen before
1893 *EXPR_P should be stored.
1895 POST_P points to the list where side effects that must happen after
1896 *EXPR_P should be stored.
1898 WANT_VALUE is nonzero iff we want to use the value of this expression
1899 in another expression. */
1901 static enum gimplify_status
1902 gimplify_self_mod_expr (tree *expr_p, tree *pre_p, tree *post_p,
1903 bool want_value)
1905 enum tree_code code;
1906 tree lhs, lvalue, rhs, t1, post = NULL, *orig_post_p = post_p;
1907 bool postfix;
1908 enum tree_code arith_code;
1909 enum gimplify_status ret;
1911 code = TREE_CODE (*expr_p);
1913 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
1914 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
1916 /* Prefix or postfix? */
1917 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
1918 /* Faster to treat as prefix if result is not used. */
1919 postfix = want_value;
1920 else
1921 postfix = false;
1923 /* For postfix, make sure the inner expression's post side effects
1924 are executed after side effects from this expression. */
1925 if (postfix)
1926 post_p = &post;
1928 /* Add or subtract? */
1929 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
1930 arith_code = PLUS_EXPR;
1931 else
1932 arith_code = MINUS_EXPR;
1934 /* Gimplify the LHS into a GIMPLE lvalue. */
1935 lvalue = TREE_OPERAND (*expr_p, 0);
1936 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
1937 if (ret == GS_ERROR)
1938 return ret;
1940 /* Extract the operands to the arithmetic operation. */
1941 lhs = lvalue;
1942 rhs = TREE_OPERAND (*expr_p, 1);
1944 /* For postfix operator, we evaluate the LHS to an rvalue and then use
1945 that as the result value and in the postqueue operation. */
1946 if (postfix)
1948 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
1949 if (ret == GS_ERROR)
1950 return ret;
1953 t1 = build2 (arith_code, TREE_TYPE (*expr_p), lhs, rhs);
1954 t1 = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (lvalue), lvalue, t1);
1956 if (postfix)
1958 gimplify_and_add (t1, orig_post_p);
1959 append_to_statement_list (post, orig_post_p);
1960 *expr_p = lhs;
1961 return GS_ALL_DONE;
1963 else
1965 *expr_p = t1;
1966 return GS_OK;
1970 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
1972 static void
1973 maybe_with_size_expr (tree *expr_p)
1975 tree expr = *expr_p;
1976 tree type = TREE_TYPE (expr);
1977 tree size;
1979 /* If we've already wrapped this or the type is error_mark_node, we can't do
1980 anything. */
1981 if (TREE_CODE (expr) == WITH_SIZE_EXPR
1982 || type == error_mark_node)
1983 return;
1985 /* If the size isn't known or is a constant, we have nothing to do. */
1986 size = TYPE_SIZE_UNIT (type);
1987 if (!size || TREE_CODE (size) == INTEGER_CST)
1988 return;
1990 /* Otherwise, make a WITH_SIZE_EXPR. */
1991 size = unshare_expr (size);
1992 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
1993 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
1996 /* Subroutine of gimplify_call_expr: Gimplify a single argument. */
1998 static enum gimplify_status
1999 gimplify_arg (tree *expr_p, tree *pre_p)
2001 bool (*test) (tree);
2002 fallback_t fb;
2004 /* In general, we allow lvalues for function arguments to avoid
2005 extra overhead of copying large aggregates out of even larger
2006 aggregates into temporaries only to copy the temporaries to
2007 the argument list. Make optimizers happy by pulling out to
2008 temporaries those types that fit in registers. */
2009 if (is_gimple_reg_type (TREE_TYPE (*expr_p)))
2010 test = is_gimple_val, fb = fb_rvalue;
2011 else
2012 test = is_gimple_lvalue, fb = fb_either;
2014 /* If this is a variable sized type, we must remember the size. */
2015 maybe_with_size_expr (expr_p);
2017 /* There is a sequence point before a function call. Side effects in
2018 the argument list must occur before the actual call. So, when
2019 gimplifying arguments, force gimplify_expr to use an internal
2020 post queue which is then appended to the end of PRE_P. */
2021 return gimplify_expr (expr_p, pre_p, NULL, test, fb);
2024 /* Gimplify the CALL_EXPR node pointed to by EXPR_P. PRE_P points to the
2025 list where side effects that must happen before *EXPR_P should be stored.
2026 WANT_VALUE is true if the result of the call is desired. */
2028 static enum gimplify_status
2029 gimplify_call_expr (tree *expr_p, tree *pre_p, bool want_value)
2031 tree decl;
2032 enum gimplify_status ret;
2033 int i, nargs;
2035 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
2037 /* For reliable diagnostics during inlining, it is necessary that
2038 every call_expr be annotated with file and line. */
2039 if (! EXPR_HAS_LOCATION (*expr_p))
2040 SET_EXPR_LOCATION (*expr_p, input_location);
2042 /* This may be a call to a builtin function.
2044 Builtin function calls may be transformed into different
2045 (and more efficient) builtin function calls under certain
2046 circumstances. Unfortunately, gimplification can muck things
2047 up enough that the builtin expanders are not aware that certain
2048 transformations are still valid.
2050 So we attempt transformation/gimplification of the call before
2051 we gimplify the CALL_EXPR. At this time we do not manage to
2052 transform all calls in the same manner as the expanders do, but
2053 we do transform most of them. */
2054 decl = get_callee_fndecl (*expr_p);
2055 if (decl && DECL_BUILT_IN (decl))
2057 tree new = fold_call_expr (*expr_p, !want_value);
2059 if (new && new != *expr_p)
2061 /* There was a transformation of this call which computes the
2062 same value, but in a more efficient way. Return and try
2063 again. */
2064 *expr_p = new;
2065 return GS_OK;
2068 if (DECL_BUILT_IN_CLASS (decl) == BUILT_IN_NORMAL
2069 && DECL_FUNCTION_CODE (decl) == BUILT_IN_VA_START)
2071 if (call_expr_nargs (*expr_p) < 2)
2073 error ("too few arguments to function %<va_start%>");
2074 *expr_p = build_empty_stmt ();
2075 return GS_OK;
2078 if (fold_builtin_next_arg (*expr_p, true))
2080 *expr_p = build_empty_stmt ();
2081 return GS_OK;
2083 /* Avoid gimplifying the second argument to va_start, which needs
2084 to be the plain PARM_DECL. */
2085 return gimplify_arg (&CALL_EXPR_ARG (*expr_p, 0), pre_p);
2089 /* There is a sequence point before the call, so any side effects in
2090 the calling expression must occur before the actual call. Force
2091 gimplify_expr to use an internal post queue. */
2092 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
2093 is_gimple_call_addr, fb_rvalue);
2095 nargs = call_expr_nargs (*expr_p);
2097 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
2098 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
2099 PUSH_ARGS_REVERSED ? i-- : i++)
2101 enum gimplify_status t;
2103 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p);
2105 if (t == GS_ERROR)
2106 ret = GS_ERROR;
2109 /* Try this again in case gimplification exposed something. */
2110 if (ret != GS_ERROR)
2112 tree new = fold_call_expr (*expr_p, !want_value);
2114 if (new && new != *expr_p)
2116 /* There was a transformation of this call which computes the
2117 same value, but in a more efficient way. Return and try
2118 again. */
2119 *expr_p = new;
2120 return GS_OK;
2124 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
2125 decl. This allows us to eliminate redundant or useless
2126 calls to "const" functions. */
2127 if (TREE_CODE (*expr_p) == CALL_EXPR
2128 && (call_expr_flags (*expr_p) & (ECF_CONST | ECF_PURE)))
2129 TREE_SIDE_EFFECTS (*expr_p) = 0;
2131 return ret;
2134 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
2135 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
2137 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
2138 condition is true or false, respectively. If null, we should generate
2139 our own to skip over the evaluation of this specific expression.
2141 This function is the tree equivalent of do_jump.
2143 shortcut_cond_r should only be called by shortcut_cond_expr. */
2145 static tree
2146 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p)
2148 tree local_label = NULL_TREE;
2149 tree t, expr = NULL;
2151 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
2152 retain the shortcut semantics. Just insert the gotos here;
2153 shortcut_cond_expr will append the real blocks later. */
2154 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
2156 /* Turn if (a && b) into
2158 if (a); else goto no;
2159 if (b) goto yes; else goto no;
2160 (no:) */
2162 if (false_label_p == NULL)
2163 false_label_p = &local_label;
2165 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p);
2166 append_to_statement_list (t, &expr);
2168 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
2169 false_label_p);
2170 append_to_statement_list (t, &expr);
2172 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
2174 /* Turn if (a || b) into
2176 if (a) goto yes;
2177 if (b) goto yes; else goto no;
2178 (yes:) */
2180 if (true_label_p == NULL)
2181 true_label_p = &local_label;
2183 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL);
2184 append_to_statement_list (t, &expr);
2186 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
2187 false_label_p);
2188 append_to_statement_list (t, &expr);
2190 else if (TREE_CODE (pred) == COND_EXPR)
2192 /* As long as we're messing with gotos, turn if (a ? b : c) into
2193 if (a)
2194 if (b) goto yes; else goto no;
2195 else
2196 if (c) goto yes; else goto no; */
2197 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
2198 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
2199 false_label_p),
2200 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
2201 false_label_p));
2203 else
2205 expr = build3 (COND_EXPR, void_type_node, pred,
2206 build_and_jump (true_label_p),
2207 build_and_jump (false_label_p));
2210 if (local_label)
2212 t = build1 (LABEL_EXPR, void_type_node, local_label);
2213 append_to_statement_list (t, &expr);
2216 return expr;
2219 static tree
2220 shortcut_cond_expr (tree expr)
2222 tree pred = TREE_OPERAND (expr, 0);
2223 tree then_ = TREE_OPERAND (expr, 1);
2224 tree else_ = TREE_OPERAND (expr, 2);
2225 tree true_label, false_label, end_label, t;
2226 tree *true_label_p;
2227 tree *false_label_p;
2228 bool emit_end, emit_false, jump_over_else;
2229 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
2230 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
2232 /* First do simple transformations. */
2233 if (!else_se)
2235 /* If there is no 'else', turn (a && b) into if (a) if (b). */
2236 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
2238 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
2239 then_ = shortcut_cond_expr (expr);
2240 then_se = then_ && TREE_SIDE_EFFECTS (then_);
2241 pred = TREE_OPERAND (pred, 0);
2242 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
2245 if (!then_se)
2247 /* If there is no 'then', turn
2248 if (a || b); else d
2249 into
2250 if (a); else if (b); else d. */
2251 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
2253 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
2254 else_ = shortcut_cond_expr (expr);
2255 else_se = else_ && TREE_SIDE_EFFECTS (else_);
2256 pred = TREE_OPERAND (pred, 0);
2257 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
2261 /* If we're done, great. */
2262 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
2263 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
2264 return expr;
2266 /* Otherwise we need to mess with gotos. Change
2267 if (a) c; else d;
2269 if (a); else goto no;
2270 c; goto end;
2271 no: d; end:
2272 and recursively gimplify the condition. */
2274 true_label = false_label = end_label = NULL_TREE;
2276 /* If our arms just jump somewhere, hijack those labels so we don't
2277 generate jumps to jumps. */
2279 if (then_
2280 && TREE_CODE (then_) == GOTO_EXPR
2281 && TREE_CODE (GOTO_DESTINATION (then_)) == LABEL_DECL)
2283 true_label = GOTO_DESTINATION (then_);
2284 then_ = NULL;
2285 then_se = false;
2288 if (else_
2289 && TREE_CODE (else_) == GOTO_EXPR
2290 && TREE_CODE (GOTO_DESTINATION (else_)) == LABEL_DECL)
2292 false_label = GOTO_DESTINATION (else_);
2293 else_ = NULL;
2294 else_se = false;
2297 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
2298 if (true_label)
2299 true_label_p = &true_label;
2300 else
2301 true_label_p = NULL;
2303 /* The 'else' branch also needs a label if it contains interesting code. */
2304 if (false_label || else_se)
2305 false_label_p = &false_label;
2306 else
2307 false_label_p = NULL;
2309 /* If there was nothing else in our arms, just forward the label(s). */
2310 if (!then_se && !else_se)
2311 return shortcut_cond_r (pred, true_label_p, false_label_p);
2313 /* If our last subexpression already has a terminal label, reuse it. */
2314 if (else_se)
2315 expr = expr_last (else_);
2316 else if (then_se)
2317 expr = expr_last (then_);
2318 else
2319 expr = NULL;
2320 if (expr && TREE_CODE (expr) == LABEL_EXPR)
2321 end_label = LABEL_EXPR_LABEL (expr);
2323 /* If we don't care about jumping to the 'else' branch, jump to the end
2324 if the condition is false. */
2325 if (!false_label_p)
2326 false_label_p = &end_label;
2328 /* We only want to emit these labels if we aren't hijacking them. */
2329 emit_end = (end_label == NULL_TREE);
2330 emit_false = (false_label == NULL_TREE);
2332 /* We only emit the jump over the else clause if we have to--if the
2333 then clause may fall through. Otherwise we can wind up with a
2334 useless jump and a useless label at the end of gimplified code,
2335 which will cause us to think that this conditional as a whole
2336 falls through even if it doesn't. If we then inline a function
2337 which ends with such a condition, that can cause us to issue an
2338 inappropriate warning about control reaching the end of a
2339 non-void function. */
2340 jump_over_else = block_may_fallthru (then_);
2342 pred = shortcut_cond_r (pred, true_label_p, false_label_p);
2344 expr = NULL;
2345 append_to_statement_list (pred, &expr);
2347 append_to_statement_list (then_, &expr);
2348 if (else_se)
2350 if (jump_over_else)
2352 t = build_and_jump (&end_label);
2353 append_to_statement_list (t, &expr);
2355 if (emit_false)
2357 t = build1 (LABEL_EXPR, void_type_node, false_label);
2358 append_to_statement_list (t, &expr);
2360 append_to_statement_list (else_, &expr);
2362 if (emit_end && end_label)
2364 t = build1 (LABEL_EXPR, void_type_node, end_label);
2365 append_to_statement_list (t, &expr);
2368 return expr;
2371 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
2373 tree
2374 gimple_boolify (tree expr)
2376 tree type = TREE_TYPE (expr);
2378 if (TREE_CODE (type) == BOOLEAN_TYPE)
2379 return expr;
2381 switch (TREE_CODE (expr))
2383 case TRUTH_AND_EXPR:
2384 case TRUTH_OR_EXPR:
2385 case TRUTH_XOR_EXPR:
2386 case TRUTH_ANDIF_EXPR:
2387 case TRUTH_ORIF_EXPR:
2388 /* Also boolify the arguments of truth exprs. */
2389 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
2390 /* FALLTHRU */
2392 case TRUTH_NOT_EXPR:
2393 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2394 /* FALLTHRU */
2396 case EQ_EXPR: case NE_EXPR:
2397 case LE_EXPR: case GE_EXPR: case LT_EXPR: case GT_EXPR:
2398 /* These expressions always produce boolean results. */
2399 TREE_TYPE (expr) = boolean_type_node;
2400 return expr;
2402 default:
2403 /* Other expressions that get here must have boolean values, but
2404 might need to be converted to the appropriate mode. */
2405 return fold_convert (boolean_type_node, expr);
2409 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
2410 into
2412 if (p) if (p)
2413 t1 = a; a;
2414 else or else
2415 t1 = b; b;
2418 The second form is used when *EXPR_P is of type void.
2420 TARGET is the tree for T1 above.
2422 PRE_P points to the list where side effects that must happen before
2423 *EXPR_P should be stored. */
2425 static enum gimplify_status
2426 gimplify_cond_expr (tree *expr_p, tree *pre_p, fallback_t fallback)
2428 tree expr = *expr_p;
2429 tree tmp, tmp2, type;
2430 enum gimplify_status ret;
2432 type = TREE_TYPE (expr);
2434 /* If this COND_EXPR has a value, copy the values into a temporary within
2435 the arms. */
2436 if (! VOID_TYPE_P (type))
2438 tree result;
2440 if ((fallback & fb_lvalue) == 0)
2442 result = tmp2 = tmp = create_tmp_var (TREE_TYPE (expr), "iftmp");
2443 ret = GS_ALL_DONE;
2445 else
2447 tree type = build_pointer_type (TREE_TYPE (expr));
2449 if (TREE_TYPE (TREE_OPERAND (expr, 1)) != void_type_node)
2450 TREE_OPERAND (expr, 1) =
2451 build_fold_addr_expr (TREE_OPERAND (expr, 1));
2453 if (TREE_TYPE (TREE_OPERAND (expr, 2)) != void_type_node)
2454 TREE_OPERAND (expr, 2) =
2455 build_fold_addr_expr (TREE_OPERAND (expr, 2));
2457 tmp2 = tmp = create_tmp_var (type, "iftmp");
2459 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (expr, 0),
2460 TREE_OPERAND (expr, 1), TREE_OPERAND (expr, 2));
2462 result = build_fold_indirect_ref (tmp);
2463 ret = GS_ALL_DONE;
2466 /* Build the then clause, 't1 = a;'. But don't build an assignment
2467 if this branch is void; in C++ it can be, if it's a throw. */
2468 if (TREE_TYPE (TREE_OPERAND (expr, 1)) != void_type_node)
2469 TREE_OPERAND (expr, 1)
2470 = build2 (GIMPLE_MODIFY_STMT, void_type_node, tmp,
2471 TREE_OPERAND (expr, 1));
2473 /* Build the else clause, 't1 = b;'. */
2474 if (TREE_TYPE (TREE_OPERAND (expr, 2)) != void_type_node)
2475 TREE_OPERAND (expr, 2)
2476 = build2 (GIMPLE_MODIFY_STMT, void_type_node, tmp2,
2477 TREE_OPERAND (expr, 2));
2479 TREE_TYPE (expr) = void_type_node;
2480 recalculate_side_effects (expr);
2482 /* Move the COND_EXPR to the prequeue. */
2483 gimplify_and_add (expr, pre_p);
2485 *expr_p = result;
2486 return ret;
2489 /* Make sure the condition has BOOLEAN_TYPE. */
2490 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2492 /* Break apart && and || conditions. */
2493 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
2494 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
2496 expr = shortcut_cond_expr (expr);
2498 if (expr != *expr_p)
2500 *expr_p = expr;
2502 /* We can't rely on gimplify_expr to re-gimplify the expanded
2503 form properly, as cleanups might cause the target labels to be
2504 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
2505 set up a conditional context. */
2506 gimple_push_condition ();
2507 gimplify_stmt (expr_p);
2508 gimple_pop_condition (pre_p);
2510 return GS_ALL_DONE;
2514 /* Now do the normal gimplification. */
2515 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
2516 is_gimple_condexpr, fb_rvalue);
2518 gimple_push_condition ();
2520 gimplify_to_stmt_list (&TREE_OPERAND (expr, 1));
2521 gimplify_to_stmt_list (&TREE_OPERAND (expr, 2));
2522 recalculate_side_effects (expr);
2524 gimple_pop_condition (pre_p);
2526 if (ret == GS_ERROR)
2528 else if (TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 1)))
2529 ret = GS_ALL_DONE;
2530 else if (TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 2)))
2531 /* Rewrite "if (a); else b" to "if (!a) b" */
2533 TREE_OPERAND (expr, 0) = invert_truthvalue (TREE_OPERAND (expr, 0));
2534 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
2535 is_gimple_condexpr, fb_rvalue);
2537 tmp = TREE_OPERAND (expr, 1);
2538 TREE_OPERAND (expr, 1) = TREE_OPERAND (expr, 2);
2539 TREE_OPERAND (expr, 2) = tmp;
2541 else
2542 /* Both arms are empty; replace the COND_EXPR with its predicate. */
2543 expr = TREE_OPERAND (expr, 0);
2545 *expr_p = expr;
2546 return ret;
2549 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
2550 a call to __builtin_memcpy. */
2552 static enum gimplify_status
2553 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value)
2555 tree t, to, to_ptr, from, from_ptr;
2557 to = GENERIC_TREE_OPERAND (*expr_p, 0);
2558 from = GENERIC_TREE_OPERAND (*expr_p, 1);
2560 from_ptr = build_fold_addr_expr (from);
2562 to_ptr = build_fold_addr_expr (to);
2563 t = implicit_built_in_decls[BUILT_IN_MEMCPY];
2564 t = build_call_expr (t, 3, to_ptr, from_ptr, size);
2566 if (want_value)
2568 t = build1 (NOP_EXPR, TREE_TYPE (to_ptr), t);
2569 t = build1 (INDIRECT_REF, TREE_TYPE (to), t);
2572 *expr_p = t;
2573 return GS_OK;
2576 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
2577 a call to __builtin_memset. In this case we know that the RHS is
2578 a CONSTRUCTOR with an empty element list. */
2580 static enum gimplify_status
2581 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value)
2583 tree t, to, to_ptr;
2585 to = GENERIC_TREE_OPERAND (*expr_p, 0);
2587 to_ptr = build_fold_addr_expr (to);
2588 t = implicit_built_in_decls[BUILT_IN_MEMSET];
2589 t = build_call_expr (t, 3, to_ptr, integer_zero_node, size);
2591 if (want_value)
2593 t = build1 (NOP_EXPR, TREE_TYPE (to_ptr), t);
2594 t = build1 (INDIRECT_REF, TREE_TYPE (to), t);
2597 *expr_p = t;
2598 return GS_OK;
2601 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
2602 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
2603 assignment. Returns non-null if we detect a potential overlap. */
2605 struct gimplify_init_ctor_preeval_data
2607 /* The base decl of the lhs object. May be NULL, in which case we
2608 have to assume the lhs is indirect. */
2609 tree lhs_base_decl;
2611 /* The alias set of the lhs object. */
2612 int lhs_alias_set;
2615 static tree
2616 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
2618 struct gimplify_init_ctor_preeval_data *data
2619 = (struct gimplify_init_ctor_preeval_data *) xdata;
2620 tree t = *tp;
2622 /* If we find the base object, obviously we have overlap. */
2623 if (data->lhs_base_decl == t)
2624 return t;
2626 /* If the constructor component is indirect, determine if we have a
2627 potential overlap with the lhs. The only bits of information we
2628 have to go on at this point are addressability and alias sets. */
2629 if (TREE_CODE (t) == INDIRECT_REF
2630 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
2631 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
2632 return t;
2634 if (IS_TYPE_OR_DECL_P (t))
2635 *walk_subtrees = 0;
2636 return NULL;
2639 /* A subroutine of gimplify_init_constructor. Pre-evaluate *EXPR_P,
2640 force values that overlap with the lhs (as described by *DATA)
2641 into temporaries. */
2643 static void
2644 gimplify_init_ctor_preeval (tree *expr_p, tree *pre_p, tree *post_p,
2645 struct gimplify_init_ctor_preeval_data *data)
2647 enum gimplify_status one;
2649 /* If the value is invariant, then there's nothing to pre-evaluate.
2650 But ensure it doesn't have any side-effects since a SAVE_EXPR is
2651 invariant but has side effects and might contain a reference to
2652 the object we're initializing. */
2653 if (TREE_INVARIANT (*expr_p) && !TREE_SIDE_EFFECTS (*expr_p))
2654 return;
2656 /* If the type has non-trivial constructors, we can't pre-evaluate. */
2657 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
2658 return;
2660 /* Recurse for nested constructors. */
2661 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
2663 unsigned HOST_WIDE_INT ix;
2664 constructor_elt *ce;
2665 VEC(constructor_elt,gc) *v = CONSTRUCTOR_ELTS (*expr_p);
2667 for (ix = 0; VEC_iterate (constructor_elt, v, ix, ce); ix++)
2668 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
2669 return;
2672 /* If this is a variable sized type, we must remember the size. */
2673 maybe_with_size_expr (expr_p);
2675 /* Gimplify the constructor element to something appropriate for the rhs
2676 of a MODIFY_EXPR. Given that we know the lhs is an aggregate, we know
2677 the gimplifier will consider this a store to memory. Doing this
2678 gimplification now means that we won't have to deal with complicated
2679 language-specific trees, nor trees like SAVE_EXPR that can induce
2680 exponential search behavior. */
2681 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
2682 if (one == GS_ERROR)
2684 *expr_p = NULL;
2685 return;
2688 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
2689 with the lhs, since "a = { .x=a }" doesn't make sense. This will
2690 always be true for all scalars, since is_gimple_mem_rhs insists on a
2691 temporary variable for them. */
2692 if (DECL_P (*expr_p))
2693 return;
2695 /* If this is of variable size, we have no choice but to assume it doesn't
2696 overlap since we can't make a temporary for it. */
2697 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
2698 return;
2700 /* Otherwise, we must search for overlap ... */
2701 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
2702 return;
2704 /* ... and if found, force the value into a temporary. */
2705 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
2708 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
2709 a RANGE_EXPR in a CONSTRUCTOR for an array.
2711 var = lower;
2712 loop_entry:
2713 object[var] = value;
2714 if (var == upper)
2715 goto loop_exit;
2716 var = var + 1;
2717 goto loop_entry;
2718 loop_exit:
2720 We increment var _after_ the loop exit check because we might otherwise
2721 fail if upper == TYPE_MAX_VALUE (type for upper).
2723 Note that we never have to deal with SAVE_EXPRs here, because this has
2724 already been taken care of for us, in gimplify_init_ctor_preeval(). */
2726 static void gimplify_init_ctor_eval (tree, VEC(constructor_elt,gc) *,
2727 tree *, bool);
2729 static void
2730 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
2731 tree value, tree array_elt_type,
2732 tree *pre_p, bool cleared)
2734 tree loop_entry_label, loop_exit_label;
2735 tree var, var_type, cref;
2737 loop_entry_label = create_artificial_label ();
2738 loop_exit_label = create_artificial_label ();
2740 /* Create and initialize the index variable. */
2741 var_type = TREE_TYPE (upper);
2742 var = create_tmp_var (var_type, NULL);
2743 append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, var_type, var, lower),
2744 pre_p);
2746 /* Add the loop entry label. */
2747 append_to_statement_list (build1 (LABEL_EXPR,
2748 void_type_node,
2749 loop_entry_label),
2750 pre_p);
2752 /* Build the reference. */
2753 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
2754 var, NULL_TREE, NULL_TREE);
2756 /* If we are a constructor, just call gimplify_init_ctor_eval to do
2757 the store. Otherwise just assign value to the reference. */
2759 if (TREE_CODE (value) == CONSTRUCTOR)
2760 /* NB we might have to call ourself recursively through
2761 gimplify_init_ctor_eval if the value is a constructor. */
2762 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
2763 pre_p, cleared);
2764 else
2765 append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (cref),
2766 cref, value),
2767 pre_p);
2769 /* We exit the loop when the index var is equal to the upper bound. */
2770 gimplify_and_add (build3 (COND_EXPR, void_type_node,
2771 build2 (EQ_EXPR, boolean_type_node,
2772 var, upper),
2773 build1 (GOTO_EXPR,
2774 void_type_node,
2775 loop_exit_label),
2776 NULL_TREE),
2777 pre_p);
2779 /* Otherwise, increment the index var... */
2780 append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, var_type, var,
2781 build2 (PLUS_EXPR, var_type, var,
2782 fold_convert (var_type,
2783 integer_one_node))),
2784 pre_p);
2786 /* ...and jump back to the loop entry. */
2787 append_to_statement_list (build1 (GOTO_EXPR,
2788 void_type_node,
2789 loop_entry_label),
2790 pre_p);
2792 /* Add the loop exit label. */
2793 append_to_statement_list (build1 (LABEL_EXPR,
2794 void_type_node,
2795 loop_exit_label),
2796 pre_p);
2799 /* Return true if FDECL is accessing a field that is zero sized. */
2801 static bool
2802 zero_sized_field_decl (tree fdecl)
2804 if (TREE_CODE (fdecl) == FIELD_DECL && DECL_SIZE (fdecl)
2805 && integer_zerop (DECL_SIZE (fdecl)))
2806 return true;
2807 return false;
2810 /* Return true if TYPE is zero sized. */
2812 static bool
2813 zero_sized_type (tree type)
2815 if (AGGREGATE_TYPE_P (type) && TYPE_SIZE (type)
2816 && integer_zerop (TYPE_SIZE (type)))
2817 return true;
2818 return false;
2821 /* A subroutine of gimplify_init_constructor. Generate individual
2822 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
2823 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
2824 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
2825 zeroed first. */
2827 static void
2828 gimplify_init_ctor_eval (tree object, VEC(constructor_elt,gc) *elts,
2829 tree *pre_p, bool cleared)
2831 tree array_elt_type = NULL;
2832 unsigned HOST_WIDE_INT ix;
2833 tree purpose, value;
2835 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
2836 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
2838 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
2840 tree cref, init;
2842 /* NULL values are created above for gimplification errors. */
2843 if (value == NULL)
2844 continue;
2846 if (cleared && initializer_zerop (value))
2847 continue;
2849 /* ??? Here's to hoping the front end fills in all of the indices,
2850 so we don't have to figure out what's missing ourselves. */
2851 gcc_assert (purpose);
2853 /* Skip zero-sized fields, unless value has side-effects. This can
2854 happen with calls to functions returning a zero-sized type, which
2855 we shouldn't discard. As a number of downstream passes don't
2856 expect sets of zero-sized fields, we rely on the gimplification of
2857 the MODIFY_EXPR we make below to drop the assignment statement. */
2858 if (! TREE_SIDE_EFFECTS (value) && zero_sized_field_decl (purpose))
2859 continue;
2861 /* If we have a RANGE_EXPR, we have to build a loop to assign the
2862 whole range. */
2863 if (TREE_CODE (purpose) == RANGE_EXPR)
2865 tree lower = TREE_OPERAND (purpose, 0);
2866 tree upper = TREE_OPERAND (purpose, 1);
2868 /* If the lower bound is equal to upper, just treat it as if
2869 upper was the index. */
2870 if (simple_cst_equal (lower, upper))
2871 purpose = upper;
2872 else
2874 gimplify_init_ctor_eval_range (object, lower, upper, value,
2875 array_elt_type, pre_p, cleared);
2876 continue;
2880 if (array_elt_type)
2882 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
2883 purpose, NULL_TREE, NULL_TREE);
2885 else
2887 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
2888 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
2889 unshare_expr (object), purpose, NULL_TREE);
2892 if (TREE_CODE (value) == CONSTRUCTOR
2893 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
2894 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
2895 pre_p, cleared);
2896 else
2898 init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
2899 gimplify_and_add (init, pre_p);
2904 /* A subroutine of gimplify_modify_expr. Break out elements of a
2905 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
2907 Note that we still need to clear any elements that don't have explicit
2908 initializers, so if not all elements are initialized we keep the
2909 original MODIFY_EXPR, we just remove all of the constructor elements. */
2911 static enum gimplify_status
2912 gimplify_init_constructor (tree *expr_p, tree *pre_p,
2913 tree *post_p, bool want_value)
2915 tree object;
2916 tree ctor = GENERIC_TREE_OPERAND (*expr_p, 1);
2917 tree type = TREE_TYPE (ctor);
2918 enum gimplify_status ret;
2919 VEC(constructor_elt,gc) *elts;
2921 if (TREE_CODE (ctor) != CONSTRUCTOR)
2922 return GS_UNHANDLED;
2924 ret = gimplify_expr (&GENERIC_TREE_OPERAND (*expr_p, 0), pre_p, post_p,
2925 is_gimple_lvalue, fb_lvalue);
2926 if (ret == GS_ERROR)
2927 return ret;
2928 object = GENERIC_TREE_OPERAND (*expr_p, 0);
2930 elts = CONSTRUCTOR_ELTS (ctor);
2932 ret = GS_ALL_DONE;
2933 switch (TREE_CODE (type))
2935 case RECORD_TYPE:
2936 case UNION_TYPE:
2937 case QUAL_UNION_TYPE:
2938 case ARRAY_TYPE:
2940 struct gimplify_init_ctor_preeval_data preeval_data;
2941 HOST_WIDE_INT num_type_elements, num_ctor_elements;
2942 HOST_WIDE_INT num_nonzero_elements;
2943 bool cleared, valid_const_initializer;
2945 /* Aggregate types must lower constructors to initialization of
2946 individual elements. The exception is that a CONSTRUCTOR node
2947 with no elements indicates zero-initialization of the whole. */
2948 if (VEC_empty (constructor_elt, elts))
2949 break;
2951 /* Fetch information about the constructor to direct later processing.
2952 We might want to make static versions of it in various cases, and
2953 can only do so if it known to be a valid constant initializer. */
2954 valid_const_initializer
2955 = categorize_ctor_elements (ctor, &num_nonzero_elements,
2956 &num_ctor_elements, &cleared);
2958 /* If a const aggregate variable is being initialized, then it
2959 should never be a lose to promote the variable to be static. */
2960 if (valid_const_initializer
2961 && num_nonzero_elements > 1
2962 && TREE_READONLY (object)
2963 && TREE_CODE (object) == VAR_DECL)
2965 DECL_INITIAL (object) = ctor;
2966 TREE_STATIC (object) = 1;
2967 if (!DECL_NAME (object))
2968 DECL_NAME (object) = create_tmp_var_name ("C");
2969 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
2971 /* ??? C++ doesn't automatically append a .<number> to the
2972 assembler name, and even when it does, it looks a FE private
2973 data structures to figure out what that number should be,
2974 which are not set for this variable. I suppose this is
2975 important for local statics for inline functions, which aren't
2976 "local" in the object file sense. So in order to get a unique
2977 TU-local symbol, we must invoke the lhd version now. */
2978 lhd_set_decl_assembler_name (object);
2980 *expr_p = NULL_TREE;
2981 break;
2984 /* If there are "lots" of initialized elements, even discounting
2985 those that are not address constants (and thus *must* be
2986 computed at runtime), then partition the constructor into
2987 constant and non-constant parts. Block copy the constant
2988 parts in, then generate code for the non-constant parts. */
2989 /* TODO. There's code in cp/typeck.c to do this. */
2991 num_type_elements = count_type_elements (type, true);
2993 /* If count_type_elements could not determine number of type elements
2994 for a constant-sized object, assume clearing is needed.
2995 Don't do this for variable-sized objects, as store_constructor
2996 will ignore the clearing of variable-sized objects. */
2997 if (num_type_elements < 0 && int_size_in_bytes (type) >= 0)
2998 cleared = true;
2999 /* If there are "lots" of zeros, then block clear the object first. */
3000 else if (num_type_elements - num_nonzero_elements > CLEAR_RATIO
3001 && num_nonzero_elements < num_type_elements/4)
3002 cleared = true;
3003 /* ??? This bit ought not be needed. For any element not present
3004 in the initializer, we should simply set them to zero. Except
3005 we'd need to *find* the elements that are not present, and that
3006 requires trickery to avoid quadratic compile-time behavior in
3007 large cases or excessive memory use in small cases. */
3008 else if (num_ctor_elements < num_type_elements)
3009 cleared = true;
3011 /* If there are "lots" of initialized elements, and all of them
3012 are valid address constants, then the entire initializer can
3013 be dropped to memory, and then memcpy'd out. Don't do this
3014 for sparse arrays, though, as it's more efficient to follow
3015 the standard CONSTRUCTOR behavior of memset followed by
3016 individual element initialization. */
3017 if (valid_const_initializer && !cleared)
3019 HOST_WIDE_INT size = int_size_in_bytes (type);
3020 unsigned int align;
3022 /* ??? We can still get unbounded array types, at least
3023 from the C++ front end. This seems wrong, but attempt
3024 to work around it for now. */
3025 if (size < 0)
3027 size = int_size_in_bytes (TREE_TYPE (object));
3028 if (size >= 0)
3029 TREE_TYPE (ctor) = type = TREE_TYPE (object);
3032 /* Find the maximum alignment we can assume for the object. */
3033 /* ??? Make use of DECL_OFFSET_ALIGN. */
3034 if (DECL_P (object))
3035 align = DECL_ALIGN (object);
3036 else
3037 align = TYPE_ALIGN (type);
3039 if (size > 0 && !can_move_by_pieces (size, align))
3041 tree new = create_tmp_var_raw (type, "C");
3043 gimple_add_tmp_var (new);
3044 TREE_STATIC (new) = 1;
3045 TREE_READONLY (new) = 1;
3046 DECL_INITIAL (new) = ctor;
3047 if (align > DECL_ALIGN (new))
3049 DECL_ALIGN (new) = align;
3050 DECL_USER_ALIGN (new) = 1;
3052 walk_tree (&DECL_INITIAL (new), force_labels_r, NULL, NULL);
3054 GENERIC_TREE_OPERAND (*expr_p, 1) = new;
3056 /* This is no longer an assignment of a CONSTRUCTOR, but
3057 we still may have processing to do on the LHS. So
3058 pretend we didn't do anything here to let that happen. */
3059 return GS_UNHANDLED;
3063 /* If there are nonzero elements, pre-evaluate to capture elements
3064 overlapping with the lhs into temporaries. We must do this before
3065 clearing to fetch the values before they are zeroed-out. */
3066 if (num_nonzero_elements > 0)
3068 preeval_data.lhs_base_decl = get_base_address (object);
3069 if (!DECL_P (preeval_data.lhs_base_decl))
3070 preeval_data.lhs_base_decl = NULL;
3071 preeval_data.lhs_alias_set = get_alias_set (object);
3073 gimplify_init_ctor_preeval (&GENERIC_TREE_OPERAND (*expr_p, 1),
3074 pre_p, post_p, &preeval_data);
3077 if (cleared)
3079 /* Zap the CONSTRUCTOR element list, which simplifies this case.
3080 Note that we still have to gimplify, in order to handle the
3081 case of variable sized types. Avoid shared tree structures. */
3082 CONSTRUCTOR_ELTS (ctor) = NULL;
3083 object = unshare_expr (object);
3084 gimplify_stmt (expr_p);
3085 append_to_statement_list (*expr_p, pre_p);
3088 /* If we have not block cleared the object, or if there are nonzero
3089 elements in the constructor, add assignments to the individual
3090 scalar fields of the object. */
3091 if (!cleared || num_nonzero_elements > 0)
3092 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
3094 *expr_p = NULL_TREE;
3096 break;
3098 case COMPLEX_TYPE:
3100 tree r, i;
3102 /* Extract the real and imaginary parts out of the ctor. */
3103 gcc_assert (VEC_length (constructor_elt, elts) == 2);
3104 r = VEC_index (constructor_elt, elts, 0)->value;
3105 i = VEC_index (constructor_elt, elts, 1)->value;
3106 if (r == NULL || i == NULL)
3108 tree zero = fold_convert (TREE_TYPE (type), integer_zero_node);
3109 if (r == NULL)
3110 r = zero;
3111 if (i == NULL)
3112 i = zero;
3115 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
3116 represent creation of a complex value. */
3117 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
3119 ctor = build_complex (type, r, i);
3120 TREE_OPERAND (*expr_p, 1) = ctor;
3122 else
3124 ctor = build2 (COMPLEX_EXPR, type, r, i);
3125 TREE_OPERAND (*expr_p, 1) = ctor;
3126 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
3127 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
3128 fb_rvalue);
3131 break;
3133 case VECTOR_TYPE:
3135 unsigned HOST_WIDE_INT ix;
3136 constructor_elt *ce;
3138 /* Go ahead and simplify constant constructors to VECTOR_CST. */
3139 if (TREE_CONSTANT (ctor))
3141 bool constant_p = true;
3142 tree value;
3144 /* Even when ctor is constant, it might contain non-*_CST
3145 elements (e.g. { 1.0/0.0 - 1.0/0.0, 0.0 }) and those don't
3146 belong into VECTOR_CST nodes. */
3147 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
3148 if (!CONSTANT_CLASS_P (value))
3150 constant_p = false;
3151 break;
3154 if (constant_p)
3156 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
3157 break;
3160 /* Don't reduce a TREE_CONSTANT vector ctor even if we can't
3161 make a VECTOR_CST. It won't do anything for us, and it'll
3162 prevent us from representing it as a single constant. */
3163 break;
3166 /* Vector types use CONSTRUCTOR all the way through gimple
3167 compilation as a general initializer. */
3168 for (ix = 0; VEC_iterate (constructor_elt, elts, ix, ce); ix++)
3170 enum gimplify_status tret;
3171 tret = gimplify_expr (&ce->value, pre_p, post_p,
3172 is_gimple_val, fb_rvalue);
3173 if (tret == GS_ERROR)
3174 ret = GS_ERROR;
3176 if (!is_gimple_reg (GENERIC_TREE_OPERAND (*expr_p, 0)))
3177 GENERIC_TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
3179 break;
3181 default:
3182 /* So how did we get a CONSTRUCTOR for a scalar type? */
3183 gcc_unreachable ();
3186 if (ret == GS_ERROR)
3187 return GS_ERROR;
3188 else if (want_value)
3190 append_to_statement_list (*expr_p, pre_p);
3191 *expr_p = object;
3192 return GS_OK;
3194 else
3195 return GS_ALL_DONE;
3198 /* Given a pointer value OP0, return a simplified version of an
3199 indirection through OP0, or NULL_TREE if no simplification is
3200 possible. This may only be applied to a rhs of an expression.
3201 Note that the resulting type may be different from the type pointed
3202 to in the sense that it is still compatible from the langhooks
3203 point of view. */
3205 static tree
3206 fold_indirect_ref_rhs (tree t)
3208 tree type = TREE_TYPE (TREE_TYPE (t));
3209 tree sub = t;
3210 tree subtype;
3212 STRIP_USELESS_TYPE_CONVERSION (sub);
3213 subtype = TREE_TYPE (sub);
3214 if (!POINTER_TYPE_P (subtype))
3215 return NULL_TREE;
3217 if (TREE_CODE (sub) == ADDR_EXPR)
3219 tree op = TREE_OPERAND (sub, 0);
3220 tree optype = TREE_TYPE (op);
3221 /* *&p => p */
3222 if (lang_hooks.types_compatible_p (type, optype))
3223 return op;
3224 /* *(foo *)&fooarray => fooarray[0] */
3225 else if (TREE_CODE (optype) == ARRAY_TYPE
3226 && lang_hooks.types_compatible_p (type, TREE_TYPE (optype)))
3228 tree type_domain = TYPE_DOMAIN (optype);
3229 tree min_val = size_zero_node;
3230 if (type_domain && TYPE_MIN_VALUE (type_domain))
3231 min_val = TYPE_MIN_VALUE (type_domain);
3232 return build4 (ARRAY_REF, type, op, min_val, NULL_TREE, NULL_TREE);
3236 /* *(foo *)fooarrptr => (*fooarrptr)[0] */
3237 if (TREE_CODE (TREE_TYPE (subtype)) == ARRAY_TYPE
3238 && lang_hooks.types_compatible_p (type, TREE_TYPE (TREE_TYPE (subtype))))
3240 tree type_domain;
3241 tree min_val = size_zero_node;
3242 tree osub = sub;
3243 sub = fold_indirect_ref_rhs (sub);
3244 if (! sub)
3245 sub = build1 (INDIRECT_REF, TREE_TYPE (subtype), osub);
3246 type_domain = TYPE_DOMAIN (TREE_TYPE (sub));
3247 if (type_domain && TYPE_MIN_VALUE (type_domain))
3248 min_val = TYPE_MIN_VALUE (type_domain);
3249 return build4 (ARRAY_REF, type, sub, min_val, NULL_TREE, NULL_TREE);
3252 return NULL_TREE;
3255 /* Subroutine of gimplify_modify_expr to do simplifications of MODIFY_EXPRs
3256 based on the code of the RHS. We loop for as long as something changes. */
3258 static enum gimplify_status
3259 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p, tree *pre_p,
3260 tree *post_p, bool want_value)
3262 enum gimplify_status ret = GS_OK;
3264 while (ret != GS_UNHANDLED)
3265 switch (TREE_CODE (*from_p))
3267 case INDIRECT_REF:
3269 /* If we have code like
3271 *(const A*)(A*)&x
3273 where the type of "x" is a (possibly cv-qualified variant
3274 of "A"), treat the entire expression as identical to "x".
3275 This kind of code arises in C++ when an object is bound
3276 to a const reference, and if "x" is a TARGET_EXPR we want
3277 to take advantage of the optimization below. */
3278 tree t = fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
3279 if (t)
3281 *from_p = t;
3282 ret = GS_OK;
3284 else
3285 ret = GS_UNHANDLED;
3286 break;
3289 case TARGET_EXPR:
3291 /* If we are initializing something from a TARGET_EXPR, strip the
3292 TARGET_EXPR and initialize it directly, if possible. This can't
3293 be done if the initializer is void, since that implies that the
3294 temporary is set in some non-trivial way.
3296 ??? What about code that pulls out the temp and uses it
3297 elsewhere? I think that such code never uses the TARGET_EXPR as
3298 an initializer. If I'm wrong, we'll die because the temp won't
3299 have any RTL. In that case, I guess we'll need to replace
3300 references somehow. */
3301 tree init = TARGET_EXPR_INITIAL (*from_p);
3303 if (!VOID_TYPE_P (TREE_TYPE (init)))
3305 *from_p = init;
3306 ret = GS_OK;
3308 else
3309 ret = GS_UNHANDLED;
3311 break;
3313 case COMPOUND_EXPR:
3314 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
3315 caught. */
3316 gimplify_compound_expr (from_p, pre_p, true);
3317 ret = GS_OK;
3318 break;
3320 case CONSTRUCTOR:
3321 /* If we're initializing from a CONSTRUCTOR, break this into
3322 individual MODIFY_EXPRs. */
3323 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value);
3325 case COND_EXPR:
3326 /* If we're assigning to a non-register type, push the assignment
3327 down into the branches. This is mandatory for ADDRESSABLE types,
3328 since we cannot generate temporaries for such, but it saves a
3329 copy in other cases as well. */
3330 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
3332 /* This code should mirror the code in gimplify_cond_expr. */
3333 enum tree_code code = TREE_CODE (*expr_p);
3334 tree cond = *from_p;
3335 tree result = *to_p;
3337 ret = gimplify_expr (&result, pre_p, post_p,
3338 is_gimple_min_lval, fb_lvalue);
3339 if (ret != GS_ERROR)
3340 ret = GS_OK;
3342 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
3343 TREE_OPERAND (cond, 1)
3344 = build2 (code, void_type_node, result,
3345 TREE_OPERAND (cond, 1));
3346 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
3347 TREE_OPERAND (cond, 2)
3348 = build2 (code, void_type_node, unshare_expr (result),
3349 TREE_OPERAND (cond, 2));
3351 TREE_TYPE (cond) = void_type_node;
3352 recalculate_side_effects (cond);
3354 if (want_value)
3356 gimplify_and_add (cond, pre_p);
3357 *expr_p = unshare_expr (result);
3359 else
3360 *expr_p = cond;
3361 return ret;
3363 else
3364 ret = GS_UNHANDLED;
3365 break;
3367 case CALL_EXPR:
3368 /* For calls that return in memory, give *to_p as the CALL_EXPR's
3369 return slot so that we don't generate a temporary. */
3370 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
3371 && aggregate_value_p (*from_p, *from_p))
3373 bool use_target;
3375 if (!(rhs_predicate_for (*to_p))(*from_p))
3376 /* If we need a temporary, *to_p isn't accurate. */
3377 use_target = false;
3378 else if (TREE_CODE (*to_p) == RESULT_DECL
3379 && DECL_NAME (*to_p) == NULL_TREE
3380 && needs_to_live_in_memory (*to_p))
3381 /* It's OK to use the return slot directly unless it's an NRV. */
3382 use_target = true;
3383 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
3384 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
3385 /* Don't force regs into memory. */
3386 use_target = false;
3387 else if (TREE_CODE (*to_p) == VAR_DECL
3388 && DECL_GIMPLE_FORMAL_TEMP_P (*to_p))
3389 /* Don't use the original target if it's a formal temp; we
3390 don't want to take their addresses. */
3391 use_target = false;
3392 else if (TREE_CODE (*expr_p) == INIT_EXPR)
3393 /* It's OK to use the target directly if it's being
3394 initialized. */
3395 use_target = true;
3396 else if (!is_gimple_non_addressable (*to_p))
3397 /* Don't use the original target if it's already addressable;
3398 if its address escapes, and the called function uses the
3399 NRV optimization, a conforming program could see *to_p
3400 change before the called function returns; see c++/19317.
3401 When optimizing, the return_slot pass marks more functions
3402 as safe after we have escape info. */
3403 use_target = false;
3404 else
3405 use_target = true;
3407 if (use_target)
3409 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
3410 lang_hooks.mark_addressable (*to_p);
3414 ret = GS_UNHANDLED;
3415 break;
3417 /* If we're initializing from a container, push the initialization
3418 inside it. */
3419 case CLEANUP_POINT_EXPR:
3420 case BIND_EXPR:
3421 case STATEMENT_LIST:
3423 tree wrap = *from_p;
3424 tree t;
3426 ret = gimplify_expr (to_p, pre_p, post_p,
3427 is_gimple_min_lval, fb_lvalue);
3428 if (ret != GS_ERROR)
3429 ret = GS_OK;
3431 t = voidify_wrapper_expr (wrap, *expr_p);
3432 gcc_assert (t == *expr_p);
3434 if (want_value)
3436 gimplify_and_add (wrap, pre_p);
3437 *expr_p = unshare_expr (*to_p);
3439 else
3440 *expr_p = wrap;
3441 return GS_OK;
3444 default:
3445 ret = GS_UNHANDLED;
3446 break;
3449 return ret;
3452 /* Destructively convert the TREE pointer in TP into a gimple tuple if
3453 appropriate. */
3455 static void
3456 tree_to_gimple_tuple (tree *tp)
3459 switch (TREE_CODE (*tp))
3461 case GIMPLE_MODIFY_STMT:
3462 return;
3463 case MODIFY_EXPR:
3465 struct gimple_stmt *gs;
3466 tree lhs = TREE_OPERAND (*tp, 0);
3467 bool def_stmt_self_p = false;
3469 if (TREE_CODE (lhs) == SSA_NAME)
3471 if (SSA_NAME_DEF_STMT (lhs) == *tp)
3472 def_stmt_self_p = true;
3475 gs = &make_node (GIMPLE_MODIFY_STMT)->gstmt;
3476 gs->base = (*tp)->base;
3477 /* The set to base above overwrites the CODE. */
3478 TREE_SET_CODE ((tree) gs, GIMPLE_MODIFY_STMT);
3480 gs->locus = EXPR_LOCUS (*tp);
3481 gs->operands[0] = TREE_OPERAND (*tp, 0);
3482 gs->operands[1] = TREE_OPERAND (*tp, 1);
3483 gs->block = TREE_BLOCK (*tp);
3484 *tp = (tree)gs;
3486 /* If we re-gimplify a set to an SSA_NAME, we must change the
3487 SSA name's DEF_STMT link. */
3488 if (def_stmt_self_p)
3489 SSA_NAME_DEF_STMT (GIMPLE_STMT_OPERAND (*tp, 0)) = *tp;
3491 return;
3493 default:
3494 break;
3498 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
3499 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a variable with
3500 DECL_GIMPLE_REG_P set. */
3502 static enum gimplify_status
3503 gimplify_modify_expr_complex_part (tree *expr_p, tree *pre_p, bool want_value)
3505 enum tree_code code, ocode;
3506 tree lhs, rhs, new_rhs, other, realpart, imagpart;
3508 lhs = GENERIC_TREE_OPERAND (*expr_p, 0);
3509 rhs = GENERIC_TREE_OPERAND (*expr_p, 1);
3510 code = TREE_CODE (lhs);
3511 lhs = TREE_OPERAND (lhs, 0);
3513 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
3514 other = build1 (ocode, TREE_TYPE (rhs), lhs);
3515 other = get_formal_tmp_var (other, pre_p);
3517 realpart = code == REALPART_EXPR ? rhs : other;
3518 imagpart = code == REALPART_EXPR ? other : rhs;
3520 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
3521 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
3522 else
3523 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
3525 GENERIC_TREE_OPERAND (*expr_p, 0) = lhs;
3526 GENERIC_TREE_OPERAND (*expr_p, 1) = new_rhs;
3528 if (want_value)
3530 tree_to_gimple_tuple (expr_p);
3532 append_to_statement_list (*expr_p, pre_p);
3533 *expr_p = rhs;
3536 return GS_ALL_DONE;
3539 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
3541 modify_expr
3542 : varname '=' rhs
3543 | '*' ID '=' rhs
3545 PRE_P points to the list where side effects that must happen before
3546 *EXPR_P should be stored.
3548 POST_P points to the list where side effects that must happen after
3549 *EXPR_P should be stored.
3551 WANT_VALUE is nonzero iff we want to use the value of this expression
3552 in another expression. */
3554 static enum gimplify_status
3555 gimplify_modify_expr (tree *expr_p, tree *pre_p, tree *post_p, bool want_value)
3557 tree *from_p = &GENERIC_TREE_OPERAND (*expr_p, 1);
3558 tree *to_p = &GENERIC_TREE_OPERAND (*expr_p, 0);
3559 enum gimplify_status ret = GS_UNHANDLED;
3561 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
3562 || TREE_CODE (*expr_p) == GIMPLE_MODIFY_STMT
3563 || TREE_CODE (*expr_p) == INIT_EXPR);
3565 /* For zero sized types only gimplify the left hand side and right hand side
3566 as statements and throw away the assignment. */
3567 if (zero_sized_type (TREE_TYPE (*from_p)))
3569 gimplify_stmt (from_p);
3570 gimplify_stmt (to_p);
3571 append_to_statement_list (*from_p, pre_p);
3572 append_to_statement_list (*to_p, pre_p);
3573 *expr_p = NULL_TREE;
3574 return GS_ALL_DONE;
3577 /* See if any simplifications can be done based on what the RHS is. */
3578 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
3579 want_value);
3580 if (ret != GS_UNHANDLED)
3581 return ret;
3583 /* If the value being copied is of variable width, compute the length
3584 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
3585 before gimplifying any of the operands so that we can resolve any
3586 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
3587 the size of the expression to be copied, not of the destination, so
3588 that is what we must here. */
3589 maybe_with_size_expr (from_p);
3591 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3592 if (ret == GS_ERROR)
3593 return ret;
3595 ret = gimplify_expr (from_p, pre_p, post_p,
3596 rhs_predicate_for (*to_p), fb_rvalue);
3597 if (ret == GS_ERROR)
3598 return ret;
3600 /* Now see if the above changed *from_p to something we handle specially. */
3601 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
3602 want_value);
3603 if (ret != GS_UNHANDLED)
3604 return ret;
3606 /* If we've got a variable sized assignment between two lvalues (i.e. does
3607 not involve a call), then we can make things a bit more straightforward
3608 by converting the assignment to memcpy or memset. */
3609 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
3611 tree from = TREE_OPERAND (*from_p, 0);
3612 tree size = TREE_OPERAND (*from_p, 1);
3614 if (TREE_CODE (from) == CONSTRUCTOR)
3615 return gimplify_modify_expr_to_memset (expr_p, size, want_value);
3616 if (is_gimple_addressable (from))
3618 *from_p = from;
3619 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value);
3623 /* Transform partial stores to non-addressable complex variables into
3624 total stores. This allows us to use real instead of virtual operands
3625 for these variables, which improves optimization. */
3626 if ((TREE_CODE (*to_p) == REALPART_EXPR
3627 || TREE_CODE (*to_p) == IMAGPART_EXPR)
3628 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
3629 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
3631 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
3633 /* If we've somehow already got an SSA_NAME on the LHS, then
3634 we're probably modified it twice. Not good. */
3635 gcc_assert (TREE_CODE (*to_p) != SSA_NAME);
3636 *to_p = make_ssa_name (*to_p, *expr_p);
3639 /* Try to alleviate the effects of the gimplification creating artificial
3640 temporaries (see for example is_gimple_reg_rhs) on the debug info. */
3641 if (!gimplify_ctxp->into_ssa
3642 && DECL_P (*from_p) && DECL_IGNORED_P (*from_p)
3643 && DECL_P (*to_p) && !DECL_IGNORED_P (*to_p))
3645 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
3646 DECL_NAME (*from_p)
3647 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
3648 DECL_DEBUG_EXPR_IS_FROM (*from_p) = 1;
3649 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
3652 if (want_value)
3654 tree_to_gimple_tuple (expr_p);
3656 append_to_statement_list (*expr_p, pre_p);
3657 *expr_p = *to_p;
3658 return GS_OK;
3661 return GS_ALL_DONE;
3664 /* Gimplify a comparison between two variable-sized objects. Do this
3665 with a call to BUILT_IN_MEMCMP. */
3667 static enum gimplify_status
3668 gimplify_variable_sized_compare (tree *expr_p)
3670 tree op0 = TREE_OPERAND (*expr_p, 0);
3671 tree op1 = TREE_OPERAND (*expr_p, 1);
3672 tree t, arg, dest, src;
3674 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
3675 arg = unshare_expr (arg);
3676 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
3677 src = build_fold_addr_expr (op1);
3678 dest = build_fold_addr_expr (op0);
3679 t = implicit_built_in_decls[BUILT_IN_MEMCMP];
3680 t = build_call_expr (t, 3, dest, src, arg);
3681 *expr_p
3682 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
3684 return GS_OK;
3687 /* Gimplify a comparison between two aggregate objects of integral scalar
3688 mode as a comparison between the bitwise equivalent scalar values. */
3690 static enum gimplify_status
3691 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
3693 tree op0 = TREE_OPERAND (*expr_p, 0);
3694 tree op1 = TREE_OPERAND (*expr_p, 1);
3696 tree type = TREE_TYPE (op0);
3697 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
3699 op0 = fold_build1 (VIEW_CONVERT_EXPR, scalar_type, op0);
3700 op1 = fold_build1 (VIEW_CONVERT_EXPR, scalar_type, op1);
3702 *expr_p
3703 = fold_build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
3705 return GS_OK;
3708 /* Gimplify TRUTH_ANDIF_EXPR and TRUTH_ORIF_EXPR expressions. EXPR_P
3709 points to the expression to gimplify.
3711 Expressions of the form 'a && b' are gimplified to:
3713 a && b ? true : false
3715 gimplify_cond_expr will do the rest.
3717 PRE_P points to the list where side effects that must happen before
3718 *EXPR_P should be stored. */
3720 static enum gimplify_status
3721 gimplify_boolean_expr (tree *expr_p)
3723 /* Preserve the original type of the expression. */
3724 tree type = TREE_TYPE (*expr_p);
3726 *expr_p = build3 (COND_EXPR, type, *expr_p,
3727 fold_convert (type, boolean_true_node),
3728 fold_convert (type, boolean_false_node));
3730 return GS_OK;
3733 /* Gimplifies an expression sequence. This function gimplifies each
3734 expression and re-writes the original expression with the last
3735 expression of the sequence in GIMPLE form.
3737 PRE_P points to the list where the side effects for all the
3738 expressions in the sequence will be emitted.
3740 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
3741 /* ??? Should rearrange to share the pre-queue with all the indirect
3742 invocations of gimplify_expr. Would probably save on creations
3743 of statement_list nodes. */
3745 static enum gimplify_status
3746 gimplify_compound_expr (tree *expr_p, tree *pre_p, bool want_value)
3748 tree t = *expr_p;
3752 tree *sub_p = &TREE_OPERAND (t, 0);
3754 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
3755 gimplify_compound_expr (sub_p, pre_p, false);
3756 else
3757 gimplify_stmt (sub_p);
3758 append_to_statement_list (*sub_p, pre_p);
3760 t = TREE_OPERAND (t, 1);
3762 while (TREE_CODE (t) == COMPOUND_EXPR);
3764 *expr_p = t;
3765 if (want_value)
3766 return GS_OK;
3767 else
3769 gimplify_stmt (expr_p);
3770 return GS_ALL_DONE;
3774 /* Gimplifies a statement list. These may be created either by an
3775 enlightened front-end, or by shortcut_cond_expr. */
3777 static enum gimplify_status
3778 gimplify_statement_list (tree *expr_p, tree *pre_p)
3780 tree temp = voidify_wrapper_expr (*expr_p, NULL);
3782 tree_stmt_iterator i = tsi_start (*expr_p);
3784 while (!tsi_end_p (i))
3786 tree t;
3788 gimplify_stmt (tsi_stmt_ptr (i));
3790 t = tsi_stmt (i);
3791 if (t == NULL)
3792 tsi_delink (&i);
3793 else if (TREE_CODE (t) == STATEMENT_LIST)
3795 tsi_link_before (&i, t, TSI_SAME_STMT);
3796 tsi_delink (&i);
3798 else
3799 tsi_next (&i);
3802 if (temp)
3804 append_to_statement_list (*expr_p, pre_p);
3805 *expr_p = temp;
3806 return GS_OK;
3809 return GS_ALL_DONE;
3812 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
3813 gimplify. After gimplification, EXPR_P will point to a new temporary
3814 that holds the original value of the SAVE_EXPR node.
3816 PRE_P points to the list where side effects that must happen before
3817 *EXPR_P should be stored. */
3819 static enum gimplify_status
3820 gimplify_save_expr (tree *expr_p, tree *pre_p, tree *post_p)
3822 enum gimplify_status ret = GS_ALL_DONE;
3823 tree val;
3825 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
3826 val = TREE_OPERAND (*expr_p, 0);
3828 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
3829 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
3831 /* The operand may be a void-valued expression such as SAVE_EXPRs
3832 generated by the Java frontend for class initialization. It is
3833 being executed only for its side-effects. */
3834 if (TREE_TYPE (val) == void_type_node)
3836 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3837 is_gimple_stmt, fb_none);
3838 append_to_statement_list (TREE_OPERAND (*expr_p, 0), pre_p);
3839 val = NULL;
3841 else
3842 val = get_initialized_tmp_var (val, pre_p, post_p);
3844 TREE_OPERAND (*expr_p, 0) = val;
3845 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
3848 *expr_p = val;
3850 return ret;
3853 /* Re-write the ADDR_EXPR node pointed to by EXPR_P
3855 unary_expr
3856 : ...
3857 | '&' varname
3860 PRE_P points to the list where side effects that must happen before
3861 *EXPR_P should be stored.
3863 POST_P points to the list where side effects that must happen after
3864 *EXPR_P should be stored. */
3866 static enum gimplify_status
3867 gimplify_addr_expr (tree *expr_p, tree *pre_p, tree *post_p)
3869 tree expr = *expr_p;
3870 tree op0 = TREE_OPERAND (expr, 0);
3871 enum gimplify_status ret;
3873 switch (TREE_CODE (op0))
3875 case INDIRECT_REF:
3876 case MISALIGNED_INDIRECT_REF:
3877 do_indirect_ref:
3878 /* Check if we are dealing with an expression of the form '&*ptr'.
3879 While the front end folds away '&*ptr' into 'ptr', these
3880 expressions may be generated internally by the compiler (e.g.,
3881 builtins like __builtin_va_end). */
3882 /* Caution: the silent array decomposition semantics we allow for
3883 ADDR_EXPR means we can't always discard the pair. */
3884 /* Gimplification of the ADDR_EXPR operand may drop
3885 cv-qualification conversions, so make sure we add them if
3886 needed. */
3888 tree op00 = TREE_OPERAND (op0, 0);
3889 tree t_expr = TREE_TYPE (expr);
3890 tree t_op00 = TREE_TYPE (op00);
3892 if (!lang_hooks.types_compatible_p (t_expr, t_op00))
3894 #ifdef ENABLE_CHECKING
3895 tree t_op0 = TREE_TYPE (op0);
3896 gcc_assert (POINTER_TYPE_P (t_expr)
3897 && cpt_same_type (TREE_CODE (t_op0) == ARRAY_TYPE
3898 ? TREE_TYPE (t_op0) : t_op0,
3899 TREE_TYPE (t_expr))
3900 && POINTER_TYPE_P (t_op00)
3901 && cpt_same_type (t_op0, TREE_TYPE (t_op00)));
3902 #endif
3903 op00 = fold_convert (TREE_TYPE (expr), op00);
3905 *expr_p = op00;
3906 ret = GS_OK;
3908 break;
3910 case VIEW_CONVERT_EXPR:
3911 /* Take the address of our operand and then convert it to the type of
3912 this ADDR_EXPR.
3914 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
3915 all clear. The impact of this transformation is even less clear. */
3917 /* If the operand is a useless conversion, look through it. Doing so
3918 guarantees that the ADDR_EXPR and its operand will remain of the
3919 same type. */
3920 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
3921 op0 = TREE_OPERAND (op0, 0);
3923 *expr_p = fold_convert (TREE_TYPE (expr),
3924 build_fold_addr_expr (TREE_OPERAND (op0, 0)));
3925 ret = GS_OK;
3926 break;
3928 default:
3929 /* We use fb_either here because the C frontend sometimes takes
3930 the address of a call that returns a struct; see
3931 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
3932 the implied temporary explicit. */
3933 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
3934 is_gimple_addressable, fb_either);
3935 if (ret != GS_ERROR)
3937 op0 = TREE_OPERAND (expr, 0);
3939 /* For various reasons, the gimplification of the expression
3940 may have made a new INDIRECT_REF. */
3941 if (TREE_CODE (op0) == INDIRECT_REF)
3942 goto do_indirect_ref;
3944 /* Make sure TREE_INVARIANT, TREE_CONSTANT, and TREE_SIDE_EFFECTS
3945 is set properly. */
3946 recompute_tree_invariant_for_addr_expr (expr);
3948 /* Mark the RHS addressable. */
3949 lang_hooks.mark_addressable (TREE_OPERAND (expr, 0));
3951 break;
3954 return ret;
3957 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
3958 value; output operands should be a gimple lvalue. */
3960 static enum gimplify_status
3961 gimplify_asm_expr (tree *expr_p, tree *pre_p, tree *post_p)
3963 tree expr = *expr_p;
3964 int noutputs = list_length (ASM_OUTPUTS (expr));
3965 const char **oconstraints
3966 = (const char **) alloca ((noutputs) * sizeof (const char *));
3967 int i;
3968 tree link;
3969 const char *constraint;
3970 bool allows_mem, allows_reg, is_inout;
3971 enum gimplify_status ret, tret;
3973 ret = GS_ALL_DONE;
3974 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = TREE_CHAIN (link))
3976 size_t constraint_len;
3977 oconstraints[i] = constraint
3978 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
3979 constraint_len = strlen (constraint);
3980 if (constraint_len == 0)
3981 continue;
3983 parse_output_constraint (&constraint, i, 0, 0,
3984 &allows_mem, &allows_reg, &is_inout);
3986 if (!allows_reg && allows_mem)
3987 lang_hooks.mark_addressable (TREE_VALUE (link));
3989 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
3990 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
3991 fb_lvalue | fb_mayfail);
3992 if (tret == GS_ERROR)
3994 error ("invalid lvalue in asm output %d", i);
3995 ret = tret;
3998 if (is_inout)
4000 /* An input/output operand. To give the optimizers more
4001 flexibility, split it into separate input and output
4002 operands. */
4003 tree input;
4004 char buf[10];
4006 /* Turn the in/out constraint into an output constraint. */
4007 char *p = xstrdup (constraint);
4008 p[0] = '=';
4009 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
4011 /* And add a matching input constraint. */
4012 if (allows_reg)
4014 sprintf (buf, "%d", i);
4016 /* If there are multiple alternatives in the constraint,
4017 handle each of them individually. Those that allow register
4018 will be replaced with operand number, the others will stay
4019 unchanged. */
4020 if (strchr (p, ',') != NULL)
4022 size_t len = 0, buflen = strlen (buf);
4023 char *beg, *end, *str, *dst;
4025 for (beg = p + 1;;)
4027 end = strchr (beg, ',');
4028 if (end == NULL)
4029 end = strchr (beg, '\0');
4030 if ((size_t) (end - beg) < buflen)
4031 len += buflen + 1;
4032 else
4033 len += end - beg + 1;
4034 if (*end)
4035 beg = end + 1;
4036 else
4037 break;
4040 str = (char *) alloca (len);
4041 for (beg = p + 1, dst = str;;)
4043 const char *tem;
4044 bool mem_p, reg_p, inout_p;
4046 end = strchr (beg, ',');
4047 if (end)
4048 *end = '\0';
4049 beg[-1] = '=';
4050 tem = beg - 1;
4051 parse_output_constraint (&tem, i, 0, 0,
4052 &mem_p, &reg_p, &inout_p);
4053 if (dst != str)
4054 *dst++ = ',';
4055 if (reg_p)
4057 memcpy (dst, buf, buflen);
4058 dst += buflen;
4060 else
4062 if (end)
4063 len = end - beg;
4064 else
4065 len = strlen (beg);
4066 memcpy (dst, beg, len);
4067 dst += len;
4069 if (end)
4070 beg = end + 1;
4071 else
4072 break;
4074 *dst = '\0';
4075 input = build_string (dst - str, str);
4077 else
4078 input = build_string (strlen (buf), buf);
4080 else
4081 input = build_string (constraint_len - 1, constraint + 1);
4083 free (p);
4085 input = build_tree_list (build_tree_list (NULL_TREE, input),
4086 unshare_expr (TREE_VALUE (link)));
4087 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
4091 for (link = ASM_INPUTS (expr); link; ++i, link = TREE_CHAIN (link))
4093 constraint
4094 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
4095 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
4096 oconstraints, &allows_mem, &allows_reg);
4098 /* If the operand is a memory input, it should be an lvalue. */
4099 if (!allows_reg && allows_mem)
4101 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
4102 is_gimple_lvalue, fb_lvalue | fb_mayfail);
4103 lang_hooks.mark_addressable (TREE_VALUE (link));
4104 if (tret == GS_ERROR)
4106 error ("memory input %d is not directly addressable", i);
4107 ret = tret;
4110 else
4112 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
4113 is_gimple_asm_val, fb_rvalue);
4114 if (tret == GS_ERROR)
4115 ret = tret;
4119 return ret;
4122 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
4123 WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
4124 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
4125 return to this function.
4127 FIXME should we complexify the prequeue handling instead? Or use flags
4128 for all the cleanups and let the optimizer tighten them up? The current
4129 code seems pretty fragile; it will break on a cleanup within any
4130 non-conditional nesting. But any such nesting would be broken, anyway;
4131 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
4132 and continues out of it. We can do that at the RTL level, though, so
4133 having an optimizer to tighten up try/finally regions would be a Good
4134 Thing. */
4136 static enum gimplify_status
4137 gimplify_cleanup_point_expr (tree *expr_p, tree *pre_p)
4139 tree_stmt_iterator iter;
4140 tree body;
4142 tree temp = voidify_wrapper_expr (*expr_p, NULL);
4144 /* We only care about the number of conditions between the innermost
4145 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
4146 any cleanups collected outside the CLEANUP_POINT_EXPR. */
4147 int old_conds = gimplify_ctxp->conditions;
4148 tree old_cleanups = gimplify_ctxp->conditional_cleanups;
4149 gimplify_ctxp->conditions = 0;
4150 gimplify_ctxp->conditional_cleanups = NULL_TREE;
4152 body = TREE_OPERAND (*expr_p, 0);
4153 gimplify_to_stmt_list (&body);
4155 gimplify_ctxp->conditions = old_conds;
4156 gimplify_ctxp->conditional_cleanups = old_cleanups;
4158 for (iter = tsi_start (body); !tsi_end_p (iter); )
4160 tree *wce_p = tsi_stmt_ptr (iter);
4161 tree wce = *wce_p;
4163 if (TREE_CODE (wce) == WITH_CLEANUP_EXPR)
4165 if (tsi_one_before_end_p (iter))
4167 tsi_link_before (&iter, TREE_OPERAND (wce, 0), TSI_SAME_STMT);
4168 tsi_delink (&iter);
4169 break;
4171 else
4173 tree sl, tfe;
4174 enum tree_code code;
4176 if (CLEANUP_EH_ONLY (wce))
4177 code = TRY_CATCH_EXPR;
4178 else
4179 code = TRY_FINALLY_EXPR;
4181 sl = tsi_split_statement_list_after (&iter);
4182 tfe = build2 (code, void_type_node, sl, NULL_TREE);
4183 append_to_statement_list (TREE_OPERAND (wce, 0),
4184 &TREE_OPERAND (tfe, 1));
4185 *wce_p = tfe;
4186 iter = tsi_start (sl);
4189 else
4190 tsi_next (&iter);
4193 if (temp)
4195 *expr_p = temp;
4196 append_to_statement_list (body, pre_p);
4197 return GS_OK;
4199 else
4201 *expr_p = body;
4202 return GS_ALL_DONE;
4206 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
4207 is the cleanup action required. */
4209 static void
4210 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, tree *pre_p)
4212 tree wce;
4214 /* Errors can result in improperly nested cleanups. Which results in
4215 confusion when trying to resolve the WITH_CLEANUP_EXPR. */
4216 if (errorcount || sorrycount)
4217 return;
4219 if (gimple_conditional_context ())
4221 /* If we're in a conditional context, this is more complex. We only
4222 want to run the cleanup if we actually ran the initialization that
4223 necessitates it, but we want to run it after the end of the
4224 conditional context. So we wrap the try/finally around the
4225 condition and use a flag to determine whether or not to actually
4226 run the destructor. Thus
4228 test ? f(A()) : 0
4230 becomes (approximately)
4232 flag = 0;
4233 try {
4234 if (test) { A::A(temp); flag = 1; val = f(temp); }
4235 else { val = 0; }
4236 } finally {
4237 if (flag) A::~A(temp);
4242 tree flag = create_tmp_var (boolean_type_node, "cleanup");
4243 tree ffalse = build2 (GIMPLE_MODIFY_STMT, void_type_node, flag,
4244 boolean_false_node);
4245 tree ftrue = build2 (GIMPLE_MODIFY_STMT, void_type_node, flag,
4246 boolean_true_node);
4247 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
4248 wce = build1 (WITH_CLEANUP_EXPR, void_type_node, cleanup);
4249 append_to_statement_list (ffalse, &gimplify_ctxp->conditional_cleanups);
4250 append_to_statement_list (wce, &gimplify_ctxp->conditional_cleanups);
4251 append_to_statement_list (ftrue, pre_p);
4253 /* Because of this manipulation, and the EH edges that jump
4254 threading cannot redirect, the temporary (VAR) will appear
4255 to be used uninitialized. Don't warn. */
4256 TREE_NO_WARNING (var) = 1;
4258 else
4260 wce = build1 (WITH_CLEANUP_EXPR, void_type_node, cleanup);
4261 CLEANUP_EH_ONLY (wce) = eh_only;
4262 append_to_statement_list (wce, pre_p);
4265 gimplify_stmt (&TREE_OPERAND (wce, 0));
4268 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
4270 static enum gimplify_status
4271 gimplify_target_expr (tree *expr_p, tree *pre_p, tree *post_p)
4273 tree targ = *expr_p;
4274 tree temp = TARGET_EXPR_SLOT (targ);
4275 tree init = TARGET_EXPR_INITIAL (targ);
4276 enum gimplify_status ret;
4278 if (init)
4280 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
4281 to the temps list. */
4282 gimple_add_tmp_var (temp);
4284 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
4285 expression is supposed to initialize the slot. */
4286 if (VOID_TYPE_P (TREE_TYPE (init)))
4287 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
4288 else
4290 init = build2 (INIT_EXPR, void_type_node, temp, init);
4291 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt,
4292 fb_none);
4294 if (ret == GS_ERROR)
4296 /* PR c++/28266 Make sure this is expanded only once. */
4297 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
4298 return GS_ERROR;
4300 append_to_statement_list (init, pre_p);
4302 /* If needed, push the cleanup for the temp. */
4303 if (TARGET_EXPR_CLEANUP (targ))
4305 gimplify_stmt (&TARGET_EXPR_CLEANUP (targ));
4306 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
4307 CLEANUP_EH_ONLY (targ), pre_p);
4310 /* Only expand this once. */
4311 TREE_OPERAND (targ, 3) = init;
4312 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
4314 else
4315 /* We should have expanded this before. */
4316 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
4318 *expr_p = temp;
4319 return GS_OK;
4322 /* Gimplification of expression trees. */
4324 /* Gimplify an expression which appears at statement context; usually, this
4325 means replacing it with a suitably gimple STATEMENT_LIST. */
4327 void
4328 gimplify_stmt (tree *stmt_p)
4330 gimplify_expr (stmt_p, NULL, NULL, is_gimple_stmt, fb_none);
4333 /* Similarly, but force the result to be a STATEMENT_LIST. */
4335 void
4336 gimplify_to_stmt_list (tree *stmt_p)
4338 gimplify_stmt (stmt_p);
4339 if (!*stmt_p)
4340 *stmt_p = alloc_stmt_list ();
4341 else if (TREE_CODE (*stmt_p) != STATEMENT_LIST)
4343 tree t = *stmt_p;
4344 *stmt_p = alloc_stmt_list ();
4345 append_to_statement_list (t, stmt_p);
4350 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
4351 to CTX. If entries already exist, force them to be some flavor of private.
4352 If there is no enclosing parallel, do nothing. */
4354 void
4355 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
4357 splay_tree_node n;
4359 if (decl == NULL || !DECL_P (decl))
4360 return;
4364 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
4365 if (n != NULL)
4367 if (n->value & GOVD_SHARED)
4368 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
4369 else
4370 return;
4372 else if (ctx->is_parallel)
4373 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
4375 ctx = ctx->outer_context;
4377 while (ctx);
4380 /* Similarly for each of the type sizes of TYPE. */
4382 static void
4383 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
4385 if (type == NULL || type == error_mark_node)
4386 return;
4387 type = TYPE_MAIN_VARIANT (type);
4389 if (pointer_set_insert (ctx->privatized_types, type))
4390 return;
4392 switch (TREE_CODE (type))
4394 case INTEGER_TYPE:
4395 case ENUMERAL_TYPE:
4396 case BOOLEAN_TYPE:
4397 case REAL_TYPE:
4398 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
4399 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
4400 break;
4402 case ARRAY_TYPE:
4403 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
4404 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
4405 break;
4407 case RECORD_TYPE:
4408 case UNION_TYPE:
4409 case QUAL_UNION_TYPE:
4411 tree field;
4412 for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
4413 if (TREE_CODE (field) == FIELD_DECL)
4415 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
4416 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
4419 break;
4421 case POINTER_TYPE:
4422 case REFERENCE_TYPE:
4423 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
4424 break;
4426 default:
4427 break;
4430 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
4431 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
4432 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
4435 /* Add an entry for DECL in the OpenMP context CTX with FLAGS. */
4437 static void
4438 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
4440 splay_tree_node n;
4441 unsigned int nflags;
4442 tree t;
4444 if (decl == error_mark_node || TREE_TYPE (decl) == error_mark_node)
4445 return;
4447 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
4448 there are constructors involved somewhere. */
4449 if (TREE_ADDRESSABLE (TREE_TYPE (decl))
4450 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
4451 flags |= GOVD_SEEN;
4453 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
4454 if (n != NULL)
4456 /* We shouldn't be re-adding the decl with the same data
4457 sharing class. */
4458 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
4459 /* The only combination of data sharing classes we should see is
4460 FIRSTPRIVATE and LASTPRIVATE. */
4461 nflags = n->value | flags;
4462 gcc_assert ((nflags & GOVD_DATA_SHARE_CLASS)
4463 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE));
4464 n->value = nflags;
4465 return;
4468 /* When adding a variable-sized variable, we have to handle all sorts
4469 of additional bits of data: the pointer replacement variable, and
4470 the parameters of the type. */
4471 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
4473 /* Add the pointer replacement variable as PRIVATE if the variable
4474 replacement is private, else FIRSTPRIVATE since we'll need the
4475 address of the original variable either for SHARED, or for the
4476 copy into or out of the context. */
4477 if (!(flags & GOVD_LOCAL))
4479 nflags = flags & GOVD_PRIVATE ? GOVD_PRIVATE : GOVD_FIRSTPRIVATE;
4480 nflags |= flags & GOVD_SEEN;
4481 t = DECL_VALUE_EXPR (decl);
4482 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
4483 t = TREE_OPERAND (t, 0);
4484 gcc_assert (DECL_P (t));
4485 omp_add_variable (ctx, t, nflags);
4488 /* Add all of the variable and type parameters (which should have
4489 been gimplified to a formal temporary) as FIRSTPRIVATE. */
4490 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
4491 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
4492 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
4494 /* The variable-sized variable itself is never SHARED, only some form
4495 of PRIVATE. The sharing would take place via the pointer variable
4496 which we remapped above. */
4497 if (flags & GOVD_SHARED)
4498 flags = GOVD_PRIVATE | GOVD_DEBUG_PRIVATE
4499 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
4501 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
4502 alloca statement we generate for the variable, so make sure it
4503 is available. This isn't automatically needed for the SHARED
4504 case, since we won't be allocating local storage then.
4505 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
4506 in this case omp_notice_variable will be called later
4507 on when it is gimplified. */
4508 else if (! (flags & GOVD_LOCAL))
4509 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
4511 else if (lang_hooks.decls.omp_privatize_by_reference (decl))
4513 gcc_assert ((flags & GOVD_LOCAL) == 0);
4514 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
4516 /* Similar to the direct variable sized case above, we'll need the
4517 size of references being privatized. */
4518 if ((flags & GOVD_SHARED) == 0)
4520 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
4521 if (TREE_CODE (t) != INTEGER_CST)
4522 omp_notice_variable (ctx, t, true);
4526 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
4529 /* Record the fact that DECL was used within the OpenMP context CTX.
4530 IN_CODE is true when real code uses DECL, and false when we should
4531 merely emit default(none) errors. Return true if DECL is going to
4532 be remapped and thus DECL shouldn't be gimplified into its
4533 DECL_VALUE_EXPR (if any). */
4535 static bool
4536 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
4538 splay_tree_node n;
4539 unsigned flags = in_code ? GOVD_SEEN : 0;
4540 bool ret = false, shared;
4542 if (decl == error_mark_node || TREE_TYPE (decl) == error_mark_node)
4543 return false;
4545 /* Threadprivate variables are predetermined. */
4546 if (is_global_var (decl))
4548 if (DECL_THREAD_LOCAL_P (decl))
4549 return false;
4551 if (DECL_HAS_VALUE_EXPR_P (decl))
4553 tree value = get_base_address (DECL_VALUE_EXPR (decl));
4555 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
4556 return false;
4560 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
4561 if (n == NULL)
4563 enum omp_clause_default_kind default_kind, kind;
4565 if (!ctx->is_parallel)
4566 goto do_outer;
4568 /* ??? Some compiler-generated variables (like SAVE_EXPRs) could be
4569 remapped firstprivate instead of shared. To some extent this is
4570 addressed in omp_firstprivatize_type_sizes, but not effectively. */
4571 default_kind = ctx->default_kind;
4572 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
4573 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
4574 default_kind = kind;
4576 switch (default_kind)
4578 case OMP_CLAUSE_DEFAULT_NONE:
4579 error ("%qs not specified in enclosing parallel",
4580 IDENTIFIER_POINTER (DECL_NAME (decl)));
4581 error ("%Henclosing parallel", &ctx->location);
4582 /* FALLTHRU */
4583 case OMP_CLAUSE_DEFAULT_SHARED:
4584 flags |= GOVD_SHARED;
4585 break;
4586 case OMP_CLAUSE_DEFAULT_PRIVATE:
4587 flags |= GOVD_PRIVATE;
4588 break;
4589 default:
4590 gcc_unreachable ();
4593 omp_add_variable (ctx, decl, flags);
4595 shared = (flags & GOVD_SHARED) != 0;
4596 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
4597 goto do_outer;
4600 shared = ((flags | n->value) & GOVD_SHARED) != 0;
4601 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
4603 /* If nothing changed, there's nothing left to do. */
4604 if ((n->value & flags) == flags)
4605 return ret;
4606 flags |= n->value;
4607 n->value = flags;
4609 do_outer:
4610 /* If the variable is private in the current context, then we don't
4611 need to propagate anything to an outer context. */
4612 if (flags & GOVD_PRIVATE)
4613 return ret;
4614 if (ctx->outer_context
4615 && omp_notice_variable (ctx->outer_context, decl, in_code))
4616 return true;
4617 return ret;
4620 /* Verify that DECL is private within CTX. If there's specific information
4621 to the contrary in the innermost scope, generate an error. */
4623 static bool
4624 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl)
4626 splay_tree_node n;
4628 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
4629 if (n != NULL)
4631 if (n->value & GOVD_SHARED)
4633 if (ctx == gimplify_omp_ctxp)
4635 error ("iteration variable %qs should be private",
4636 IDENTIFIER_POINTER (DECL_NAME (decl)));
4637 n->value = GOVD_PRIVATE;
4638 return true;
4640 else
4641 return false;
4643 else if ((n->value & GOVD_EXPLICIT) != 0
4644 && (ctx == gimplify_omp_ctxp
4645 || (ctx->is_combined_parallel
4646 && gimplify_omp_ctxp->outer_context == ctx)))
4648 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
4649 error ("iteration variable %qs should not be firstprivate",
4650 IDENTIFIER_POINTER (DECL_NAME (decl)));
4651 else if ((n->value & GOVD_REDUCTION) != 0)
4652 error ("iteration variable %qs should not be reduction",
4653 IDENTIFIER_POINTER (DECL_NAME (decl)));
4655 return true;
4658 if (ctx->is_parallel)
4659 return false;
4660 else if (ctx->outer_context)
4661 return omp_is_private (ctx->outer_context, decl);
4662 else
4663 return !is_global_var (decl);
4666 /* Return true if DECL is private within a parallel region
4667 that binds to the current construct's context or in parallel
4668 region's REDUCTION clause. */
4670 static bool
4671 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl)
4673 splay_tree_node n;
4677 ctx = ctx->outer_context;
4678 if (ctx == NULL)
4679 return !(is_global_var (decl)
4680 /* References might be private, but might be shared too. */
4681 || lang_hooks.decls.omp_privatize_by_reference (decl));
4683 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
4684 if (n != NULL)
4685 return (n->value & GOVD_SHARED) == 0;
4687 while (!ctx->is_parallel);
4688 return false;
4691 /* Scan the OpenMP clauses in *LIST_P, installing mappings into a new
4692 and previous omp contexts. */
4694 static void
4695 gimplify_scan_omp_clauses (tree *list_p, tree *pre_p, bool in_parallel,
4696 bool in_combined_parallel)
4698 struct gimplify_omp_ctx *ctx, *outer_ctx;
4699 tree c;
4701 ctx = new_omp_context (in_parallel, in_combined_parallel);
4702 outer_ctx = ctx->outer_context;
4704 while ((c = *list_p) != NULL)
4706 enum gimplify_status gs;
4707 bool remove = false;
4708 bool notice_outer = true;
4709 const char *check_non_private = NULL;
4710 unsigned int flags;
4711 tree decl;
4713 switch (OMP_CLAUSE_CODE (c))
4715 case OMP_CLAUSE_PRIVATE:
4716 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
4717 notice_outer = false;
4718 goto do_add;
4719 case OMP_CLAUSE_SHARED:
4720 flags = GOVD_SHARED | GOVD_EXPLICIT;
4721 goto do_add;
4722 case OMP_CLAUSE_FIRSTPRIVATE:
4723 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
4724 check_non_private = "firstprivate";
4725 goto do_add;
4726 case OMP_CLAUSE_LASTPRIVATE:
4727 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
4728 check_non_private = "lastprivate";
4729 goto do_add;
4730 case OMP_CLAUSE_REDUCTION:
4731 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
4732 check_non_private = "reduction";
4733 goto do_add;
4735 do_add:
4736 decl = OMP_CLAUSE_DECL (c);
4737 if (decl == error_mark_node || TREE_TYPE (decl) == error_mark_node)
4739 remove = true;
4740 break;
4742 omp_add_variable (ctx, decl, flags);
4743 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
4744 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
4746 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
4747 GOVD_LOCAL | GOVD_SEEN);
4748 gimplify_omp_ctxp = ctx;
4749 push_gimplify_context ();
4750 gimplify_stmt (&OMP_CLAUSE_REDUCTION_INIT (c));
4751 pop_gimplify_context (OMP_CLAUSE_REDUCTION_INIT (c));
4752 push_gimplify_context ();
4753 gimplify_stmt (&OMP_CLAUSE_REDUCTION_MERGE (c));
4754 pop_gimplify_context (OMP_CLAUSE_REDUCTION_MERGE (c));
4755 gimplify_omp_ctxp = outer_ctx;
4757 if (notice_outer)
4758 goto do_notice;
4759 break;
4761 case OMP_CLAUSE_COPYIN:
4762 case OMP_CLAUSE_COPYPRIVATE:
4763 decl = OMP_CLAUSE_DECL (c);
4764 if (decl == error_mark_node || TREE_TYPE (decl) == error_mark_node)
4766 remove = true;
4767 break;
4769 do_notice:
4770 if (outer_ctx)
4771 omp_notice_variable (outer_ctx, decl, true);
4772 if (check_non_private
4773 && !in_parallel
4774 && omp_check_private (ctx, decl))
4776 error ("%s variable %qs is private in outer context",
4777 check_non_private, IDENTIFIER_POINTER (DECL_NAME (decl)));
4778 remove = true;
4780 break;
4782 case OMP_CLAUSE_IF:
4783 OMP_CLAUSE_OPERAND (c, 0)
4784 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
4785 /* Fall through. */
4787 case OMP_CLAUSE_SCHEDULE:
4788 case OMP_CLAUSE_NUM_THREADS:
4789 gs = gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
4790 is_gimple_val, fb_rvalue);
4791 if (gs == GS_ERROR)
4792 remove = true;
4793 break;
4795 case OMP_CLAUSE_NOWAIT:
4796 case OMP_CLAUSE_ORDERED:
4797 break;
4799 case OMP_CLAUSE_DEFAULT:
4800 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
4801 break;
4803 default:
4804 gcc_unreachable ();
4807 if (remove)
4808 *list_p = OMP_CLAUSE_CHAIN (c);
4809 else
4810 list_p = &OMP_CLAUSE_CHAIN (c);
4813 gimplify_omp_ctxp = ctx;
4816 /* For all variables that were not actually used within the context,
4817 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
4819 static int
4820 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
4822 tree *list_p = (tree *) data;
4823 tree decl = (tree) n->key;
4824 unsigned flags = n->value;
4825 enum omp_clause_code code;
4826 tree clause;
4827 bool private_debug;
4829 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
4830 return 0;
4831 if ((flags & GOVD_SEEN) == 0)
4832 return 0;
4833 if (flags & GOVD_DEBUG_PRIVATE)
4835 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_PRIVATE);
4836 private_debug = true;
4838 else
4839 private_debug
4840 = lang_hooks.decls.omp_private_debug_clause (decl,
4841 !!(flags & GOVD_SHARED));
4842 if (private_debug)
4843 code = OMP_CLAUSE_PRIVATE;
4844 else if (flags & GOVD_SHARED)
4846 if (is_global_var (decl))
4847 return 0;
4848 code = OMP_CLAUSE_SHARED;
4850 else if (flags & GOVD_PRIVATE)
4851 code = OMP_CLAUSE_PRIVATE;
4852 else if (flags & GOVD_FIRSTPRIVATE)
4853 code = OMP_CLAUSE_FIRSTPRIVATE;
4854 else
4855 gcc_unreachable ();
4857 clause = build_omp_clause (code);
4858 OMP_CLAUSE_DECL (clause) = decl;
4859 OMP_CLAUSE_CHAIN (clause) = *list_p;
4860 if (private_debug)
4861 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
4862 *list_p = clause;
4864 return 0;
4867 static void
4868 gimplify_adjust_omp_clauses (tree *list_p)
4870 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
4871 tree c, decl;
4873 while ((c = *list_p) != NULL)
4875 splay_tree_node n;
4876 bool remove = false;
4878 switch (OMP_CLAUSE_CODE (c))
4880 case OMP_CLAUSE_PRIVATE:
4881 case OMP_CLAUSE_SHARED:
4882 case OMP_CLAUSE_FIRSTPRIVATE:
4883 decl = OMP_CLAUSE_DECL (c);
4884 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
4885 remove = !(n->value & GOVD_SEEN);
4886 if (! remove)
4888 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
4889 if ((n->value & GOVD_DEBUG_PRIVATE)
4890 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
4892 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
4893 || ((n->value & GOVD_DATA_SHARE_CLASS)
4894 == GOVD_PRIVATE));
4895 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
4896 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
4899 break;
4901 case OMP_CLAUSE_LASTPRIVATE:
4902 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
4903 accurately reflect the presence of a FIRSTPRIVATE clause. */
4904 decl = OMP_CLAUSE_DECL (c);
4905 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
4906 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
4907 = (n->value & GOVD_FIRSTPRIVATE) != 0;
4908 break;
4910 case OMP_CLAUSE_REDUCTION:
4911 case OMP_CLAUSE_COPYIN:
4912 case OMP_CLAUSE_COPYPRIVATE:
4913 case OMP_CLAUSE_IF:
4914 case OMP_CLAUSE_NUM_THREADS:
4915 case OMP_CLAUSE_SCHEDULE:
4916 case OMP_CLAUSE_NOWAIT:
4917 case OMP_CLAUSE_ORDERED:
4918 case OMP_CLAUSE_DEFAULT:
4919 break;
4921 default:
4922 gcc_unreachable ();
4925 if (remove)
4926 *list_p = OMP_CLAUSE_CHAIN (c);
4927 else
4928 list_p = &OMP_CLAUSE_CHAIN (c);
4931 /* Add in any implicit data sharing. */
4932 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, list_p);
4934 gimplify_omp_ctxp = ctx->outer_context;
4935 delete_omp_context (ctx);
4938 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
4939 gimplification of the body, as well as scanning the body for used
4940 variables. We need to do this scan now, because variable-sized
4941 decls will be decomposed during gimplification. */
4943 static enum gimplify_status
4944 gimplify_omp_parallel (tree *expr_p, tree *pre_p)
4946 tree expr = *expr_p;
4948 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p, true,
4949 OMP_PARALLEL_COMBINED (expr));
4951 push_gimplify_context ();
4953 gimplify_stmt (&OMP_PARALLEL_BODY (expr));
4955 if (TREE_CODE (OMP_PARALLEL_BODY (expr)) == BIND_EXPR)
4956 pop_gimplify_context (OMP_PARALLEL_BODY (expr));
4957 else
4958 pop_gimplify_context (NULL_TREE);
4960 gimplify_adjust_omp_clauses (&OMP_PARALLEL_CLAUSES (expr));
4962 return GS_ALL_DONE;
4965 /* Gimplify the gross structure of an OMP_FOR statement. */
4967 static enum gimplify_status
4968 gimplify_omp_for (tree *expr_p, tree *pre_p)
4970 tree for_stmt, decl, t;
4971 enum gimplify_status ret = GS_OK;
4973 for_stmt = *expr_p;
4975 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, false, false);
4977 t = OMP_FOR_INIT (for_stmt);
4978 gcc_assert (TREE_CODE (t) == MODIFY_EXPR
4979 || TREE_CODE (t) == GIMPLE_MODIFY_STMT);
4980 decl = GENERIC_TREE_OPERAND (t, 0);
4981 gcc_assert (DECL_P (decl));
4982 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl)));
4984 /* Make sure the iteration variable is private. */
4985 if (omp_is_private (gimplify_omp_ctxp, decl))
4986 omp_notice_variable (gimplify_omp_ctxp, decl, true);
4987 else
4988 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
4990 ret |= gimplify_expr (&GENERIC_TREE_OPERAND (t, 1),
4991 &OMP_FOR_PRE_BODY (for_stmt),
4992 NULL, is_gimple_val, fb_rvalue);
4994 tree_to_gimple_tuple (&OMP_FOR_INIT (for_stmt));
4996 t = OMP_FOR_COND (for_stmt);
4997 gcc_assert (COMPARISON_CLASS_P (t));
4998 gcc_assert (GENERIC_TREE_OPERAND (t, 0) == decl);
5000 ret |= gimplify_expr (&GENERIC_TREE_OPERAND (t, 1),
5001 &OMP_FOR_PRE_BODY (for_stmt),
5002 NULL, is_gimple_val, fb_rvalue);
5004 tree_to_gimple_tuple (&OMP_FOR_INCR (for_stmt));
5005 t = OMP_FOR_INCR (for_stmt);
5006 switch (TREE_CODE (t))
5008 case PREINCREMENT_EXPR:
5009 case POSTINCREMENT_EXPR:
5010 t = build_int_cst (TREE_TYPE (decl), 1);
5011 goto build_modify;
5012 case PREDECREMENT_EXPR:
5013 case POSTDECREMENT_EXPR:
5014 t = build_int_cst (TREE_TYPE (decl), -1);
5015 goto build_modify;
5016 build_modify:
5017 t = build2 (PLUS_EXPR, TREE_TYPE (decl), decl, t);
5018 t = build2 (GIMPLE_MODIFY_STMT, void_type_node, decl, t);
5019 OMP_FOR_INCR (for_stmt) = t;
5020 break;
5022 case GIMPLE_MODIFY_STMT:
5023 gcc_assert (GIMPLE_STMT_OPERAND (t, 0) == decl);
5024 t = GIMPLE_STMT_OPERAND (t, 1);
5025 switch (TREE_CODE (t))
5027 case PLUS_EXPR:
5028 if (TREE_OPERAND (t, 1) == decl)
5030 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
5031 TREE_OPERAND (t, 0) = decl;
5032 break;
5034 case MINUS_EXPR:
5035 gcc_assert (TREE_OPERAND (t, 0) == decl);
5036 break;
5037 default:
5038 gcc_unreachable ();
5041 ret |= gimplify_expr (&TREE_OPERAND (t, 1), &OMP_FOR_PRE_BODY (for_stmt),
5042 NULL, is_gimple_val, fb_rvalue);
5043 break;
5045 default:
5046 gcc_unreachable ();
5049 gimplify_to_stmt_list (&OMP_FOR_BODY (for_stmt));
5050 gimplify_adjust_omp_clauses (&OMP_FOR_CLAUSES (for_stmt));
5052 return ret == GS_ALL_DONE ? GS_ALL_DONE : GS_ERROR;
5055 /* Gimplify the gross structure of other OpenMP worksharing constructs.
5056 In particular, OMP_SECTIONS and OMP_SINGLE. */
5058 static enum gimplify_status
5059 gimplify_omp_workshare (tree *expr_p, tree *pre_p)
5061 tree stmt = *expr_p;
5063 gimplify_scan_omp_clauses (&OMP_CLAUSES (stmt), pre_p, false, false);
5064 gimplify_to_stmt_list (&OMP_BODY (stmt));
5065 gimplify_adjust_omp_clauses (&OMP_CLAUSES (stmt));
5067 return GS_ALL_DONE;
5070 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
5071 stabilized the lhs of the atomic operation as *ADDR. Return true if
5072 EXPR is this stabilized form. */
5074 static bool
5075 goa_lhs_expr_p (tree expr, tree addr)
5077 /* Also include casts to other type variants. The C front end is fond
5078 of adding these for e.g. volatile variables. This is like
5079 STRIP_TYPE_NOPS but includes the main variant lookup. */
5080 while ((TREE_CODE (expr) == NOP_EXPR
5081 || TREE_CODE (expr) == CONVERT_EXPR
5082 || TREE_CODE (expr) == NON_LVALUE_EXPR)
5083 && TREE_OPERAND (expr, 0) != error_mark_node
5084 && (TYPE_MAIN_VARIANT (TREE_TYPE (expr))
5085 == TYPE_MAIN_VARIANT (TREE_TYPE (TREE_OPERAND (expr, 0)))))
5086 expr = TREE_OPERAND (expr, 0);
5088 if (TREE_CODE (expr) == INDIRECT_REF && TREE_OPERAND (expr, 0) == addr)
5089 return true;
5090 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
5091 return true;
5092 return false;
5095 /* A subroutine of gimplify_omp_atomic. Attempt to implement the atomic
5096 operation as a __sync_fetch_and_op builtin. INDEX is log2 of the
5097 size of the data type, and thus usable to find the index of the builtin
5098 decl. Returns GS_UNHANDLED if the expression is not of the proper form. */
5100 static enum gimplify_status
5101 gimplify_omp_atomic_fetch_op (tree *expr_p, tree addr, tree rhs, int index)
5103 enum built_in_function base;
5104 tree decl, itype;
5105 enum insn_code *optab;
5107 /* Check for one of the supported fetch-op operations. */
5108 switch (TREE_CODE (rhs))
5110 case PLUS_EXPR:
5111 base = BUILT_IN_FETCH_AND_ADD_N;
5112 optab = sync_add_optab;
5113 break;
5114 case MINUS_EXPR:
5115 base = BUILT_IN_FETCH_AND_SUB_N;
5116 optab = sync_add_optab;
5117 break;
5118 case BIT_AND_EXPR:
5119 base = BUILT_IN_FETCH_AND_AND_N;
5120 optab = sync_and_optab;
5121 break;
5122 case BIT_IOR_EXPR:
5123 base = BUILT_IN_FETCH_AND_OR_N;
5124 optab = sync_ior_optab;
5125 break;
5126 case BIT_XOR_EXPR:
5127 base = BUILT_IN_FETCH_AND_XOR_N;
5128 optab = sync_xor_optab;
5129 break;
5130 default:
5131 return GS_UNHANDLED;
5134 /* Make sure the expression is of the proper form. */
5135 if (goa_lhs_expr_p (TREE_OPERAND (rhs, 0), addr))
5136 rhs = TREE_OPERAND (rhs, 1);
5137 else if (commutative_tree_code (TREE_CODE (rhs))
5138 && goa_lhs_expr_p (TREE_OPERAND (rhs, 1), addr))
5139 rhs = TREE_OPERAND (rhs, 0);
5140 else
5141 return GS_UNHANDLED;
5143 decl = built_in_decls[base + index + 1];
5144 itype = TREE_TYPE (TREE_TYPE (decl));
5146 if (optab[TYPE_MODE (itype)] == CODE_FOR_nothing)
5147 return GS_UNHANDLED;
5149 *expr_p = build_call_expr (decl, 2, addr, fold_convert (itype, rhs));
5150 return GS_OK;
5153 /* A subroutine of gimplify_omp_atomic_pipeline. Walk *EXPR_P and replace
5154 appearances of *LHS_ADDR with LHS_VAR. If an expression does not involve
5155 the lhs, evaluate it into a temporary. Return 1 if the lhs appeared as
5156 a subexpression, 0 if it did not, or -1 if an error was encountered. */
5158 static int
5159 goa_stabilize_expr (tree *expr_p, tree *pre_p, tree lhs_addr, tree lhs_var)
5161 tree expr = *expr_p;
5162 int saw_lhs;
5164 if (goa_lhs_expr_p (expr, lhs_addr))
5166 *expr_p = lhs_var;
5167 return 1;
5169 if (is_gimple_val (expr))
5170 return 0;
5172 saw_lhs = 0;
5173 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
5175 case tcc_binary:
5176 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
5177 lhs_addr, lhs_var);
5178 case tcc_unary:
5179 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
5180 lhs_addr, lhs_var);
5181 break;
5182 default:
5183 break;
5186 if (saw_lhs == 0)
5188 enum gimplify_status gs;
5189 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
5190 if (gs != GS_ALL_DONE)
5191 saw_lhs = -1;
5194 return saw_lhs;
5197 /* A subroutine of gimplify_omp_atomic. Implement the atomic operation as:
5199 oldval = *addr;
5200 repeat:
5201 newval = rhs; // with oldval replacing *addr in rhs
5202 oldval = __sync_val_compare_and_swap (addr, oldval, newval);
5203 if (oldval != newval)
5204 goto repeat;
5206 INDEX is log2 of the size of the data type, and thus usable to find the
5207 index of the builtin decl. */
5209 static enum gimplify_status
5210 gimplify_omp_atomic_pipeline (tree *expr_p, tree *pre_p, tree addr,
5211 tree rhs, int index)
5213 tree oldval, oldival, oldival2, newval, newival, label;
5214 tree type, itype, cmpxchg, x, iaddr;
5216 cmpxchg = built_in_decls[BUILT_IN_VAL_COMPARE_AND_SWAP_N + index + 1];
5217 type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
5218 itype = TREE_TYPE (TREE_TYPE (cmpxchg));
5220 if (sync_compare_and_swap[TYPE_MODE (itype)] == CODE_FOR_nothing)
5221 return GS_UNHANDLED;
5223 oldval = create_tmp_var (type, NULL);
5224 newval = create_tmp_var (type, NULL);
5226 /* Precompute as much of RHS as possible. In the same walk, replace
5227 occurrences of the lhs value with our temporary. */
5228 if (goa_stabilize_expr (&rhs, pre_p, addr, oldval) < 0)
5229 return GS_ERROR;
5231 x = build_fold_indirect_ref (addr);
5232 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldval, x);
5233 gimplify_and_add (x, pre_p);
5235 /* For floating-point values, we'll need to view-convert them to integers
5236 so that we can perform the atomic compare and swap. Simplify the
5237 following code by always setting up the "i"ntegral variables. */
5238 if (INTEGRAL_TYPE_P (type) || POINTER_TYPE_P (type))
5240 oldival = oldval;
5241 newival = newval;
5242 iaddr = addr;
5244 else
5246 oldival = create_tmp_var (itype, NULL);
5247 newival = create_tmp_var (itype, NULL);
5249 x = build1 (VIEW_CONVERT_EXPR, itype, oldval);
5250 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival, x);
5251 gimplify_and_add (x, pre_p);
5252 iaddr = fold_convert (build_pointer_type (itype), addr);
5255 oldival2 = create_tmp_var (itype, NULL);
5257 label = create_artificial_label ();
5258 x = build1 (LABEL_EXPR, void_type_node, label);
5259 gimplify_and_add (x, pre_p);
5261 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, newval, rhs);
5262 gimplify_and_add (x, pre_p);
5264 if (newval != newival)
5266 x = build1 (VIEW_CONVERT_EXPR, itype, newval);
5267 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, newival, x);
5268 gimplify_and_add (x, pre_p);
5271 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival2,
5272 fold_convert (itype, oldival));
5273 gimplify_and_add (x, pre_p);
5275 x = build_call_expr (cmpxchg, 3, iaddr, fold_convert (itype, oldival),
5276 fold_convert (itype, newival));
5277 if (oldval == oldival)
5278 x = fold_convert (type, x);
5279 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival, x);
5280 gimplify_and_add (x, pre_p);
5282 /* For floating point, be prepared for the loop backedge. */
5283 if (oldval != oldival)
5285 x = build1 (VIEW_CONVERT_EXPR, type, oldival);
5286 x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldval, x);
5287 gimplify_and_add (x, pre_p);
5290 /* Note that we always perform the comparison as an integer, even for
5291 floating point. This allows the atomic operation to properly
5292 succeed even with NaNs and -0.0. */
5293 x = build3 (COND_EXPR, void_type_node,
5294 build2 (NE_EXPR, boolean_type_node, oldival, oldival2),
5295 build1 (GOTO_EXPR, void_type_node, label), NULL);
5296 gimplify_and_add (x, pre_p);
5298 *expr_p = NULL;
5299 return GS_ALL_DONE;
5302 /* A subroutine of gimplify_omp_atomic. Implement the atomic operation as:
5304 GOMP_atomic_start ();
5305 *addr = rhs;
5306 GOMP_atomic_end ();
5308 The result is not globally atomic, but works so long as all parallel
5309 references are within #pragma omp atomic directives. According to
5310 responses received from omp@openmp.org, appears to be within spec.
5311 Which makes sense, since that's how several other compilers handle
5312 this situation as well. */
5314 static enum gimplify_status
5315 gimplify_omp_atomic_mutex (tree *expr_p, tree *pre_p, tree addr, tree rhs)
5317 tree t;
5319 t = built_in_decls[BUILT_IN_GOMP_ATOMIC_START];
5320 t = build_call_expr (t, 0);
5321 gimplify_and_add (t, pre_p);
5323 t = build_fold_indirect_ref (addr);
5324 t = build2 (GIMPLE_MODIFY_STMT, void_type_node, t, rhs);
5325 gimplify_and_add (t, pre_p);
5327 t = built_in_decls[BUILT_IN_GOMP_ATOMIC_END];
5328 t = build_call_expr (t, 0);
5329 gimplify_and_add (t, pre_p);
5331 *expr_p = NULL;
5332 return GS_ALL_DONE;
5335 /* Gimplify an OMP_ATOMIC statement. */
5337 static enum gimplify_status
5338 gimplify_omp_atomic (tree *expr_p, tree *pre_p)
5340 tree addr = TREE_OPERAND (*expr_p, 0);
5341 tree rhs = TREE_OPERAND (*expr_p, 1);
5342 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
5343 HOST_WIDE_INT index;
5345 /* Make sure the type is one of the supported sizes. */
5346 index = tree_low_cst (TYPE_SIZE_UNIT (type), 1);
5347 index = exact_log2 (index);
5348 if (index >= 0 && index <= 4)
5350 enum gimplify_status gs;
5351 unsigned int align;
5353 if (DECL_P (TREE_OPERAND (addr, 0)))
5354 align = DECL_ALIGN_UNIT (TREE_OPERAND (addr, 0));
5355 else if (TREE_CODE (TREE_OPERAND (addr, 0)) == COMPONENT_REF
5356 && TREE_CODE (TREE_OPERAND (TREE_OPERAND (addr, 0), 1))
5357 == FIELD_DECL)
5358 align = DECL_ALIGN_UNIT (TREE_OPERAND (TREE_OPERAND (addr, 0), 1));
5359 else
5360 align = TYPE_ALIGN_UNIT (type);
5362 /* __sync builtins require strict data alignment. */
5363 if (exact_log2 (align) >= index)
5365 /* When possible, use specialized atomic update functions. */
5366 if (INTEGRAL_TYPE_P (type) || POINTER_TYPE_P (type))
5368 gs = gimplify_omp_atomic_fetch_op (expr_p, addr, rhs, index);
5369 if (gs != GS_UNHANDLED)
5370 return gs;
5373 /* If we don't have specialized __sync builtins, try and implement
5374 as a compare and swap loop. */
5375 gs = gimplify_omp_atomic_pipeline (expr_p, pre_p, addr, rhs, index);
5376 if (gs != GS_UNHANDLED)
5377 return gs;
5381 /* The ultimate fallback is wrapping the operation in a mutex. */
5382 return gimplify_omp_atomic_mutex (expr_p, pre_p, addr, rhs);
5385 /* Gimplifies the expression tree pointed to by EXPR_P. Return 0 if
5386 gimplification failed.
5388 PRE_P points to the list where side effects that must happen before
5389 EXPR should be stored.
5391 POST_P points to the list where side effects that must happen after
5392 EXPR should be stored, or NULL if there is no suitable list. In
5393 that case, we copy the result to a temporary, emit the
5394 post-effects, and then return the temporary.
5396 GIMPLE_TEST_F points to a function that takes a tree T and
5397 returns nonzero if T is in the GIMPLE form requested by the
5398 caller. The GIMPLE predicates are in tree-gimple.c.
5400 This test is used twice. Before gimplification, the test is
5401 invoked to determine whether *EXPR_P is already gimple enough. If
5402 that fails, *EXPR_P is gimplified according to its code and
5403 GIMPLE_TEST_F is called again. If the test still fails, then a new
5404 temporary variable is created and assigned the value of the
5405 gimplified expression.
5407 FALLBACK tells the function what sort of a temporary we want. If the 1
5408 bit is set, an rvalue is OK. If the 2 bit is set, an lvalue is OK.
5409 If both are set, either is OK, but an lvalue is preferable.
5411 The return value is either GS_ERROR or GS_ALL_DONE, since this function
5412 iterates until solution. */
5414 enum gimplify_status
5415 gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p,
5416 bool (* gimple_test_f) (tree), fallback_t fallback)
5418 tree tmp;
5419 tree internal_pre = NULL_TREE;
5420 tree internal_post = NULL_TREE;
5421 tree save_expr;
5422 int is_statement = (pre_p == NULL);
5423 location_t saved_location;
5424 enum gimplify_status ret;
5426 save_expr = *expr_p;
5427 if (save_expr == NULL_TREE)
5428 return GS_ALL_DONE;
5430 /* We used to check the predicate here and return immediately if it
5431 succeeds. This is wrong; the design is for gimplification to be
5432 idempotent, and for the predicates to only test for valid forms, not
5433 whether they are fully simplified. */
5435 /* Set up our internal queues if needed. */
5436 if (pre_p == NULL)
5437 pre_p = &internal_pre;
5438 if (post_p == NULL)
5439 post_p = &internal_post;
5441 saved_location = input_location;
5442 if (save_expr != error_mark_node
5443 && EXPR_HAS_LOCATION (*expr_p))
5444 input_location = EXPR_LOCATION (*expr_p);
5446 /* Loop over the specific gimplifiers until the toplevel node
5447 remains the same. */
5450 /* Strip away as many useless type conversions as possible
5451 at the toplevel. */
5452 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
5454 /* Remember the expr. */
5455 save_expr = *expr_p;
5457 /* Die, die, die, my darling. */
5458 if (save_expr == error_mark_node
5459 || (!GIMPLE_STMT_P (save_expr)
5460 && TREE_TYPE (save_expr)
5461 && TREE_TYPE (save_expr) == error_mark_node))
5463 ret = GS_ERROR;
5464 break;
5467 /* Do any language-specific gimplification. */
5468 ret = lang_hooks.gimplify_expr (expr_p, pre_p, post_p);
5469 if (ret == GS_OK)
5471 if (*expr_p == NULL_TREE)
5472 break;
5473 if (*expr_p != save_expr)
5474 continue;
5476 else if (ret != GS_UNHANDLED)
5477 break;
5479 ret = GS_OK;
5480 switch (TREE_CODE (*expr_p))
5482 /* First deal with the special cases. */
5484 case POSTINCREMENT_EXPR:
5485 case POSTDECREMENT_EXPR:
5486 case PREINCREMENT_EXPR:
5487 case PREDECREMENT_EXPR:
5488 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
5489 fallback != fb_none);
5490 break;
5492 case ARRAY_REF:
5493 case ARRAY_RANGE_REF:
5494 case REALPART_EXPR:
5495 case IMAGPART_EXPR:
5496 case COMPONENT_REF:
5497 case VIEW_CONVERT_EXPR:
5498 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
5499 fallback ? fallback : fb_rvalue);
5500 break;
5502 case COND_EXPR:
5503 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
5504 /* C99 code may assign to an array in a structure value of a
5505 conditional expression, and this has undefined behavior
5506 only on execution, so create a temporary if an lvalue is
5507 required. */
5508 if (fallback == fb_lvalue)
5510 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
5511 lang_hooks.mark_addressable (*expr_p);
5513 break;
5515 case CALL_EXPR:
5516 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
5517 /* C99 code may assign to an array in a structure returned
5518 from a function, and this has undefined behavior only on
5519 execution, so create a temporary if an lvalue is
5520 required. */
5521 if (fallback == fb_lvalue)
5523 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
5524 lang_hooks.mark_addressable (*expr_p);
5526 break;
5528 case TREE_LIST:
5529 gcc_unreachable ();
5531 case COMPOUND_EXPR:
5532 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
5533 break;
5535 case MODIFY_EXPR:
5536 case GIMPLE_MODIFY_STMT:
5537 case INIT_EXPR:
5538 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
5539 fallback != fb_none);
5541 if (*expr_p)
5543 /* The distinction between MODIFY_EXPR and INIT_EXPR is no longer
5544 useful. */
5545 if (TREE_CODE (*expr_p) == INIT_EXPR)
5546 TREE_SET_CODE (*expr_p, MODIFY_EXPR);
5548 /* Convert MODIFY_EXPR to GIMPLE_MODIFY_STMT. */
5549 if (TREE_CODE (*expr_p) == MODIFY_EXPR)
5550 tree_to_gimple_tuple (expr_p);
5553 break;
5555 case TRUTH_ANDIF_EXPR:
5556 case TRUTH_ORIF_EXPR:
5557 ret = gimplify_boolean_expr (expr_p);
5558 break;
5560 case TRUTH_NOT_EXPR:
5561 TREE_OPERAND (*expr_p, 0)
5562 = gimple_boolify (TREE_OPERAND (*expr_p, 0));
5563 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5564 is_gimple_val, fb_rvalue);
5565 recalculate_side_effects (*expr_p);
5566 break;
5568 case ADDR_EXPR:
5569 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
5570 break;
5572 case VA_ARG_EXPR:
5573 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
5574 break;
5576 case CONVERT_EXPR:
5577 case NOP_EXPR:
5578 if (IS_EMPTY_STMT (*expr_p))
5580 ret = GS_ALL_DONE;
5581 break;
5584 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
5585 || fallback == fb_none)
5587 /* Just strip a conversion to void (or in void context) and
5588 try again. */
5589 *expr_p = TREE_OPERAND (*expr_p, 0);
5590 break;
5593 ret = gimplify_conversion (expr_p);
5594 if (ret == GS_ERROR)
5595 break;
5596 if (*expr_p != save_expr)
5597 break;
5598 /* FALLTHRU */
5600 case FIX_TRUNC_EXPR:
5601 /* unary_expr: ... | '(' cast ')' val | ... */
5602 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5603 is_gimple_val, fb_rvalue);
5604 recalculate_side_effects (*expr_p);
5605 break;
5607 case INDIRECT_REF:
5608 *expr_p = fold_indirect_ref (*expr_p);
5609 if (*expr_p != save_expr)
5610 break;
5611 /* else fall through. */
5612 case ALIGN_INDIRECT_REF:
5613 case MISALIGNED_INDIRECT_REF:
5614 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5615 is_gimple_reg, fb_rvalue);
5616 recalculate_side_effects (*expr_p);
5617 break;
5619 /* Constants need not be gimplified. */
5620 case INTEGER_CST:
5621 case REAL_CST:
5622 case STRING_CST:
5623 case COMPLEX_CST:
5624 case VECTOR_CST:
5625 ret = GS_ALL_DONE;
5626 break;
5628 case CONST_DECL:
5629 /* If we require an lvalue, such as for ADDR_EXPR, retain the
5630 CONST_DECL node. Otherwise the decl is replaceable by its
5631 value. */
5632 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
5633 if (fallback & fb_lvalue)
5634 ret = GS_ALL_DONE;
5635 else
5636 *expr_p = DECL_INITIAL (*expr_p);
5637 break;
5639 case DECL_EXPR:
5640 ret = gimplify_decl_expr (expr_p);
5641 break;
5643 case EXC_PTR_EXPR:
5644 /* FIXME make this a decl. */
5645 ret = GS_ALL_DONE;
5646 break;
5648 case BIND_EXPR:
5649 ret = gimplify_bind_expr (expr_p, pre_p);
5650 break;
5652 case LOOP_EXPR:
5653 ret = gimplify_loop_expr (expr_p, pre_p);
5654 break;
5656 case SWITCH_EXPR:
5657 ret = gimplify_switch_expr (expr_p, pre_p);
5658 break;
5660 case EXIT_EXPR:
5661 ret = gimplify_exit_expr (expr_p);
5662 break;
5664 case GOTO_EXPR:
5665 /* If the target is not LABEL, then it is a computed jump
5666 and the target needs to be gimplified. */
5667 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
5668 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
5669 NULL, is_gimple_val, fb_rvalue);
5670 break;
5672 case LABEL_EXPR:
5673 ret = GS_ALL_DONE;
5674 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
5675 == current_function_decl);
5676 break;
5678 case CASE_LABEL_EXPR:
5679 ret = gimplify_case_label_expr (expr_p);
5680 break;
5682 case RETURN_EXPR:
5683 ret = gimplify_return_expr (*expr_p, pre_p);
5684 break;
5686 case CONSTRUCTOR:
5687 /* Don't reduce this in place; let gimplify_init_constructor work its
5688 magic. Buf if we're just elaborating this for side effects, just
5689 gimplify any element that has side-effects. */
5690 if (fallback == fb_none)
5692 unsigned HOST_WIDE_INT ix;
5693 constructor_elt *ce;
5694 tree temp = NULL_TREE;
5695 for (ix = 0;
5696 VEC_iterate (constructor_elt, CONSTRUCTOR_ELTS (*expr_p),
5697 ix, ce);
5698 ix++)
5699 if (TREE_SIDE_EFFECTS (ce->value))
5700 append_to_statement_list (ce->value, &temp);
5702 *expr_p = temp;
5703 ret = GS_OK;
5705 /* C99 code may assign to an array in a constructed
5706 structure or union, and this has undefined behavior only
5707 on execution, so create a temporary if an lvalue is
5708 required. */
5709 else if (fallback == fb_lvalue)
5711 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
5712 lang_hooks.mark_addressable (*expr_p);
5714 else
5715 ret = GS_ALL_DONE;
5716 break;
5718 /* The following are special cases that are not handled by the
5719 original GIMPLE grammar. */
5721 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
5722 eliminated. */
5723 case SAVE_EXPR:
5724 ret = gimplify_save_expr (expr_p, pre_p, post_p);
5725 break;
5727 case BIT_FIELD_REF:
5729 enum gimplify_status r0, r1, r2;
5731 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5732 is_gimple_lvalue, fb_either);
5733 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
5734 is_gimple_val, fb_rvalue);
5735 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p, post_p,
5736 is_gimple_val, fb_rvalue);
5737 recalculate_side_effects (*expr_p);
5739 ret = MIN (r0, MIN (r1, r2));
5741 break;
5743 case NON_LVALUE_EXPR:
5744 /* This should have been stripped above. */
5745 gcc_unreachable ();
5747 case ASM_EXPR:
5748 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
5749 break;
5751 case TRY_FINALLY_EXPR:
5752 case TRY_CATCH_EXPR:
5753 gimplify_to_stmt_list (&TREE_OPERAND (*expr_p, 0));
5754 gimplify_to_stmt_list (&TREE_OPERAND (*expr_p, 1));
5755 ret = GS_ALL_DONE;
5756 break;
5758 case CLEANUP_POINT_EXPR:
5759 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
5760 break;
5762 case TARGET_EXPR:
5763 ret = gimplify_target_expr (expr_p, pre_p, post_p);
5764 break;
5766 case CATCH_EXPR:
5767 gimplify_to_stmt_list (&CATCH_BODY (*expr_p));
5768 ret = GS_ALL_DONE;
5769 break;
5771 case EH_FILTER_EXPR:
5772 gimplify_to_stmt_list (&EH_FILTER_FAILURE (*expr_p));
5773 ret = GS_ALL_DONE;
5774 break;
5776 case OBJ_TYPE_REF:
5778 enum gimplify_status r0, r1;
5779 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p, post_p,
5780 is_gimple_val, fb_rvalue);
5781 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p, post_p,
5782 is_gimple_val, fb_rvalue);
5783 ret = MIN (r0, r1);
5785 break;
5787 case LABEL_DECL:
5788 /* We get here when taking the address of a label. We mark
5789 the label as "forced"; meaning it can never be removed and
5790 it is a potential target for any computed goto. */
5791 FORCED_LABEL (*expr_p) = 1;
5792 ret = GS_ALL_DONE;
5793 break;
5795 case STATEMENT_LIST:
5796 ret = gimplify_statement_list (expr_p, pre_p);
5797 break;
5799 case WITH_SIZE_EXPR:
5801 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
5802 post_p == &internal_post ? NULL : post_p,
5803 gimple_test_f, fallback);
5804 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
5805 is_gimple_val, fb_rvalue);
5807 break;
5809 case VAR_DECL:
5810 case PARM_DECL:
5811 ret = gimplify_var_or_parm_decl (expr_p);
5812 break;
5814 case RESULT_DECL:
5815 /* When within an OpenMP context, notice uses of variables. */
5816 if (gimplify_omp_ctxp)
5817 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
5818 ret = GS_ALL_DONE;
5819 break;
5821 case SSA_NAME:
5822 /* Allow callbacks into the gimplifier during optimization. */
5823 ret = GS_ALL_DONE;
5824 break;
5826 case OMP_PARALLEL:
5827 ret = gimplify_omp_parallel (expr_p, pre_p);
5828 break;
5830 case OMP_FOR:
5831 ret = gimplify_omp_for (expr_p, pre_p);
5832 break;
5834 case OMP_SECTIONS:
5835 case OMP_SINGLE:
5836 ret = gimplify_omp_workshare (expr_p, pre_p);
5837 break;
5839 case OMP_SECTION:
5840 case OMP_MASTER:
5841 case OMP_ORDERED:
5842 case OMP_CRITICAL:
5843 gimplify_to_stmt_list (&OMP_BODY (*expr_p));
5844 break;
5846 case OMP_ATOMIC:
5847 ret = gimplify_omp_atomic (expr_p, pre_p);
5848 break;
5850 case OMP_RETURN:
5851 case OMP_CONTINUE:
5852 ret = GS_ALL_DONE;
5853 break;
5855 default:
5856 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
5858 case tcc_comparison:
5859 /* Handle comparison of objects of non scalar mode aggregates
5860 with a call to memcmp. It would be nice to only have to do
5861 this for variable-sized objects, but then we'd have to allow
5862 the same nest of reference nodes we allow for MODIFY_EXPR and
5863 that's too complex.
5865 Compare scalar mode aggregates as scalar mode values. Using
5866 memcmp for them would be very inefficient at best, and is
5867 plain wrong if bitfields are involved. */
5870 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
5872 if (!AGGREGATE_TYPE_P (type))
5873 goto expr_2;
5874 else if (TYPE_MODE (type) != BLKmode)
5875 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
5876 else
5877 ret = gimplify_variable_sized_compare (expr_p);
5879 break;
5882 /* If *EXPR_P does not need to be special-cased, handle it
5883 according to its class. */
5884 case tcc_unary:
5885 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
5886 post_p, is_gimple_val, fb_rvalue);
5887 break;
5889 case tcc_binary:
5890 expr_2:
5892 enum gimplify_status r0, r1;
5894 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
5895 post_p, is_gimple_val, fb_rvalue);
5896 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
5897 post_p, is_gimple_val, fb_rvalue);
5899 ret = MIN (r0, r1);
5900 break;
5903 case tcc_declaration:
5904 case tcc_constant:
5905 ret = GS_ALL_DONE;
5906 goto dont_recalculate;
5908 default:
5909 gcc_assert (TREE_CODE (*expr_p) == TRUTH_AND_EXPR
5910 || TREE_CODE (*expr_p) == TRUTH_OR_EXPR
5911 || TREE_CODE (*expr_p) == TRUTH_XOR_EXPR);
5912 goto expr_2;
5915 recalculate_side_effects (*expr_p);
5916 dont_recalculate:
5917 break;
5920 /* If we replaced *expr_p, gimplify again. */
5921 if (ret == GS_OK && (*expr_p == NULL || *expr_p == save_expr))
5922 ret = GS_ALL_DONE;
5924 while (ret == GS_OK);
5926 /* If we encountered an error_mark somewhere nested inside, either
5927 stub out the statement or propagate the error back out. */
5928 if (ret == GS_ERROR)
5930 if (is_statement)
5931 *expr_p = NULL;
5932 goto out;
5935 /* This was only valid as a return value from the langhook, which
5936 we handled. Make sure it doesn't escape from any other context. */
5937 gcc_assert (ret != GS_UNHANDLED);
5939 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
5941 /* We aren't looking for a value, and we don't have a valid
5942 statement. If it doesn't have side-effects, throw it away. */
5943 if (!TREE_SIDE_EFFECTS (*expr_p))
5944 *expr_p = NULL;
5945 else if (!TREE_THIS_VOLATILE (*expr_p))
5947 /* This is probably a _REF that contains something nested that
5948 has side effects. Recurse through the operands to find it. */
5949 enum tree_code code = TREE_CODE (*expr_p);
5951 switch (code)
5953 case COMPONENT_REF:
5954 case REALPART_EXPR:
5955 case IMAGPART_EXPR:
5956 case VIEW_CONVERT_EXPR:
5957 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5958 gimple_test_f, fallback);
5959 break;
5961 case ARRAY_REF:
5962 case ARRAY_RANGE_REF:
5963 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5964 gimple_test_f, fallback);
5965 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
5966 gimple_test_f, fallback);
5967 break;
5969 default:
5970 /* Anything else with side-effects must be converted to
5971 a valid statement before we get here. */
5972 gcc_unreachable ();
5975 *expr_p = NULL;
5977 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
5978 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
5980 /* Historically, the compiler has treated a bare reference
5981 to a non-BLKmode volatile lvalue as forcing a load. */
5982 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
5983 /* Normally, we do not want to create a temporary for a
5984 TREE_ADDRESSABLE type because such a type should not be
5985 copied by bitwise-assignment. However, we make an
5986 exception here, as all we are doing here is ensuring that
5987 we read the bytes that make up the type. We use
5988 create_tmp_var_raw because create_tmp_var will abort when
5989 given a TREE_ADDRESSABLE type. */
5990 tree tmp = create_tmp_var_raw (type, "vol");
5991 gimple_add_tmp_var (tmp);
5992 *expr_p = build2 (GIMPLE_MODIFY_STMT, type, tmp, *expr_p);
5994 else
5995 /* We can't do anything useful with a volatile reference to
5996 an incomplete type, so just throw it away. Likewise for
5997 a BLKmode type, since any implicit inner load should
5998 already have been turned into an explicit one by the
5999 gimplification process. */
6000 *expr_p = NULL;
6003 /* If we are gimplifying at the statement level, we're done. Tack
6004 everything together and replace the original statement with the
6005 gimplified form. */
6006 if (fallback == fb_none || is_statement)
6008 if (internal_pre || internal_post)
6010 append_to_statement_list (*expr_p, &internal_pre);
6011 append_to_statement_list (internal_post, &internal_pre);
6012 annotate_all_with_locus (&internal_pre, input_location);
6013 *expr_p = internal_pre;
6015 else if (!*expr_p)
6017 else if (TREE_CODE (*expr_p) == STATEMENT_LIST)
6018 annotate_all_with_locus (expr_p, input_location);
6019 else
6020 annotate_one_with_locus (*expr_p, input_location);
6021 goto out;
6024 /* Otherwise we're gimplifying a subexpression, so the resulting value is
6025 interesting. */
6027 /* If it's sufficiently simple already, we're done. Unless we are
6028 handling some post-effects internally; if that's the case, we need to
6029 copy into a temp before adding the post-effects to the tree. */
6030 if (!internal_post && (*gimple_test_f) (*expr_p))
6031 goto out;
6033 /* Otherwise, we need to create a new temporary for the gimplified
6034 expression. */
6036 /* We can't return an lvalue if we have an internal postqueue. The
6037 object the lvalue refers to would (probably) be modified by the
6038 postqueue; we need to copy the value out first, which means an
6039 rvalue. */
6040 if ((fallback & fb_lvalue) && !internal_post
6041 && is_gimple_addressable (*expr_p))
6043 /* An lvalue will do. Take the address of the expression, store it
6044 in a temporary, and replace the expression with an INDIRECT_REF of
6045 that temporary. */
6046 tmp = build_fold_addr_expr (*expr_p);
6047 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
6048 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (TREE_TYPE (tmp)), tmp);
6050 else if ((fallback & fb_rvalue) && is_gimple_formal_tmp_rhs (*expr_p))
6052 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
6054 /* An rvalue will do. Assign the gimplified expression into a new
6055 temporary TMP and replace the original expression with TMP. */
6057 if (internal_post || (fallback & fb_lvalue))
6058 /* The postqueue might change the value of the expression between
6059 the initialization and use of the temporary, so we can't use a
6060 formal temp. FIXME do we care? */
6061 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
6062 else
6063 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
6065 if (TREE_CODE (*expr_p) != SSA_NAME)
6066 DECL_GIMPLE_FORMAL_TEMP_P (*expr_p) = 1;
6068 else
6070 #ifdef ENABLE_CHECKING
6071 if (!(fallback & fb_mayfail))
6073 fprintf (stderr, "gimplification failed:\n");
6074 print_generic_expr (stderr, *expr_p, 0);
6075 debug_tree (*expr_p);
6076 internal_error ("gimplification failed");
6078 #endif
6079 gcc_assert (fallback & fb_mayfail);
6080 /* If this is an asm statement, and the user asked for the
6081 impossible, don't die. Fail and let gimplify_asm_expr
6082 issue an error. */
6083 ret = GS_ERROR;
6084 goto out;
6087 /* Make sure the temporary matches our predicate. */
6088 gcc_assert ((*gimple_test_f) (*expr_p));
6090 if (internal_post)
6092 annotate_all_with_locus (&internal_post, input_location);
6093 append_to_statement_list (internal_post, pre_p);
6096 out:
6097 input_location = saved_location;
6098 return ret;
6101 /* Look through TYPE for variable-sized objects and gimplify each such
6102 size that we find. Add to LIST_P any statements generated. */
6104 void
6105 gimplify_type_sizes (tree type, tree *list_p)
6107 tree field, t;
6109 if (type == NULL || type == error_mark_node)
6110 return;
6112 /* We first do the main variant, then copy into any other variants. */
6113 type = TYPE_MAIN_VARIANT (type);
6115 /* Avoid infinite recursion. */
6116 if (TYPE_SIZES_GIMPLIFIED (type))
6117 return;
6119 TYPE_SIZES_GIMPLIFIED (type) = 1;
6121 switch (TREE_CODE (type))
6123 case INTEGER_TYPE:
6124 case ENUMERAL_TYPE:
6125 case BOOLEAN_TYPE:
6126 case REAL_TYPE:
6127 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
6128 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
6130 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
6132 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
6133 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
6135 break;
6137 case ARRAY_TYPE:
6138 /* These types may not have declarations, so handle them here. */
6139 gimplify_type_sizes (TREE_TYPE (type), list_p);
6140 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
6141 break;
6143 case RECORD_TYPE:
6144 case UNION_TYPE:
6145 case QUAL_UNION_TYPE:
6146 for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
6147 if (TREE_CODE (field) == FIELD_DECL)
6149 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
6150 gimplify_type_sizes (TREE_TYPE (field), list_p);
6152 break;
6154 case POINTER_TYPE:
6155 case REFERENCE_TYPE:
6156 /* We used to recurse on the pointed-to type here, which turned out to
6157 be incorrect because its definition might refer to variables not
6158 yet initialized at this point if a forward declaration is involved.
6160 It was actually useful for anonymous pointed-to types to ensure
6161 that the sizes evaluation dominates every possible later use of the
6162 values. Restricting to such types here would be safe since there
6163 is no possible forward declaration around, but would introduce an
6164 undesirable middle-end semantic to anonymity. We then defer to
6165 front-ends the responsibility of ensuring that the sizes are
6166 evaluated both early and late enough, e.g. by attaching artificial
6167 type declarations to the tree. */
6168 break;
6170 default:
6171 break;
6174 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
6175 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
6177 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
6179 TYPE_SIZE (t) = TYPE_SIZE (type);
6180 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
6181 TYPE_SIZES_GIMPLIFIED (t) = 1;
6185 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
6186 a size or position, has had all of its SAVE_EXPRs evaluated.
6187 We add any required statements to STMT_P. */
6189 void
6190 gimplify_one_sizepos (tree *expr_p, tree *stmt_p)
6192 tree type, expr = *expr_p;
6194 /* We don't do anything if the value isn't there, is constant, or contains
6195 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
6196 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
6197 will want to replace it with a new variable, but that will cause problems
6198 if this type is from outside the function. It's OK to have that here. */
6199 if (expr == NULL_TREE || TREE_CONSTANT (expr)
6200 || TREE_CODE (expr) == VAR_DECL
6201 || CONTAINS_PLACEHOLDER_P (expr))
6202 return;
6204 type = TREE_TYPE (expr);
6205 *expr_p = unshare_expr (expr);
6207 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue);
6208 expr = *expr_p;
6210 /* Verify that we've an exact type match with the original expression.
6211 In particular, we do not wish to drop a "sizetype" in favour of a
6212 type of similar dimensions. We don't want to pollute the generic
6213 type-stripping code with this knowledge because it doesn't matter
6214 for the bulk of GENERIC/GIMPLE. It only matters that TYPE_SIZE_UNIT
6215 and friends retain their "sizetype-ness". */
6216 if (TREE_TYPE (expr) != type
6217 && TREE_CODE (type) == INTEGER_TYPE
6218 && TYPE_IS_SIZETYPE (type))
6220 tree tmp;
6222 *expr_p = create_tmp_var (type, NULL);
6223 tmp = build1 (NOP_EXPR, type, expr);
6224 tmp = build2 (GIMPLE_MODIFY_STMT, type, *expr_p, tmp);
6225 if (EXPR_HAS_LOCATION (expr))
6226 SET_EXPR_LOCUS (tmp, EXPR_LOCUS (expr));
6227 else
6228 SET_EXPR_LOCATION (tmp, input_location);
6230 gimplify_and_add (tmp, stmt_p);
6234 #ifdef ENABLE_CHECKING
6235 /* Compare types A and B for a "close enough" match. */
6237 static bool
6238 cpt_same_type (tree a, tree b)
6240 if (lang_hooks.types_compatible_p (a, b))
6241 return true;
6243 /* ??? The C++ FE decomposes METHOD_TYPES to FUNCTION_TYPES and doesn't
6244 link them together. This routine is intended to catch type errors
6245 that will affect the optimizers, and the optimizers don't add new
6246 dereferences of function pointers, so ignore it. */
6247 if ((TREE_CODE (a) == FUNCTION_TYPE || TREE_CODE (a) == METHOD_TYPE)
6248 && (TREE_CODE (b) == FUNCTION_TYPE || TREE_CODE (b) == METHOD_TYPE))
6249 return true;
6251 /* ??? The C FE pushes type qualifiers after the fact into the type of
6252 the element from the type of the array. See build_unary_op's handling
6253 of ADDR_EXPR. This seems wrong -- if we were going to do this, we
6254 should have done it when creating the variable in the first place.
6255 Alternately, why aren't the two array types made variants? */
6256 if (TREE_CODE (a) == ARRAY_TYPE && TREE_CODE (b) == ARRAY_TYPE)
6257 return cpt_same_type (TREE_TYPE (a), TREE_TYPE (b));
6259 /* And because of those, we have to recurse down through pointers. */
6260 if (POINTER_TYPE_P (a) && POINTER_TYPE_P (b))
6261 return cpt_same_type (TREE_TYPE (a), TREE_TYPE (b));
6263 return false;
6266 /* Check for some cases of the front end missing cast expressions.
6267 The type of a dereference should correspond to the pointer type;
6268 similarly the type of an address should match its object. */
6270 static tree
6271 check_pointer_types_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
6272 void *data ATTRIBUTE_UNUSED)
6274 tree t = *tp;
6275 tree ptype, otype, dtype;
6277 switch (TREE_CODE (t))
6279 case INDIRECT_REF:
6280 case ARRAY_REF:
6281 otype = TREE_TYPE (t);
6282 ptype = TREE_TYPE (TREE_OPERAND (t, 0));
6283 dtype = TREE_TYPE (ptype);
6284 gcc_assert (cpt_same_type (otype, dtype));
6285 break;
6287 case ADDR_EXPR:
6288 ptype = TREE_TYPE (t);
6289 otype = TREE_TYPE (TREE_OPERAND (t, 0));
6290 dtype = TREE_TYPE (ptype);
6291 if (!cpt_same_type (otype, dtype))
6293 /* &array is allowed to produce a pointer to the element, rather than
6294 a pointer to the array type. We must allow this in order to
6295 properly represent assigning the address of an array in C into
6296 pointer to the element type. */
6297 gcc_assert (TREE_CODE (otype) == ARRAY_TYPE
6298 && POINTER_TYPE_P (ptype)
6299 && cpt_same_type (TREE_TYPE (otype), dtype));
6300 break;
6302 break;
6304 default:
6305 return NULL_TREE;
6309 return NULL_TREE;
6311 #endif
6313 /* Gimplify the body of statements pointed to by BODY_P. FNDECL is the
6314 function decl containing BODY. */
6316 void
6317 gimplify_body (tree *body_p, tree fndecl, bool do_parms)
6319 location_t saved_location = input_location;
6320 tree body, parm_stmts;
6322 timevar_push (TV_TREE_GIMPLIFY);
6324 gcc_assert (gimplify_ctxp == NULL);
6325 push_gimplify_context ();
6327 /* Unshare most shared trees in the body and in that of any nested functions.
6328 It would seem we don't have to do this for nested functions because
6329 they are supposed to be output and then the outer function gimplified
6330 first, but the g++ front end doesn't always do it that way. */
6331 unshare_body (body_p, fndecl);
6332 unvisit_body (body_p, fndecl);
6334 /* Make sure input_location isn't set to something wierd. */
6335 input_location = DECL_SOURCE_LOCATION (fndecl);
6337 /* Resolve callee-copies. This has to be done before processing
6338 the body so that DECL_VALUE_EXPR gets processed correctly. */
6339 parm_stmts = do_parms ? gimplify_parameters () : NULL;
6341 /* Gimplify the function's body. */
6342 gimplify_stmt (body_p);
6343 body = *body_p;
6345 if (!body)
6346 body = alloc_stmt_list ();
6347 else if (TREE_CODE (body) == STATEMENT_LIST)
6349 tree t = expr_only (*body_p);
6350 if (t)
6351 body = t;
6354 /* If there isn't an outer BIND_EXPR, add one. */
6355 if (TREE_CODE (body) != BIND_EXPR)
6357 tree b = build3 (BIND_EXPR, void_type_node, NULL_TREE,
6358 NULL_TREE, NULL_TREE);
6359 TREE_SIDE_EFFECTS (b) = 1;
6360 append_to_statement_list_force (body, &BIND_EXPR_BODY (b));
6361 body = b;
6364 /* If we had callee-copies statements, insert them at the beginning
6365 of the function. */
6366 if (parm_stmts)
6368 append_to_statement_list_force (BIND_EXPR_BODY (body), &parm_stmts);
6369 BIND_EXPR_BODY (body) = parm_stmts;
6372 /* Unshare again, in case gimplification was sloppy. */
6373 unshare_all_trees (body);
6375 *body_p = body;
6377 pop_gimplify_context (body);
6378 gcc_assert (gimplify_ctxp == NULL);
6380 #ifdef ENABLE_CHECKING
6381 walk_tree (body_p, check_pointer_types_r, NULL, NULL);
6382 #endif
6384 timevar_pop (TV_TREE_GIMPLIFY);
6385 input_location = saved_location;
6388 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
6389 node for the function we want to gimplify. */
6391 void
6392 gimplify_function_tree (tree fndecl)
6394 tree oldfn, parm, ret;
6396 oldfn = current_function_decl;
6397 current_function_decl = fndecl;
6398 cfun = DECL_STRUCT_FUNCTION (fndecl);
6399 if (cfun == NULL)
6400 allocate_struct_function (fndecl);
6402 for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = TREE_CHAIN (parm))
6404 /* Preliminarily mark non-addressed complex variables as eligible
6405 for promotion to gimple registers. We'll transform their uses
6406 as we find them. */
6407 if ((TREE_CODE (TREE_TYPE (parm)) == COMPLEX_TYPE
6408 || TREE_CODE (TREE_TYPE (parm)) == VECTOR_TYPE)
6409 && !TREE_THIS_VOLATILE (parm)
6410 && !needs_to_live_in_memory (parm))
6411 DECL_GIMPLE_REG_P (parm) = 1;
6414 ret = DECL_RESULT (fndecl);
6415 if ((TREE_CODE (TREE_TYPE (ret)) == COMPLEX_TYPE
6416 || TREE_CODE (TREE_TYPE (ret)) == VECTOR_TYPE)
6417 && !needs_to_live_in_memory (ret))
6418 DECL_GIMPLE_REG_P (ret) = 1;
6420 gimplify_body (&DECL_SAVED_TREE (fndecl), fndecl, true);
6422 /* If we're instrumenting function entry/exit, then prepend the call to
6423 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
6424 catch the exit hook. */
6425 /* ??? Add some way to ignore exceptions for this TFE. */
6426 if (flag_instrument_function_entry_exit
6427 && ! DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl))
6429 tree tf, x, bind;
6431 tf = build2 (TRY_FINALLY_EXPR, void_type_node, NULL, NULL);
6432 TREE_SIDE_EFFECTS (tf) = 1;
6433 x = DECL_SAVED_TREE (fndecl);
6434 append_to_statement_list (x, &TREE_OPERAND (tf, 0));
6435 x = implicit_built_in_decls[BUILT_IN_PROFILE_FUNC_EXIT];
6436 x = build_call_expr (x, 0);
6437 append_to_statement_list (x, &TREE_OPERAND (tf, 1));
6439 bind = build3 (BIND_EXPR, void_type_node, NULL, NULL, NULL);
6440 TREE_SIDE_EFFECTS (bind) = 1;
6441 x = implicit_built_in_decls[BUILT_IN_PROFILE_FUNC_ENTER];
6442 x = build_call_expr (x, 0);
6443 append_to_statement_list (x, &BIND_EXPR_BODY (bind));
6444 append_to_statement_list (tf, &BIND_EXPR_BODY (bind));
6446 DECL_SAVED_TREE (fndecl) = bind;
6449 cfun->gimplified = true;
6450 current_function_decl = oldfn;
6451 cfun = oldfn ? DECL_STRUCT_FUNCTION (oldfn) : NULL;
6454 /* Expands EXPR to list of gimple statements STMTS. If SIMPLE is true,
6455 force the result to be either ssa_name or an invariant, otherwise
6456 just force it to be a rhs expression. If VAR is not NULL, make the
6457 base variable of the final destination be VAR if suitable. */
6459 tree
6460 force_gimple_operand (tree expr, tree *stmts, bool simple, tree var)
6462 tree t;
6463 enum gimplify_status ret;
6464 gimple_predicate gimple_test_f;
6466 *stmts = NULL_TREE;
6468 if (is_gimple_val (expr))
6469 return expr;
6471 gimple_test_f = simple ? is_gimple_val : is_gimple_reg_rhs;
6473 push_gimplify_context ();
6474 gimplify_ctxp->into_ssa = gimple_in_ssa_p (cfun);
6476 if (var)
6477 expr = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (var), var, expr);
6479 ret = gimplify_expr (&expr, stmts, NULL,
6480 gimple_test_f, fb_rvalue);
6481 gcc_assert (ret != GS_ERROR);
6483 if (gimple_referenced_vars (cfun))
6485 for (t = gimplify_ctxp->temps; t ; t = TREE_CHAIN (t))
6486 add_referenced_var (t);
6489 pop_gimplify_context (NULL);
6491 return expr;
6494 /* Invokes force_gimple_operand for EXPR with parameters SIMPLE_P and VAR. If
6495 some statements are produced, emits them before BSI. */
6497 tree
6498 force_gimple_operand_bsi (block_stmt_iterator *bsi, tree expr,
6499 bool simple_p, tree var)
6501 tree stmts;
6503 expr = force_gimple_operand (expr, &stmts, simple_p, var);
6504 if (stmts)
6505 bsi_insert_before (bsi, stmts, BSI_SAME_STMT);
6507 return expr;
6510 #include "gt-gimplify.h"