Convert diagnostics to use quoting flag q 2/n
[official-gcc.git] / gcc / gimplify.c
blobca233617b897467877425a6a4184c1120cb3559b
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 Free Software Foundation, Inc.
4 Major work done by Sebastian Pop <s.pop@laposte.net>,
5 Diego Novillo <dnovillo@redhat.com> and Jason Merrill <jason@redhat.com>.
7 This file is part of GCC.
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 2, or (at your option) any later
12 version.
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
17 for more details.
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING. If not, write to the Free
21 Software Foundation, 59 Temple Place - Suite 330, Boston, MA
22 02111-1307, USA. */
24 #include "config.h"
25 #include "system.h"
26 #include "coretypes.h"
27 #include "tm.h"
28 #include "tree.h"
29 #include "rtl.h"
30 #include "errors.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 "target.h"
50 static struct gimplify_ctx
52 tree current_bind_expr;
53 tree temps;
54 tree conditional_cleanups;
55 tree exit_label;
56 tree return_temp;
57 varray_type case_labels;
58 /* The formal temporary table. Should this be persistent? */
59 htab_t temp_htab;
60 int conditions;
61 bool save_stack;
62 bool into_ssa;
63 } *gimplify_ctxp;
66 /* Formal (expression) temporary table handling: Multiple occurrences of
67 the same scalar expression are evaluated into the same temporary. */
69 typedef struct gimple_temp_hash_elt
71 tree val; /* Key */
72 tree temp; /* Value */
73 } elt_t;
75 /* Forward declarations. */
76 static enum gimplify_status gimplify_compound_expr (tree *, tree *, bool);
77 #ifdef ENABLE_CHECKING
78 static bool cpt_same_type (tree a, tree b);
79 #endif
82 /* Return a hash value for a formal temporary table entry. */
84 static hashval_t
85 gimple_tree_hash (const void *p)
87 tree t = ((const elt_t *) p)->val;
88 return iterative_hash_expr (t, 0);
91 /* Compare two formal temporary table entries. */
93 static int
94 gimple_tree_eq (const void *p1, const void *p2)
96 tree t1 = ((const elt_t *) p1)->val;
97 tree t2 = ((const elt_t *) p2)->val;
98 enum tree_code code = TREE_CODE (t1);
100 if (TREE_CODE (t2) != code
101 || TREE_TYPE (t1) != TREE_TYPE (t2))
102 return 0;
104 if (!operand_equal_p (t1, t2, 0))
105 return 0;
107 /* Only allow them to compare equal if they also hash equal; otherwise
108 results are nondeterminate, and we fail bootstrap comparison. */
109 gcc_assert (gimple_tree_hash (p1) == gimple_tree_hash (p2));
111 return 1;
114 /* Set up a context for the gimplifier. */
116 void
117 push_gimplify_context (void)
119 gcc_assert (!gimplify_ctxp);
120 gimplify_ctxp
121 = (struct gimplify_ctx *) xcalloc (1, sizeof (struct gimplify_ctx));
122 if (optimize)
123 gimplify_ctxp->temp_htab
124 = htab_create (1000, gimple_tree_hash, gimple_tree_eq, free);
125 else
126 gimplify_ctxp->temp_htab = NULL;
129 /* Tear down a context for the gimplifier. If BODY is non-null, then
130 put the temporaries into the outer BIND_EXPR. Otherwise, put them
131 in the unexpanded_var_list. */
133 void
134 pop_gimplify_context (tree body)
136 tree t;
138 gcc_assert (gimplify_ctxp && !gimplify_ctxp->current_bind_expr);
140 for (t = gimplify_ctxp->temps; t ; t = TREE_CHAIN (t))
141 DECL_GIMPLE_FORMAL_TEMP_P (t) = 0;
143 if (body)
144 declare_tmp_vars (gimplify_ctxp->temps, body);
145 else
146 record_vars (gimplify_ctxp->temps);
148 #if 0
149 if (!quiet_flag && optimize)
150 fprintf (stderr, " collisions: %f ",
151 htab_collisions (gimplify_ctxp->temp_htab));
152 #endif
154 if (optimize)
155 htab_delete (gimplify_ctxp->temp_htab);
156 free (gimplify_ctxp);
157 gimplify_ctxp = NULL;
160 void
161 gimple_push_bind_expr (tree bind)
163 TREE_CHAIN (bind) = gimplify_ctxp->current_bind_expr;
164 gimplify_ctxp->current_bind_expr = bind;
167 void
168 gimple_pop_bind_expr (void)
170 gimplify_ctxp->current_bind_expr
171 = TREE_CHAIN (gimplify_ctxp->current_bind_expr);
174 tree
175 gimple_current_bind_expr (void)
177 return gimplify_ctxp->current_bind_expr;
180 /* Returns true iff there is a COND_EXPR between us and the innermost
181 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
183 static bool
184 gimple_conditional_context (void)
186 return gimplify_ctxp->conditions > 0;
189 /* Note that we've entered a COND_EXPR. */
191 static void
192 gimple_push_condition (void)
194 ++(gimplify_ctxp->conditions);
197 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
198 now, add any conditional cleanups we've seen to the prequeue. */
200 static void
201 gimple_pop_condition (tree *pre_p)
203 int conds = --(gimplify_ctxp->conditions);
205 gcc_assert (conds >= 0);
206 if (conds == 0)
208 append_to_statement_list (gimplify_ctxp->conditional_cleanups, pre_p);
209 gimplify_ctxp->conditional_cleanups = NULL_TREE;
213 /* A subroutine of append_to_statement_list{,_force}. */
215 static void
216 append_to_statement_list_1 (tree t, tree *list_p, bool side_effects)
218 tree list = *list_p;
219 tree_stmt_iterator i;
221 if (!side_effects)
222 return;
224 if (!list)
226 if (t && TREE_CODE (t) == STATEMENT_LIST)
228 *list_p = t;
229 return;
231 *list_p = list = alloc_stmt_list ();
234 i = tsi_last (list);
235 tsi_link_after (&i, t, TSI_CONTINUE_LINKING);
238 /* Add T to the end of the list container pointed by LIST_P.
239 If T is an expression with no effects, it is ignored. */
241 void
242 append_to_statement_list (tree t, tree *list_p)
244 append_to_statement_list_1 (t, list_p, t ? TREE_SIDE_EFFECTS (t) : false);
247 /* Similar, but the statement is always added, regardless of side effects. */
249 void
250 append_to_statement_list_force (tree t, tree *list_p)
252 append_to_statement_list_1 (t, list_p, t != NULL);
255 /* Both gimplify the statement T and append it to LIST_P. */
257 void
258 gimplify_and_add (tree t, tree *list_p)
260 gimplify_stmt (&t);
261 append_to_statement_list (t, list_p);
264 /* Strip off a legitimate source ending from the input string NAME of
265 length LEN. Rather than having to know the names used by all of
266 our front ends, we strip off an ending of a period followed by
267 up to five characters. (Java uses ".class".) */
269 static inline void
270 remove_suffix (char *name, int len)
272 int i;
274 for (i = 2; i < 8 && len > i; i++)
276 if (name[len - i] == '.')
278 name[len - i] = '\0';
279 break;
284 /* Create a nameless artificial label and put it in the current function
285 context. Returns the newly created label. */
287 tree
288 create_artificial_label (void)
290 tree lab = build_decl (LABEL_DECL, NULL_TREE, void_type_node);
292 DECL_ARTIFICIAL (lab) = 1;
293 DECL_CONTEXT (lab) = current_function_decl;
294 return lab;
297 /* Create a new temporary name with PREFIX. Returns an identifier. */
299 static GTY(()) unsigned int tmp_var_id_num;
301 tree
302 create_tmp_var_name (const char *prefix)
304 char *tmp_name;
306 if (prefix)
308 char *preftmp = ASTRDUP (prefix);
310 remove_suffix (preftmp, strlen (preftmp));
311 prefix = preftmp;
314 ASM_FORMAT_PRIVATE_NAME (tmp_name, prefix ? prefix : "T", tmp_var_id_num++);
315 return get_identifier (tmp_name);
319 /* Create a new temporary variable declaration of type TYPE.
320 Does NOT push it into the current binding. */
322 tree
323 create_tmp_var_raw (tree type, const char *prefix)
325 tree tmp_var;
326 tree new_type;
328 /* Make the type of the variable writable. */
329 new_type = build_type_variant (type, 0, 0);
330 TYPE_ATTRIBUTES (new_type) = TYPE_ATTRIBUTES (type);
332 tmp_var = build_decl (VAR_DECL, prefix ? create_tmp_var_name (prefix) : NULL,
333 type);
335 /* The variable was declared by the compiler. */
336 DECL_ARTIFICIAL (tmp_var) = 1;
337 /* And we don't want debug info for it. */
338 DECL_IGNORED_P (tmp_var) = 1;
340 /* Make the variable writable. */
341 TREE_READONLY (tmp_var) = 0;
343 DECL_EXTERNAL (tmp_var) = 0;
344 TREE_STATIC (tmp_var) = 0;
345 TREE_USED (tmp_var) = 1;
347 return tmp_var;
350 /* Create a new temporary variable declaration of type TYPE. DOES push the
351 variable into the current binding. Further, assume that this is called
352 only from gimplification or optimization, at which point the creation of
353 certain types are bugs. */
355 tree
356 create_tmp_var (tree type, const char *prefix)
358 tree tmp_var;
360 /* We don't allow types that are addressable (meaning we can't make copies),
361 incomplete, or of variable size. */
362 gcc_assert (!TREE_ADDRESSABLE (type)
363 && COMPLETE_TYPE_P (type)
364 && TREE_CODE (TYPE_SIZE_UNIT (type)) == INTEGER_CST);
366 tmp_var = create_tmp_var_raw (type, prefix);
367 gimple_add_tmp_var (tmp_var);
368 return tmp_var;
371 /* Given a tree, try to return a useful variable name that we can use
372 to prefix a temporary that is being assigned the value of the tree.
373 I.E. given <temp> = &A, return A. */
375 const char *
376 get_name (tree t)
378 tree stripped_decl;
380 stripped_decl = t;
381 STRIP_NOPS (stripped_decl);
382 if (DECL_P (stripped_decl) && DECL_NAME (stripped_decl))
383 return IDENTIFIER_POINTER (DECL_NAME (stripped_decl));
384 else
386 switch (TREE_CODE (stripped_decl))
388 case ADDR_EXPR:
389 return get_name (TREE_OPERAND (stripped_decl, 0));
390 break;
391 default:
392 return NULL;
397 /* Create a temporary with a name derived from VAL. Subroutine of
398 lookup_tmp_var; nobody else should call this function. */
400 static inline tree
401 create_tmp_from_val (tree val)
403 return create_tmp_var (TREE_TYPE (val), get_name (val));
406 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
407 an existing expression temporary. */
409 static tree
410 lookup_tmp_var (tree val, bool is_formal)
412 tree ret;
414 /* If not optimizing, never really reuse a temporary. local-alloc
415 won't allocate any variable that is used in more than one basic
416 block, which means it will go into memory, causing much extra
417 work in reload and final and poorer code generation, outweighing
418 the extra memory allocation here. */
419 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
420 ret = create_tmp_from_val (val);
421 else
423 elt_t elt, *elt_p;
424 void **slot;
426 elt.val = val;
427 slot = htab_find_slot (gimplify_ctxp->temp_htab, (void *)&elt, INSERT);
428 if (*slot == NULL)
430 elt_p = xmalloc (sizeof (*elt_p));
431 elt_p->val = val;
432 elt_p->temp = ret = create_tmp_from_val (val);
433 *slot = (void *) elt_p;
435 else
437 elt_p = (elt_t *) *slot;
438 ret = elt_p->temp;
442 if (is_formal)
443 DECL_GIMPLE_FORMAL_TEMP_P (ret) = 1;
445 return ret;
448 /* Returns a formal temporary variable initialized with VAL. PRE_P is as
449 in gimplify_expr. Only use this function if:
451 1) The value of the unfactored expression represented by VAL will not
452 change between the initialization and use of the temporary, and
453 2) The temporary will not be otherwise modified.
455 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
456 and #2 means it is inappropriate for && temps.
458 For other cases, use get_initialized_tmp_var instead. */
460 static tree
461 internal_get_tmp_var (tree val, tree *pre_p, tree *post_p, bool is_formal)
463 tree t, mod;
465 gimplify_expr (&val, pre_p, post_p, is_gimple_formal_tmp_rhs, fb_rvalue);
467 t = lookup_tmp_var (val, is_formal);
469 mod = build (MODIFY_EXPR, TREE_TYPE (t), t, val);
471 if (EXPR_HAS_LOCATION (val))
472 SET_EXPR_LOCUS (mod, EXPR_LOCUS (val));
473 else
474 SET_EXPR_LOCATION (mod, input_location);
476 /* gimplify_modify_expr might want to reduce this further. */
477 gimplify_and_add (mod, pre_p);
479 /* If we're gimplifying into ssa, gimplify_modify_expr will have
480 given our temporary an ssa name. Find and return it. */
481 if (gimplify_ctxp->into_ssa)
482 t = TREE_OPERAND (mod, 0);
484 return t;
487 tree
488 get_formal_tmp_var (tree val, tree *pre_p)
490 return internal_get_tmp_var (val, pre_p, NULL, true);
493 /* Returns a temporary variable initialized with VAL. PRE_P and POST_P
494 are as in gimplify_expr. */
496 tree
497 get_initialized_tmp_var (tree val, tree *pre_p, tree *post_p)
499 return internal_get_tmp_var (val, pre_p, post_p, false);
502 /* Declares all the variables in VARS in SCOPE. */
504 void
505 declare_tmp_vars (tree vars, tree scope)
507 tree last = vars;
508 if (last)
510 tree temps;
512 /* C99 mode puts the default 'return 0;' for main outside the outer
513 braces. So drill down until we find an actual scope. */
514 while (TREE_CODE (scope) == COMPOUND_EXPR)
515 scope = TREE_OPERAND (scope, 0);
517 gcc_assert (TREE_CODE (scope) == BIND_EXPR);
519 temps = nreverse (last);
520 TREE_CHAIN (last) = BIND_EXPR_VARS (scope);
521 BIND_EXPR_VARS (scope) = temps;
525 void
526 gimple_add_tmp_var (tree tmp)
528 gcc_assert (!TREE_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
530 DECL_CONTEXT (tmp) = current_function_decl;
531 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
533 if (gimplify_ctxp)
535 TREE_CHAIN (tmp) = gimplify_ctxp->temps;
536 gimplify_ctxp->temps = tmp;
538 else if (cfun)
539 record_vars (tmp);
540 else
541 declare_tmp_vars (tmp, DECL_SAVED_TREE (current_function_decl));
544 /* Determines whether to assign a locus to the statement STMT. */
546 static bool
547 should_carry_locus_p (tree stmt)
549 /* Don't emit a line note for a label. We particularly don't want to
550 emit one for the break label, since it doesn't actually correspond
551 to the beginning of the loop/switch. */
552 if (TREE_CODE (stmt) == LABEL_EXPR)
553 return false;
555 /* Do not annotate empty statements, since it confuses gcov. */
556 if (!TREE_SIDE_EFFECTS (stmt))
557 return false;
559 return true;
562 static void
563 annotate_one_with_locus (tree t, location_t locus)
565 if (EXPR_P (t) && ! EXPR_HAS_LOCATION (t) && should_carry_locus_p (t))
566 SET_EXPR_LOCATION (t, locus);
569 void
570 annotate_all_with_locus (tree *stmt_p, location_t locus)
572 tree_stmt_iterator i;
574 if (!*stmt_p)
575 return;
577 for (i = tsi_start (*stmt_p); !tsi_end_p (i); tsi_next (&i))
579 tree t = tsi_stmt (i);
581 /* Assuming we've already been gimplified, we shouldn't
582 see nested chaining constructs anymore. */
583 gcc_assert (TREE_CODE (t) != STATEMENT_LIST
584 && TREE_CODE (t) != COMPOUND_EXPR);
586 annotate_one_with_locus (t, locus);
590 /* Similar to copy_tree_r() but do not copy SAVE_EXPR or TARGET_EXPR nodes.
591 These nodes model computations that should only be done once. If we
592 were to unshare something like SAVE_EXPR(i++), the gimplification
593 process would create wrong code. */
595 static tree
596 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
598 enum tree_code code = TREE_CODE (*tp);
599 /* Don't unshare types, decls, constants and SAVE_EXPR nodes. */
600 if (TREE_CODE_CLASS (code) == tcc_type
601 || TREE_CODE_CLASS (code) == tcc_declaration
602 || TREE_CODE_CLASS (code) == tcc_constant
603 || code == SAVE_EXPR || code == TARGET_EXPR
604 /* We can't do anything sensible with a BLOCK used as an expression,
605 but we also can't abort when we see it because of non-expression
606 uses. So just avert our eyes and cross our fingers. Silly Java. */
607 || code == BLOCK)
608 *walk_subtrees = 0;
609 else
611 gcc_assert (code != BIND_EXPR);
612 copy_tree_r (tp, walk_subtrees, data);
615 return NULL_TREE;
618 /* Callback for walk_tree to unshare most of the shared trees rooted at
619 *TP. If *TP has been visited already (i.e., TREE_VISITED (*TP) == 1),
620 then *TP is deep copied by calling copy_tree_r.
622 This unshares the same trees as copy_tree_r with the exception of
623 SAVE_EXPR nodes. These nodes model computations that should only be
624 done once. If we were to unshare something like SAVE_EXPR(i++), the
625 gimplification process would create wrong code. */
627 static tree
628 copy_if_shared_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
629 void *data ATTRIBUTE_UNUSED)
631 tree t = *tp;
632 enum tree_code code = TREE_CODE (t);
634 /* Skip types, decls, and constants. But we do want to look at their
635 types and the bounds of types. Mark them as visited so we properly
636 unmark their subtrees on the unmark pass. If we've already seen them,
637 don't look down further. */
638 if (TREE_CODE_CLASS (code) == tcc_type
639 || TREE_CODE_CLASS (code) == tcc_declaration
640 || TREE_CODE_CLASS (code) == tcc_constant)
642 if (TREE_VISITED (t))
643 *walk_subtrees = 0;
644 else
645 TREE_VISITED (t) = 1;
648 /* If this node has been visited already, unshare it and don't look
649 any deeper. */
650 else if (TREE_VISITED (t))
652 walk_tree (tp, mostly_copy_tree_r, NULL, NULL);
653 *walk_subtrees = 0;
656 /* Otherwise, mark the tree as visited and keep looking. */
657 else
658 TREE_VISITED (t) = 1;
660 return NULL_TREE;
663 static tree
664 unmark_visited_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
665 void *data ATTRIBUTE_UNUSED)
667 if (TREE_VISITED (*tp))
668 TREE_VISITED (*tp) = 0;
669 else
670 *walk_subtrees = 0;
672 return NULL_TREE;
675 /* Unshare all the trees in BODY_P, a pointer into the body of FNDECL, and the
676 bodies of any nested functions if we are unsharing the entire body of
677 FNDECL. */
679 static void
680 unshare_body (tree *body_p, tree fndecl)
682 struct cgraph_node *cgn = cgraph_node (fndecl);
684 walk_tree (body_p, copy_if_shared_r, NULL, NULL);
685 if (body_p == &DECL_SAVED_TREE (fndecl))
686 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
687 unshare_body (&DECL_SAVED_TREE (cgn->decl), cgn->decl);
690 /* Likewise, but mark all trees as not visited. */
692 static void
693 unvisit_body (tree *body_p, tree fndecl)
695 struct cgraph_node *cgn = cgraph_node (fndecl);
697 walk_tree (body_p, unmark_visited_r, NULL, NULL);
698 if (body_p == &DECL_SAVED_TREE (fndecl))
699 for (cgn = cgn->nested; cgn; cgn = cgn->next_nested)
700 unvisit_body (&DECL_SAVED_TREE (cgn->decl), cgn->decl);
703 /* Unshare T and all the trees reached from T via TREE_CHAIN. */
705 void
706 unshare_all_trees (tree t)
708 walk_tree (&t, copy_if_shared_r, NULL, NULL);
709 walk_tree (&t, unmark_visited_r, NULL, NULL);
712 /* Unconditionally make an unshared copy of EXPR. This is used when using
713 stored expressions which span multiple functions, such as BINFO_VTABLE,
714 as the normal unsharing process can't tell that they're shared. */
716 tree
717 unshare_expr (tree expr)
719 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
720 return expr;
723 /* A terser interface for building a representation of a exception
724 specification. */
726 tree
727 gimple_build_eh_filter (tree body, tree allowed, tree failure)
729 tree t;
731 /* FIXME should the allowed types go in TREE_TYPE? */
732 t = build (EH_FILTER_EXPR, void_type_node, allowed, NULL_TREE);
733 append_to_statement_list (failure, &EH_FILTER_FAILURE (t));
735 t = build (TRY_CATCH_EXPR, void_type_node, NULL_TREE, t);
736 append_to_statement_list (body, &TREE_OPERAND (t, 0));
738 return t;
742 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
743 contain statements and have a value. Assign its value to a temporary
744 and give it void_type_node. Returns the temporary, or NULL_TREE if
745 WRAPPER was already void. */
747 tree
748 voidify_wrapper_expr (tree wrapper, tree temp)
750 if (!VOID_TYPE_P (TREE_TYPE (wrapper)))
752 tree *p, sub = wrapper;
754 restart:
755 /* Set p to point to the body of the wrapper. */
756 switch (TREE_CODE (sub))
758 case BIND_EXPR:
759 /* For a BIND_EXPR, the body is operand 1. */
760 p = &BIND_EXPR_BODY (sub);
761 break;
763 default:
764 p = &TREE_OPERAND (sub, 0);
765 break;
768 /* Advance to the last statement. Set all container types to void. */
769 if (TREE_CODE (*p) == STATEMENT_LIST)
771 tree_stmt_iterator i = tsi_last (*p);
772 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
774 else
776 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
778 TREE_SIDE_EFFECTS (*p) = 1;
779 TREE_TYPE (*p) = void_type_node;
783 if (p == NULL || IS_EMPTY_STMT (*p))
785 /* Look through exception handling. */
786 else if (TREE_CODE (*p) == TRY_FINALLY_EXPR
787 || TREE_CODE (*p) == TRY_CATCH_EXPR)
789 sub = *p;
790 goto restart;
792 /* The C++ frontend already did this for us. */
793 else if (TREE_CODE (*p) == INIT_EXPR
794 || TREE_CODE (*p) == TARGET_EXPR)
795 temp = TREE_OPERAND (*p, 0);
796 /* If we're returning a dereference, move the dereference
797 outside the wrapper. */
798 else if (TREE_CODE (*p) == INDIRECT_REF)
800 tree ptr = TREE_OPERAND (*p, 0);
801 temp = create_tmp_var (TREE_TYPE (ptr), "retval");
802 *p = build (MODIFY_EXPR, TREE_TYPE (ptr), temp, ptr);
803 temp = build1 (INDIRECT_REF, TREE_TYPE (TREE_TYPE (temp)), temp);
804 /* If this is a BIND_EXPR for a const inline function, it might not
805 have TREE_SIDE_EFFECTS set. That is no longer accurate. */
806 TREE_SIDE_EFFECTS (wrapper) = 1;
808 else
810 if (!temp)
811 temp = create_tmp_var (TREE_TYPE (wrapper), "retval");
812 *p = build (MODIFY_EXPR, TREE_TYPE (temp), temp, *p);
813 TREE_SIDE_EFFECTS (wrapper) = 1;
816 TREE_TYPE (wrapper) = void_type_node;
817 return temp;
820 return NULL_TREE;
823 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
824 a temporary through which they communicate. */
826 static void
827 build_stack_save_restore (tree *save, tree *restore)
829 tree save_call, tmp_var;
831 save_call =
832 build_function_call_expr (implicit_built_in_decls[BUILT_IN_STACK_SAVE],
833 NULL_TREE);
834 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
836 *save = build (MODIFY_EXPR, ptr_type_node, tmp_var, save_call);
837 *restore =
838 build_function_call_expr (implicit_built_in_decls[BUILT_IN_STACK_RESTORE],
839 tree_cons (NULL_TREE, tmp_var, NULL_TREE));
842 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
844 static enum gimplify_status
845 gimplify_bind_expr (tree *expr_p, tree temp, tree *pre_p)
847 tree bind_expr = *expr_p;
848 bool old_save_stack = gimplify_ctxp->save_stack;
849 tree t;
851 temp = voidify_wrapper_expr (bind_expr, temp);
853 /* Mark variables seen in this bind expr. */
854 for (t = BIND_EXPR_VARS (bind_expr); t ; t = TREE_CHAIN (t))
855 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
857 gimple_push_bind_expr (bind_expr);
858 gimplify_ctxp->save_stack = false;
860 gimplify_to_stmt_list (&BIND_EXPR_BODY (bind_expr));
862 if (gimplify_ctxp->save_stack)
864 tree stack_save, stack_restore;
866 /* Save stack on entry and restore it on exit. Add a try_finally
867 block to achieve this. Note that mudflap depends on the
868 format of the emitted code: see mx_register_decls(). */
869 build_stack_save_restore (&stack_save, &stack_restore);
871 t = build (TRY_FINALLY_EXPR, void_type_node,
872 BIND_EXPR_BODY (bind_expr), NULL_TREE);
873 append_to_statement_list (stack_restore, &TREE_OPERAND (t, 1));
875 BIND_EXPR_BODY (bind_expr) = NULL_TREE;
876 append_to_statement_list (stack_save, &BIND_EXPR_BODY (bind_expr));
877 append_to_statement_list (t, &BIND_EXPR_BODY (bind_expr));
880 gimplify_ctxp->save_stack = old_save_stack;
881 gimple_pop_bind_expr ();
883 if (temp)
885 *expr_p = temp;
886 append_to_statement_list (bind_expr, pre_p);
887 return GS_OK;
889 else
890 return GS_ALL_DONE;
893 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
894 GIMPLE value, it is assigned to a new temporary and the statement is
895 re-written to return the temporary.
897 PRE_P points to the list where side effects that must happen before
898 STMT should be stored. */
900 static enum gimplify_status
901 gimplify_return_expr (tree stmt, tree *pre_p)
903 tree ret_expr = TREE_OPERAND (stmt, 0);
904 tree result_decl, result;
906 if (!ret_expr || TREE_CODE (ret_expr) == RESULT_DECL
907 || ret_expr == error_mark_node)
908 return GS_ALL_DONE;
910 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
911 result_decl = NULL_TREE;
912 else
914 result_decl = TREE_OPERAND (ret_expr, 0);
915 if (TREE_CODE (result_decl) == INDIRECT_REF)
916 /* See through a return by reference. */
917 result_decl = TREE_OPERAND (result_decl, 0);
919 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
920 || TREE_CODE (ret_expr) == INIT_EXPR)
921 && TREE_CODE (result_decl) == RESULT_DECL);
924 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
925 Recall that aggregate_value_p is FALSE for any aggregate type that is
926 returned in registers. If we're returning values in registers, then
927 we don't want to extend the lifetime of the RESULT_DECL, particularly
928 across another call. In addition, for those aggregates for which
929 hard_function_value generates a PARALLEL, we'll abort during normal
930 expansion of structure assignments; there's special code in expand_return
931 to handle this case that does not exist in expand_expr. */
932 if (!result_decl
933 || aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
934 result = result_decl;
935 else if (gimplify_ctxp->return_temp)
936 result = gimplify_ctxp->return_temp;
937 else
939 result = create_tmp_var (TREE_TYPE (result_decl), NULL);
941 /* ??? With complex control flow (usually involving abnormal edges),
942 we can wind up warning about an uninitialized value for this. Due
943 to how this variable is constructed and initialized, this is never
944 true. Give up and never warn. */
945 TREE_NO_WARNING (result) = 1;
947 gimplify_ctxp->return_temp = result;
950 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
951 Then gimplify the whole thing. */
952 if (result != result_decl)
953 TREE_OPERAND (ret_expr, 0) = result;
955 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
957 /* If we didn't use a temporary, then the result is just the result_decl.
958 Otherwise we need a simple copy. This should already be gimple. */
959 if (result == result_decl)
960 ret_expr = result;
961 else
962 ret_expr = build (MODIFY_EXPR, TREE_TYPE (result), result_decl, result);
963 TREE_OPERAND (stmt, 0) = ret_expr;
965 return GS_ALL_DONE;
968 /* Gimplifies a DECL_EXPR node *STMT_P by making any necessary allocation
969 and initialization explicit. */
971 static enum gimplify_status
972 gimplify_decl_expr (tree *stmt_p)
974 tree stmt = *stmt_p;
975 tree decl = DECL_EXPR_DECL (stmt);
977 *stmt_p = NULL_TREE;
979 if (TREE_TYPE (decl) == error_mark_node)
980 return GS_ERROR;
982 else if (TREE_CODE (decl) == TYPE_DECL)
983 gimplify_type_sizes (TREE_TYPE (decl), stmt_p);
985 else if (TREE_CODE (decl) == VAR_DECL && !DECL_EXTERNAL (decl))
987 tree init = DECL_INITIAL (decl);
989 if (!TREE_CONSTANT (DECL_SIZE (decl)))
991 /* This is a variable-sized decl. Simplify its size and mark it
992 for deferred expansion. Note that mudflap depends on the format
993 of the emitted code: see mx_register_decls(). */
994 tree t, args, addr, ptr_type;
996 gimplify_type_sizes (TREE_TYPE (decl), stmt_p);
997 gimplify_one_sizepos (&DECL_SIZE (decl), stmt_p);
998 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), stmt_p);
1000 /* All occurrences of this decl in final gimplified code will be
1001 replaced by indirection. Setting DECL_VALUE_EXPR does two
1002 things: First, it lets the rest of the gimplifier know what
1003 replacement to use. Second, it lets the debug info know
1004 where to find the value. */
1005 ptr_type = build_pointer_type (TREE_TYPE (decl));
1006 addr = create_tmp_var (ptr_type, get_name (decl));
1007 DECL_IGNORED_P (addr) = 0;
1008 t = build_fold_indirect_ref (addr);
1009 DECL_VALUE_EXPR (decl) = t;
1011 args = tree_cons (NULL, DECL_SIZE_UNIT (decl), NULL);
1012 t = built_in_decls[BUILT_IN_ALLOCA];
1013 t = build_function_call_expr (t, args);
1014 t = fold_convert (ptr_type, t);
1015 t = build2 (MODIFY_EXPR, void_type_node, addr, t);
1017 gimplify_and_add (t, stmt_p);
1019 /* Indicate that we need to restore the stack level when the
1020 enclosing BIND_EXPR is exited. */
1021 gimplify_ctxp->save_stack = true;
1024 if (init && init != error_mark_node)
1026 if (!TREE_STATIC (decl))
1028 DECL_INITIAL (decl) = NULL_TREE;
1029 init = build (MODIFY_EXPR, void_type_node, decl, init);
1030 gimplify_and_add (init, stmt_p);
1032 else
1033 /* We must still examine initializers for static variables
1034 as they may contain a label address. */
1035 walk_tree (&init, force_labels_r, NULL, NULL);
1038 /* This decl isn't mentioned in the enclosing block, so add it to the
1039 list of temps. FIXME it seems a bit of a kludge to say that
1040 anonymous artificial vars aren't pushed, but everything else is. */
1041 if (DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1042 gimple_add_tmp_var (decl);
1045 return GS_ALL_DONE;
1048 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1049 and replacing the LOOP_EXPR with goto, but if the loop contains an
1050 EXIT_EXPR, we need to append a label for it to jump to. */
1052 static enum gimplify_status
1053 gimplify_loop_expr (tree *expr_p, tree *pre_p)
1055 tree saved_label = gimplify_ctxp->exit_label;
1056 tree start_label = build1 (LABEL_EXPR, void_type_node, NULL_TREE);
1057 tree jump_stmt = build_and_jump (&LABEL_EXPR_LABEL (start_label));
1059 append_to_statement_list (start_label, pre_p);
1061 gimplify_ctxp->exit_label = NULL_TREE;
1063 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1065 if (gimplify_ctxp->exit_label)
1067 append_to_statement_list (jump_stmt, pre_p);
1068 *expr_p = build1 (LABEL_EXPR, void_type_node, gimplify_ctxp->exit_label);
1070 else
1071 *expr_p = jump_stmt;
1073 gimplify_ctxp->exit_label = saved_label;
1075 return GS_ALL_DONE;
1078 /* Compare two case labels. Because the front end should already have
1079 made sure that case ranges do not overlap, it is enough to only compare
1080 the CASE_LOW values of each case label. */
1082 static int
1083 compare_case_labels (const void *p1, const void *p2)
1085 tree case1 = *(tree *)p1;
1086 tree case2 = *(tree *)p2;
1088 return tree_int_cst_compare (CASE_LOW (case1), CASE_LOW (case2));
1091 /* Sort the case labels in LABEL_VEC in place in ascending order. */
1093 void
1094 sort_case_labels (tree label_vec)
1096 size_t len = TREE_VEC_LENGTH (label_vec);
1097 tree default_case = TREE_VEC_ELT (label_vec, len - 1);
1099 if (CASE_LOW (default_case))
1101 size_t i;
1103 /* The last label in the vector should be the default case
1104 but it is not. */
1105 for (i = 0; i < len; ++i)
1107 tree t = TREE_VEC_ELT (label_vec, i);
1108 if (!CASE_LOW (t))
1110 default_case = t;
1111 TREE_VEC_ELT (label_vec, i) = TREE_VEC_ELT (label_vec, len - 1);
1112 TREE_VEC_ELT (label_vec, len - 1) = default_case;
1113 break;
1118 qsort (&TREE_VEC_ELT (label_vec, 0), len - 1, sizeof (tree),
1119 compare_case_labels);
1122 /* Gimplify a SWITCH_EXPR, and collect a TREE_VEC of the labels it can
1123 branch to. */
1125 static enum gimplify_status
1126 gimplify_switch_expr (tree *expr_p, tree *pre_p)
1128 tree switch_expr = *expr_p;
1129 enum gimplify_status ret;
1131 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL,
1132 is_gimple_val, fb_rvalue);
1134 if (SWITCH_BODY (switch_expr))
1136 varray_type labels, saved_labels;
1137 tree label_vec, default_case = NULL_TREE;
1138 size_t i, len;
1140 /* If someone can be bothered to fill in the labels, they can
1141 be bothered to null out the body too. */
1142 gcc_assert (!SWITCH_LABELS (switch_expr));
1144 saved_labels = gimplify_ctxp->case_labels;
1145 VARRAY_TREE_INIT (gimplify_ctxp->case_labels, 8, "case_labels");
1147 gimplify_to_stmt_list (&SWITCH_BODY (switch_expr));
1149 labels = gimplify_ctxp->case_labels;
1150 gimplify_ctxp->case_labels = saved_labels;
1152 len = VARRAY_ACTIVE_SIZE (labels);
1154 for (i = 0; i < len; ++i)
1156 tree t = VARRAY_TREE (labels, i);
1157 if (!CASE_LOW (t))
1159 /* The default case must be the last label in the list. */
1160 default_case = t;
1161 VARRAY_TREE (labels, i) = VARRAY_TREE (labels, len - 1);
1162 len--;
1163 break;
1167 label_vec = make_tree_vec (len + 1);
1168 SWITCH_LABELS (*expr_p) = label_vec;
1169 append_to_statement_list (switch_expr, pre_p);
1171 if (! default_case)
1173 /* If the switch has no default label, add one, so that we jump
1174 around the switch body. */
1175 default_case = build (CASE_LABEL_EXPR, void_type_node, NULL_TREE,
1176 NULL_TREE, create_artificial_label ());
1177 append_to_statement_list (SWITCH_BODY (switch_expr), pre_p);
1178 *expr_p = build (LABEL_EXPR, void_type_node,
1179 CASE_LABEL (default_case));
1181 else
1182 *expr_p = SWITCH_BODY (switch_expr);
1184 for (i = 0; i < len; ++i)
1185 TREE_VEC_ELT (label_vec, i) = VARRAY_TREE (labels, i);
1186 TREE_VEC_ELT (label_vec, len) = default_case;
1188 sort_case_labels (label_vec);
1190 SWITCH_BODY (switch_expr) = NULL;
1192 else
1193 gcc_assert (SWITCH_LABELS (switch_expr));
1195 return ret;
1198 static enum gimplify_status
1199 gimplify_case_label_expr (tree *expr_p)
1201 tree expr = *expr_p;
1203 gcc_assert (gimplify_ctxp->case_labels);
1204 VARRAY_PUSH_TREE (gimplify_ctxp->case_labels, expr);
1205 *expr_p = build (LABEL_EXPR, void_type_node, CASE_LABEL (expr));
1206 return GS_ALL_DONE;
1209 /* Gimplify a LABELED_BLOCK_EXPR into a LABEL_EXPR following
1210 a (possibly empty) body. */
1212 static enum gimplify_status
1213 gimplify_labeled_block_expr (tree *expr_p)
1215 tree body = LABELED_BLOCK_BODY (*expr_p);
1216 tree label = LABELED_BLOCK_LABEL (*expr_p);
1217 tree t;
1219 DECL_CONTEXT (label) = current_function_decl;
1220 t = build (LABEL_EXPR, void_type_node, label);
1221 if (body != NULL_TREE)
1222 t = build (COMPOUND_EXPR, void_type_node, body, t);
1223 *expr_p = t;
1225 return GS_OK;
1228 /* Gimplify a EXIT_BLOCK_EXPR into a GOTO_EXPR. */
1230 static enum gimplify_status
1231 gimplify_exit_block_expr (tree *expr_p)
1233 tree labeled_block = TREE_OPERAND (*expr_p, 0);
1234 tree label;
1236 /* First operand must be a LABELED_BLOCK_EXPR, which should
1237 already be lowered (or partially lowered) when we get here. */
1238 gcc_assert (TREE_CODE (labeled_block) == LABELED_BLOCK_EXPR);
1240 label = LABELED_BLOCK_LABEL (labeled_block);
1241 *expr_p = build1 (GOTO_EXPR, void_type_node, label);
1243 return GS_OK;
1246 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
1247 if necessary. */
1249 tree
1250 build_and_jump (tree *label_p)
1252 if (label_p == NULL)
1253 /* If there's nowhere to jump, just fall through. */
1254 return NULL_TREE;
1256 if (*label_p == NULL_TREE)
1258 tree label = create_artificial_label ();
1259 *label_p = label;
1262 return build1 (GOTO_EXPR, void_type_node, *label_p);
1265 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
1266 This also involves building a label to jump to and communicating it to
1267 gimplify_loop_expr through gimplify_ctxp->exit_label. */
1269 static enum gimplify_status
1270 gimplify_exit_expr (tree *expr_p)
1272 tree cond = TREE_OPERAND (*expr_p, 0);
1273 tree expr;
1275 expr = build_and_jump (&gimplify_ctxp->exit_label);
1276 expr = build (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
1277 *expr_p = expr;
1279 return GS_OK;
1282 /* A helper function to be called via walk_tree. Mark all labels under *TP
1283 as being forced. To be called for DECL_INITIAL of static variables. */
1285 tree
1286 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1288 if (TYPE_P (*tp))
1289 *walk_subtrees = 0;
1290 if (TREE_CODE (*tp) == LABEL_DECL)
1291 FORCED_LABEL (*tp) = 1;
1293 return NULL_TREE;
1296 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
1297 different from its canonical type, wrap the whole thing inside a
1298 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
1299 type.
1301 The canonical type of a COMPONENT_REF is the type of the field being
1302 referenced--unless the field is a bit-field which can be read directly
1303 in a smaller mode, in which case the canonical type is the
1304 sign-appropriate type corresponding to that mode. */
1306 static void
1307 canonicalize_component_ref (tree *expr_p)
1309 tree expr = *expr_p;
1310 tree type;
1312 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
1314 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
1315 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
1316 else
1317 type = TREE_TYPE (TREE_OPERAND (expr, 1));
1319 if (TREE_TYPE (expr) != type)
1321 tree old_type = TREE_TYPE (expr);
1323 /* Set the type of the COMPONENT_REF to the underlying type. */
1324 TREE_TYPE (expr) = type;
1326 /* And wrap the whole thing inside a NOP_EXPR. */
1327 expr = build1 (NOP_EXPR, old_type, expr);
1329 *expr_p = expr;
1333 /* If a NOP conversion is changing a pointer to array of foo to a pointer
1334 to foo, embed that change in the ADDR_EXPR by converting
1335 T array[U];
1336 (T *)&array
1338 &array[L]
1339 where L is the lower bound. For simplicity, only do this for constant
1340 lower bound. */
1342 static void
1343 canonicalize_addr_expr (tree *expr_p)
1345 tree expr = *expr_p;
1346 tree ctype = TREE_TYPE (expr);
1347 tree addr_expr = TREE_OPERAND (expr, 0);
1348 tree atype = TREE_TYPE (addr_expr);
1349 tree dctype, datype, ddatype, otype, obj_expr;
1351 /* Both cast and addr_expr types should be pointers. */
1352 if (!POINTER_TYPE_P (ctype) || !POINTER_TYPE_P (atype))
1353 return;
1355 /* The addr_expr type should be a pointer to an array. */
1356 datype = TREE_TYPE (atype);
1357 if (TREE_CODE (datype) != ARRAY_TYPE)
1358 return;
1360 /* Both cast and addr_expr types should address the same object type. */
1361 dctype = TREE_TYPE (ctype);
1362 ddatype = TREE_TYPE (datype);
1363 if (!lang_hooks.types_compatible_p (ddatype, dctype))
1364 return;
1366 /* The addr_expr and the object type should match. */
1367 obj_expr = TREE_OPERAND (addr_expr, 0);
1368 otype = TREE_TYPE (obj_expr);
1369 if (!lang_hooks.types_compatible_p (otype, datype))
1370 return;
1372 /* The lower bound and element sizes must be constant. */
1373 if (TREE_CODE (TYPE_SIZE_UNIT (dctype)) != INTEGER_CST
1374 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
1375 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
1376 return;
1378 /* All checks succeeded. Build a new node to merge the cast. */
1379 *expr_p = build4 (ARRAY_REF, dctype, obj_expr,
1380 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
1381 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
1382 size_binop (EXACT_DIV_EXPR, TYPE_SIZE_UNIT (dctype),
1383 size_int (TYPE_ALIGN_UNIT (dctype))));
1384 *expr_p = build1 (ADDR_EXPR, ctype, *expr_p);
1387 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
1388 underneath as appropriate. */
1390 static enum gimplify_status
1391 gimplify_conversion (tree *expr_p)
1393 /* If we still have a conversion at the toplevel, then strip
1394 away all but the outermost conversion. */
1395 if (TREE_CODE (*expr_p) == NOP_EXPR || TREE_CODE (*expr_p) == CONVERT_EXPR)
1397 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
1399 /* And remove the outermost conversion if it's useless. */
1400 if (tree_ssa_useless_type_conversion (*expr_p))
1401 *expr_p = TREE_OPERAND (*expr_p, 0);
1404 /* If we still have a conversion at the toplevel,
1405 then canonicalize some constructs. */
1406 if (TREE_CODE (*expr_p) == NOP_EXPR || TREE_CODE (*expr_p) == CONVERT_EXPR)
1408 tree sub = TREE_OPERAND (*expr_p, 0);
1410 /* If a NOP conversion is changing the type of a COMPONENT_REF
1411 expression, then canonicalize its type now in order to expose more
1412 redundant conversions. */
1413 if (TREE_CODE (sub) == COMPONENT_REF)
1414 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
1416 /* If a NOP conversion is changing a pointer to array of foo
1417 to a pointer to foo, embed that change in the ADDR_EXPR. */
1418 else if (TREE_CODE (sub) == ADDR_EXPR)
1419 canonicalize_addr_expr (expr_p);
1422 return GS_OK;
1425 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
1426 node pointed by EXPR_P.
1428 compound_lval
1429 : min_lval '[' val ']'
1430 | min_lval '.' ID
1431 | compound_lval '[' val ']'
1432 | compound_lval '.' ID
1434 This is not part of the original SIMPLE definition, which separates
1435 array and member references, but it seems reasonable to handle them
1436 together. Also, this way we don't run into problems with union
1437 aliasing; gcc requires that for accesses through a union to alias, the
1438 union reference must be explicit, which was not always the case when we
1439 were splitting up array and member refs.
1441 PRE_P points to the list where side effects that must happen before
1442 *EXPR_P should be stored.
1444 POST_P points to the list where side effects that must happen after
1445 *EXPR_P should be stored. */
1447 static enum gimplify_status
1448 gimplify_compound_lval (tree *expr_p, tree *pre_p,
1449 tree *post_p, fallback_t fallback)
1451 tree *p;
1452 varray_type stack;
1453 enum gimplify_status ret = GS_OK, tret;
1454 int i;
1456 /* Create a stack of the subexpressions so later we can walk them in
1457 order from inner to outer.
1459 This array is very memory consuming. Don't even think of making
1460 it VARRAY_TREE. */
1461 VARRAY_GENERIC_PTR_NOGC_INIT (stack, 10, "stack");
1463 /* We can either handle REALPART_EXPR, IMAGEPART_EXPR anything that
1464 handled_components can deal with. */
1465 for (p = expr_p;
1466 (handled_component_p (*p)
1467 || TREE_CODE (*p) == REALPART_EXPR || TREE_CODE (*p) == IMAGPART_EXPR);
1468 p = &TREE_OPERAND (*p, 0))
1469 VARRAY_PUSH_GENERIC_PTR_NOGC (stack, *p);
1471 gcc_assert (VARRAY_ACTIVE_SIZE (stack));
1473 /* Now STACK is a stack of pointers to all the refs we've walked through
1474 and P points to the innermost expression.
1476 Java requires that we elaborated nodes in source order. That
1477 means we must gimplify the inner expression followed by each of
1478 the indices, in order. But we can't gimplify the inner
1479 expression until we deal with any variable bounds, sizes, or
1480 positions in order to deal with PLACEHOLDER_EXPRs.
1482 So we do this in three steps. First we deal with the annotations
1483 for any variables in the components, then we gimplify the base,
1484 then we gimplify any indices, from left to right. */
1485 for (i = VARRAY_ACTIVE_SIZE (stack) - 1; i >= 0; i--)
1487 tree t = VARRAY_GENERIC_PTR_NOGC (stack, i);
1489 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
1491 /* Gimplify the low bound and element type size and put them into
1492 the ARRAY_REF. If these values are set, they have already been
1493 gimplified. */
1494 if (!TREE_OPERAND (t, 2))
1496 tree low = unshare_expr (array_ref_low_bound (t));
1497 if (!is_gimple_min_invariant (low))
1499 TREE_OPERAND (t, 2) = low;
1500 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1501 is_gimple_formal_tmp_reg, fb_rvalue);
1502 ret = MIN (ret, tret);
1506 if (!TREE_OPERAND (t, 3))
1508 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
1509 tree elmt_size = unshare_expr (array_ref_element_size (t));
1510 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
1512 /* Divide the element size by the alignment of the element
1513 type (above). */
1514 elmt_size = size_binop (EXACT_DIV_EXPR, elmt_size, factor);
1516 if (!is_gimple_min_invariant (elmt_size))
1518 TREE_OPERAND (t, 3) = elmt_size;
1519 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
1520 is_gimple_formal_tmp_reg, fb_rvalue);
1521 ret = MIN (ret, tret);
1525 else if (TREE_CODE (t) == COMPONENT_REF)
1527 /* Set the field offset into T and gimplify it. */
1528 if (!TREE_OPERAND (t, 2))
1530 tree offset = unshare_expr (component_ref_field_offset (t));
1531 tree field = TREE_OPERAND (t, 1);
1532 tree factor
1533 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
1535 /* Divide the offset by its alignment. */
1536 offset = size_binop (EXACT_DIV_EXPR, offset, factor);
1538 if (!is_gimple_min_invariant (offset))
1540 TREE_OPERAND (t, 2) = offset;
1541 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1542 is_gimple_formal_tmp_reg, fb_rvalue);
1543 ret = MIN (ret, tret);
1549 /* Step 2 is to gimplify the base expression. */
1550 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval, fallback);
1551 ret = MIN (ret, tret);
1553 /* And finally, the indices and operands to BIT_FIELD_REF. During this
1554 loop we also remove any useless conversions. */
1555 for (; VARRAY_ACTIVE_SIZE (stack) > 0; )
1557 tree t = VARRAY_TOP_TREE (stack);
1559 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
1561 /* Gimplify the dimension.
1562 Temporary fix for gcc.c-torture/execute/20040313-1.c.
1563 Gimplify non-constant array indices into a temporary
1564 variable.
1565 FIXME - The real fix is to gimplify post-modify
1566 expressions into a minimal gimple lvalue. However, that
1567 exposes bugs in alias analysis. The alias analyzer does
1568 not handle &PTR->FIELD very well. Will fix after the
1569 branch is merged into mainline (dnovillo 2004-05-03). */
1570 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
1572 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
1573 is_gimple_formal_tmp_reg, fb_rvalue);
1574 ret = MIN (ret, tret);
1577 else if (TREE_CODE (t) == BIT_FIELD_REF)
1579 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
1580 is_gimple_val, fb_rvalue);
1581 ret = MIN (ret, tret);
1582 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
1583 is_gimple_val, fb_rvalue);
1584 ret = MIN (ret, tret);
1587 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
1589 /* The innermost expression P may have originally had TREE_SIDE_EFFECTS
1590 set which would have caused all the outer expressions in EXPR_P
1591 leading to P to also have had TREE_SIDE_EFFECTS set. */
1592 recalculate_side_effects (t);
1593 VARRAY_POP (stack);
1596 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval, fallback);
1597 ret = MIN (ret, tret);
1599 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
1600 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
1602 canonicalize_component_ref (expr_p);
1603 ret = MIN (ret, GS_OK);
1606 VARRAY_FREE (stack);
1608 return ret;
1611 /* Gimplify the self modifying expression pointed by EXPR_P (++, --, +=, -=).
1613 PRE_P points to the list where side effects that must happen before
1614 *EXPR_P should be stored.
1616 POST_P points to the list where side effects that must happen after
1617 *EXPR_P should be stored.
1619 WANT_VALUE is nonzero iff we want to use the value of this expression
1620 in another expression. */
1622 static enum gimplify_status
1623 gimplify_self_mod_expr (tree *expr_p, tree *pre_p, tree *post_p,
1624 bool want_value)
1626 enum tree_code code;
1627 tree lhs, lvalue, rhs, t1;
1628 bool postfix;
1629 enum tree_code arith_code;
1630 enum gimplify_status ret;
1632 code = TREE_CODE (*expr_p);
1634 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
1635 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
1637 /* Prefix or postfix? */
1638 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
1639 /* Faster to treat as prefix if result is not used. */
1640 postfix = want_value;
1641 else
1642 postfix = false;
1644 /* Add or subtract? */
1645 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
1646 arith_code = PLUS_EXPR;
1647 else
1648 arith_code = MINUS_EXPR;
1650 /* Gimplify the LHS into a GIMPLE lvalue. */
1651 lvalue = TREE_OPERAND (*expr_p, 0);
1652 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
1653 if (ret == GS_ERROR)
1654 return ret;
1656 /* Extract the operands to the arithmetic operation. */
1657 lhs = lvalue;
1658 rhs = TREE_OPERAND (*expr_p, 1);
1660 /* For postfix operator, we evaluate the LHS to an rvalue and then use
1661 that as the result value and in the postqueue operation. */
1662 if (postfix)
1664 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
1665 if (ret == GS_ERROR)
1666 return ret;
1669 t1 = build (arith_code, TREE_TYPE (*expr_p), lhs, rhs);
1670 t1 = build (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
1672 if (postfix)
1674 gimplify_and_add (t1, post_p);
1675 *expr_p = lhs;
1676 return GS_ALL_DONE;
1678 else
1680 *expr_p = t1;
1681 return GS_OK;
1685 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
1687 static void
1688 maybe_with_size_expr (tree *expr_p)
1690 tree expr = *expr_p;
1691 tree type = TREE_TYPE (expr);
1692 tree size;
1694 /* If we've already wrapped this or the type is error_mark_node, we can't do
1695 anything. */
1696 if (TREE_CODE (expr) == WITH_SIZE_EXPR
1697 || type == error_mark_node)
1698 return;
1700 /* If the size isn't known or is a constant, we have nothing to do. */
1701 size = TYPE_SIZE_UNIT (type);
1702 if (!size || TREE_CODE (size) == INTEGER_CST)
1703 return;
1705 /* Otherwise, make a WITH_SIZE_EXPR. */
1706 size = unshare_expr (size);
1707 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
1708 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
1711 /* Subroutine of gimplify_call_expr: Gimplify a single argument. */
1713 static enum gimplify_status
1714 gimplify_arg (tree *expr_p, tree *pre_p)
1716 bool (*test) (tree);
1717 fallback_t fb;
1719 /* In general, we allow lvalues for function arguments to avoid
1720 extra overhead of copying large aggregates out of even larger
1721 aggregates into temporaries only to copy the temporaries to
1722 the argument list. Make optimizers happy by pulling out to
1723 temporaries those types that fit in registers. */
1724 if (is_gimple_reg_type (TREE_TYPE (*expr_p)))
1725 test = is_gimple_val, fb = fb_rvalue;
1726 else
1727 test = is_gimple_lvalue, fb = fb_either;
1729 /* If this is a variable sized type, we must remember the size. */
1730 maybe_with_size_expr (expr_p);
1732 /* There is a sequence point before a function call. Side effects in
1733 the argument list must occur before the actual call. So, when
1734 gimplifying arguments, force gimplify_expr to use an internal
1735 post queue which is then appended to the end of PRE_P. */
1736 return gimplify_expr (expr_p, pre_p, NULL, test, fb);
1739 /* Gimplify the CALL_EXPR node pointed by EXPR_P. PRE_P points to the
1740 list where side effects that must happen before *EXPR_P should be stored.
1741 WANT_VALUE is true if the result of the call is desired. */
1743 static enum gimplify_status
1744 gimplify_call_expr (tree *expr_p, tree *pre_p, bool want_value)
1746 tree decl;
1747 tree arglist;
1748 enum gimplify_status ret;
1750 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
1752 /* For reliable diagnostics during inlining, it is necessary that
1753 every call_expr be annotated with file and line. */
1754 if (! EXPR_HAS_LOCATION (*expr_p))
1755 SET_EXPR_LOCATION (*expr_p, input_location);
1757 /* This may be a call to a builtin function.
1759 Builtin function calls may be transformed into different
1760 (and more efficient) builtin function calls under certain
1761 circumstances. Unfortunately, gimplification can muck things
1762 up enough that the builtin expanders are not aware that certain
1763 transformations are still valid.
1765 So we attempt transformation/gimplification of the call before
1766 we gimplify the CALL_EXPR. At this time we do not manage to
1767 transform all calls in the same manner as the expanders do, but
1768 we do transform most of them. */
1769 decl = get_callee_fndecl (*expr_p);
1770 if (decl && DECL_BUILT_IN (decl))
1772 tree new = fold_builtin (*expr_p, !want_value);
1774 if (new && new != *expr_p)
1776 /* There was a transformation of this call which computes the
1777 same value, but in a more efficient way. Return and try
1778 again. */
1779 *expr_p = new;
1780 return GS_OK;
1783 if (DECL_FUNCTION_CODE (decl) == BUILT_IN_VA_START)
1784 /* Avoid gimplifying the second argument to va_start, which needs
1785 to be the plain PARM_DECL. */
1786 return gimplify_arg (&TREE_VALUE (TREE_OPERAND (*expr_p, 1)), pre_p);
1789 /* There is a sequence point before the call, so any side effects in
1790 the calling expression must occur before the actual call. Force
1791 gimplify_expr to use an internal post queue. */
1792 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, NULL,
1793 is_gimple_call_addr, fb_rvalue);
1795 if (PUSH_ARGS_REVERSED)
1796 TREE_OPERAND (*expr_p, 1) = nreverse (TREE_OPERAND (*expr_p, 1));
1797 for (arglist = TREE_OPERAND (*expr_p, 1); arglist;
1798 arglist = TREE_CHAIN (arglist))
1800 enum gimplify_status t;
1802 t = gimplify_arg (&TREE_VALUE (arglist), pre_p);
1804 if (t == GS_ERROR)
1805 ret = GS_ERROR;
1807 if (PUSH_ARGS_REVERSED)
1808 TREE_OPERAND (*expr_p, 1) = nreverse (TREE_OPERAND (*expr_p, 1));
1810 /* Try this again in case gimplification exposed something. */
1811 if (ret != GS_ERROR && decl && DECL_BUILT_IN (decl))
1813 tree new = fold_builtin (*expr_p, !want_value);
1815 if (new && new != *expr_p)
1817 /* There was a transformation of this call which computes the
1818 same value, but in a more efficient way. Return and try
1819 again. */
1820 *expr_p = new;
1821 return GS_OK;
1825 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
1826 decl. This allows us to eliminate redundant or useless
1827 calls to "const" functions. */
1828 if (TREE_CODE (*expr_p) == CALL_EXPR
1829 && (call_expr_flags (*expr_p) & (ECF_CONST | ECF_PURE)))
1830 TREE_SIDE_EFFECTS (*expr_p) = 0;
1832 return ret;
1835 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
1836 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
1838 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
1839 condition is true or false, respectively. If null, we should generate
1840 our own to skip over the evaluation of this specific expression.
1842 This function is the tree equivalent of do_jump.
1844 shortcut_cond_r should only be called by shortcut_cond_expr. */
1846 static tree
1847 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p)
1849 tree local_label = NULL_TREE;
1850 tree t, expr = NULL;
1852 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
1853 retain the shortcut semantics. Just insert the gotos here;
1854 shortcut_cond_expr will append the real blocks later. */
1855 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
1857 /* Turn if (a && b) into
1859 if (a); else goto no;
1860 if (b) goto yes; else goto no;
1861 (no:) */
1863 if (false_label_p == NULL)
1864 false_label_p = &local_label;
1866 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p);
1867 append_to_statement_list (t, &expr);
1869 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
1870 false_label_p);
1871 append_to_statement_list (t, &expr);
1873 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
1875 /* Turn if (a || b) into
1877 if (a) goto yes;
1878 if (b) goto yes; else goto no;
1879 (yes:) */
1881 if (true_label_p == NULL)
1882 true_label_p = &local_label;
1884 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL);
1885 append_to_statement_list (t, &expr);
1887 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
1888 false_label_p);
1889 append_to_statement_list (t, &expr);
1891 else if (TREE_CODE (pred) == COND_EXPR)
1893 /* As long as we're messing with gotos, turn if (a ? b : c) into
1894 if (a)
1895 if (b) goto yes; else goto no;
1896 else
1897 if (c) goto yes; else goto no; */
1898 expr = build (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
1899 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
1900 false_label_p),
1901 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
1902 false_label_p));
1904 else
1906 expr = build (COND_EXPR, void_type_node, pred,
1907 build_and_jump (true_label_p),
1908 build_and_jump (false_label_p));
1911 if (local_label)
1913 t = build1 (LABEL_EXPR, void_type_node, local_label);
1914 append_to_statement_list (t, &expr);
1917 return expr;
1920 static tree
1921 shortcut_cond_expr (tree expr)
1923 tree pred = TREE_OPERAND (expr, 0);
1924 tree then_ = TREE_OPERAND (expr, 1);
1925 tree else_ = TREE_OPERAND (expr, 2);
1926 tree true_label, false_label, end_label, t;
1927 tree *true_label_p;
1928 tree *false_label_p;
1929 bool emit_end, emit_false;
1930 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
1931 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
1933 /* First do simple transformations. */
1934 if (!else_se)
1936 /* If there is no 'else', turn (a && b) into if (a) if (b). */
1937 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
1939 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
1940 then_ = shortcut_cond_expr (expr);
1941 pred = TREE_OPERAND (pred, 0);
1942 expr = build (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
1945 if (!then_se)
1947 /* If there is no 'then', turn
1948 if (a || b); else d
1949 into
1950 if (a); else if (b); else d. */
1951 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
1953 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
1954 else_ = shortcut_cond_expr (expr);
1955 pred = TREE_OPERAND (pred, 0);
1956 expr = build (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
1960 /* If we're done, great. */
1961 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
1962 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
1963 return expr;
1965 /* Otherwise we need to mess with gotos. Change
1966 if (a) c; else d;
1968 if (a); else goto no;
1969 c; goto end;
1970 no: d; end:
1971 and recursively gimplify the condition. */
1973 true_label = false_label = end_label = NULL_TREE;
1975 /* If our arms just jump somewhere, hijack those labels so we don't
1976 generate jumps to jumps. */
1978 if (then_
1979 && TREE_CODE (then_) == GOTO_EXPR
1980 && TREE_CODE (GOTO_DESTINATION (then_)) == LABEL_DECL)
1982 true_label = GOTO_DESTINATION (then_);
1983 then_ = NULL;
1984 then_se = false;
1987 if (else_
1988 && TREE_CODE (else_) == GOTO_EXPR
1989 && TREE_CODE (GOTO_DESTINATION (else_)) == LABEL_DECL)
1991 false_label = GOTO_DESTINATION (else_);
1992 else_ = NULL;
1993 else_se = false;
1996 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
1997 if (true_label)
1998 true_label_p = &true_label;
1999 else
2000 true_label_p = NULL;
2002 /* The 'else' branch also needs a label if it contains interesting code. */
2003 if (false_label || else_se)
2004 false_label_p = &false_label;
2005 else
2006 false_label_p = NULL;
2008 /* If there was nothing else in our arms, just forward the label(s). */
2009 if (!then_se && !else_se)
2010 return shortcut_cond_r (pred, true_label_p, false_label_p);
2012 /* If our last subexpression already has a terminal label, reuse it. */
2013 if (else_se)
2014 expr = expr_last (else_);
2015 else if (then_se)
2016 expr = expr_last (then_);
2017 else
2018 expr = NULL;
2019 if (expr && TREE_CODE (expr) == LABEL_EXPR)
2020 end_label = LABEL_EXPR_LABEL (expr);
2022 /* If we don't care about jumping to the 'else' branch, jump to the end
2023 if the condition is false. */
2024 if (!false_label_p)
2025 false_label_p = &end_label;
2027 /* We only want to emit these labels if we aren't hijacking them. */
2028 emit_end = (end_label == NULL_TREE);
2029 emit_false = (false_label == NULL_TREE);
2031 pred = shortcut_cond_r (pred, true_label_p, false_label_p);
2033 expr = NULL;
2034 append_to_statement_list (pred, &expr);
2036 append_to_statement_list (then_, &expr);
2037 if (else_se)
2039 t = build_and_jump (&end_label);
2040 append_to_statement_list (t, &expr);
2041 if (emit_false)
2043 t = build1 (LABEL_EXPR, void_type_node, false_label);
2044 append_to_statement_list (t, &expr);
2046 append_to_statement_list (else_, &expr);
2048 if (emit_end && end_label)
2050 t = build1 (LABEL_EXPR, void_type_node, end_label);
2051 append_to_statement_list (t, &expr);
2054 return expr;
2057 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
2059 static tree
2060 gimple_boolify (tree expr)
2062 tree type = TREE_TYPE (expr);
2064 if (TREE_CODE (type) == BOOLEAN_TYPE)
2065 return expr;
2067 /* If this is the predicate of a COND_EXPR, it might not even be a
2068 truthvalue yet. */
2069 expr = lang_hooks.truthvalue_conversion (expr);
2071 switch (TREE_CODE (expr))
2073 case TRUTH_AND_EXPR:
2074 case TRUTH_OR_EXPR:
2075 case TRUTH_XOR_EXPR:
2076 case TRUTH_ANDIF_EXPR:
2077 case TRUTH_ORIF_EXPR:
2078 /* Also boolify the arguments of truth exprs. */
2079 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
2080 /* FALLTHRU */
2082 case TRUTH_NOT_EXPR:
2083 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2084 /* FALLTHRU */
2086 case EQ_EXPR: case NE_EXPR:
2087 case LE_EXPR: case GE_EXPR: case LT_EXPR: case GT_EXPR:
2088 /* These expressions always produce boolean results. */
2089 TREE_TYPE (expr) = boolean_type_node;
2090 return expr;
2092 default:
2093 /* Other expressions that get here must have boolean values, but
2094 might need to be converted to the appropriate mode. */
2095 return convert (boolean_type_node, expr);
2099 /* Convert the conditional expression pointed by EXPR_P '(p) ? a : b;'
2100 into
2102 if (p) if (p)
2103 t1 = a; a;
2104 else or else
2105 t1 = b; b;
2108 The second form is used when *EXPR_P is of type void.
2110 TARGET is the tree for T1 above.
2112 PRE_P points to the list where side effects that must happen before
2113 *EXPR_P should be stored. */
2115 static enum gimplify_status
2116 gimplify_cond_expr (tree *expr_p, tree *pre_p, tree target)
2118 tree expr = *expr_p;
2119 tree tmp, tmp2, type;
2120 enum gimplify_status ret;
2122 type = TREE_TYPE (expr);
2123 if (!type)
2124 TREE_TYPE (expr) = void_type_node;
2126 /* If this COND_EXPR has a value, copy the values into a temporary within
2127 the arms. */
2128 else if (! VOID_TYPE_P (type))
2130 if (target)
2132 ret = gimplify_expr (&target, pre_p, NULL,
2133 is_gimple_min_lval, fb_lvalue);
2134 if (ret != GS_ERROR)
2135 ret = GS_OK;
2136 tmp = target;
2137 tmp2 = unshare_expr (target);
2139 else
2141 tmp2 = tmp = create_tmp_var (TREE_TYPE (expr), "iftmp");
2142 ret = GS_ALL_DONE;
2145 /* Build the then clause, 't1 = a;'. But don't build an assignment
2146 if this branch is void; in C++ it can be, if it's a throw. */
2147 if (TREE_TYPE (TREE_OPERAND (expr, 1)) != void_type_node)
2148 TREE_OPERAND (expr, 1)
2149 = build (MODIFY_EXPR, void_type_node, tmp, TREE_OPERAND (expr, 1));
2151 /* Build the else clause, 't1 = b;'. */
2152 if (TREE_TYPE (TREE_OPERAND (expr, 2)) != void_type_node)
2153 TREE_OPERAND (expr, 2)
2154 = build (MODIFY_EXPR, void_type_node, tmp2, TREE_OPERAND (expr, 2));
2156 TREE_TYPE (expr) = void_type_node;
2157 recalculate_side_effects (expr);
2159 /* Move the COND_EXPR to the prequeue. */
2160 gimplify_and_add (expr, pre_p);
2162 *expr_p = tmp;
2163 return ret;
2166 /* Make sure the condition has BOOLEAN_TYPE. */
2167 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
2169 /* Break apart && and || conditions. */
2170 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
2171 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
2173 expr = shortcut_cond_expr (expr);
2175 if (expr != *expr_p)
2177 *expr_p = expr;
2179 /* We can't rely on gimplify_expr to re-gimplify the expanded
2180 form properly, as cleanups might cause the target labels to be
2181 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
2182 set up a conditional context. */
2183 gimple_push_condition ();
2184 gimplify_stmt (expr_p);
2185 gimple_pop_condition (pre_p);
2187 return GS_ALL_DONE;
2191 /* Now do the normal gimplification. */
2192 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
2193 is_gimple_condexpr, fb_rvalue);
2195 gimple_push_condition ();
2197 gimplify_to_stmt_list (&TREE_OPERAND (expr, 1));
2198 gimplify_to_stmt_list (&TREE_OPERAND (expr, 2));
2199 recalculate_side_effects (expr);
2201 gimple_pop_condition (pre_p);
2203 if (ret == GS_ERROR)
2205 else if (TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 1)))
2206 ret = GS_ALL_DONE;
2207 else if (TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 2)))
2208 /* Rewrite "if (a); else b" to "if (!a) b" */
2210 TREE_OPERAND (expr, 0) = invert_truthvalue (TREE_OPERAND (expr, 0));
2211 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
2212 is_gimple_condexpr, fb_rvalue);
2214 tmp = TREE_OPERAND (expr, 1);
2215 TREE_OPERAND (expr, 1) = TREE_OPERAND (expr, 2);
2216 TREE_OPERAND (expr, 2) = tmp;
2218 else
2219 /* Both arms are empty; replace the COND_EXPR with its predicate. */
2220 expr = TREE_OPERAND (expr, 0);
2222 *expr_p = expr;
2223 return ret;
2226 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
2227 a call to __builtin_memcpy. */
2229 static enum gimplify_status
2230 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value)
2232 tree args, t, to, to_ptr, from;
2234 to = TREE_OPERAND (*expr_p, 0);
2235 from = TREE_OPERAND (*expr_p, 1);
2237 args = tree_cons (NULL, size, NULL);
2239 t = build_fold_addr_expr (from);
2240 args = tree_cons (NULL, t, args);
2242 to_ptr = build_fold_addr_expr (to);
2243 args = tree_cons (NULL, to_ptr, args);
2244 t = implicit_built_in_decls[BUILT_IN_MEMCPY];
2245 t = build_function_call_expr (t, args);
2247 if (want_value)
2249 t = build1 (NOP_EXPR, TREE_TYPE (to_ptr), t);
2250 t = build1 (INDIRECT_REF, TREE_TYPE (to), t);
2253 *expr_p = t;
2254 return GS_OK;
2257 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
2258 a call to __builtin_memset. In this case we know that the RHS is
2259 a CONSTRUCTOR with an empty element list. */
2261 static enum gimplify_status
2262 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value)
2264 tree args, t, to, to_ptr;
2266 to = TREE_OPERAND (*expr_p, 0);
2268 args = tree_cons (NULL, size, NULL);
2270 args = tree_cons (NULL, integer_zero_node, args);
2272 to_ptr = build_fold_addr_expr (to);
2273 args = tree_cons (NULL, to_ptr, args);
2274 t = implicit_built_in_decls[BUILT_IN_MEMSET];
2275 t = build_function_call_expr (t, args);
2277 if (want_value)
2279 t = build1 (NOP_EXPR, TREE_TYPE (to_ptr), t);
2280 t = build1 (INDIRECT_REF, TREE_TYPE (to), t);
2283 *expr_p = t;
2284 return GS_OK;
2287 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
2288 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
2289 assignment. Returns non-null if we detect a potential overlap. */
2291 struct gimplify_init_ctor_preeval_data
2293 /* The base decl of the lhs object. May be NULL, in which case we
2294 have to assume the lhs is indirect. */
2295 tree lhs_base_decl;
2297 /* The alias set of the lhs object. */
2298 int lhs_alias_set;
2301 static tree
2302 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
2304 struct gimplify_init_ctor_preeval_data *data
2305 = (struct gimplify_init_ctor_preeval_data *) xdata;
2306 tree t = *tp;
2308 /* If we find the base object, obviously we have overlap. */
2309 if (data->lhs_base_decl == t)
2310 return t;
2312 /* If the constructor component is indirect, determine if we have a
2313 potential overlap with the lhs. The only bits of information we
2314 have to go on at this point are addressability and alias sets. */
2315 if (TREE_CODE (t) == INDIRECT_REF
2316 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
2317 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
2318 return t;
2320 if (IS_TYPE_OR_DECL_P (t))
2321 *walk_subtrees = 0;
2322 return NULL;
2325 /* A subroutine of gimplify_init_constructor. Pre-evaluate *EXPR_P,
2326 force values that overlap with the lhs (as described by *DATA)
2327 into temporaries. */
2329 static void
2330 gimplify_init_ctor_preeval (tree *expr_p, tree *pre_p, tree *post_p,
2331 struct gimplify_init_ctor_preeval_data *data)
2333 enum gimplify_status one;
2335 /* If the value is invariant, then there's nothing to pre-evaluate.
2336 But ensure it doesn't have any side-effects since a SAVE_EXPR is
2337 invariant but has side effects and might contain a reference to
2338 the object we're initializing. */
2339 if (TREE_INVARIANT (*expr_p) && !TREE_SIDE_EFFECTS (*expr_p))
2340 return;
2342 /* If the type has non-trivial constructors, we can't pre-evaluate. */
2343 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
2344 return;
2346 /* Recurse for nested constructors. */
2347 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
2349 tree list;
2350 for (list = CONSTRUCTOR_ELTS (*expr_p); list ; list = TREE_CHAIN (list))
2351 gimplify_init_ctor_preeval (&TREE_VALUE (list), pre_p, post_p, data);
2352 return;
2355 /* We can't preevaluate if the type contains a placeholder. */
2356 if (type_contains_placeholder_p (TREE_TYPE (*expr_p)))
2357 return;
2359 /* Gimplify the constructor element to something appropriate for the rhs
2360 of a MODIFY_EXPR. Given that we know the lhs is an aggregate, we know
2361 the gimplifier will consider this a store to memory. Doing this
2362 gimplification now means that we won't have to deal with complicated
2363 language-specific trees, nor trees like SAVE_EXPR that can induce
2364 exponential search behavior. */
2365 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
2366 if (one == GS_ERROR)
2368 *expr_p = NULL;
2369 return;
2372 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
2373 with the lhs, since "a = { .x=a }" doesn't make sense. This will
2374 always be true for all scalars, since is_gimple_mem_rhs insists on a
2375 temporary variable for them. */
2376 if (DECL_P (*expr_p))
2377 return;
2379 /* If this is of variable size, we have no choice but to assume it doesn't
2380 overlap since we can't make a temporary for it. */
2381 if (!TREE_CONSTANT (TYPE_SIZE (TREE_TYPE (*expr_p))))
2382 return;
2384 /* Otherwise, we must search for overlap ... */
2385 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
2386 return;
2388 /* ... and if found, force the value into a temporary. */
2389 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
2392 /* A subroutine of gimplify_init_constructor. Generate individual
2393 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
2394 assignments should happen. LIST is the CONSTRUCTOR_ELTS of the
2395 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
2396 zeroed first. */
2398 static void
2399 gimplify_init_ctor_eval (tree object, tree list, tree *pre_p, bool cleared)
2401 tree array_elt_type = NULL;
2403 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
2404 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
2406 for (; list; list = TREE_CHAIN (list))
2408 tree purpose, value, cref, init;
2410 purpose = TREE_PURPOSE (list);
2411 value = TREE_VALUE (list);
2413 /* NULL values are created above for gimplification errors. */
2414 if (value == NULL)
2415 continue;
2417 if (cleared && initializer_zerop (value))
2418 continue;
2420 if (array_elt_type)
2422 /* ??? Here's to hoping the front end fills in all of the indicies,
2423 so we don't have to figure out what's missing ourselves. */
2424 gcc_assert (purpose);
2425 /* ??? Need to handle this. */
2426 gcc_assert (TREE_CODE (purpose) != RANGE_EXPR);
2428 cref = build (ARRAY_REF, array_elt_type, unshare_expr (object),
2429 purpose, NULL_TREE, NULL_TREE);
2431 else
2432 cref = build (COMPONENT_REF, TREE_TYPE (purpose),
2433 unshare_expr (object), purpose, NULL_TREE);
2435 if (TREE_CODE (value) == CONSTRUCTOR)
2436 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
2437 pre_p, cleared);
2438 else
2440 init = build (MODIFY_EXPR, TREE_TYPE (cref), cref, value);
2441 gimplify_and_add (init, pre_p);
2446 /* A subroutine of gimplify_modify_expr. Break out elements of a
2447 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
2449 Note that we still need to clear any elements that don't have explicit
2450 initializers, so if not all elements are initialized we keep the
2451 original MODIFY_EXPR, we just remove all of the constructor elements. */
2453 static enum gimplify_status
2454 gimplify_init_constructor (tree *expr_p, tree *pre_p,
2455 tree *post_p, bool want_value)
2457 tree object;
2458 tree ctor = TREE_OPERAND (*expr_p, 1);
2459 tree type = TREE_TYPE (ctor);
2460 enum gimplify_status ret;
2461 tree elt_list;
2463 if (TREE_CODE (ctor) != CONSTRUCTOR)
2464 return GS_UNHANDLED;
2466 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
2467 is_gimple_lvalue, fb_lvalue);
2468 if (ret == GS_ERROR)
2469 return ret;
2470 object = TREE_OPERAND (*expr_p, 0);
2472 elt_list = CONSTRUCTOR_ELTS (ctor);
2474 ret = GS_ALL_DONE;
2475 switch (TREE_CODE (type))
2477 case RECORD_TYPE:
2478 case UNION_TYPE:
2479 case QUAL_UNION_TYPE:
2480 case ARRAY_TYPE:
2482 struct gimplify_init_ctor_preeval_data preeval_data;
2483 HOST_WIDE_INT num_elements, num_nonzero_elements;
2484 HOST_WIDE_INT num_nonconstant_elements;
2485 bool cleared;
2487 /* Aggregate types must lower constructors to initialization of
2488 individual elements. The exception is that a CONSTRUCTOR node
2489 with no elements indicates zero-initialization of the whole. */
2490 if (elt_list == NULL)
2491 break;
2493 categorize_ctor_elements (ctor, &num_nonzero_elements,
2494 &num_nonconstant_elements);
2496 /* If a const aggregate variable is being initialized, then it
2497 should never be a lose to promote the variable to be static. */
2498 if (num_nonconstant_elements == 0
2499 && TREE_READONLY (object)
2500 && TREE_CODE (object) == VAR_DECL)
2502 DECL_INITIAL (object) = ctor;
2503 TREE_STATIC (object) = 1;
2504 if (!DECL_NAME (object))
2505 DECL_NAME (object) = create_tmp_var_name ("C");
2506 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
2508 /* ??? C++ doesn't automatically append a .<number> to the
2509 assembler name, and even when it does, it looks a FE private
2510 data structures to figure out what that number should be,
2511 which are not set for this variable. I suppose this is
2512 important for local statics for inline functions, which aren't
2513 "local" in the object file sense. So in order to get a unique
2514 TU-local symbol, we must invoke the lhd version now. */
2515 lhd_set_decl_assembler_name (object);
2517 *expr_p = NULL_TREE;
2518 break;
2521 /* If there are "lots" of initialized elements, and all of them
2522 are valid address constants, then the entire initializer can
2523 be dropped to memory, and then memcpy'd out. */
2524 if (num_nonconstant_elements == 0)
2526 HOST_WIDE_INT size = int_size_in_bytes (type);
2527 unsigned int align;
2529 /* ??? We can still get unbounded array types, at least
2530 from the C++ front end. This seems wrong, but attempt
2531 to work around it for now. */
2532 if (size < 0)
2534 size = int_size_in_bytes (TREE_TYPE (object));
2535 if (size >= 0)
2536 TREE_TYPE (ctor) = type = TREE_TYPE (object);
2539 /* Find the maximum alignment we can assume for the object. */
2540 /* ??? Make use of DECL_OFFSET_ALIGN. */
2541 if (DECL_P (object))
2542 align = DECL_ALIGN (object);
2543 else
2544 align = TYPE_ALIGN (type);
2546 if (size > 0 && !can_move_by_pieces (size, align))
2548 tree new = create_tmp_var_raw (type, "C");
2550 gimple_add_tmp_var (new);
2551 TREE_STATIC (new) = 1;
2552 TREE_READONLY (new) = 1;
2553 DECL_INITIAL (new) = ctor;
2554 if (align > DECL_ALIGN (new))
2556 DECL_ALIGN (new) = align;
2557 DECL_USER_ALIGN (new) = 1;
2559 walk_tree (&DECL_INITIAL (new), force_labels_r, NULL, NULL);
2561 TREE_OPERAND (*expr_p, 1) = new;
2563 /* This is no longer an assignment of a CONSTRUCTOR, but
2564 we still may have processing to do on the LHS. So
2565 pretend we didn't do anything here to let that happen. */
2566 return GS_UNHANDLED;
2570 /* If there are "lots" of initialized elements, even discounting
2571 those that are not address constants (and thus *must* be
2572 computed at runtime), then partition the constructor into
2573 constant and non-constant parts. Block copy the constant
2574 parts in, then generate code for the non-constant parts. */
2575 /* TODO. There's code in cp/typeck.c to do this. */
2577 num_elements = count_type_elements (TREE_TYPE (ctor));
2579 /* If there are "lots" of zeros, then block clear the object first. */
2580 cleared = false;
2581 if (num_elements - num_nonzero_elements > CLEAR_RATIO
2582 && num_nonzero_elements < num_elements/4)
2583 cleared = true;
2585 /* ??? This bit ought not be needed. For any element not present
2586 in the initializer, we should simply set them to zero. Except
2587 we'd need to *find* the elements that are not present, and that
2588 requires trickery to avoid quadratic compile-time behavior in
2589 large cases or excessive memory use in small cases. */
2590 else
2592 HOST_WIDE_INT len = list_length (elt_list);
2593 if (TREE_CODE (type) == ARRAY_TYPE)
2595 tree nelts = array_type_nelts (type);
2596 if (!host_integerp (nelts, 1)
2597 || tree_low_cst (nelts, 1) + 1 != len)
2598 cleared = true;
2600 else if (len != fields_length (type))
2601 cleared = true;
2604 if (cleared)
2606 /* Zap the CONSTRUCTOR element list, which simplifies this case.
2607 Note that we still have to gimplify, in order to handle the
2608 case of variable sized types. Avoid shared tree structures. */
2609 CONSTRUCTOR_ELTS (ctor) = NULL_TREE;
2610 object = unshare_expr (object);
2611 gimplify_stmt (expr_p);
2612 append_to_statement_list (*expr_p, pre_p);
2615 preeval_data.lhs_base_decl = get_base_address (object);
2616 if (!DECL_P (preeval_data.lhs_base_decl))
2617 preeval_data.lhs_base_decl = NULL;
2618 preeval_data.lhs_alias_set = get_alias_set (object);
2620 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
2621 pre_p, post_p, &preeval_data);
2622 gimplify_init_ctor_eval (object, elt_list, pre_p, cleared);
2624 *expr_p = NULL_TREE;
2626 break;
2628 case COMPLEX_TYPE:
2630 tree r, i;
2632 /* Extract the real and imaginary parts out of the ctor. */
2633 r = i = NULL_TREE;
2634 if (elt_list)
2636 r = TREE_VALUE (elt_list);
2637 elt_list = TREE_CHAIN (elt_list);
2638 if (elt_list)
2640 i = TREE_VALUE (elt_list);
2641 gcc_assert (!TREE_CHAIN (elt_list));
2644 if (r == NULL || i == NULL)
2646 tree zero = convert (TREE_TYPE (type), integer_zero_node);
2647 if (r == NULL)
2648 r = zero;
2649 if (i == NULL)
2650 i = zero;
2653 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
2654 represent creation of a complex value. */
2655 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
2657 ctor = build_complex (type, r, i);
2658 TREE_OPERAND (*expr_p, 1) = ctor;
2660 else
2662 ctor = build (COMPLEX_EXPR, type, r, i);
2663 TREE_OPERAND (*expr_p, 1) = ctor;
2664 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
2665 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
2666 fb_rvalue);
2669 break;
2671 case VECTOR_TYPE:
2672 /* Go ahead and simplify constant constructors to VECTOR_CST. */
2673 if (TREE_CONSTANT (ctor))
2674 TREE_OPERAND (*expr_p, 1) = build_vector (type, elt_list);
2675 else
2677 /* Vector types use CONSTRUCTOR all the way through gimple
2678 compilation as a general initializer. */
2679 for (; elt_list; elt_list = TREE_CHAIN (elt_list))
2681 enum gimplify_status tret;
2682 tret = gimplify_expr (&TREE_VALUE (elt_list), pre_p, post_p,
2683 is_gimple_val, fb_rvalue);
2684 if (tret == GS_ERROR)
2685 ret = GS_ERROR;
2688 break;
2690 default:
2691 /* So how did we get a CONSTRUCTOR for a scalar type? */
2692 gcc_unreachable ();
2695 if (ret == GS_ERROR)
2696 return GS_ERROR;
2697 else if (want_value)
2699 append_to_statement_list (*expr_p, pre_p);
2700 *expr_p = object;
2701 return GS_OK;
2703 else
2704 return GS_ALL_DONE;
2707 /* Subroutine of gimplify_modify_expr to do simplifications of MODIFY_EXPRs
2708 based on the code of the RHS. We loop for as long as something changes. */
2710 static enum gimplify_status
2711 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p, tree *pre_p,
2712 tree *post_p, bool want_value)
2714 enum gimplify_status ret = GS_OK;
2716 while (ret != GS_UNHANDLED)
2717 switch (TREE_CODE (*from_p))
2719 case TARGET_EXPR:
2721 /* If we are initializing something from a TARGET_EXPR, strip the
2722 TARGET_EXPR and initialize it directly, if possible. This can't
2723 be done if the initializer is void, since that implies that the
2724 temporary is set in some non-trivial way.
2726 ??? What about code that pulls out the temp and uses it
2727 elsewhere? I think that such code never uses the TARGET_EXPR as
2728 an initializer. If I'm wrong, we'll abort because the temp won't
2729 have any RTL. In that case, I guess we'll need to replace
2730 references somehow. */
2731 tree init = TARGET_EXPR_INITIAL (*from_p);
2733 if (!VOID_TYPE_P (TREE_TYPE (init)))
2735 *from_p = init;
2736 ret = GS_OK;
2738 else
2739 ret = GS_UNHANDLED;
2741 break;
2743 case COMPOUND_EXPR:
2744 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
2745 caught. */
2746 gimplify_compound_expr (from_p, pre_p, true);
2747 ret = GS_OK;
2748 break;
2750 case CONSTRUCTOR:
2751 /* If we're initializing from a CONSTRUCTOR, break this into
2752 individual MODIFY_EXPRs. */
2753 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value);
2755 case COND_EXPR:
2756 /* If we're assigning to a non-register type, push the assignment
2757 down into the branches. This is mandatory for ADDRESSABLE types,
2758 since we cannot generate temporaries for such, but it saves a
2759 copy in other cases as well. */
2760 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
2762 *expr_p = *from_p;
2763 return gimplify_cond_expr (expr_p, pre_p, *to_p);
2765 else
2766 ret = GS_UNHANDLED;
2767 break;
2769 default:
2770 ret = GS_UNHANDLED;
2771 break;
2774 return ret;
2777 /* Gimplify the MODIFY_EXPR node pointed by EXPR_P.
2779 modify_expr
2780 : varname '=' rhs
2781 | '*' ID '=' rhs
2783 PRE_P points to the list where side effects that must happen before
2784 *EXPR_P should be stored.
2786 POST_P points to the list where side effects that must happen after
2787 *EXPR_P should be stored.
2789 WANT_VALUE is nonzero iff we want to use the value of this expression
2790 in another expression. */
2792 static enum gimplify_status
2793 gimplify_modify_expr (tree *expr_p, tree *pre_p, tree *post_p, bool want_value)
2795 tree *from_p = &TREE_OPERAND (*expr_p, 1);
2796 tree *to_p = &TREE_OPERAND (*expr_p, 0);
2797 enum gimplify_status ret = GS_UNHANDLED;
2799 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
2800 || TREE_CODE (*expr_p) == INIT_EXPR);
2802 /* The distinction between MODIFY_EXPR and INIT_EXPR is no longer useful. */
2803 if (TREE_CODE (*expr_p) == INIT_EXPR)
2804 TREE_SET_CODE (*expr_p, MODIFY_EXPR);
2806 /* See if any simplifications can be done based on what the RHS is. */
2807 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
2808 want_value);
2809 if (ret != GS_UNHANDLED)
2810 return ret;
2812 /* If the value being copied is of variable width, compute the length
2813 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
2814 before gimplifying any of the operands so that we can resolve any
2815 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
2816 the size of the expression to be copied, not of the destination, so
2817 that is what we must here. */
2818 maybe_with_size_expr (from_p);
2820 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
2821 if (ret == GS_ERROR)
2822 return ret;
2824 ret = gimplify_expr (from_p, pre_p, post_p,
2825 rhs_predicate_for (*to_p), fb_rvalue);
2826 if (ret == GS_ERROR)
2827 return ret;
2829 /* Now see if the above changed *from_p to something we handle specially. */
2830 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
2831 want_value);
2832 if (ret != GS_UNHANDLED)
2833 return ret;
2835 /* If we've got a variable sized assignment between two lvalues (i.e. does
2836 not involve a call), then we can make things a bit more straightforward
2837 by converting the assignment to memcpy or memset. */
2838 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
2840 tree from = TREE_OPERAND (*from_p, 0);
2841 tree size = TREE_OPERAND (*from_p, 1);
2843 if (TREE_CODE (from) == CONSTRUCTOR)
2844 return gimplify_modify_expr_to_memset (expr_p, size, want_value);
2845 if (is_gimple_addressable (from))
2847 *from_p = from;
2848 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value);
2852 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
2854 /* If we've somehow already got an SSA_NAME on the LHS, then
2855 we're probably modifying it twice. Not good. */
2856 gcc_assert (TREE_CODE (*to_p) != SSA_NAME);
2857 *to_p = make_ssa_name (*to_p, *expr_p);
2860 if (want_value)
2862 append_to_statement_list (*expr_p, pre_p);
2863 *expr_p = *to_p;
2864 return GS_OK;
2867 return GS_ALL_DONE;
2870 /* Gimplify a comparison between two variable-sized objects. Do this
2871 with a call to BUILT_IN_MEMCMP. */
2873 static enum gimplify_status
2874 gimplify_variable_sized_compare (tree *expr_p)
2876 tree op0 = TREE_OPERAND (*expr_p, 0);
2877 tree op1 = TREE_OPERAND (*expr_p, 1);
2878 tree args, t, dest;
2880 t = TYPE_SIZE_UNIT (TREE_TYPE (op0));
2881 t = unshare_expr (t);
2882 t = SUBSTITUTE_PLACEHOLDER_IN_EXPR (t, op0);
2883 args = tree_cons (NULL, t, NULL);
2884 t = build_fold_addr_expr (op1);
2885 args = tree_cons (NULL, t, args);
2886 dest = build_fold_addr_expr (op0);
2887 args = tree_cons (NULL, dest, args);
2888 t = implicit_built_in_decls[BUILT_IN_MEMCMP];
2889 t = build_function_call_expr (t, args);
2890 *expr_p
2891 = build (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
2893 return GS_OK;
2896 /* Gimplify TRUTH_ANDIF_EXPR and TRUTH_ORIF_EXPR expressions. EXPR_P
2897 points to the expression to gimplify.
2899 Expressions of the form 'a && b' are gimplified to:
2901 a && b ? true : false
2903 gimplify_cond_expr will do the rest.
2905 PRE_P points to the list where side effects that must happen before
2906 *EXPR_P should be stored. */
2908 static enum gimplify_status
2909 gimplify_boolean_expr (tree *expr_p)
2911 /* Preserve the original type of the expression. */
2912 tree type = TREE_TYPE (*expr_p);
2914 *expr_p = build (COND_EXPR, type, *expr_p,
2915 convert (type, boolean_true_node),
2916 convert (type, boolean_false_node));
2918 return GS_OK;
2921 /* Gimplifies an expression sequence. This function gimplifies each
2922 expression and re-writes the original expression with the last
2923 expression of the sequence in GIMPLE form.
2925 PRE_P points to the list where the side effects for all the
2926 expressions in the sequence will be emitted.
2928 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
2929 /* ??? Should rearrange to share the pre-queue with all the indirect
2930 invocations of gimplify_expr. Would probably save on creations
2931 of statement_list nodes. */
2933 static enum gimplify_status
2934 gimplify_compound_expr (tree *expr_p, tree *pre_p, bool want_value)
2936 tree t = *expr_p;
2940 tree *sub_p = &TREE_OPERAND (t, 0);
2942 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
2943 gimplify_compound_expr (sub_p, pre_p, false);
2944 else
2945 gimplify_stmt (sub_p);
2946 append_to_statement_list (*sub_p, pre_p);
2948 t = TREE_OPERAND (t, 1);
2950 while (TREE_CODE (t) == COMPOUND_EXPR);
2952 *expr_p = t;
2953 if (want_value)
2954 return GS_OK;
2955 else
2957 gimplify_stmt (expr_p);
2958 return GS_ALL_DONE;
2962 /* Gimplifies a statement list. These may be created either by an
2963 enlightened front-end, or by shortcut_cond_expr. */
2965 static enum gimplify_status
2966 gimplify_statement_list (tree *expr_p)
2968 tree_stmt_iterator i = tsi_start (*expr_p);
2970 while (!tsi_end_p (i))
2972 tree t;
2974 gimplify_stmt (tsi_stmt_ptr (i));
2976 t = tsi_stmt (i);
2977 if (t == NULL)
2978 tsi_delink (&i);
2979 else if (TREE_CODE (t) == STATEMENT_LIST)
2981 tsi_link_before (&i, t, TSI_SAME_STMT);
2982 tsi_delink (&i);
2984 else
2985 tsi_next (&i);
2988 return GS_ALL_DONE;
2991 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
2992 gimplify. After gimplification, EXPR_P will point to a new temporary
2993 that holds the original value of the SAVE_EXPR node.
2995 PRE_P points to the list where side effects that must happen before
2996 *EXPR_P should be stored. */
2998 static enum gimplify_status
2999 gimplify_save_expr (tree *expr_p, tree *pre_p, tree *post_p)
3001 enum gimplify_status ret = GS_ALL_DONE;
3002 tree val;
3004 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
3005 val = TREE_OPERAND (*expr_p, 0);
3007 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
3008 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
3010 /* The operand may be a void-valued expression such as SAVE_EXPRs
3011 generated by the Java frontend for class initialization. It is
3012 being executed only for its side-effects. */
3013 if (TREE_TYPE (val) == void_type_node)
3015 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3016 is_gimple_stmt, fb_none);
3017 append_to_statement_list (TREE_OPERAND (*expr_p, 0), pre_p);
3018 val = NULL;
3020 else
3021 val = get_initialized_tmp_var (val, pre_p, post_p);
3023 TREE_OPERAND (*expr_p, 0) = val;
3024 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
3027 *expr_p = val;
3029 return ret;
3032 /* Re-write the ADDR_EXPR node pointed by EXPR_P
3034 unary_expr
3035 : ...
3036 | '&' varname
3039 PRE_P points to the list where side effects that must happen before
3040 *EXPR_P should be stored.
3042 POST_P points to the list where side effects that must happen after
3043 *EXPR_P should be stored. */
3045 static enum gimplify_status
3046 gimplify_addr_expr (tree *expr_p, tree *pre_p, tree *post_p)
3048 tree expr = *expr_p;
3049 tree op0 = TREE_OPERAND (expr, 0);
3050 enum gimplify_status ret;
3052 switch (TREE_CODE (op0))
3054 case INDIRECT_REF:
3055 case MISALIGNED_INDIRECT_REF:
3056 do_indirect_ref:
3057 /* Check if we are dealing with an expression of the form '&*ptr'.
3058 While the front end folds away '&*ptr' into 'ptr', these
3059 expressions may be generated internally by the compiler (e.g.,
3060 builtins like __builtin_va_end). */
3061 /* Caution: the silent array decomposition semantics we allow for
3062 ADDR_EXPR means we can't always discard the pair. */
3064 tree op00 = TREE_OPERAND (op0, 0);
3065 tree t_expr = TREE_TYPE (expr);
3066 tree t_op00 = TREE_TYPE (op00);
3068 if (!lang_hooks.types_compatible_p (t_expr, t_op00))
3070 #ifdef ENABLE_CHECKING
3071 tree t_op0 = TREE_TYPE (op0);
3072 gcc_assert (TREE_CODE (t_op0) == ARRAY_TYPE
3073 && POINTER_TYPE_P (t_expr)
3074 && cpt_same_type (TREE_TYPE (t_op0),
3075 TREE_TYPE (t_expr))
3076 && POINTER_TYPE_P (t_op00)
3077 && cpt_same_type (t_op0, TREE_TYPE (t_op00)));
3078 #endif
3079 op00 = fold_convert (TREE_TYPE (expr), op00);
3081 *expr_p = op00;
3082 ret = GS_OK;
3084 break;
3086 case VIEW_CONVERT_EXPR:
3087 /* Take the address of our operand and then convert it to the type of
3088 this ADDR_EXPR.
3090 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
3091 all clear. The impact of this transformation is even less clear. */
3092 *expr_p = fold_convert (TREE_TYPE (expr),
3093 build_fold_addr_expr (TREE_OPERAND (op0, 0)));
3094 ret = GS_OK;
3095 break;
3097 default:
3098 /* We use fb_either here because the C frontend sometimes takes
3099 the address of a call that returns a struct; see
3100 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
3101 the implied temporary explicit. */
3102 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
3103 is_gimple_addressable, fb_either);
3104 if (ret != GS_ERROR)
3106 op0 = TREE_OPERAND (expr, 0);
3108 /* For various reasons, the gimplification of the expression
3109 may have made a new INDIRECT_REF. */
3110 if (TREE_CODE (op0) == INDIRECT_REF)
3111 goto do_indirect_ref;
3113 /* Make sure TREE_INVARIANT, TREE_CONSTANT, and TREE_SIDE_EFFECTS
3114 is set properly. */
3115 recompute_tree_invarant_for_addr_expr (expr);
3117 /* Mark the RHS addressable. */
3118 lang_hooks.mark_addressable (TREE_OPERAND (expr, 0));
3120 break;
3123 return ret;
3126 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
3127 value; output operands should be a gimple lvalue. */
3129 static enum gimplify_status
3130 gimplify_asm_expr (tree *expr_p, tree *pre_p, tree *post_p)
3132 tree expr = *expr_p;
3133 int noutputs = list_length (ASM_OUTPUTS (expr));
3134 const char **oconstraints
3135 = (const char **) alloca ((noutputs) * sizeof (const char *));
3136 int i;
3137 tree link;
3138 const char *constraint;
3139 bool allows_mem, allows_reg, is_inout;
3140 enum gimplify_status ret, tret;
3142 ASM_STRING (expr)
3143 = resolve_asm_operand_names (ASM_STRING (expr), ASM_OUTPUTS (expr),
3144 ASM_INPUTS (expr));
3146 ret = GS_ALL_DONE;
3147 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = TREE_CHAIN (link))
3149 oconstraints[i] = constraint
3150 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
3152 parse_output_constraint (&constraint, i, 0, 0,
3153 &allows_mem, &allows_reg, &is_inout);
3155 if (!allows_reg && allows_mem)
3156 lang_hooks.mark_addressable (TREE_VALUE (link));
3158 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
3159 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
3160 fb_lvalue | fb_mayfail);
3161 if (tret == GS_ERROR)
3163 error ("invalid lvalue in asm output %d", i);
3164 ret = tret;
3167 if (is_inout)
3169 /* An input/output operand. To give the optimizers more
3170 flexibility, split it into separate input and output
3171 operands. */
3172 tree input;
3173 char buf[10];
3174 size_t constraint_len = strlen (constraint);
3176 /* Turn the in/out constraint into an output constraint. */
3177 char *p = xstrdup (constraint);
3178 p[0] = '=';
3179 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
3180 free (p);
3182 /* And add a matching input constraint. */
3183 if (allows_reg)
3185 sprintf (buf, "%d", i);
3186 input = build_string (strlen (buf), buf);
3188 else
3189 input = build_string (constraint_len - 1, constraint + 1);
3190 input = build_tree_list (build_tree_list (NULL_TREE, input),
3191 unshare_expr (TREE_VALUE (link)));
3192 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
3196 for (link = ASM_INPUTS (expr); link; ++i, link = TREE_CHAIN (link))
3198 constraint
3199 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
3200 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
3201 oconstraints, &allows_mem, &allows_reg);
3203 /* If the operand is a memory input, it should be an lvalue. */
3204 if (!allows_reg && allows_mem)
3206 lang_hooks.mark_addressable (TREE_VALUE (link));
3207 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
3208 is_gimple_lvalue, fb_lvalue | fb_mayfail);
3209 if (tret == GS_ERROR)
3211 error ("memory input %d is not directly addressable", i);
3212 ret = tret;
3215 else
3217 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
3218 is_gimple_asm_val, fb_rvalue);
3219 if (tret == GS_ERROR)
3220 ret = tret;
3224 return ret;
3227 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
3228 WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
3229 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
3230 return to this function.
3232 FIXME should we complexify the prequeue handling instead? Or use flags
3233 for all the cleanups and let the optimizer tighten them up? The current
3234 code seems pretty fragile; it will break on a cleanup within any
3235 non-conditional nesting. But any such nesting would be broken, anyway;
3236 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
3237 and continues out of it. We can do that at the RTL level, though, so
3238 having an optimizer to tighten up try/finally regions would be a Good
3239 Thing. */
3241 static enum gimplify_status
3242 gimplify_cleanup_point_expr (tree *expr_p, tree *pre_p)
3244 tree_stmt_iterator iter;
3245 tree body;
3247 tree temp = voidify_wrapper_expr (*expr_p, NULL);
3249 /* We only care about the number of conditions between the innermost
3250 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count. */
3251 int old_conds = gimplify_ctxp->conditions;
3252 gimplify_ctxp->conditions = 0;
3254 body = TREE_OPERAND (*expr_p, 0);
3255 gimplify_to_stmt_list (&body);
3257 gimplify_ctxp->conditions = old_conds;
3259 for (iter = tsi_start (body); !tsi_end_p (iter); )
3261 tree *wce_p = tsi_stmt_ptr (iter);
3262 tree wce = *wce_p;
3264 if (TREE_CODE (wce) == WITH_CLEANUP_EXPR)
3266 if (tsi_one_before_end_p (iter))
3268 tsi_link_before (&iter, TREE_OPERAND (wce, 0), TSI_SAME_STMT);
3269 tsi_delink (&iter);
3270 break;
3272 else
3274 tree sl, tfe;
3275 enum tree_code code;
3277 if (CLEANUP_EH_ONLY (wce))
3278 code = TRY_CATCH_EXPR;
3279 else
3280 code = TRY_FINALLY_EXPR;
3282 sl = tsi_split_statement_list_after (&iter);
3283 tfe = build (code, void_type_node, sl, NULL_TREE);
3284 append_to_statement_list (TREE_OPERAND (wce, 0),
3285 &TREE_OPERAND (tfe, 1));
3286 *wce_p = tfe;
3287 iter = tsi_start (sl);
3290 else
3291 tsi_next (&iter);
3294 if (temp)
3296 *expr_p = temp;
3297 append_to_statement_list (body, pre_p);
3298 return GS_OK;
3300 else
3302 *expr_p = body;
3303 return GS_ALL_DONE;
3307 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
3308 is the cleanup action required. */
3310 static void
3311 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, tree *pre_p)
3313 tree wce;
3315 /* Errors can result in improperly nested cleanups. Which results in
3316 confusion when trying to resolve the WITH_CLEANUP_EXPR. */
3317 if (errorcount || sorrycount)
3318 return;
3320 if (gimple_conditional_context ())
3322 /* If we're in a conditional context, this is more complex. We only
3323 want to run the cleanup if we actually ran the initialization that
3324 necessitates it, but we want to run it after the end of the
3325 conditional context. So we wrap the try/finally around the
3326 condition and use a flag to determine whether or not to actually
3327 run the destructor. Thus
3329 test ? f(A()) : 0
3331 becomes (approximately)
3333 flag = 0;
3334 try {
3335 if (test) { A::A(temp); flag = 1; val = f(temp); }
3336 else { val = 0; }
3337 } finally {
3338 if (flag) A::~A(temp);
3343 tree flag = create_tmp_var (boolean_type_node, "cleanup");
3344 tree ffalse = build (MODIFY_EXPR, void_type_node, flag,
3345 boolean_false_node);
3346 tree ftrue = build (MODIFY_EXPR, void_type_node, flag,
3347 boolean_true_node);
3348 cleanup = build (COND_EXPR, void_type_node, flag, cleanup, NULL);
3349 wce = build (WITH_CLEANUP_EXPR, void_type_node, cleanup);
3350 append_to_statement_list (ffalse, &gimplify_ctxp->conditional_cleanups);
3351 append_to_statement_list (wce, &gimplify_ctxp->conditional_cleanups);
3352 append_to_statement_list (ftrue, pre_p);
3354 /* Because of this manipulation, and the EH edges that jump
3355 threading cannot redirect, the temporary (VAR) will appear
3356 to be used uninitialized. Don't warn. */
3357 TREE_NO_WARNING (var) = 1;
3359 else
3361 wce = build (WITH_CLEANUP_EXPR, void_type_node, cleanup);
3362 CLEANUP_EH_ONLY (wce) = eh_only;
3363 append_to_statement_list (wce, pre_p);
3366 gimplify_stmt (&TREE_OPERAND (wce, 0));
3369 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
3371 static enum gimplify_status
3372 gimplify_target_expr (tree *expr_p, tree *pre_p, tree *post_p)
3374 tree targ = *expr_p;
3375 tree temp = TARGET_EXPR_SLOT (targ);
3376 tree init = TARGET_EXPR_INITIAL (targ);
3377 enum gimplify_status ret;
3379 if (init)
3381 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
3382 to the temps list. */
3383 gimple_add_tmp_var (temp);
3385 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
3386 expression is supposed to initialize the slot. */
3387 if (VOID_TYPE_P (TREE_TYPE (init)))
3388 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
3389 else
3391 /* Special handling for BIND_EXPR can result in fewer temps. */
3392 ret = GS_OK;
3393 if (TREE_CODE (init) == BIND_EXPR)
3394 gimplify_bind_expr (&init, temp, pre_p);
3395 if (init != temp)
3397 init = build (MODIFY_EXPR, void_type_node, temp, init);
3398 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt,
3399 fb_none);
3402 if (ret == GS_ERROR)
3403 return GS_ERROR;
3404 append_to_statement_list (init, pre_p);
3406 /* If needed, push the cleanup for the temp. */
3407 if (TARGET_EXPR_CLEANUP (targ))
3409 gimplify_stmt (&TARGET_EXPR_CLEANUP (targ));
3410 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
3411 CLEANUP_EH_ONLY (targ), pre_p);
3414 /* Only expand this once. */
3415 TREE_OPERAND (targ, 3) = init;
3416 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
3418 else
3419 /* We should have expanded this before. */
3420 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
3422 *expr_p = temp;
3423 return GS_OK;
3426 /* Gimplification of expression trees. */
3428 /* Gimplify an expression which appears at statement context; usually, this
3429 means replacing it with a suitably gimple STATEMENT_LIST. */
3431 void
3432 gimplify_stmt (tree *stmt_p)
3434 gimplify_expr (stmt_p, NULL, NULL, is_gimple_stmt, fb_none);
3437 /* Similarly, but force the result to be a STATEMENT_LIST. */
3439 void
3440 gimplify_to_stmt_list (tree *stmt_p)
3442 gimplify_stmt (stmt_p);
3443 if (!*stmt_p)
3444 *stmt_p = alloc_stmt_list ();
3445 else if (TREE_CODE (*stmt_p) != STATEMENT_LIST)
3447 tree t = *stmt_p;
3448 *stmt_p = alloc_stmt_list ();
3449 append_to_statement_list (t, stmt_p);
3454 /* Gimplifies the expression tree pointed by EXPR_P. Return 0 if
3455 gimplification failed.
3457 PRE_P points to the list where side effects that must happen before
3458 EXPR should be stored.
3460 POST_P points to the list where side effects that must happen after
3461 EXPR should be stored, or NULL if there is no suitable list. In
3462 that case, we copy the result to a temporary, emit the
3463 post-effects, and then return the temporary.
3465 GIMPLE_TEST_F points to a function that takes a tree T and
3466 returns nonzero if T is in the GIMPLE form requested by the
3467 caller. The GIMPLE predicates are in tree-gimple.c.
3469 This test is used twice. Before gimplification, the test is
3470 invoked to determine whether *EXPR_P is already gimple enough. If
3471 that fails, *EXPR_P is gimplified according to its code and
3472 GIMPLE_TEST_F is called again. If the test still fails, then a new
3473 temporary variable is created and assigned the value of the
3474 gimplified expression.
3476 FALLBACK tells the function what sort of a temporary we want. If the 1
3477 bit is set, an rvalue is OK. If the 2 bit is set, an lvalue is OK.
3478 If both are set, either is OK, but an lvalue is preferable.
3480 The return value is either GS_ERROR or GS_ALL_DONE, since this function
3481 iterates until solution. */
3483 enum gimplify_status
3484 gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p,
3485 bool (* gimple_test_f) (tree), fallback_t fallback)
3487 tree tmp;
3488 tree internal_pre = NULL_TREE;
3489 tree internal_post = NULL_TREE;
3490 tree save_expr;
3491 int is_statement = (pre_p == NULL);
3492 location_t saved_location;
3493 enum gimplify_status ret;
3495 save_expr = *expr_p;
3496 if (save_expr == NULL_TREE)
3497 return GS_ALL_DONE;
3499 /* We used to check the predicate here and return immediately if it
3500 succeeds. This is wrong; the design is for gimplification to be
3501 idempotent, and for the predicates to only test for valid forms, not
3502 whether they are fully simplified. */
3504 /* Set up our internal queues if needed. */
3505 if (pre_p == NULL)
3506 pre_p = &internal_pre;
3507 if (post_p == NULL)
3508 post_p = &internal_post;
3510 saved_location = input_location;
3511 if (save_expr != error_mark_node
3512 && EXPR_HAS_LOCATION (*expr_p))
3513 input_location = EXPR_LOCATION (*expr_p);
3515 /* Loop over the specific gimplifiers until the toplevel node
3516 remains the same. */
3519 /* Strip away as many useless type conversions as possible
3520 at the toplevel. */
3521 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
3523 /* Remember the expr. */
3524 save_expr = *expr_p;
3526 /* Die, die, die, my darling. */
3527 if (save_expr == error_mark_node
3528 || (TREE_TYPE (save_expr)
3529 && TREE_TYPE (save_expr) == error_mark_node))
3531 ret = GS_ERROR;
3532 break;
3535 /* Do any language-specific gimplification. */
3536 ret = lang_hooks.gimplify_expr (expr_p, pre_p, post_p);
3537 if (ret == GS_OK)
3539 if (*expr_p == NULL_TREE)
3540 break;
3541 if (*expr_p != save_expr)
3542 continue;
3544 else if (ret != GS_UNHANDLED)
3545 break;
3547 ret = GS_OK;
3548 switch (TREE_CODE (*expr_p))
3550 /* First deal with the special cases. */
3552 case POSTINCREMENT_EXPR:
3553 case POSTDECREMENT_EXPR:
3554 case PREINCREMENT_EXPR:
3555 case PREDECREMENT_EXPR:
3556 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
3557 fallback != fb_none);
3558 break;
3560 case ARRAY_REF:
3561 case ARRAY_RANGE_REF:
3562 case REALPART_EXPR:
3563 case IMAGPART_EXPR:
3564 case COMPONENT_REF:
3565 case VIEW_CONVERT_EXPR:
3566 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
3567 fallback ? fallback : fb_rvalue);
3568 break;
3570 case COND_EXPR:
3571 ret = gimplify_cond_expr (expr_p, pre_p, NULL_TREE);
3572 break;
3574 case CALL_EXPR:
3575 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
3576 break;
3578 case TREE_LIST:
3579 gcc_unreachable ();
3581 case COMPOUND_EXPR:
3582 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
3583 break;
3585 case MODIFY_EXPR:
3586 case INIT_EXPR:
3587 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
3588 fallback != fb_none);
3589 break;
3591 case TRUTH_ANDIF_EXPR:
3592 case TRUTH_ORIF_EXPR:
3593 ret = gimplify_boolean_expr (expr_p);
3594 break;
3596 case TRUTH_NOT_EXPR:
3597 TREE_OPERAND (*expr_p, 0)
3598 = gimple_boolify (TREE_OPERAND (*expr_p, 0));
3599 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3600 is_gimple_val, fb_rvalue);
3601 recalculate_side_effects (*expr_p);
3602 break;
3604 case ADDR_EXPR:
3605 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
3606 break;
3608 case VA_ARG_EXPR:
3609 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
3610 break;
3612 case CONVERT_EXPR:
3613 case NOP_EXPR:
3614 if (IS_EMPTY_STMT (*expr_p))
3616 ret = GS_ALL_DONE;
3617 break;
3620 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
3621 || fallback == fb_none)
3623 /* Just strip a conversion to void (or in void context) and
3624 try again. */
3625 *expr_p = TREE_OPERAND (*expr_p, 0);
3626 break;
3629 ret = gimplify_conversion (expr_p);
3630 if (ret == GS_ERROR)
3631 break;
3632 if (*expr_p != save_expr)
3633 break;
3634 /* FALLTHRU */
3636 case FIX_TRUNC_EXPR:
3637 case FIX_CEIL_EXPR:
3638 case FIX_FLOOR_EXPR:
3639 case FIX_ROUND_EXPR:
3640 /* unary_expr: ... | '(' cast ')' val | ... */
3641 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3642 is_gimple_val, fb_rvalue);
3643 recalculate_side_effects (*expr_p);
3644 break;
3646 case ALIGN_INDIRECT_REF:
3647 case MISALIGNED_INDIRECT_REF:
3648 case INDIRECT_REF:
3649 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3650 is_gimple_reg, fb_rvalue);
3651 recalculate_side_effects (*expr_p);
3652 break;
3654 /* Constants need not be gimplified. */
3655 case INTEGER_CST:
3656 case REAL_CST:
3657 case STRING_CST:
3658 case COMPLEX_CST:
3659 case VECTOR_CST:
3660 ret = GS_ALL_DONE;
3661 break;
3663 case CONST_DECL:
3664 /* If we require an lvalue, such as for ADDR_EXPR, retain the
3665 CONST_DECL node. Otherwise the decl is replaceable by its
3666 value. */
3667 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
3668 if (fallback & fb_lvalue)
3669 ret = GS_ALL_DONE;
3670 else
3671 *expr_p = DECL_INITIAL (*expr_p);
3672 break;
3674 case DECL_EXPR:
3675 ret = gimplify_decl_expr (expr_p);
3676 break;
3678 case EXC_PTR_EXPR:
3679 /* FIXME make this a decl. */
3680 ret = GS_ALL_DONE;
3681 break;
3683 case BIND_EXPR:
3684 ret = gimplify_bind_expr (expr_p, NULL, pre_p);
3685 break;
3687 case LOOP_EXPR:
3688 ret = gimplify_loop_expr (expr_p, pre_p);
3689 break;
3691 case SWITCH_EXPR:
3692 ret = gimplify_switch_expr (expr_p, pre_p);
3693 break;
3695 case LABELED_BLOCK_EXPR:
3696 ret = gimplify_labeled_block_expr (expr_p);
3697 break;
3699 case EXIT_BLOCK_EXPR:
3700 ret = gimplify_exit_block_expr (expr_p);
3701 break;
3703 case EXIT_EXPR:
3704 ret = gimplify_exit_expr (expr_p);
3705 break;
3707 case GOTO_EXPR:
3708 /* If the target is not LABEL, then it is a computed jump
3709 and the target needs to be gimplified. */
3710 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
3711 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
3712 NULL, is_gimple_val, fb_rvalue);
3713 break;
3715 case LABEL_EXPR:
3716 ret = GS_ALL_DONE;
3717 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
3718 == current_function_decl);
3719 break;
3721 case CASE_LABEL_EXPR:
3722 ret = gimplify_case_label_expr (expr_p);
3723 break;
3725 case RETURN_EXPR:
3726 ret = gimplify_return_expr (*expr_p, pre_p);
3727 break;
3729 case CONSTRUCTOR:
3730 /* Don't reduce this in place; let gimplify_init_constructor work its
3731 magic. Buf if we're just elaborating this for side effects, just
3732 gimplify any element that has side-effects. */
3733 if (fallback == fb_none)
3735 for (tmp = CONSTRUCTOR_ELTS (*expr_p); tmp;
3736 tmp = TREE_CHAIN (tmp))
3737 if (TREE_SIDE_EFFECTS (TREE_VALUE (tmp)))
3738 gimplify_expr (&TREE_VALUE (tmp), pre_p, post_p,
3739 gimple_test_f, fallback);
3741 *expr_p = NULL_TREE;
3744 ret = GS_ALL_DONE;
3745 break;
3747 /* The following are special cases that are not handled by the
3748 original GIMPLE grammar. */
3750 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
3751 eliminated. */
3752 case SAVE_EXPR:
3753 ret = gimplify_save_expr (expr_p, pre_p, post_p);
3754 break;
3756 case BIT_FIELD_REF:
3758 enum gimplify_status r0, r1, r2;
3760 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3761 is_gimple_lvalue, fb_either);
3762 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
3763 is_gimple_val, fb_rvalue);
3764 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p, post_p,
3765 is_gimple_val, fb_rvalue);
3766 recalculate_side_effects (*expr_p);
3768 ret = MIN (r0, MIN (r1, r2));
3770 break;
3772 case NON_LVALUE_EXPR:
3773 /* This should have been stripped above. */
3774 gcc_unreachable ();
3776 case ASM_EXPR:
3777 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
3778 break;
3780 case TRY_FINALLY_EXPR:
3781 case TRY_CATCH_EXPR:
3782 gimplify_to_stmt_list (&TREE_OPERAND (*expr_p, 0));
3783 gimplify_to_stmt_list (&TREE_OPERAND (*expr_p, 1));
3784 ret = GS_ALL_DONE;
3785 break;
3787 case CLEANUP_POINT_EXPR:
3788 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
3789 break;
3791 case TARGET_EXPR:
3792 ret = gimplify_target_expr (expr_p, pre_p, post_p);
3793 break;
3795 case CATCH_EXPR:
3796 gimplify_to_stmt_list (&CATCH_BODY (*expr_p));
3797 ret = GS_ALL_DONE;
3798 break;
3800 case EH_FILTER_EXPR:
3801 gimplify_to_stmt_list (&EH_FILTER_FAILURE (*expr_p));
3802 ret = GS_ALL_DONE;
3803 break;
3805 case OBJ_TYPE_REF:
3807 enum gimplify_status r0, r1;
3808 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p, post_p,
3809 is_gimple_val, fb_rvalue);
3810 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p, post_p,
3811 is_gimple_val, fb_rvalue);
3812 ret = MIN (r0, r1);
3814 break;
3816 case LABEL_DECL:
3817 /* We get here when taking the address of a label. We mark
3818 the label as "forced"; meaning it can never be removed and
3819 it is a potential target for any computed goto. */
3820 FORCED_LABEL (*expr_p) = 1;
3821 ret = GS_ALL_DONE;
3822 break;
3824 case STATEMENT_LIST:
3825 ret = gimplify_statement_list (expr_p);
3826 break;
3828 case WITH_SIZE_EXPR:
3830 enum gimplify_status r0, r1;
3831 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
3832 post_p == &internal_post ? NULL : post_p,
3833 gimple_test_f, fallback);
3834 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
3835 is_gimple_val, fb_rvalue);
3837 break;
3839 case VAR_DECL:
3840 /* ??? If this is a local variable, and it has not been seen in any
3841 outer BIND_EXPR, then it's probably the result of a duplicate
3842 declaration, for which we've already issued an error. It would
3843 be really nice if the front end wouldn't leak these at all.
3844 Currently the only known culprit is C++ destructors, as seen
3845 in g++.old-deja/g++.jason/binding.C. */
3846 tmp = *expr_p;
3847 if (!TREE_STATIC (tmp) && !DECL_EXTERNAL (tmp)
3848 && decl_function_context (tmp) == current_function_decl
3849 && !DECL_SEEN_IN_BIND_EXPR_P (tmp))
3851 gcc_assert (errorcount || sorrycount);
3852 ret = GS_ERROR;
3853 break;
3856 /* If this is a local variable sized decl, it must be accessed
3857 indirectly. Perform that substitution. */
3858 if (DECL_VALUE_EXPR (tmp))
3860 *expr_p = unshare_expr (DECL_VALUE_EXPR (tmp));
3861 ret = GS_OK;
3862 break;
3865 ret = GS_ALL_DONE;
3866 break;
3868 case SSA_NAME:
3869 /* Allow callbacks into the gimplifier during optimization. */
3870 ret = GS_ALL_DONE;
3871 break;
3873 default:
3874 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
3876 case tcc_comparison:
3877 /* If this is a comparison of objects of aggregate type,
3878 handle it specially (by converting to a call to
3879 memcmp). It would be nice to only have to do this
3880 for variable-sized objects, but then we'd have to
3881 allow the same nest of reference nodes we allow for
3882 MODIFY_EXPR and that's too complex. */
3883 if (!AGGREGATE_TYPE_P (TREE_TYPE (TREE_OPERAND (*expr_p, 1))))
3884 goto expr_2;
3885 ret = gimplify_variable_sized_compare (expr_p);
3886 break;
3888 /* If *EXPR_P does not need to be special-cased, handle it
3889 according to its class. */
3890 case tcc_unary:
3891 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
3892 post_p, is_gimple_val, fb_rvalue);
3893 break;
3895 case tcc_binary:
3896 expr_2:
3898 enum gimplify_status r0, r1;
3900 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
3901 post_p, is_gimple_val, fb_rvalue);
3902 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
3903 post_p, is_gimple_val, fb_rvalue);
3905 ret = MIN (r0, r1);
3906 break;
3909 case tcc_declaration:
3910 case tcc_constant:
3911 ret = GS_ALL_DONE;
3912 goto dont_recalculate;
3914 default:
3915 gcc_assert (TREE_CODE (*expr_p) == TRUTH_AND_EXPR
3916 || TREE_CODE (*expr_p) == TRUTH_OR_EXPR
3917 || TREE_CODE (*expr_p) == TRUTH_XOR_EXPR);
3918 goto expr_2;
3921 recalculate_side_effects (*expr_p);
3922 dont_recalculate:
3923 break;
3926 /* If we replaced *expr_p, gimplify again. */
3927 if (ret == GS_OK && (*expr_p == NULL || *expr_p == save_expr))
3928 ret = GS_ALL_DONE;
3930 while (ret == GS_OK);
3932 /* If we encountered an error_mark somewhere nested inside, either
3933 stub out the statement or propagate the error back out. */
3934 if (ret == GS_ERROR)
3936 if (is_statement)
3937 *expr_p = NULL;
3938 goto out;
3941 /* This was only valid as a return value from the langhook, which
3942 we handled. Make sure it doesn't escape from any other context. */
3943 gcc_assert (ret != GS_UNHANDLED);
3945 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
3947 /* We aren't looking for a value, and we don't have a valid
3948 statement. If it doesn't have side-effects, throw it away. */
3949 if (!TREE_SIDE_EFFECTS (*expr_p))
3950 *expr_p = NULL;
3951 else if (!TREE_THIS_VOLATILE (*expr_p))
3953 /* This is probably a _REF that contains something nested that
3954 has side effects. Recurse through the operands to find it. */
3955 enum tree_code code = TREE_CODE (*expr_p);
3957 switch (code)
3959 case COMPONENT_REF:
3960 case REALPART_EXPR: case IMAGPART_EXPR:
3961 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3962 gimple_test_f, fallback);
3963 break;
3965 case ARRAY_REF: case ARRAY_RANGE_REF:
3966 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
3967 gimple_test_f, fallback);
3968 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
3969 gimple_test_f, fallback);
3970 break;
3972 default:
3973 /* Anything else with side-effects must be converted to
3974 a valid statement before we get here. */
3975 gcc_unreachable ();
3978 *expr_p = NULL;
3980 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p)))
3982 /* Historically, the compiler has treated a bare
3983 reference to a volatile lvalue as forcing a load. */
3984 tree tmp = create_tmp_var (TREE_TYPE (*expr_p), "vol");
3985 *expr_p = build (MODIFY_EXPR, TREE_TYPE (tmp), tmp, *expr_p);
3987 else
3988 /* We can't do anything useful with a volatile reference to
3989 incomplete type, so just throw it away. */
3990 *expr_p = NULL;
3993 /* If we are gimplifying at the statement level, we're done. Tack
3994 everything together and replace the original statement with the
3995 gimplified form. */
3996 if (fallback == fb_none || is_statement)
3998 if (internal_pre || internal_post)
4000 append_to_statement_list (*expr_p, &internal_pre);
4001 append_to_statement_list (internal_post, &internal_pre);
4002 annotate_all_with_locus (&internal_pre, input_location);
4003 *expr_p = internal_pre;
4005 else if (!*expr_p)
4007 else if (TREE_CODE (*expr_p) == STATEMENT_LIST)
4008 annotate_all_with_locus (expr_p, input_location);
4009 else
4010 annotate_one_with_locus (*expr_p, input_location);
4011 goto out;
4014 /* Otherwise we're gimplifying a subexpression, so the resulting value is
4015 interesting. */
4017 /* If it's sufficiently simple already, we're done. Unless we are
4018 handling some post-effects internally; if that's the case, we need to
4019 copy into a temp before adding the post-effects to the tree. */
4020 if (!internal_post && (*gimple_test_f) (*expr_p))
4021 goto out;
4023 /* Otherwise, we need to create a new temporary for the gimplified
4024 expression. */
4026 /* We can't return an lvalue if we have an internal postqueue. The
4027 object the lvalue refers to would (probably) be modified by the
4028 postqueue; we need to copy the value out first, which means an
4029 rvalue. */
4030 if ((fallback & fb_lvalue) && !internal_post
4031 && is_gimple_addressable (*expr_p))
4033 /* An lvalue will do. Take the address of the expression, store it
4034 in a temporary, and replace the expression with an INDIRECT_REF of
4035 that temporary. */
4036 tmp = build_fold_addr_expr (*expr_p);
4037 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
4038 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (TREE_TYPE (tmp)), tmp);
4040 else if ((fallback & fb_rvalue) && is_gimple_formal_tmp_rhs (*expr_p))
4042 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
4044 /* An rvalue will do. Assign the gimplified expression into a new
4045 temporary TMP and replace the original expression with TMP. */
4047 if (internal_post || (fallback & fb_lvalue))
4048 /* The postqueue might change the value of the expression between
4049 the initialization and use of the temporary, so we can't use a
4050 formal temp. FIXME do we care? */
4051 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p);
4052 else
4053 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
4055 if (TREE_CODE (*expr_p) != SSA_NAME)
4056 DECL_GIMPLE_FORMAL_TEMP_P (*expr_p) = 1;
4058 else
4060 #ifdef ENABLE_CHECKING
4061 if (!(fallback & fb_mayfail))
4063 fprintf (stderr, "gimplification failed:\n");
4064 print_generic_expr (stderr, *expr_p, 0);
4065 debug_tree (*expr_p);
4066 internal_error ("gimplification failed");
4068 #endif
4069 gcc_assert (fallback & fb_mayfail);
4070 /* If this is an asm statement, and the user asked for the
4071 impossible, don't abort. Fail and let gimplify_asm_expr
4072 issue an error. */
4073 ret = GS_ERROR;
4074 goto out;
4077 /* Make sure the temporary matches our predicate. */
4078 gcc_assert ((*gimple_test_f) (*expr_p));
4080 if (internal_post)
4082 annotate_all_with_locus (&internal_post, input_location);
4083 append_to_statement_list (internal_post, pre_p);
4086 out:
4087 input_location = saved_location;
4088 return ret;
4091 /* Look through TYPE for variable-sized objects and gimplify each such
4092 size that we find. Add to LIST_P any statements generated. */
4094 void
4095 gimplify_type_sizes (tree type, tree *list_p)
4097 tree field;
4099 switch (TREE_CODE (type))
4101 case ERROR_MARK:
4102 return;
4104 case INTEGER_TYPE:
4105 case ENUMERAL_TYPE:
4106 case BOOLEAN_TYPE:
4107 case CHAR_TYPE:
4108 case REAL_TYPE:
4109 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
4110 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
4111 break;
4113 case ARRAY_TYPE:
4114 /* These anonymous types don't have declarations, so handle them here. */
4115 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
4116 break;
4118 case RECORD_TYPE:
4119 case UNION_TYPE:
4120 case QUAL_UNION_TYPE:
4121 for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
4122 if (TREE_CODE (field) == FIELD_DECL)
4123 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
4124 break;
4126 default:
4127 break;
4130 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
4131 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
4134 /* Subroutine of the above to gimplify one size or position, *EXPR_P.
4135 We add any required statements to STMT_P. */
4137 void
4138 gimplify_one_sizepos (tree *expr_p, tree *stmt_p)
4140 /* We don't do anything if the value isn't there, is constant, or contains
4141 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
4142 a VAR_DECL. If it's a VAR_DECL from another function, the gimplfier
4143 will want to replace it with a new variable, but that will cause problems
4144 if this type is from outside the function. It's OK to have that here. */
4145 if (*expr_p == NULL_TREE || TREE_CONSTANT (*expr_p)
4146 || TREE_CODE (*expr_p) == VAR_DECL
4147 || CONTAINS_PLACEHOLDER_P (*expr_p))
4148 return;
4150 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue);
4153 #ifdef ENABLE_CHECKING
4154 /* Compare types A and B for a "close enough" match. */
4156 static bool
4157 cpt_same_type (tree a, tree b)
4159 if (lang_hooks.types_compatible_p (a, b))
4160 return true;
4162 /* ??? The C++ FE decomposes METHOD_TYPES to FUNCTION_TYPES and doesn't
4163 link them together. This routine is intended to catch type errors
4164 that will affect the optimizers, and the optimizers don't add new
4165 dereferences of function pointers, so ignore it. */
4166 if ((TREE_CODE (a) == FUNCTION_TYPE || TREE_CODE (a) == METHOD_TYPE)
4167 && (TREE_CODE (b) == FUNCTION_TYPE || TREE_CODE (b) == METHOD_TYPE))
4168 return true;
4170 /* ??? The C FE pushes type qualifiers after the fact into the type of
4171 the element from the type of the array. See build_unary_op's handling
4172 of ADDR_EXPR. This seems wrong -- if we were going to do this, we
4173 should have done it when creating the variable in the first place.
4174 Alternately, why aren't the two array types made variants? */
4175 if (TREE_CODE (a) == ARRAY_TYPE && TREE_CODE (b) == ARRAY_TYPE)
4176 return cpt_same_type (TREE_TYPE (a), TREE_TYPE (b));
4178 /* And because of those, we have to recurse down through pointers. */
4179 if (POINTER_TYPE_P (a) && POINTER_TYPE_P (b))
4180 return cpt_same_type (TREE_TYPE (a), TREE_TYPE (b));
4182 return false;
4185 /* Check for some cases of the front end missing cast expressions.
4186 The type of a dereference should correspond to the pointer type;
4187 similarly the type of an address should match its object. */
4189 static tree
4190 check_pointer_types_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
4191 void *data ATTRIBUTE_UNUSED)
4193 tree t = *tp;
4194 tree ptype, otype, dtype;
4196 switch (TREE_CODE (t))
4198 case INDIRECT_REF:
4199 case ARRAY_REF:
4200 otype = TREE_TYPE (t);
4201 ptype = TREE_TYPE (TREE_OPERAND (t, 0));
4202 dtype = TREE_TYPE (ptype);
4203 gcc_assert (cpt_same_type (otype, dtype));
4204 break;
4206 case ADDR_EXPR:
4207 ptype = TREE_TYPE (t);
4208 otype = TREE_TYPE (TREE_OPERAND (t, 0));
4209 dtype = TREE_TYPE (ptype);
4210 if (!cpt_same_type (otype, dtype))
4212 /* &array is allowed to produce a pointer to the element, rather than
4213 a pointer to the array type. We must allow this in order to
4214 properly represent assigning the address of an array in C into
4215 pointer to the element type. */
4216 gcc_assert (TREE_CODE (otype) == ARRAY_TYPE
4217 && POINTER_TYPE_P (ptype)
4218 && cpt_same_type (TREE_TYPE (otype), dtype));
4219 break;
4221 break;
4223 default:
4224 return NULL_TREE;
4228 return NULL_TREE;
4230 #endif
4232 /* Gimplify the body of statements pointed by BODY_P. FNDECL is the
4233 function decl containing BODY. */
4235 void
4236 gimplify_body (tree *body_p, tree fndecl)
4238 location_t saved_location = input_location;
4239 tree body;
4241 timevar_push (TV_TREE_GIMPLIFY);
4242 push_gimplify_context ();
4244 /* Unshare most shared trees in the body and in that of any nested functions.
4245 It would seem we don't have to do this for nested functions because
4246 they are supposed to be output and then the outer function gimplified
4247 first, but the g++ front end doesn't always do it that way. */
4248 unshare_body (body_p, fndecl);
4249 unvisit_body (body_p, fndecl);
4251 /* Make sure input_location isn't set to something wierd. */
4252 input_location = DECL_SOURCE_LOCATION (fndecl);
4254 /* Gimplify the function's body. */
4255 gimplify_stmt (body_p);
4256 body = *body_p;
4258 /* Unshare again, in case gimplification was sloppy. */
4259 unshare_all_trees (body);
4261 if (!body)
4262 body = alloc_stmt_list ();
4263 else if (TREE_CODE (body) == STATEMENT_LIST)
4265 tree t = expr_only (*body_p);
4266 if (t)
4267 body = t;
4270 /* If there isn't an outer BIND_EXPR, add one. */
4271 if (TREE_CODE (body) != BIND_EXPR)
4273 tree b = build (BIND_EXPR, void_type_node, NULL_TREE,
4274 NULL_TREE, NULL_TREE);
4275 TREE_SIDE_EFFECTS (b) = 1;
4276 append_to_statement_list_force (body, &BIND_EXPR_BODY (b));
4277 body = b;
4279 *body_p = body;
4281 pop_gimplify_context (body);
4283 #ifdef ENABLE_CHECKING
4284 walk_tree (body_p, check_pointer_types_r, NULL, NULL);
4285 #endif
4287 timevar_pop (TV_TREE_GIMPLIFY);
4288 input_location = saved_location;
4291 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
4292 node for the function we want to gimplify. */
4294 void
4295 gimplify_function_tree (tree fndecl)
4297 tree oldfn;
4299 oldfn = current_function_decl;
4300 current_function_decl = fndecl;
4302 gimplify_body (&DECL_SAVED_TREE (fndecl), fndecl);
4304 /* If we're instrumenting function entry/exit, then prepend the call to
4305 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
4306 catch the exit hook. */
4307 /* ??? Add some way to ignore exceptions for this TFE. */
4308 if (flag_instrument_function_entry_exit
4309 && ! DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl))
4311 tree tf, x, bind;
4313 tf = build (TRY_FINALLY_EXPR, void_type_node, NULL, NULL);
4314 TREE_SIDE_EFFECTS (tf) = 1;
4315 x = DECL_SAVED_TREE (fndecl);
4316 append_to_statement_list (x, &TREE_OPERAND (tf, 0));
4317 x = implicit_built_in_decls[BUILT_IN_PROFILE_FUNC_EXIT];
4318 x = build_function_call_expr (x, NULL);
4319 append_to_statement_list (x, &TREE_OPERAND (tf, 1));
4321 bind = build (BIND_EXPR, void_type_node, NULL, NULL, NULL);
4322 TREE_SIDE_EFFECTS (bind) = 1;
4323 x = implicit_built_in_decls[BUILT_IN_PROFILE_FUNC_ENTER];
4324 x = build_function_call_expr (x, NULL);
4325 append_to_statement_list (x, &BIND_EXPR_BODY (bind));
4326 append_to_statement_list (tf, &BIND_EXPR_BODY (bind));
4328 DECL_SAVED_TREE (fndecl) = bind;
4331 current_function_decl = oldfn;
4335 /* Expands EXPR to list of gimple statements STMTS. If SIMPLE is true,
4336 force the result to be either ssa_name or an invariant, otherwise
4337 just force it to be a rhs expression. If VAR is not NULL, make the
4338 base variable of the final destination be VAR if suitable. */
4340 tree
4341 force_gimple_operand (tree expr, tree *stmts, bool simple, tree var)
4343 tree t;
4344 enum gimplify_status ret;
4345 gimple_predicate gimple_test_f;
4347 *stmts = NULL_TREE;
4349 if (is_gimple_val (expr))
4350 return expr;
4352 gimple_test_f = simple ? is_gimple_val : is_gimple_reg_rhs;
4354 push_gimplify_context ();
4355 gimplify_ctxp->into_ssa = true;
4357 if (var)
4358 expr = build (MODIFY_EXPR, TREE_TYPE (var), var, expr);
4360 ret = gimplify_expr (&expr, stmts, NULL,
4361 gimple_test_f, fb_rvalue);
4362 gcc_assert (ret != GS_ERROR);
4364 for (t = gimplify_ctxp->temps; t ; t = TREE_CHAIN (t))
4365 add_referenced_tmp_var (t);
4367 pop_gimplify_context (NULL);
4369 return expr;
4372 #include "gt-gimplify.h"