PR other/22202
[official-gcc.git] / gcc / tree-inline.c
blobf22785c0e800f86b3749ce48213446c3bcacd207
1 /* Tree inlining.
2 Copyright 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
3 Contributed by Alexandre Oliva <aoliva@redhat.com>
5 This file is part of GCC.
7 GCC is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2, or (at your option)
10 any later version.
12 GCC is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 GNU General Public License for more details.
17 You should have received a copy of the GNU General Public License
18 along with GCC; see the file COPYING. If not, write to
19 the Free Software Foundation, 51 Franklin Street, Fifth Floor,
20 Boston, MA 02110-1301, USA. */
22 #include "config.h"
23 #include "system.h"
24 #include "coretypes.h"
25 #include "tm.h"
26 #include "toplev.h"
27 #include "tree.h"
28 #include "tree-inline.h"
29 #include "rtl.h"
30 #include "expr.h"
31 #include "flags.h"
32 #include "params.h"
33 #include "input.h"
34 #include "insn-config.h"
35 #include "varray.h"
36 #include "hashtab.h"
37 #include "splay-tree.h"
38 #include "langhooks.h"
39 #include "basic-block.h"
40 #include "tree-iterator.h"
41 #include "cgraph.h"
42 #include "intl.h"
43 #include "tree-mudflap.h"
44 #include "tree-flow.h"
45 #include "function.h"
46 #include "ggc.h"
47 #include "tree-flow.h"
48 #include "diagnostic.h"
49 #include "except.h"
50 #include "debug.h"
51 #include "pointer-set.h"
52 #include "ipa-prop.h"
54 /* I'm not real happy about this, but we need to handle gimple and
55 non-gimple trees. */
56 #include "tree-gimple.h"
58 /* Inlining, Saving, Cloning
60 Inlining: a function body is duplicated, but the PARM_DECLs are
61 remapped into VAR_DECLs, and non-void RETURN_EXPRs become
62 MODIFY_EXPRs that store to a dedicated returned-value variable.
63 The duplicated eh_region info of the copy will later be appended
64 to the info for the caller; the eh_region info in copied throwing
65 statements and RESX_EXPRs is adjusted accordingly.
67 Saving: make a semantically-identical copy of the function body.
68 Necessary when we want to generate code for the body (a destructive
69 operation), but we expect to need this body in the future (e.g. for
70 inlining into another function).
72 Cloning: (only in C++) We have one body for a con/de/structor, and
73 multiple function decls, each with a unique parameter list.
74 Duplicate the body, using the given splay tree; some parameters
75 will become constants (like 0 or 1).
77 All of these will simultaneously lookup any callgraph edges. If
78 we're going to inline the duplicated function body, and the given
79 function has some cloned callgraph nodes (one for each place this
80 function will be inlined) those callgraph edges will be duplicated.
81 If we're saving or cloning the body, those callgraph edges will be
82 updated to point into the new body. (Note that the original
83 callgraph node and edge list will not be altered.)
85 See the CALL_EXPR handling case in copy_body_r (). */
87 /* 0 if we should not perform inlining.
88 1 if we should expand functions calls inline at the tree level.
89 2 if we should consider *all* functions to be inline
90 candidates. */
92 int flag_inline_trees = 0;
94 /* To Do:
96 o In order to make inlining-on-trees work, we pessimized
97 function-local static constants. In particular, they are now
98 always output, even when not addressed. Fix this by treating
99 function-local static constants just like global static
100 constants; the back-end already knows not to output them if they
101 are not needed.
103 o Provide heuristics to clamp inlining of recursive template
104 calls? */
106 /* Data required for function inlining. */
108 typedef struct inline_data
110 /* FUNCTION_DECL for function being inlined. */
111 tree callee;
112 /* FUNCTION_DECL for function being inlined into. */
113 tree caller;
114 /* struct function for function being inlined. Usually this is the same
115 as DECL_STRUCT_FUNCTION (callee), but can be different if saved_cfg
116 and saved_eh are in use. */
117 struct function *callee_cfun;
118 /* The VAR_DECL for the return value. */
119 tree retvar;
120 /* The map from local declarations in the inlined function to
121 equivalents in the function into which it is being inlined. */
122 splay_tree decl_map;
123 /* We use the same mechanism to build clones that we do to perform
124 inlining. However, there are a few places where we need to
125 distinguish between those two situations. This flag is true if
126 we are cloning, rather than inlining. */
127 bool cloning_p;
128 /* Similarly for saving function body. */
129 bool saving_p;
130 /* Versioning function is slightly different from inlining. */
131 bool versioning_p;
132 /* Callgraph node of function we are inlining into. */
133 struct cgraph_node *node;
134 /* Callgraph node of currently inlined function. */
135 struct cgraph_node *current_node;
136 /* Current BLOCK. */
137 tree block;
138 varray_type ipa_info;
139 /* Exception region the inlined call lie in. */
140 int eh_region;
141 /* Take region number in the function being copied, add this value and
142 get eh region number of the duplicate in the function we inline into. */
143 int eh_region_offset;
144 } inline_data;
146 /* Prototypes. */
148 static tree declare_return_variable (inline_data *, tree, tree, tree *);
149 static tree copy_body_r (tree *, int *, void *);
150 static tree copy_generic_body (inline_data *);
151 static bool inlinable_function_p (tree);
152 static tree remap_decl (tree, inline_data *);
153 static tree remap_type (tree, inline_data *);
154 static void remap_block (tree *, inline_data *);
155 static tree remap_decl (tree, inline_data *);
156 static tree remap_decls (tree, inline_data *);
157 static void copy_bind_expr (tree *, int *, inline_data *);
158 static tree mark_local_for_remap_r (tree *, int *, void *);
159 static void unsave_expr_1 (tree);
160 static tree unsave_r (tree *, int *, void *);
161 static void declare_inline_vars (tree, tree);
162 static void remap_save_expr (tree *, void *, int *);
163 static bool replace_ref_tree (inline_data *, tree *);
164 static inline bool inlining_p (inline_data *);
165 static void add_lexical_block (tree current_block, tree new_block);
167 /* Insert a tree->tree mapping for ID. Despite the name suggests
168 that the trees should be variables, it is used for more than that. */
170 static void
171 insert_decl_map (inline_data *id, tree key, tree value)
173 splay_tree_insert (id->decl_map, (splay_tree_key) key,
174 (splay_tree_value) value);
176 /* Always insert an identity map as well. If we see this same new
177 node again, we won't want to duplicate it a second time. */
178 if (key != value)
179 splay_tree_insert (id->decl_map, (splay_tree_key) value,
180 (splay_tree_value) value);
183 /* Remap DECL during the copying of the BLOCK tree for the function. */
185 static tree
186 remap_decl (tree decl, inline_data *id)
188 splay_tree_node n;
189 tree fn;
191 /* We only remap local variables in the current function. */
192 fn = id->callee;
194 /* See if we have remapped this declaration. */
196 n = splay_tree_lookup (id->decl_map, (splay_tree_key) decl);
198 /* If we didn't already have an equivalent for this declaration,
199 create one now. */
200 if (!n)
202 /* Make a copy of the variable or label. */
203 tree t;
204 t = copy_decl_for_dup (decl, fn, id->caller, id->versioning_p);
206 /* Remember it, so that if we encounter this local entity again
207 we can reuse this copy. Do this early because remap_type may
208 need this decl for TYPE_STUB_DECL. */
209 insert_decl_map (id, decl, t);
211 /* Remap types, if necessary. */
212 TREE_TYPE (t) = remap_type (TREE_TYPE (t), id);
213 if (TREE_CODE (t) == TYPE_DECL)
214 DECL_ORIGINAL_TYPE (t) = remap_type (DECL_ORIGINAL_TYPE (t), id);
216 /* Remap sizes as necessary. */
217 walk_tree (&DECL_SIZE (t), copy_body_r, id, NULL);
218 walk_tree (&DECL_SIZE_UNIT (t), copy_body_r, id, NULL);
220 /* If fields, do likewise for offset and qualifier. */
221 if (TREE_CODE (t) == FIELD_DECL)
223 walk_tree (&DECL_FIELD_OFFSET (t), copy_body_r, id, NULL);
224 if (TREE_CODE (DECL_CONTEXT (t)) == QUAL_UNION_TYPE)
225 walk_tree (&DECL_QUALIFIER (t), copy_body_r, id, NULL);
228 #if 0
229 /* FIXME handle anon aggrs. */
230 if (! DECL_NAME (t) && TREE_TYPE (t)
231 && lang_hooks.tree_inlining.anon_aggr_type_p (TREE_TYPE (t)))
233 /* For a VAR_DECL of anonymous type, we must also copy the
234 member VAR_DECLS here and rechain the DECL_ANON_UNION_ELEMS. */
235 tree members = NULL;
236 tree src;
238 for (src = DECL_ANON_UNION_ELEMS (t); src;
239 src = TREE_CHAIN (src))
241 tree member = remap_decl (TREE_VALUE (src), id);
243 gcc_assert (!TREE_PURPOSE (src));
244 members = tree_cons (NULL, member, members);
246 DECL_ANON_UNION_ELEMS (t) = nreverse (members);
248 #endif
250 /* Remember it, so that if we encounter this local entity
251 again we can reuse this copy. */
252 insert_decl_map (id, decl, t);
253 return t;
256 return unshare_expr ((tree) n->value);
259 static tree
260 remap_type (tree type, inline_data *id)
262 splay_tree_node node;
263 tree new, t;
265 if (type == NULL)
266 return type;
268 /* See if we have remapped this type. */
269 node = splay_tree_lookup (id->decl_map, (splay_tree_key) type);
270 if (node)
271 return (tree) node->value;
273 /* The type only needs remapping if it's variably modified. */
274 if (! variably_modified_type_p (type, id->callee))
276 insert_decl_map (id, type, type);
277 return type;
280 /* We do need a copy. build and register it now. If this is a pointer or
281 reference type, remap the designated type and make a new pointer or
282 reference type. */
283 if (TREE_CODE (type) == POINTER_TYPE)
285 new = build_pointer_type_for_mode (remap_type (TREE_TYPE (type), id),
286 TYPE_MODE (type),
287 TYPE_REF_CAN_ALIAS_ALL (type));
288 insert_decl_map (id, type, new);
289 return new;
291 else if (TREE_CODE (type) == REFERENCE_TYPE)
293 new = build_reference_type_for_mode (remap_type (TREE_TYPE (type), id),
294 TYPE_MODE (type),
295 TYPE_REF_CAN_ALIAS_ALL (type));
296 insert_decl_map (id, type, new);
297 return new;
299 else
300 new = copy_node (type);
302 insert_decl_map (id, type, new);
304 /* This is a new type, not a copy of an old type. Need to reassociate
305 variants. We can handle everything except the main variant lazily. */
306 t = TYPE_MAIN_VARIANT (type);
307 if (type != t)
309 t = remap_type (t, id);
310 TYPE_MAIN_VARIANT (new) = t;
311 TYPE_NEXT_VARIANT (new) = TYPE_MAIN_VARIANT (t);
312 TYPE_NEXT_VARIANT (t) = new;
314 else
316 TYPE_MAIN_VARIANT (new) = new;
317 TYPE_NEXT_VARIANT (new) = NULL;
320 if (TYPE_STUB_DECL (type))
321 TYPE_STUB_DECL (new) = remap_decl (TYPE_STUB_DECL (type), id);
323 /* Lazily create pointer and reference types. */
324 TYPE_POINTER_TO (new) = NULL;
325 TYPE_REFERENCE_TO (new) = NULL;
327 switch (TREE_CODE (new))
329 case INTEGER_TYPE:
330 case REAL_TYPE:
331 case ENUMERAL_TYPE:
332 case BOOLEAN_TYPE:
333 case CHAR_TYPE:
334 t = TYPE_MIN_VALUE (new);
335 if (t && TREE_CODE (t) != INTEGER_CST)
336 walk_tree (&TYPE_MIN_VALUE (new), copy_body_r, id, NULL);
338 t = TYPE_MAX_VALUE (new);
339 if (t && TREE_CODE (t) != INTEGER_CST)
340 walk_tree (&TYPE_MAX_VALUE (new), copy_body_r, id, NULL);
341 return new;
343 case FUNCTION_TYPE:
344 TREE_TYPE (new) = remap_type (TREE_TYPE (new), id);
345 walk_tree (&TYPE_ARG_TYPES (new), copy_body_r, id, NULL);
346 return new;
348 case ARRAY_TYPE:
349 TREE_TYPE (new) = remap_type (TREE_TYPE (new), id);
350 TYPE_DOMAIN (new) = remap_type (TYPE_DOMAIN (new), id);
351 break;
353 case RECORD_TYPE:
354 case UNION_TYPE:
355 case QUAL_UNION_TYPE:
356 walk_tree (&TYPE_FIELDS (new), copy_body_r, id, NULL);
357 break;
359 case OFFSET_TYPE:
360 default:
361 /* Shouldn't have been thought variable sized. */
362 gcc_unreachable ();
365 walk_tree (&TYPE_SIZE (new), copy_body_r, id, NULL);
366 walk_tree (&TYPE_SIZE_UNIT (new), copy_body_r, id, NULL);
368 return new;
371 static tree
372 remap_decls (tree decls, inline_data *id)
374 tree old_var;
375 tree new_decls = NULL_TREE;
377 /* Remap its variables. */
378 for (old_var = decls; old_var; old_var = TREE_CHAIN (old_var))
380 tree new_var;
382 /* We can not chain the local static declarations into the unexpanded_var_list
383 as we can't duplicate them or break one decl rule. Go ahead and link
384 them into unexpanded_var_list. */
385 if (!lang_hooks.tree_inlining.auto_var_in_fn_p (old_var, id->callee)
386 && !DECL_EXTERNAL (old_var))
388 cfun->unexpanded_var_list = tree_cons (NULL_TREE, old_var,
389 cfun->unexpanded_var_list);
390 continue;
393 /* Remap the variable. */
394 new_var = remap_decl (old_var, id);
396 /* If we didn't remap this variable, so we can't mess with its
397 TREE_CHAIN. If we remapped this variable to the return slot, it's
398 already declared somewhere else, so don't declare it here. */
399 if (!new_var || new_var == id->retvar)
401 else
403 gcc_assert (DECL_P (new_var));
404 TREE_CHAIN (new_var) = new_decls;
405 new_decls = new_var;
409 return nreverse (new_decls);
412 /* Copy the BLOCK to contain remapped versions of the variables
413 therein. And hook the new block into the block-tree. */
415 static void
416 remap_block (tree *block, inline_data *id)
418 tree old_block;
419 tree new_block;
420 tree fn;
422 /* Make the new block. */
423 old_block = *block;
424 new_block = make_node (BLOCK);
425 TREE_USED (new_block) = TREE_USED (old_block);
426 BLOCK_ABSTRACT_ORIGIN (new_block) = old_block;
427 BLOCK_SOURCE_LOCATION (new_block) = BLOCK_SOURCE_LOCATION (old_block);
428 *block = new_block;
430 /* Remap its variables. */
431 BLOCK_VARS (new_block) = remap_decls (BLOCK_VARS (old_block), id);
433 fn = id->caller;
434 if (id->cloning_p)
435 /* We're building a clone; DECL_INITIAL is still
436 error_mark_node, and current_binding_level is the parm
437 binding level. */
438 lang_hooks.decls.insert_block (new_block);
439 /* Remember the remapped block. */
440 insert_decl_map (id, old_block, new_block);
443 /* Copy the whole block tree and root it in id->block. */
444 static tree
445 remap_blocks (tree block, inline_data *id)
447 tree t;
448 tree new = block;
450 if (!block)
451 return NULL;
453 remap_block (&new, id);
454 gcc_assert (new != block);
455 for (t = BLOCK_SUBBLOCKS (block); t ; t = BLOCK_CHAIN (t))
456 add_lexical_block (new, remap_blocks (t, id));
457 return new;
460 static void
461 copy_statement_list (tree *tp)
463 tree_stmt_iterator oi, ni;
464 tree new;
466 new = alloc_stmt_list ();
467 ni = tsi_start (new);
468 oi = tsi_start (*tp);
469 *tp = new;
471 for (; !tsi_end_p (oi); tsi_next (&oi))
472 tsi_link_after (&ni, tsi_stmt (oi), TSI_NEW_STMT);
475 static void
476 copy_bind_expr (tree *tp, int *walk_subtrees, inline_data *id)
478 tree block = BIND_EXPR_BLOCK (*tp);
479 /* Copy (and replace) the statement. */
480 copy_tree_r (tp, walk_subtrees, NULL);
481 if (block)
483 remap_block (&block, id);
484 BIND_EXPR_BLOCK (*tp) = block;
487 if (BIND_EXPR_VARS (*tp))
488 /* This will remap a lot of the same decls again, but this should be
489 harmless. */
490 BIND_EXPR_VARS (*tp) = remap_decls (BIND_EXPR_VARS (*tp), id);
493 /* Called from copy_body_id via walk_tree. DATA is really an
494 `inline_data *'. */
496 static tree
497 copy_body_r (tree *tp, int *walk_subtrees, void *data)
499 inline_data *id = (inline_data *) data;
500 tree fn = id->callee;
501 tree new_block;
503 /* Begin by recognizing trees that we'll completely rewrite for the
504 inlining context. Our output for these trees is completely
505 different from out input (e.g. RETURN_EXPR is deleted, and morphs
506 into an edge). Further down, we'll handle trees that get
507 duplicated and/or tweaked. */
509 /* If this is a RETURN_STMT, change it into an EXPR_STMT and a
510 GOTO_STMT with the RET_LABEL as its target. */
511 if (TREE_CODE (*tp) == RETURN_EXPR && inlining_p (id))
513 tree assignment = TREE_OPERAND (*tp, 0);
515 /* If we're returning something, just turn that into an
516 assignment into the equivalent of the original RESULT_DECL.
517 If the "assignment" is just the result decl, the result
518 decl has already been set (e.g. a recent "foo (&result_decl,
519 ...)"); just toss the entire RETURN_EXPR. */
520 if (assignment && TREE_CODE (assignment) == MODIFY_EXPR)
522 /* Replace the RETURN_EXPR with (a copy of) the
523 MODIFY_EXPR hanging underneath. */
524 *tp = copy_node (assignment);
526 else /* Else the RETURN_EXPR returns no value. */
528 *tp = NULL;
529 return (void *)1;
533 /* Local variables and labels need to be replaced by equivalent
534 variables. We don't want to copy static variables; there's only
535 one of those, no matter how many times we inline the containing
536 function. Similarly for globals from an outer function. */
537 else if (lang_hooks.tree_inlining.auto_var_in_fn_p (*tp, fn))
539 tree new_decl;
541 /* Remap the declaration. */
542 new_decl = remap_decl (*tp, id);
543 gcc_assert (new_decl);
544 /* Replace this variable with the copy. */
545 STRIP_TYPE_NOPS (new_decl);
546 *tp = new_decl;
547 *walk_subtrees = 0;
549 else if (TREE_CODE (*tp) == STATEMENT_LIST)
550 copy_statement_list (tp);
551 else if (TREE_CODE (*tp) == SAVE_EXPR)
552 remap_save_expr (tp, id->decl_map, walk_subtrees);
553 else if (TREE_CODE (*tp) == LABEL_DECL
554 && (! DECL_CONTEXT (*tp)
555 || decl_function_context (*tp) == id->callee))
556 /* These may need to be remapped for EH handling. */
557 *tp = remap_decl (*tp, id);
558 else if (TREE_CODE (*tp) == BIND_EXPR)
559 copy_bind_expr (tp, walk_subtrees, id);
560 /* Types may need remapping as well. */
561 else if (TYPE_P (*tp))
562 *tp = remap_type (*tp, id);
564 /* If this is a constant, we have to copy the node iff the type will be
565 remapped. copy_tree_r will not copy a constant. */
566 else if (CONSTANT_CLASS_P (*tp))
568 tree new_type = remap_type (TREE_TYPE (*tp), id);
570 if (new_type == TREE_TYPE (*tp))
571 *walk_subtrees = 0;
573 else if (TREE_CODE (*tp) == INTEGER_CST)
574 *tp = build_int_cst_wide (new_type, TREE_INT_CST_LOW (*tp),
575 TREE_INT_CST_HIGH (*tp));
576 else
578 *tp = copy_node (*tp);
579 TREE_TYPE (*tp) = new_type;
583 /* Otherwise, just copy the node. Note that copy_tree_r already
584 knows not to copy VAR_DECLs, etc., so this is safe. */
585 else
587 /* Here we handle trees that are not completely rewritten.
588 First we detect some inlining-induced bogosities for
589 discarding. */
590 if (TREE_CODE (*tp) == MODIFY_EXPR
591 && TREE_OPERAND (*tp, 0) == TREE_OPERAND (*tp, 1)
592 && (lang_hooks.tree_inlining.auto_var_in_fn_p
593 (TREE_OPERAND (*tp, 0), fn)))
595 /* Some assignments VAR = VAR; don't generate any rtl code
596 and thus don't count as variable modification. Avoid
597 keeping bogosities like 0 = 0. */
598 tree decl = TREE_OPERAND (*tp, 0), value;
599 splay_tree_node n;
601 n = splay_tree_lookup (id->decl_map, (splay_tree_key) decl);
602 if (n)
604 value = (tree) n->value;
605 STRIP_TYPE_NOPS (value);
606 if (TREE_CONSTANT (value) || TREE_READONLY_DECL_P (value))
608 *tp = build_empty_stmt ();
609 return copy_body_r (tp, walk_subtrees, data);
613 else if (TREE_CODE (*tp) == INDIRECT_REF
614 && !id->versioning_p)
616 /* Get rid of *& from inline substitutions that can happen when a
617 pointer argument is an ADDR_EXPR. */
618 tree decl = TREE_OPERAND (*tp, 0);
619 splay_tree_node n;
621 n = splay_tree_lookup (id->decl_map, (splay_tree_key) decl);
622 if (n)
624 /* If we happen to get an ADDR_EXPR in n->value, strip
625 it manually here as we'll eventually get ADDR_EXPRs
626 which lie about their types pointed to. In this case
627 build_fold_indirect_ref wouldn't strip the INDIRECT_REF,
628 but we absolutely rely on that. As fold_indirect_ref
629 does other useful transformations, try that first, though. */
630 tree type = TREE_TYPE (TREE_TYPE ((tree)n->value));
631 *tp = fold_indirect_ref_1 (type, (tree)n->value);
632 if (! *tp)
634 if (TREE_CODE ((tree)n->value) == ADDR_EXPR)
635 *tp = TREE_OPERAND ((tree)n->value, 0);
636 else
637 *tp = build1 (INDIRECT_REF, type, (tree)n->value);
639 *walk_subtrees = 0;
640 return NULL;
644 /* Here is the "usual case". Copy this tree node, and then
645 tweak some special cases. */
646 copy_tree_r (tp, walk_subtrees, id->versioning_p ? data : NULL);
648 /* If EXPR has block defined, map it to newly constructed block.
649 When inlining we want EXPRs without block appear in the block
650 of function call. */
651 if (IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (TREE_CODE (*tp))))
653 new_block = id->block;
654 if (TREE_BLOCK (*tp))
656 splay_tree_node n;
657 n = splay_tree_lookup (id->decl_map,
658 (splay_tree_key) TREE_BLOCK (*tp));
659 gcc_assert (n);
660 new_block = (tree) n->value;
662 TREE_BLOCK (*tp) = new_block;
665 if (TREE_CODE (*tp) == RESX_EXPR && id->eh_region_offset)
666 TREE_OPERAND (*tp, 0) =
667 build_int_cst
668 (NULL_TREE,
669 id->eh_region_offset + TREE_INT_CST_LOW (TREE_OPERAND (*tp, 0)));
671 TREE_TYPE (*tp) = remap_type (TREE_TYPE (*tp), id);
673 /* The copied TARGET_EXPR has never been expanded, even if the
674 original node was expanded already. */
675 if (TREE_CODE (*tp) == TARGET_EXPR && TREE_OPERAND (*tp, 3))
677 TREE_OPERAND (*tp, 1) = TREE_OPERAND (*tp, 3);
678 TREE_OPERAND (*tp, 3) = NULL_TREE;
681 /* Variable substitution need not be simple. In particular, the
682 INDIRECT_REF substitution above. Make sure that TREE_CONSTANT
683 and friends are up-to-date. */
684 else if (TREE_CODE (*tp) == ADDR_EXPR)
686 walk_tree (&TREE_OPERAND (*tp, 0), copy_body_r, id, NULL);
687 recompute_tree_invarant_for_addr_expr (*tp);
688 *walk_subtrees = 0;
692 /* Keep iterating. */
693 return NULL_TREE;
696 /* Copy basic block, scale profile accordingly. Edges will be taken care of
697 later */
699 static basic_block
700 copy_bb (inline_data *id, basic_block bb, int frequency_scale, int count_scale)
702 block_stmt_iterator bsi, copy_bsi;
703 basic_block copy_basic_block;
705 /* create_basic_block() will append every new block to
706 basic_block_info automatically. */
707 copy_basic_block = create_basic_block (NULL, (void *) 0, bb->prev_bb->aux);
708 copy_basic_block->count = bb->count * count_scale / REG_BR_PROB_BASE;
709 copy_basic_block->frequency = (bb->frequency
710 * frequency_scale / REG_BR_PROB_BASE);
711 copy_bsi = bsi_start (copy_basic_block);
713 for (bsi = bsi_start (bb);
714 !bsi_end_p (bsi); bsi_next (&bsi))
716 tree stmt = bsi_stmt (bsi);
717 tree orig_stmt = stmt;
719 walk_tree (&stmt, copy_body_r, id, NULL);
721 /* RETURN_EXPR might be removed,
722 this is signalled by making stmt pointer NULL. */
723 if (stmt)
725 tree call, decl;
726 bsi_insert_after (&copy_bsi, stmt, BSI_NEW_STMT);
727 call = get_call_expr_in (stmt);
728 /* We're duplicating a CALL_EXPR. Find any corresponding
729 callgraph edges and update or duplicate them. */
730 if (call && (decl = get_callee_fndecl (call)))
732 if (id->saving_p)
734 struct cgraph_node *node;
735 struct cgraph_edge *edge;
737 /* We're saving a copy of the body, so we'll update the
738 callgraph nodes in place. Note that we avoid
739 altering the original callgraph node; we begin with
740 the first clone. */
741 for (node = id->node->next_clone;
742 node;
743 node = node->next_clone)
745 edge = cgraph_edge (node, orig_stmt);
746 gcc_assert (edge);
747 edge->call_stmt = stmt;
750 else
752 struct cgraph_edge *edge;
754 /* We're cloning or inlining this body; duplicate the
755 associate callgraph nodes. */
756 if (!id->versioning_p)
758 edge = cgraph_edge (id->current_node, orig_stmt);
759 if (edge)
760 cgraph_clone_edge (edge, id->node, stmt,
761 REG_BR_PROB_BASE, 1, true);
764 if (id->versioning_p)
766 /* Update the call_expr on the edges from the new version
767 to its callees. */
768 struct cgraph_edge *edge;
769 edge = cgraph_edge (id->node, orig_stmt);
770 if (edge)
771 edge->call_stmt = stmt;
774 /* If you think we can abort here, you are wrong.
775 There is no region 0 in tree land. */
776 gcc_assert (lookup_stmt_eh_region_fn (id->callee_cfun, orig_stmt)
777 != 0);
779 if (tree_could_throw_p (stmt))
781 int region = lookup_stmt_eh_region_fn (id->callee_cfun, orig_stmt);
782 /* Add an entry for the copied tree in the EH hashtable.
783 When saving or cloning or versioning, use the hashtable in
784 cfun, and just copy the EH number. When inlining, use the
785 hashtable in the caller, and adjust the region number. */
786 if (region > 0)
787 add_stmt_to_eh_region (stmt, region + id->eh_region_offset);
789 /* If this tree doesn't have a region associated with it,
790 and there is a "current region,"
791 then associate this tree with the current region
792 and add edges associated with this region. */
793 if ((lookup_stmt_eh_region_fn (id->callee_cfun,
794 orig_stmt) <= 0
795 && id->eh_region > 0)
796 && tree_could_throw_p (stmt))
797 add_stmt_to_eh_region (stmt, id->eh_region);
801 return copy_basic_block;
804 /* Copy edges from BB into its copy constructed earlier, scale profile
805 accordingly. Edges will be taken care of later. Assume aux
806 pointers to point to the copies of each BB. */
807 static void
808 copy_edges_for_bb (basic_block bb, int count_scale)
810 basic_block new_bb = bb->aux;
811 edge_iterator ei;
812 edge old_edge;
813 block_stmt_iterator bsi;
814 int flags;
816 /* Use the indices from the original blocks to create edges for the
817 new ones. */
818 FOR_EACH_EDGE (old_edge, ei, bb->succs)
819 if (!(old_edge->flags & EDGE_EH))
821 edge new;
823 flags = old_edge->flags;
825 /* Return edges do get a FALLTHRU flag when the get inlined. */
826 if (old_edge->dest->index == EXIT_BLOCK && !old_edge->flags
827 && old_edge->dest->aux != EXIT_BLOCK_PTR)
828 flags |= EDGE_FALLTHRU;
829 new = make_edge (new_bb, old_edge->dest->aux, flags);
830 new->count = old_edge->count * count_scale / REG_BR_PROB_BASE;
831 new->probability = old_edge->probability;
834 if (bb->index == ENTRY_BLOCK || bb->index == EXIT_BLOCK)
835 return;
837 for (bsi = bsi_start (new_bb); !bsi_end_p (bsi);)
839 tree copy_stmt;
841 copy_stmt = bsi_stmt (bsi);
842 update_stmt (copy_stmt);
843 /* Do this before the possible split_block. */
844 bsi_next (&bsi);
846 /* If this tree could throw an exception, there are two
847 cases where we need to add abnormal edge(s): the
848 tree wasn't in a region and there is a "current
849 region" in the caller; or the original tree had
850 EH edges. In both cases split the block after the tree,
851 and add abnormal edge(s) as needed; we need both
852 those from the callee and the caller.
853 We check whether the copy can throw, because the const
854 propagation can change an INDIRECT_REF which throws
855 into a COMPONENT_REF which doesn't. If the copy
856 can throw, the original could also throw. */
858 if (tree_can_throw_internal (copy_stmt))
860 if (!bsi_end_p (bsi))
861 /* Note that bb's predecessor edges aren't necessarily
862 right at this point; split_block doesn't care. */
864 edge e = split_block (new_bb, copy_stmt);
865 new_bb = e->dest;
866 bsi = bsi_start (new_bb);
869 make_eh_edges (copy_stmt);
874 /* Wrapper for remap_decl so it can be used as a callback. */
875 static tree
876 remap_decl_1 (tree decl, void *data)
878 return remap_decl (decl, data);
881 /* Make a copy of the body of FN so that it can be inserted inline in
882 another function. Walks FN via CFG, returns new fndecl. */
884 static tree
885 copy_cfg_body (inline_data * id, gcov_type count, int frequency,
886 basic_block entry_block_map, basic_block exit_block_map)
888 tree callee_fndecl = id->callee;
889 /* Original cfun for the callee, doesn't change. */
890 struct function *callee_cfun = DECL_STRUCT_FUNCTION (callee_fndecl);
891 /* Copy, built by this function. */
892 struct function *new_cfun;
893 /* Place to copy from; when a copy of the function was saved off earlier,
894 use that instead of the main copy. */
895 struct function *cfun_to_copy =
896 (struct function *) ggc_alloc_cleared (sizeof (struct function));
897 basic_block bb;
898 tree new_fndecl = NULL;
899 bool saving_or_cloning;
900 int count_scale, frequency_scale;
902 if (ENTRY_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->count)
903 count_scale = (REG_BR_PROB_BASE * count
904 / ENTRY_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->count);
905 else
906 count_scale = 1;
908 if (ENTRY_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->frequency)
909 frequency_scale = (REG_BR_PROB_BASE * frequency
911 ENTRY_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->frequency);
912 else
913 frequency_scale = count_scale;
915 /* Register specific tree functions. */
916 tree_register_cfg_hooks ();
918 /* Must have a CFG here at this point. */
919 gcc_assert (ENTRY_BLOCK_PTR_FOR_FUNCTION
920 (DECL_STRUCT_FUNCTION (callee_fndecl)));
922 *cfun_to_copy = *DECL_STRUCT_FUNCTION (callee_fndecl);
924 /* If there is a saved_cfg+saved_args lurking in the
925 struct function, a copy of the callee body was saved there, and
926 the 'struct cgraph edge' nodes have been fudged to point into the
927 saved body. Accordingly, we want to copy that saved body so the
928 callgraph edges will be recognized and cloned properly. */
929 if (cfun_to_copy->saved_cfg)
931 cfun_to_copy->cfg = cfun_to_copy->saved_cfg;
932 cfun_to_copy->eh = cfun_to_copy->saved_eh;
934 id->callee_cfun = cfun_to_copy;
936 /* If saving or cloning a function body, create new basic_block_info
937 and label_to_block_maps. Otherwise, we're duplicating a function
938 body for inlining; insert our new blocks and labels into the
939 existing varrays. */
940 saving_or_cloning = (id->saving_p || id->cloning_p || id->versioning_p);
941 if (saving_or_cloning)
943 new_cfun =
944 (struct function *) ggc_alloc_cleared (sizeof (struct function));
945 *new_cfun = *DECL_STRUCT_FUNCTION (callee_fndecl);
946 new_cfun->cfg = NULL;
947 new_cfun->decl = new_fndecl = copy_node (callee_fndecl);
948 new_cfun->ib_boundaries_block = (varray_type) 0;
949 DECL_STRUCT_FUNCTION (new_fndecl) = new_cfun;
950 push_cfun (new_cfun);
951 init_empty_tree_cfg ();
953 ENTRY_BLOCK_PTR->count =
954 (ENTRY_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->count * count_scale /
955 REG_BR_PROB_BASE);
956 ENTRY_BLOCK_PTR->frequency =
957 (ENTRY_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->frequency *
958 frequency_scale / REG_BR_PROB_BASE);
959 EXIT_BLOCK_PTR->count =
960 (EXIT_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->count * count_scale /
961 REG_BR_PROB_BASE);
962 EXIT_BLOCK_PTR->frequency =
963 (EXIT_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->frequency *
964 frequency_scale / REG_BR_PROB_BASE);
966 entry_block_map = ENTRY_BLOCK_PTR;
967 exit_block_map = EXIT_BLOCK_PTR;
970 ENTRY_BLOCK_PTR_FOR_FUNCTION (cfun_to_copy)->aux = entry_block_map;
971 EXIT_BLOCK_PTR_FOR_FUNCTION (cfun_to_copy)->aux = exit_block_map;
974 /* Duplicate any exception-handling regions. */
975 if (cfun->eh)
977 if (saving_or_cloning)
978 init_eh_for_function ();
979 id->eh_region_offset = duplicate_eh_regions (cfun_to_copy,
980 remap_decl_1,
981 id, id->eh_region);
982 gcc_assert (inlining_p (id) || !id->eh_region_offset);
984 /* Use aux pointers to map the original blocks to copy. */
985 FOR_EACH_BB_FN (bb, cfun_to_copy)
986 bb->aux = copy_bb (id, bb, frequency_scale, count_scale);
987 /* Now that we've duplicated the blocks, duplicate their edges. */
988 FOR_ALL_BB_FN (bb, cfun_to_copy)
989 copy_edges_for_bb (bb, count_scale);
990 FOR_ALL_BB_FN (bb, cfun_to_copy)
991 bb->aux = NULL;
993 if (saving_or_cloning)
994 pop_cfun ();
996 return new_fndecl;
999 /* Make a copy of the body of FN so that it can be inserted inline in
1000 another function. */
1002 static tree
1003 copy_generic_body (inline_data *id)
1005 tree body;
1006 tree fndecl = id->callee;
1008 body = DECL_SAVED_TREE (fndecl);
1009 walk_tree (&body, copy_body_r, id, NULL);
1011 return body;
1014 static tree
1015 copy_body (inline_data *id, gcov_type count, int frequency,
1016 basic_block entry_block_map, basic_block exit_block_map)
1018 tree fndecl = id->callee;
1019 tree body;
1021 /* If this body has a CFG, walk CFG and copy. */
1022 gcc_assert (ENTRY_BLOCK_PTR_FOR_FUNCTION (DECL_STRUCT_FUNCTION (fndecl)));
1023 body = copy_cfg_body (id, count, frequency, entry_block_map, exit_block_map);
1025 return body;
1028 /* Return true if VALUE is an ADDR_EXPR of an automatic variable
1029 defined in function FN, or of a data member thereof. */
1031 static bool
1032 self_inlining_addr_expr (tree value, tree fn)
1034 tree var;
1036 if (TREE_CODE (value) != ADDR_EXPR)
1037 return false;
1039 var = get_base_address (TREE_OPERAND (value, 0));
1041 return var && lang_hooks.tree_inlining.auto_var_in_fn_p (var, fn);
1044 static void
1045 setup_one_parameter (inline_data *id, tree p, tree value, tree fn,
1046 basic_block bb, tree *vars)
1048 tree init_stmt;
1049 tree var;
1050 tree var_sub;
1052 /* If the parameter is never assigned to, we may not need to
1053 create a new variable here at all. Instead, we may be able
1054 to just use the argument value. */
1055 if (TREE_READONLY (p)
1056 && !TREE_ADDRESSABLE (p)
1057 && value && !TREE_SIDE_EFFECTS (value))
1059 /* We may produce non-gimple trees by adding NOPs or introduce
1060 invalid sharing when operand is not really constant.
1061 It is not big deal to prohibit constant propagation here as
1062 we will constant propagate in DOM1 pass anyway. */
1063 if (is_gimple_min_invariant (value)
1064 && lang_hooks.types_compatible_p (TREE_TYPE (value), TREE_TYPE (p))
1065 /* We have to be very careful about ADDR_EXPR. Make sure
1066 the base variable isn't a local variable of the inlined
1067 function, e.g., when doing recursive inlining, direct or
1068 mutually-recursive or whatever, which is why we don't
1069 just test whether fn == current_function_decl. */
1070 && ! self_inlining_addr_expr (value, fn))
1072 insert_decl_map (id, p, value);
1073 return;
1077 /* Make an equivalent VAR_DECL. Note that we must NOT remap the type
1078 here since the type of this decl must be visible to the calling
1079 function. */
1080 var = copy_decl_for_dup (p, fn, id->caller, /*versioning=*/false);
1082 /* See if the frontend wants to pass this by invisible reference. If
1083 so, our new VAR_DECL will have REFERENCE_TYPE, and we need to
1084 replace uses of the PARM_DECL with dereferences. */
1085 if (TREE_TYPE (var) != TREE_TYPE (p)
1086 && POINTER_TYPE_P (TREE_TYPE (var))
1087 && TREE_TYPE (TREE_TYPE (var)) == TREE_TYPE (p))
1089 insert_decl_map (id, var, var);
1090 var_sub = build_fold_indirect_ref (var);
1092 else
1093 var_sub = var;
1095 /* Register the VAR_DECL as the equivalent for the PARM_DECL;
1096 that way, when the PARM_DECL is encountered, it will be
1097 automatically replaced by the VAR_DECL. */
1098 insert_decl_map (id, p, var_sub);
1100 /* Declare this new variable. */
1101 TREE_CHAIN (var) = *vars;
1102 *vars = var;
1104 /* Make gimplifier happy about this variable. */
1105 DECL_SEEN_IN_BIND_EXPR_P (var) = 1;
1107 /* Even if P was TREE_READONLY, the new VAR should not be.
1108 In the original code, we would have constructed a
1109 temporary, and then the function body would have never
1110 changed the value of P. However, now, we will be
1111 constructing VAR directly. The constructor body may
1112 change its value multiple times as it is being
1113 constructed. Therefore, it must not be TREE_READONLY;
1114 the back-end assumes that TREE_READONLY variable is
1115 assigned to only once. */
1116 if (TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (p)))
1117 TREE_READONLY (var) = 0;
1119 /* Initialize this VAR_DECL from the equivalent argument. Convert
1120 the argument to the proper type in case it was promoted. */
1121 if (value)
1123 tree rhs = fold_convert (TREE_TYPE (var), value);
1124 block_stmt_iterator bsi = bsi_last (bb);
1126 if (rhs == error_mark_node)
1127 return;
1129 /* We want to use MODIFY_EXPR, not INIT_EXPR here so that we
1130 keep our trees in gimple form. */
1131 init_stmt = build (MODIFY_EXPR, TREE_TYPE (var), var, rhs);
1133 /* If we did not create a gimple value and we did not create a gimple
1134 cast of a gimple value, then we will need to gimplify INIT_STMTS
1135 at the end. Note that is_gimple_cast only checks the outer
1136 tree code, not its operand. Thus the explicit check that its
1137 operand is a gimple value. */
1138 if (!is_gimple_val (rhs)
1139 && (!is_gimple_cast (rhs)
1140 || !is_gimple_val (TREE_OPERAND (rhs, 0))))
1141 gimplify_stmt (&init_stmt);
1142 bsi_insert_after (&bsi, init_stmt, BSI_NEW_STMT);
1146 /* Generate code to initialize the parameters of the function at the
1147 top of the stack in ID from the ARGS (presented as a TREE_LIST). */
1149 static void
1150 initialize_inlined_parameters (inline_data *id, tree args, tree static_chain,
1151 tree fn, basic_block bb)
1153 tree parms;
1154 tree a;
1155 tree p;
1156 tree vars = NULL_TREE;
1157 int argnum = 0;
1159 /* Figure out what the parameters are. */
1160 parms = DECL_ARGUMENTS (fn);
1161 if (fn == current_function_decl)
1162 parms = cfun->saved_args;
1164 /* Loop through the parameter declarations, replacing each with an
1165 equivalent VAR_DECL, appropriately initialized. */
1166 for (p = parms, a = args; p;
1167 a = a ? TREE_CHAIN (a) : a, p = TREE_CHAIN (p))
1169 tree value;
1171 ++argnum;
1173 /* Find the initializer. */
1174 value = lang_hooks.tree_inlining.convert_parm_for_inlining
1175 (p, a ? TREE_VALUE (a) : NULL_TREE, fn, argnum);
1177 setup_one_parameter (id, p, value, fn, bb, &vars);
1180 /* Initialize the static chain. */
1181 p = DECL_STRUCT_FUNCTION (fn)->static_chain_decl;
1182 if (fn == current_function_decl)
1183 p = DECL_STRUCT_FUNCTION (fn)->saved_static_chain_decl;
1184 if (p)
1186 /* No static chain? Seems like a bug in tree-nested.c. */
1187 gcc_assert (static_chain);
1189 setup_one_parameter (id, p, static_chain, fn, bb, &vars);
1192 declare_inline_vars (id->block, vars);
1195 /* Declare a return variable to replace the RESULT_DECL for the
1196 function we are calling. An appropriate DECL_STMT is returned.
1197 The USE_STMT is filled to contain a use of the declaration to
1198 indicate the return value of the function.
1200 RETURN_SLOT_ADDR, if non-null, was a fake parameter that
1201 took the address of the result. MODIFY_DEST, if non-null, was the LHS of
1202 the MODIFY_EXPR to which this call is the RHS.
1204 The return value is a (possibly null) value that is the result of the
1205 function as seen by the callee. *USE_P is a (possibly null) value that
1206 holds the result as seen by the caller. */
1208 static tree
1209 declare_return_variable (inline_data *id, tree return_slot_addr,
1210 tree modify_dest, tree *use_p)
1212 tree callee = id->callee;
1213 tree caller = id->caller;
1214 tree result = DECL_RESULT (callee);
1215 tree callee_type = TREE_TYPE (result);
1216 tree caller_type = TREE_TYPE (TREE_TYPE (callee));
1217 tree var, use;
1219 /* We don't need to do anything for functions that don't return
1220 anything. */
1221 if (!result || VOID_TYPE_P (callee_type))
1223 *use_p = NULL_TREE;
1224 return NULL_TREE;
1227 /* If there was a return slot, then the return value is the
1228 dereferenced address of that object. */
1229 if (return_slot_addr)
1231 /* The front end shouldn't have used both return_slot_addr and
1232 a modify expression. */
1233 gcc_assert (!modify_dest);
1234 if (DECL_BY_REFERENCE (result))
1235 var = return_slot_addr;
1236 else
1237 var = build_fold_indirect_ref (return_slot_addr);
1238 use = NULL;
1239 goto done;
1242 /* All types requiring non-trivial constructors should have been handled. */
1243 gcc_assert (!TREE_ADDRESSABLE (callee_type));
1245 /* Attempt to avoid creating a new temporary variable. */
1246 if (modify_dest)
1248 bool use_it = false;
1250 /* We can't use MODIFY_DEST if there's type promotion involved. */
1251 if (!lang_hooks.types_compatible_p (caller_type, callee_type))
1252 use_it = false;
1254 /* ??? If we're assigning to a variable sized type, then we must
1255 reuse the destination variable, because we've no good way to
1256 create variable sized temporaries at this point. */
1257 else if (TREE_CODE (TYPE_SIZE_UNIT (caller_type)) != INTEGER_CST)
1258 use_it = true;
1260 /* If the callee cannot possibly modify MODIFY_DEST, then we can
1261 reuse it as the result of the call directly. Don't do this if
1262 it would promote MODIFY_DEST to addressable. */
1263 else if (TREE_ADDRESSABLE (result))
1264 use_it = false;
1265 else
1267 tree base_m = get_base_address (modify_dest);
1269 /* If the base isn't a decl, then it's a pointer, and we don't
1270 know where that's going to go. */
1271 if (!DECL_P (base_m))
1272 use_it = false;
1273 else if (is_global_var (base_m))
1274 use_it = false;
1275 else if (!TREE_ADDRESSABLE (base_m))
1276 use_it = true;
1279 if (use_it)
1281 var = modify_dest;
1282 use = NULL;
1283 goto done;
1287 gcc_assert (TREE_CODE (TYPE_SIZE_UNIT (callee_type)) == INTEGER_CST);
1289 var = copy_decl_for_dup (result, callee, caller, /*versioning=*/false);
1291 DECL_SEEN_IN_BIND_EXPR_P (var) = 1;
1292 DECL_STRUCT_FUNCTION (caller)->unexpanded_var_list
1293 = tree_cons (NULL_TREE, var,
1294 DECL_STRUCT_FUNCTION (caller)->unexpanded_var_list);
1296 /* Do not have the rest of GCC warn about this variable as it should
1297 not be visible to the user. */
1298 TREE_NO_WARNING (var) = 1;
1300 /* Build the use expr. If the return type of the function was
1301 promoted, convert it back to the expected type. */
1302 use = var;
1303 if (!lang_hooks.types_compatible_p (TREE_TYPE (var), caller_type))
1304 use = fold_convert (caller_type, var);
1306 done:
1307 /* Register the VAR_DECL as the equivalent for the RESULT_DECL; that
1308 way, when the RESULT_DECL is encountered, it will be
1309 automatically replaced by the VAR_DECL. */
1310 insert_decl_map (id, result, var);
1312 /* Remember this so we can ignore it in remap_decls. */
1313 id->retvar = var;
1315 *use_p = use;
1316 return var;
1319 /* Returns nonzero if a function can be inlined as a tree. */
1321 bool
1322 tree_inlinable_function_p (tree fn)
1324 return inlinable_function_p (fn);
1327 static const char *inline_forbidden_reason;
1329 static tree
1330 inline_forbidden_p_1 (tree *nodep, int *walk_subtrees ATTRIBUTE_UNUSED,
1331 void *fnp)
1333 tree node = *nodep;
1334 tree fn = (tree) fnp;
1335 tree t;
1337 switch (TREE_CODE (node))
1339 case CALL_EXPR:
1340 /* Refuse to inline alloca call unless user explicitly forced so as
1341 this may change program's memory overhead drastically when the
1342 function using alloca is called in loop. In GCC present in
1343 SPEC2000 inlining into schedule_block cause it to require 2GB of
1344 RAM instead of 256MB. */
1345 if (alloca_call_p (node)
1346 && !lookup_attribute ("always_inline", DECL_ATTRIBUTES (fn)))
1348 inline_forbidden_reason
1349 = G_("function %q+F can never be inlined because it uses "
1350 "alloca (override using the always_inline attribute)");
1351 return node;
1353 t = get_callee_fndecl (node);
1354 if (! t)
1355 break;
1357 /* We cannot inline functions that call setjmp. */
1358 if (setjmp_call_p (t))
1360 inline_forbidden_reason
1361 = G_("function %q+F can never be inlined because it uses setjmp");
1362 return node;
1365 if (DECL_BUILT_IN_CLASS (t) == BUILT_IN_NORMAL)
1366 switch (DECL_FUNCTION_CODE (t))
1368 /* We cannot inline functions that take a variable number of
1369 arguments. */
1370 case BUILT_IN_VA_START:
1371 case BUILT_IN_STDARG_START:
1372 case BUILT_IN_NEXT_ARG:
1373 case BUILT_IN_VA_END:
1374 inline_forbidden_reason
1375 = G_("function %q+F can never be inlined because it "
1376 "uses variable argument lists");
1377 return node;
1379 case BUILT_IN_LONGJMP:
1380 /* We can't inline functions that call __builtin_longjmp at
1381 all. The non-local goto machinery really requires the
1382 destination be in a different function. If we allow the
1383 function calling __builtin_longjmp to be inlined into the
1384 function calling __builtin_setjmp, Things will Go Awry. */
1385 inline_forbidden_reason
1386 = G_("function %q+F can never be inlined because "
1387 "it uses setjmp-longjmp exception handling");
1388 return node;
1390 case BUILT_IN_NONLOCAL_GOTO:
1391 /* Similarly. */
1392 inline_forbidden_reason
1393 = G_("function %q+F can never be inlined because "
1394 "it uses non-local goto");
1395 return node;
1397 case BUILT_IN_RETURN:
1398 case BUILT_IN_APPLY_ARGS:
1399 /* If a __builtin_apply_args caller would be inlined,
1400 it would be saving arguments of the function it has
1401 been inlined into. Similarly __builtin_return would
1402 return from the function the inline has been inlined into. */
1403 inline_forbidden_reason
1404 = G_("function %q+F can never be inlined because "
1405 "it uses __builtin_return or __builtin_apply_args");
1406 return node;
1408 default:
1409 break;
1411 break;
1413 case GOTO_EXPR:
1414 t = TREE_OPERAND (node, 0);
1416 /* We will not inline a function which uses computed goto. The
1417 addresses of its local labels, which may be tucked into
1418 global storage, are of course not constant across
1419 instantiations, which causes unexpected behavior. */
1420 if (TREE_CODE (t) != LABEL_DECL)
1422 inline_forbidden_reason
1423 = G_("function %q+F can never be inlined "
1424 "because it contains a computed goto");
1425 return node;
1427 break;
1429 case LABEL_EXPR:
1430 t = TREE_OPERAND (node, 0);
1431 if (DECL_NONLOCAL (t))
1433 /* We cannot inline a function that receives a non-local goto
1434 because we cannot remap the destination label used in the
1435 function that is performing the non-local goto. */
1436 inline_forbidden_reason
1437 = G_("function %q+F can never be inlined "
1438 "because it receives a non-local goto");
1439 return node;
1441 break;
1443 case RECORD_TYPE:
1444 case UNION_TYPE:
1445 /* We cannot inline a function of the form
1447 void F (int i) { struct S { int ar[i]; } s; }
1449 Attempting to do so produces a catch-22.
1450 If walk_tree examines the TYPE_FIELDS chain of RECORD_TYPE/
1451 UNION_TYPE nodes, then it goes into infinite recursion on a
1452 structure containing a pointer to its own type. If it doesn't,
1453 then the type node for S doesn't get adjusted properly when
1454 F is inlined.
1456 ??? This is likely no longer true, but it's too late in the 4.0
1457 cycle to try to find out. This should be checked for 4.1. */
1458 for (t = TYPE_FIELDS (node); t; t = TREE_CHAIN (t))
1459 if (variably_modified_type_p (TREE_TYPE (t), NULL))
1461 inline_forbidden_reason
1462 = G_("function %q+F can never be inlined "
1463 "because it uses variable sized variables");
1464 return node;
1467 default:
1468 break;
1471 return NULL_TREE;
1474 /* Return subexpression representing possible alloca call, if any. */
1475 static tree
1476 inline_forbidden_p (tree fndecl)
1478 location_t saved_loc = input_location;
1479 block_stmt_iterator bsi;
1480 basic_block bb;
1481 tree ret = NULL_TREE;
1483 FOR_EACH_BB_FN (bb, DECL_STRUCT_FUNCTION (fndecl))
1484 for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi))
1486 ret = walk_tree_without_duplicates (bsi_stmt_ptr (bsi),
1487 inline_forbidden_p_1, fndecl);
1488 if (ret)
1489 goto egress;
1492 egress:
1493 input_location = saved_loc;
1494 return ret;
1497 /* Returns nonzero if FN is a function that does not have any
1498 fundamental inline blocking properties. */
1500 static bool
1501 inlinable_function_p (tree fn)
1503 bool inlinable = true;
1505 /* If we've already decided this function shouldn't be inlined,
1506 there's no need to check again. */
1507 if (DECL_UNINLINABLE (fn))
1508 return false;
1510 /* See if there is any language-specific reason it cannot be
1511 inlined. (It is important that this hook be called early because
1512 in C++ it may result in template instantiation.)
1513 If the function is not inlinable for language-specific reasons,
1514 it is left up to the langhook to explain why. */
1515 inlinable = !lang_hooks.tree_inlining.cannot_inline_tree_fn (&fn);
1517 /* If we don't have the function body available, we can't inline it.
1518 However, this should not be recorded since we also get here for
1519 forward declared inline functions. Therefore, return at once. */
1520 if (!DECL_SAVED_TREE (fn))
1521 return false;
1523 /* If we're not inlining at all, then we cannot inline this function. */
1524 else if (!flag_inline_trees)
1525 inlinable = false;
1527 /* Only try to inline functions if DECL_INLINE is set. This should be
1528 true for all functions declared `inline', and for all other functions
1529 as well with -finline-functions.
1531 Don't think of disregarding DECL_INLINE when flag_inline_trees == 2;
1532 it's the front-end that must set DECL_INLINE in this case, because
1533 dwarf2out loses if a function that does not have DECL_INLINE set is
1534 inlined anyway. That is why we have both DECL_INLINE and
1535 DECL_DECLARED_INLINE_P. */
1536 /* FIXME: When flag_inline_trees dies, the check for flag_unit_at_a_time
1537 here should be redundant. */
1538 else if (!DECL_INLINE (fn) && !flag_unit_at_a_time)
1539 inlinable = false;
1541 else if (inline_forbidden_p (fn))
1543 /* See if we should warn about uninlinable functions. Previously,
1544 some of these warnings would be issued while trying to expand
1545 the function inline, but that would cause multiple warnings
1546 about functions that would for example call alloca. But since
1547 this a property of the function, just one warning is enough.
1548 As a bonus we can now give more details about the reason why a
1549 function is not inlinable.
1550 We only warn for functions declared `inline' by the user. */
1551 bool do_warning = (warn_inline
1552 && DECL_INLINE (fn)
1553 && DECL_DECLARED_INLINE_P (fn)
1554 && !DECL_IN_SYSTEM_HEADER (fn));
1556 if (lookup_attribute ("always_inline", DECL_ATTRIBUTES (fn)))
1557 sorry (inline_forbidden_reason, fn);
1558 else if (do_warning)
1559 warning (OPT_Winline, inline_forbidden_reason, fn);
1561 inlinable = false;
1564 /* Squirrel away the result so that we don't have to check again. */
1565 DECL_UNINLINABLE (fn) = !inlinable;
1567 return inlinable;
1570 /* Estimate the cost of a memory move. Use machine dependent
1571 word size and take possible memcpy call into account. */
1574 estimate_move_cost (tree type)
1576 HOST_WIDE_INT size;
1578 size = int_size_in_bytes (type);
1580 if (size < 0 || size > MOVE_MAX_PIECES * MOVE_RATIO)
1581 /* Cost of a memcpy call, 3 arguments and the call. */
1582 return 4;
1583 else
1584 return ((size + MOVE_MAX_PIECES - 1) / MOVE_MAX_PIECES);
1587 /* Used by estimate_num_insns. Estimate number of instructions seen
1588 by given statement. */
1590 static tree
1591 estimate_num_insns_1 (tree *tp, int *walk_subtrees, void *data)
1593 int *count = data;
1594 tree x = *tp;
1596 if (IS_TYPE_OR_DECL_P (x))
1598 *walk_subtrees = 0;
1599 return NULL;
1601 /* Assume that constants and references counts nothing. These should
1602 be majorized by amount of operations among them we count later
1603 and are common target of CSE and similar optimizations. */
1604 else if (CONSTANT_CLASS_P (x) || REFERENCE_CLASS_P (x))
1605 return NULL;
1607 switch (TREE_CODE (x))
1609 /* Containers have no cost. */
1610 case TREE_LIST:
1611 case TREE_VEC:
1612 case BLOCK:
1613 case COMPONENT_REF:
1614 case BIT_FIELD_REF:
1615 case INDIRECT_REF:
1616 case ALIGN_INDIRECT_REF:
1617 case MISALIGNED_INDIRECT_REF:
1618 case ARRAY_REF:
1619 case ARRAY_RANGE_REF:
1620 case OBJ_TYPE_REF:
1621 case EXC_PTR_EXPR: /* ??? */
1622 case FILTER_EXPR: /* ??? */
1623 case COMPOUND_EXPR:
1624 case BIND_EXPR:
1625 case WITH_CLEANUP_EXPR:
1626 case NOP_EXPR:
1627 case VIEW_CONVERT_EXPR:
1628 case SAVE_EXPR:
1629 case ADDR_EXPR:
1630 case COMPLEX_EXPR:
1631 case RANGE_EXPR:
1632 case CASE_LABEL_EXPR:
1633 case SSA_NAME:
1634 case CATCH_EXPR:
1635 case EH_FILTER_EXPR:
1636 case STATEMENT_LIST:
1637 case ERROR_MARK:
1638 case NON_LVALUE_EXPR:
1639 case FDESC_EXPR:
1640 case VA_ARG_EXPR:
1641 case TRY_CATCH_EXPR:
1642 case TRY_FINALLY_EXPR:
1643 case LABEL_EXPR:
1644 case GOTO_EXPR:
1645 case RETURN_EXPR:
1646 case EXIT_EXPR:
1647 case LOOP_EXPR:
1648 case PHI_NODE:
1649 case WITH_SIZE_EXPR:
1650 break;
1652 /* We don't account constants for now. Assume that the cost is amortized
1653 by operations that do use them. We may re-consider this decision once
1654 we are able to optimize the tree before estimating its size and break
1655 out static initializers. */
1656 case IDENTIFIER_NODE:
1657 case INTEGER_CST:
1658 case REAL_CST:
1659 case COMPLEX_CST:
1660 case VECTOR_CST:
1661 case STRING_CST:
1662 *walk_subtrees = 0;
1663 return NULL;
1665 /* Try to estimate the cost of assignments. We have three cases to
1666 deal with:
1667 1) Simple assignments to registers;
1668 2) Stores to things that must live in memory. This includes
1669 "normal" stores to scalars, but also assignments of large
1670 structures, or constructors of big arrays;
1671 3) TARGET_EXPRs.
1673 Let us look at the first two cases, assuming we have "a = b + C":
1674 <modify_expr <var_decl "a"> <plus_expr <var_decl "b"> <constant C>>
1675 If "a" is a GIMPLE register, the assignment to it is free on almost
1676 any target, because "a" usually ends up in a real register. Hence
1677 the only cost of this expression comes from the PLUS_EXPR, and we
1678 can ignore the MODIFY_EXPR.
1679 If "a" is not a GIMPLE register, the assignment to "a" will most
1680 likely be a real store, so the cost of the MODIFY_EXPR is the cost
1681 of moving something into "a", which we compute using the function
1682 estimate_move_cost.
1684 The third case deals with TARGET_EXPRs, for which the semantics are
1685 that a temporary is assigned, unless the TARGET_EXPR itself is being
1686 assigned to something else. In the latter case we do not need the
1687 temporary. E.g. in <modify_expr <var_decl "a"> <target_expr>>, the
1688 MODIFY_EXPR is free. */
1689 case INIT_EXPR:
1690 case MODIFY_EXPR:
1691 /* Is the right and side a TARGET_EXPR? */
1692 if (TREE_CODE (TREE_OPERAND (x, 1)) == TARGET_EXPR)
1693 break;
1694 /* ... fall through ... */
1696 case TARGET_EXPR:
1697 x = TREE_OPERAND (x, 0);
1698 /* Is this an assignments to a register? */
1699 if (is_gimple_reg (x))
1700 break;
1701 /* Otherwise it's a store, so fall through to compute the move cost. */
1703 case CONSTRUCTOR:
1704 *count += estimate_move_cost (TREE_TYPE (x));
1705 break;
1707 /* Assign cost of 1 to usual operations.
1708 ??? We may consider mapping RTL costs to this. */
1709 case COND_EXPR:
1710 case VEC_COND_EXPR:
1712 case PLUS_EXPR:
1713 case MINUS_EXPR:
1714 case MULT_EXPR:
1716 case FIX_TRUNC_EXPR:
1717 case FIX_CEIL_EXPR:
1718 case FIX_FLOOR_EXPR:
1719 case FIX_ROUND_EXPR:
1721 case NEGATE_EXPR:
1722 case FLOAT_EXPR:
1723 case MIN_EXPR:
1724 case MAX_EXPR:
1725 case ABS_EXPR:
1727 case LSHIFT_EXPR:
1728 case RSHIFT_EXPR:
1729 case LROTATE_EXPR:
1730 case RROTATE_EXPR:
1731 case VEC_LSHIFT_EXPR:
1732 case VEC_RSHIFT_EXPR:
1734 case BIT_IOR_EXPR:
1735 case BIT_XOR_EXPR:
1736 case BIT_AND_EXPR:
1737 case BIT_NOT_EXPR:
1739 case TRUTH_ANDIF_EXPR:
1740 case TRUTH_ORIF_EXPR:
1741 case TRUTH_AND_EXPR:
1742 case TRUTH_OR_EXPR:
1743 case TRUTH_XOR_EXPR:
1744 case TRUTH_NOT_EXPR:
1746 case LT_EXPR:
1747 case LE_EXPR:
1748 case GT_EXPR:
1749 case GE_EXPR:
1750 case EQ_EXPR:
1751 case NE_EXPR:
1752 case ORDERED_EXPR:
1753 case UNORDERED_EXPR:
1755 case UNLT_EXPR:
1756 case UNLE_EXPR:
1757 case UNGT_EXPR:
1758 case UNGE_EXPR:
1759 case UNEQ_EXPR:
1760 case LTGT_EXPR:
1762 case CONVERT_EXPR:
1764 case CONJ_EXPR:
1766 case PREDECREMENT_EXPR:
1767 case PREINCREMENT_EXPR:
1768 case POSTDECREMENT_EXPR:
1769 case POSTINCREMENT_EXPR:
1771 case SWITCH_EXPR:
1773 case ASM_EXPR:
1775 case REALIGN_LOAD_EXPR:
1777 case REDUC_MAX_EXPR:
1778 case REDUC_MIN_EXPR:
1779 case REDUC_PLUS_EXPR:
1781 case RESX_EXPR:
1782 *count += 1;
1783 break;
1785 /* Few special cases of expensive operations. This is useful
1786 to avoid inlining on functions having too many of these. */
1787 case TRUNC_DIV_EXPR:
1788 case CEIL_DIV_EXPR:
1789 case FLOOR_DIV_EXPR:
1790 case ROUND_DIV_EXPR:
1791 case EXACT_DIV_EXPR:
1792 case TRUNC_MOD_EXPR:
1793 case CEIL_MOD_EXPR:
1794 case FLOOR_MOD_EXPR:
1795 case ROUND_MOD_EXPR:
1796 case RDIV_EXPR:
1797 *count += 10;
1798 break;
1799 case CALL_EXPR:
1801 tree decl = get_callee_fndecl (x);
1802 tree arg;
1804 if (decl && DECL_BUILT_IN_CLASS (decl) == BUILT_IN_NORMAL)
1805 switch (DECL_FUNCTION_CODE (decl))
1807 case BUILT_IN_CONSTANT_P:
1808 *walk_subtrees = 0;
1809 return NULL_TREE;
1810 case BUILT_IN_EXPECT:
1811 return NULL_TREE;
1812 default:
1813 break;
1816 /* Our cost must be kept in sync with cgraph_estimate_size_after_inlining
1817 that does use function declaration to figure out the arguments. */
1818 if (!decl)
1820 for (arg = TREE_OPERAND (x, 1); arg; arg = TREE_CHAIN (arg))
1821 *count += estimate_move_cost (TREE_TYPE (TREE_VALUE (arg)));
1823 else
1825 for (arg = DECL_ARGUMENTS (decl); arg; arg = TREE_CHAIN (arg))
1826 *count += estimate_move_cost (TREE_TYPE (arg));
1829 *count += PARAM_VALUE (PARAM_INLINE_CALL_COST);
1830 break;
1832 default:
1833 gcc_unreachable ();
1835 return NULL;
1838 /* Estimate number of instructions that will be created by expanding EXPR. */
1841 estimate_num_insns (tree expr)
1843 int num = 0;
1844 struct pointer_set_t *visited_nodes;
1845 basic_block bb;
1846 block_stmt_iterator bsi;
1847 struct function *my_function;
1849 /* If we're given an entire function, walk the CFG. */
1850 if (TREE_CODE (expr) == FUNCTION_DECL)
1852 my_function = DECL_STRUCT_FUNCTION (expr);
1853 gcc_assert (my_function && my_function->cfg);
1854 visited_nodes = pointer_set_create ();
1855 FOR_EACH_BB_FN (bb, my_function)
1857 for (bsi = bsi_start (bb);
1858 !bsi_end_p (bsi);
1859 bsi_next (&bsi))
1861 walk_tree (bsi_stmt_ptr (bsi), estimate_num_insns_1,
1862 &num, visited_nodes);
1865 pointer_set_destroy (visited_nodes);
1867 else
1868 walk_tree_without_duplicates (&expr, estimate_num_insns_1, &num);
1870 return num;
1873 typedef struct function *function_p;
1875 DEF_VEC_P(function_p);
1876 DEF_VEC_ALLOC_P(function_p,heap);
1878 /* Initialized with NOGC, making this poisonous to the garbage collector. */
1879 static VEC(function_p,heap) *cfun_stack;
1881 void
1882 push_cfun (struct function *new_cfun)
1884 VEC_safe_push (function_p, heap, cfun_stack, cfun);
1885 cfun = new_cfun;
1888 void
1889 pop_cfun (void)
1891 cfun = VEC_pop (function_p, cfun_stack);
1894 /* Install new lexical TREE_BLOCK underneath 'current_block'. */
1895 static void
1896 add_lexical_block (tree current_block, tree new_block)
1898 tree *blk_p;
1900 /* Walk to the last sub-block. */
1901 for (blk_p = &BLOCK_SUBBLOCKS (current_block);
1902 *blk_p;
1903 blk_p = &TREE_CHAIN (*blk_p))
1905 *blk_p = new_block;
1906 BLOCK_SUPERCONTEXT (new_block) = current_block;
1909 /* If *TP is a CALL_EXPR, replace it with its inline expansion. */
1911 static bool
1912 expand_call_inline (basic_block bb, tree stmt, tree *tp, void *data)
1914 inline_data *id;
1915 tree t;
1916 tree use_retvar;
1917 tree fn;
1918 splay_tree st;
1919 tree args;
1920 tree return_slot_addr;
1921 tree modify_dest;
1922 location_t saved_location;
1923 struct cgraph_edge *cg_edge;
1924 const char *reason;
1925 basic_block return_block;
1926 edge e;
1927 block_stmt_iterator bsi, stmt_bsi;
1928 bool successfully_inlined = FALSE;
1929 tree t_step;
1930 tree var;
1931 struct cgraph_node *old_node;
1932 tree decl;
1934 /* See what we've got. */
1935 id = (inline_data *) data;
1936 t = *tp;
1938 /* Set input_location here so we get the right instantiation context
1939 if we call instantiate_decl from inlinable_function_p. */
1940 saved_location = input_location;
1941 if (EXPR_HAS_LOCATION (t))
1942 input_location = EXPR_LOCATION (t);
1944 /* From here on, we're only interested in CALL_EXPRs. */
1945 if (TREE_CODE (t) != CALL_EXPR)
1946 goto egress;
1948 /* First, see if we can figure out what function is being called.
1949 If we cannot, then there is no hope of inlining the function. */
1950 fn = get_callee_fndecl (t);
1951 if (!fn)
1952 goto egress;
1954 /* Turn forward declarations into real ones. */
1955 fn = cgraph_node (fn)->decl;
1957 /* If fn is a declaration of a function in a nested scope that was
1958 globally declared inline, we don't set its DECL_INITIAL.
1959 However, we can't blindly follow DECL_ABSTRACT_ORIGIN because the
1960 C++ front-end uses it for cdtors to refer to their internal
1961 declarations, that are not real functions. Fortunately those
1962 don't have trees to be saved, so we can tell by checking their
1963 DECL_SAVED_TREE. */
1964 if (! DECL_INITIAL (fn)
1965 && DECL_ABSTRACT_ORIGIN (fn)
1966 && DECL_SAVED_TREE (DECL_ABSTRACT_ORIGIN (fn)))
1967 fn = DECL_ABSTRACT_ORIGIN (fn);
1969 /* Objective C and fortran still calls tree_rest_of_compilation directly.
1970 Kill this check once this is fixed. */
1971 if (!id->current_node->analyzed)
1972 goto egress;
1974 cg_edge = cgraph_edge (id->current_node, stmt);
1976 /* Constant propagation on argument done during previous inlining
1977 may create new direct call. Produce an edge for it. */
1978 if (!cg_edge)
1980 struct cgraph_node *dest = cgraph_node (fn);
1982 /* We have missing edge in the callgraph. This can happen in one case
1983 where previous inlining turned indirect call into direct call by
1984 constant propagating arguments. In all other cases we hit a bug
1985 (incorrect node sharing is most common reason for missing edges. */
1986 gcc_assert (dest->needed || !flag_unit_at_a_time);
1987 cgraph_create_edge (id->node, dest, stmt,
1988 bb->count, bb->loop_depth)->inline_failed
1989 = N_("originally indirect function call not considered for inlining");
1990 goto egress;
1993 /* Don't try to inline functions that are not well-suited to
1994 inlining. */
1995 if (!cgraph_inline_p (cg_edge, &reason))
1997 if (lookup_attribute ("always_inline", DECL_ATTRIBUTES (fn))
1998 /* Avoid warnings during early inline pass. */
1999 && (!flag_unit_at_a_time || cgraph_global_info_ready))
2001 sorry ("inlining failed in call to %q+F: %s", fn, reason);
2002 sorry ("called from here");
2004 else if (warn_inline && DECL_DECLARED_INLINE_P (fn)
2005 && !DECL_IN_SYSTEM_HEADER (fn)
2006 && strlen (reason)
2007 && !lookup_attribute ("noinline", DECL_ATTRIBUTES (fn))
2008 /* Avoid warnings during early inline pass. */
2009 && (!flag_unit_at_a_time || cgraph_global_info_ready))
2011 warning (OPT_Winline, "inlining failed in call to %q+F: %s",
2012 fn, reason);
2013 warning (OPT_Winline, "called from here");
2015 goto egress;
2018 #ifdef ENABLE_CHECKING
2019 if (cg_edge->callee->decl != id->node->decl)
2020 verify_cgraph_node (cg_edge->callee);
2021 #endif
2023 /* We will be inlining this callee. */
2025 id->eh_region = lookup_stmt_eh_region (stmt);
2027 /* Split the block holding the CALL_EXPR. */
2029 e = split_block (bb, stmt);
2030 bb = e->src;
2031 return_block = e->dest;
2032 remove_edge (e);
2034 /* split_block splits before the statement, work around this by moving
2035 the call into the first half_bb. Not pretty, but seems easier than
2036 doing the CFG manipulation by hand when the CALL_EXPR is in the last
2037 statement in BB. */
2038 stmt_bsi = bsi_last (bb);
2039 bsi = bsi_start (return_block);
2040 if (!bsi_end_p (bsi))
2041 bsi_move_before (&stmt_bsi, &bsi);
2042 else
2044 tree stmt = bsi_stmt (stmt_bsi);
2045 bsi_remove (&stmt_bsi);
2046 bsi_insert_after (&bsi, stmt, BSI_NEW_STMT);
2048 stmt_bsi = bsi_start (return_block);
2050 /* Build a block containing code to initialize the arguments, the
2051 actual inline expansion of the body, and a label for the return
2052 statements within the function to jump to. The type of the
2053 statement expression is the return type of the function call. */
2054 id->block = make_node (BLOCK);
2055 BLOCK_ABSTRACT_ORIGIN (id->block) = fn;
2056 BLOCK_SOURCE_LOCATION (id->block) = input_location;
2057 add_lexical_block (TREE_BLOCK (stmt), id->block);
2059 /* Local declarations will be replaced by their equivalents in this
2060 map. */
2061 st = id->decl_map;
2062 id->decl_map = splay_tree_new (splay_tree_compare_pointers,
2063 NULL, NULL);
2065 /* Initialize the parameters. */
2066 args = TREE_OPERAND (t, 1);
2068 initialize_inlined_parameters (id, args, TREE_OPERAND (t, 2), fn, bb);
2070 /* Record the function we are about to inline. */
2071 id->callee = fn;
2073 if (DECL_STRUCT_FUNCTION (fn)->saved_blocks)
2074 add_lexical_block (id->block, remap_blocks (DECL_STRUCT_FUNCTION (fn)->saved_blocks, id));
2075 else if (DECL_INITIAL (fn))
2076 add_lexical_block (id->block, remap_blocks (DECL_INITIAL (fn), id));
2078 /* Return statements in the function body will be replaced by jumps
2079 to the RET_LABEL. */
2081 gcc_assert (DECL_INITIAL (fn));
2082 gcc_assert (TREE_CODE (DECL_INITIAL (fn)) == BLOCK);
2084 /* Find the lhs to which the result of this call is assigned. */
2085 return_slot_addr = NULL;
2086 if (TREE_CODE (stmt) == MODIFY_EXPR)
2088 modify_dest = TREE_OPERAND (stmt, 0);
2090 /* The function which we are inlining might not return a value,
2091 in which case we should issue a warning that the function
2092 does not return a value. In that case the optimizers will
2093 see that the variable to which the value is assigned was not
2094 initialized. We do not want to issue a warning about that
2095 uninitialized variable. */
2096 if (DECL_P (modify_dest))
2097 TREE_NO_WARNING (modify_dest) = 1;
2098 if (CALL_EXPR_RETURN_SLOT_OPT (t))
2100 return_slot_addr = build_fold_addr_expr (modify_dest);
2101 modify_dest = NULL;
2104 else
2105 modify_dest = NULL;
2107 /* Declare the return variable for the function. */
2108 decl = declare_return_variable (id, return_slot_addr,
2109 modify_dest, &use_retvar);
2110 /* Do this only if declare_return_variable created a new one. */
2111 if (decl && !return_slot_addr && decl != modify_dest)
2112 declare_inline_vars (id->block, decl);
2114 /* After we've initialized the parameters, we insert the body of the
2115 function itself. */
2116 old_node = id->current_node;
2118 /* Anoint the callee-to-be-duplicated as the "current_node." When
2119 CALL_EXPRs within callee are duplicated, the edges from callee to
2120 callee's callees (caller's grandchildren) will be cloned. */
2121 id->current_node = cg_edge->callee;
2123 /* This is it. Duplicate the callee body. Assume callee is
2124 pre-gimplified. Note that we must not alter the caller
2125 function in any way before this point, as this CALL_EXPR may be
2126 a self-referential call; if we're calling ourselves, we need to
2127 duplicate our body before altering anything. */
2128 copy_body (id, bb->count, bb->frequency, bb, return_block);
2129 id->current_node = old_node;
2131 /* Add local vars in this inlined callee to caller. */
2132 t_step = id->callee_cfun->unexpanded_var_list;
2133 if (id->callee_cfun->saved_unexpanded_var_list)
2134 t_step = id->callee_cfun->saved_unexpanded_var_list;
2135 for (; t_step; t_step = TREE_CHAIN (t_step))
2137 var = TREE_VALUE (t_step);
2138 if (TREE_STATIC (var) && !TREE_ASM_WRITTEN (var))
2139 cfun->unexpanded_var_list = tree_cons (NULL_TREE, var,
2140 cfun->unexpanded_var_list);
2141 else
2142 cfun->unexpanded_var_list = tree_cons (NULL_TREE, remap_decl (var, id),
2143 cfun->unexpanded_var_list);
2146 /* Clean up. */
2147 splay_tree_delete (id->decl_map);
2148 id->decl_map = st;
2150 /* If the inlined function returns a result that we care about,
2151 clobber the CALL_EXPR with a reference to the return variable. */
2152 if (use_retvar && (TREE_CODE (bsi_stmt (stmt_bsi)) != CALL_EXPR))
2154 *tp = use_retvar;
2155 maybe_clean_or_replace_eh_stmt (stmt, stmt);
2157 else
2158 /* We're modifying a TSI owned by gimple_expand_calls_inline();
2159 tsi_delink() will leave the iterator in a sane state. */
2160 bsi_remove (&stmt_bsi);
2162 bsi_next (&bsi);
2163 if (bsi_end_p (bsi))
2164 tree_purge_dead_eh_edges (return_block);
2166 /* If the value of the new expression is ignored, that's OK. We
2167 don't warn about this for CALL_EXPRs, so we shouldn't warn about
2168 the equivalent inlined version either. */
2169 TREE_USED (*tp) = 1;
2171 /* Output the inlining info for this abstract function, since it has been
2172 inlined. If we don't do this now, we can lose the information about the
2173 variables in the function when the blocks get blown away as soon as we
2174 remove the cgraph node. */
2175 (*debug_hooks->outlining_inline_function) (cg_edge->callee->decl);
2177 /* Update callgraph if needed. */
2178 cgraph_remove_node (cg_edge->callee);
2180 /* Declare the 'auto' variables added with this inlined body. */
2181 record_vars (BLOCK_VARS (id->block));
2182 id->block = NULL_TREE;
2183 successfully_inlined = TRUE;
2185 egress:
2186 input_location = saved_location;
2187 return successfully_inlined;
2190 /* Expand call statements reachable from STMT_P.
2191 We can only have CALL_EXPRs as the "toplevel" tree code or nested
2192 in a MODIFY_EXPR. See tree-gimple.c:get_call_expr_in(). We can
2193 unfortunately not use that function here because we need a pointer
2194 to the CALL_EXPR, not the tree itself. */
2196 static bool
2197 gimple_expand_calls_inline (basic_block bb, inline_data *id)
2199 block_stmt_iterator bsi;
2201 /* Register specific tree functions. */
2202 tree_register_cfg_hooks ();
2203 for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi))
2205 tree *expr_p = bsi_stmt_ptr (bsi);
2206 tree stmt = *expr_p;
2208 if (TREE_CODE (*expr_p) == MODIFY_EXPR)
2209 expr_p = &TREE_OPERAND (*expr_p, 1);
2210 if (TREE_CODE (*expr_p) == WITH_SIZE_EXPR)
2211 expr_p = &TREE_OPERAND (*expr_p, 0);
2212 if (TREE_CODE (*expr_p) == CALL_EXPR)
2213 if (expand_call_inline (bb, stmt, expr_p, id))
2214 return true;
2216 return false;
2219 /* Expand calls to inline functions in the body of FN. */
2221 void
2222 optimize_inline_calls (tree fn)
2224 inline_data id;
2225 tree prev_fn;
2226 basic_block bb;
2227 /* There is no point in performing inlining if errors have already
2228 occurred -- and we might crash if we try to inline invalid
2229 code. */
2230 if (errorcount || sorrycount)
2231 return;
2233 /* Clear out ID. */
2234 memset (&id, 0, sizeof (id));
2236 id.current_node = id.node = cgraph_node (fn);
2237 id.caller = fn;
2238 /* Or any functions that aren't finished yet. */
2239 prev_fn = NULL_TREE;
2240 if (current_function_decl)
2242 id.caller = current_function_decl;
2243 prev_fn = current_function_decl;
2245 push_gimplify_context ();
2247 /* Reach the trees by walking over the CFG, and note the
2248 enclosing basic-blocks in the call edges. */
2249 /* We walk the blocks going forward, because inlined function bodies
2250 will split id->current_basic_block, and the new blocks will
2251 follow it; we'll trudge through them, processing their CALL_EXPRs
2252 along the way. */
2253 FOR_EACH_BB (bb)
2254 gimple_expand_calls_inline (bb, &id);
2257 pop_gimplify_context (NULL);
2258 /* Renumber the (code) basic_blocks consecutively. */
2259 compact_blocks ();
2260 /* Renumber the lexical scoping (non-code) blocks consecutively. */
2261 number_blocks (fn);
2263 #ifdef ENABLE_CHECKING
2265 struct cgraph_edge *e;
2267 verify_cgraph_node (id.node);
2269 /* Double check that we inlined everything we are supposed to inline. */
2270 for (e = id.node->callees; e; e = e->next_callee)
2271 gcc_assert (e->inline_failed);
2273 #endif
2274 /* We need to rescale frequencies again to peak at REG_BR_PROB_BASE
2275 as inlining loops might increase the maximum. */
2276 if (ENTRY_BLOCK_PTR->count)
2277 counts_to_freqs ();
2278 fold_cond_expr_cond ();
2281 /* FN is a function that has a complete body, and CLONE is a function whose
2282 body is to be set to a copy of FN, mapping argument declarations according
2283 to the ARG_MAP splay_tree. */
2285 void
2286 clone_body (tree clone, tree fn, void *arg_map)
2288 inline_data id;
2290 /* Clone the body, as if we were making an inline call. But, remap the
2291 parameters in the callee to the parameters of caller. */
2292 memset (&id, 0, sizeof (id));
2293 id.caller = clone;
2294 id.callee = fn;
2295 id.callee_cfun = DECL_STRUCT_FUNCTION (fn);
2296 id.decl_map = (splay_tree)arg_map;
2298 /* Cloning is treated slightly differently from inlining. Set
2299 CLONING_P so that it's clear which operation we're performing. */
2300 id.cloning_p = true;
2302 /* We're not inside any EH region. */
2303 id.eh_region = -1;
2305 /* Actually copy the body. */
2306 append_to_statement_list_force (copy_generic_body (&id), &DECL_SAVED_TREE (clone));
2309 /* Save duplicate body in FN. MAP is used to pass around splay tree
2310 used to update arguments in restore_body. */
2312 /* Make and return duplicate of body in FN. Put copies of DECL_ARGUMENTS
2313 in *arg_copy and of the static chain, if any, in *sc_copy. */
2315 void
2316 save_body (tree fn, tree *arg_copy, tree *sc_copy)
2318 inline_data id;
2319 tree newdecl, *parg;
2320 basic_block fn_entry_block;
2321 tree t_step;
2323 memset (&id, 0, sizeof (id));
2324 id.callee = fn;
2325 id.callee_cfun = DECL_STRUCT_FUNCTION (fn);
2326 id.caller = fn;
2327 id.node = cgraph_node (fn);
2328 id.saving_p = true;
2329 id.decl_map = splay_tree_new (splay_tree_compare_pointers, NULL, NULL);
2330 *arg_copy = DECL_ARGUMENTS (fn);
2332 for (parg = arg_copy; *parg; parg = &TREE_CHAIN (*parg))
2334 tree new = copy_node (*parg);
2336 lang_hooks.dup_lang_specific_decl (new);
2337 DECL_ABSTRACT_ORIGIN (new) = DECL_ORIGIN (*parg);
2338 insert_decl_map (&id, *parg, new);
2339 TREE_CHAIN (new) = TREE_CHAIN (*parg);
2340 *parg = new;
2343 *sc_copy = DECL_STRUCT_FUNCTION (fn)->static_chain_decl;
2344 if (*sc_copy)
2346 tree new = copy_node (*sc_copy);
2348 lang_hooks.dup_lang_specific_decl (new);
2349 DECL_ABSTRACT_ORIGIN (new) = DECL_ORIGIN (*sc_copy);
2350 insert_decl_map (&id, *sc_copy, new);
2351 TREE_CHAIN (new) = TREE_CHAIN (*sc_copy);
2352 *sc_copy = new;
2355 /* We're not inside any EH region. */
2356 id.eh_region = -1;
2358 insert_decl_map (&id, DECL_RESULT (fn), DECL_RESULT (fn));
2360 DECL_STRUCT_FUNCTION (fn)->saved_blocks
2361 = remap_blocks (DECL_INITIAL (fn), &id);
2362 for (t_step = id.callee_cfun->unexpanded_var_list;
2363 t_step;
2364 t_step = TREE_CHAIN (t_step))
2366 tree var = TREE_VALUE (t_step);
2367 if (TREE_STATIC (var) && !TREE_ASM_WRITTEN (var))
2368 cfun->saved_unexpanded_var_list
2369 = tree_cons (NULL_TREE, var, cfun->saved_unexpanded_var_list);
2370 else
2371 cfun->saved_unexpanded_var_list
2372 = tree_cons (NULL_TREE, remap_decl (var, &id),
2373 cfun->saved_unexpanded_var_list);
2376 /* Actually copy the body, including a new (struct function *) and CFG.
2377 EH info is also duplicated so its labels point into the copied
2378 CFG, not the original. */
2379 fn_entry_block = ENTRY_BLOCK_PTR_FOR_FUNCTION (DECL_STRUCT_FUNCTION (fn));
2380 newdecl = copy_body (&id, fn_entry_block->count, fn_entry_block->frequency,
2381 NULL, NULL);
2382 DECL_STRUCT_FUNCTION (fn)->saved_cfg = DECL_STRUCT_FUNCTION (newdecl)->cfg;
2383 DECL_STRUCT_FUNCTION (fn)->saved_eh = DECL_STRUCT_FUNCTION (newdecl)->eh;
2385 /* Clean up. */
2386 splay_tree_delete (id.decl_map);
2389 /* Passed to walk_tree. Copies the node pointed to, if appropriate. */
2391 tree
2392 copy_tree_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
2394 enum tree_code code = TREE_CODE (*tp);
2395 inline_data *id = (inline_data *) data;
2397 /* We make copies of most nodes. */
2398 if (IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (code))
2399 || code == TREE_LIST
2400 || code == TREE_VEC
2401 || code == TYPE_DECL)
2403 /* Because the chain gets clobbered when we make a copy, we save it
2404 here. */
2405 tree chain = TREE_CHAIN (*tp);
2406 tree new;
2408 if (id && id->versioning_p && replace_ref_tree (id, tp))
2410 *walk_subtrees = 0;
2411 return NULL_TREE;
2413 /* Copy the node. */
2414 new = copy_node (*tp);
2416 /* Propagate mudflap marked-ness. */
2417 if (flag_mudflap && mf_marked_p (*tp))
2418 mf_mark (new);
2420 *tp = new;
2422 /* Now, restore the chain, if appropriate. That will cause
2423 walk_tree to walk into the chain as well. */
2424 if (code == PARM_DECL || code == TREE_LIST)
2425 TREE_CHAIN (*tp) = chain;
2427 /* For now, we don't update BLOCKs when we make copies. So, we
2428 have to nullify all BIND_EXPRs. */
2429 if (TREE_CODE (*tp) == BIND_EXPR)
2430 BIND_EXPR_BLOCK (*tp) = NULL_TREE;
2432 else if (code == CONSTRUCTOR)
2434 /* CONSTRUCTOR nodes need special handling because
2435 we need to duplicate the vector of elements. */
2436 tree new;
2438 new = copy_node (*tp);
2440 /* Propagate mudflap marked-ness. */
2441 if (flag_mudflap && mf_marked_p (*tp))
2442 mf_mark (new);
2444 CONSTRUCTOR_ELTS (new) = VEC_copy (constructor_elt, gc,
2445 CONSTRUCTOR_ELTS (*tp));
2446 *tp = new;
2448 else if (TREE_CODE_CLASS (code) == tcc_type)
2449 *walk_subtrees = 0;
2450 else if (TREE_CODE_CLASS (code) == tcc_declaration)
2451 *walk_subtrees = 0;
2452 else if (TREE_CODE_CLASS (code) == tcc_constant)
2453 *walk_subtrees = 0;
2454 else
2455 gcc_assert (code != STATEMENT_LIST);
2456 return NULL_TREE;
2459 /* The SAVE_EXPR pointed to by TP is being copied. If ST contains
2460 information indicating to what new SAVE_EXPR this one should be mapped,
2461 use that one. Otherwise, create a new node and enter it in ST. FN is
2462 the function into which the copy will be placed. */
2464 static void
2465 remap_save_expr (tree *tp, void *st_, int *walk_subtrees)
2467 splay_tree st = (splay_tree) st_;
2468 splay_tree_node n;
2469 tree t;
2471 /* See if we already encountered this SAVE_EXPR. */
2472 n = splay_tree_lookup (st, (splay_tree_key) *tp);
2474 /* If we didn't already remap this SAVE_EXPR, do so now. */
2475 if (!n)
2477 t = copy_node (*tp);
2479 /* Remember this SAVE_EXPR. */
2480 splay_tree_insert (st, (splay_tree_key) *tp, (splay_tree_value) t);
2481 /* Make sure we don't remap an already-remapped SAVE_EXPR. */
2482 splay_tree_insert (st, (splay_tree_key) t, (splay_tree_value) t);
2484 else
2486 /* We've already walked into this SAVE_EXPR; don't do it again. */
2487 *walk_subtrees = 0;
2488 t = (tree) n->value;
2491 /* Replace this SAVE_EXPR with the copy. */
2492 *tp = t;
2495 /* Called via walk_tree. If *TP points to a DECL_STMT for a local label,
2496 copies the declaration and enters it in the splay_tree in DATA (which is
2497 really an `inline_data *'). */
2499 static tree
2500 mark_local_for_remap_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
2501 void *data)
2503 inline_data *id = (inline_data *) data;
2505 /* Don't walk into types. */
2506 if (TYPE_P (*tp))
2507 *walk_subtrees = 0;
2509 else if (TREE_CODE (*tp) == LABEL_EXPR)
2511 tree decl = TREE_OPERAND (*tp, 0);
2513 /* Copy the decl and remember the copy. */
2514 insert_decl_map (id, decl,
2515 copy_decl_for_dup (decl, DECL_CONTEXT (decl),
2516 DECL_CONTEXT (decl), /*versioning=*/false));
2519 return NULL_TREE;
2522 /* Perform any modifications to EXPR required when it is unsaved. Does
2523 not recurse into EXPR's subtrees. */
2525 static void
2526 unsave_expr_1 (tree expr)
2528 switch (TREE_CODE (expr))
2530 case TARGET_EXPR:
2531 /* Don't mess with a TARGET_EXPR that hasn't been expanded.
2532 It's OK for this to happen if it was part of a subtree that
2533 isn't immediately expanded, such as operand 2 of another
2534 TARGET_EXPR. */
2535 if (TREE_OPERAND (expr, 1))
2536 break;
2538 TREE_OPERAND (expr, 1) = TREE_OPERAND (expr, 3);
2539 TREE_OPERAND (expr, 3) = NULL_TREE;
2540 break;
2542 default:
2543 break;
2547 /* Called via walk_tree when an expression is unsaved. Using the
2548 splay_tree pointed to by ST (which is really a `splay_tree'),
2549 remaps all local declarations to appropriate replacements. */
2551 static tree
2552 unsave_r (tree *tp, int *walk_subtrees, void *data)
2554 inline_data *id = (inline_data *) data;
2555 splay_tree st = id->decl_map;
2556 splay_tree_node n;
2558 /* Only a local declaration (variable or label). */
2559 if ((TREE_CODE (*tp) == VAR_DECL && !TREE_STATIC (*tp))
2560 || TREE_CODE (*tp) == LABEL_DECL)
2562 /* Lookup the declaration. */
2563 n = splay_tree_lookup (st, (splay_tree_key) *tp);
2565 /* If it's there, remap it. */
2566 if (n)
2567 *tp = (tree) n->value;
2570 else if (TREE_CODE (*tp) == STATEMENT_LIST)
2571 copy_statement_list (tp);
2572 else if (TREE_CODE (*tp) == BIND_EXPR)
2573 copy_bind_expr (tp, walk_subtrees, id);
2574 else if (TREE_CODE (*tp) == SAVE_EXPR)
2575 remap_save_expr (tp, st, walk_subtrees);
2576 else
2578 copy_tree_r (tp, walk_subtrees, NULL);
2580 /* Do whatever unsaving is required. */
2581 unsave_expr_1 (*tp);
2584 /* Keep iterating. */
2585 return NULL_TREE;
2588 /* Copies everything in EXPR and replaces variables, labels
2589 and SAVE_EXPRs local to EXPR. */
2591 tree
2592 unsave_expr_now (tree expr)
2594 inline_data id;
2596 /* There's nothing to do for NULL_TREE. */
2597 if (expr == 0)
2598 return expr;
2600 /* Set up ID. */
2601 memset (&id, 0, sizeof (id));
2602 id.callee = current_function_decl;
2603 id.caller = current_function_decl;
2604 id.decl_map = splay_tree_new (splay_tree_compare_pointers, NULL, NULL);
2606 /* Walk the tree once to find local labels. */
2607 walk_tree_without_duplicates (&expr, mark_local_for_remap_r, &id);
2609 /* Walk the tree again, copying, remapping, and unsaving. */
2610 walk_tree (&expr, unsave_r, &id, NULL);
2612 /* Clean up. */
2613 splay_tree_delete (id.decl_map);
2615 return expr;
2618 /* Allow someone to determine if SEARCH is a child of TOP from gdb. */
2620 static tree
2621 debug_find_tree_1 (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED, void *data)
2623 if (*tp == data)
2624 return (tree) data;
2625 else
2626 return NULL;
2629 bool
2630 debug_find_tree (tree top, tree search)
2632 return walk_tree_without_duplicates (&top, debug_find_tree_1, search) != 0;
2636 /* Declare the variables created by the inliner. Add all the variables in
2637 VARS to BIND_EXPR. */
2639 static void
2640 declare_inline_vars (tree block, tree vars)
2642 tree t;
2643 for (t = vars; t; t = TREE_CHAIN (t))
2644 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
2646 if (block)
2647 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), vars);
2651 /* Copy NODE (which must be a DECL). The DECL originally was in the FROM_FN,
2652 but now it will be in the TO_FN. VERSIONING means that this function
2653 is used by the versioning utility (not inlining or cloning). */
2655 tree
2656 copy_decl_for_dup (tree decl, tree from_fn, tree to_fn, bool versioning)
2658 tree copy;
2660 gcc_assert (DECL_P (decl));
2661 /* Copy the declaration. */
2662 if (!versioning
2663 && (TREE_CODE (decl) == PARM_DECL
2664 || TREE_CODE (decl) == RESULT_DECL))
2666 tree type = TREE_TYPE (decl);
2668 /* For a parameter or result, we must make an equivalent VAR_DECL,
2669 not a new PARM_DECL. */
2670 copy = build_decl (VAR_DECL, DECL_NAME (decl), type);
2671 TREE_ADDRESSABLE (copy) = TREE_ADDRESSABLE (decl);
2672 TREE_READONLY (copy) = TREE_READONLY (decl);
2673 TREE_THIS_VOLATILE (copy) = TREE_THIS_VOLATILE (decl);
2674 DECL_COMPLEX_GIMPLE_REG_P (copy) = DECL_COMPLEX_GIMPLE_REG_P (decl);
2676 else
2678 copy = copy_node (decl);
2679 /* The COPY is not abstract; it will be generated in TO_FN. */
2680 DECL_ABSTRACT (copy) = 0;
2681 lang_hooks.dup_lang_specific_decl (copy);
2683 /* TREE_ADDRESSABLE isn't used to indicate that a label's
2684 address has been taken; it's for internal bookkeeping in
2685 expand_goto_internal. */
2686 if (TREE_CODE (copy) == LABEL_DECL)
2688 TREE_ADDRESSABLE (copy) = 0;
2689 LABEL_DECL_UID (copy) = -1;
2693 /* Don't generate debug information for the copy if we wouldn't have
2694 generated it for the copy either. */
2695 DECL_ARTIFICIAL (copy) = DECL_ARTIFICIAL (decl);
2696 DECL_IGNORED_P (copy) = DECL_IGNORED_P (decl);
2698 /* Set the DECL_ABSTRACT_ORIGIN so the debugging routines know what
2699 declaration inspired this copy. */
2700 DECL_ABSTRACT_ORIGIN (copy) = DECL_ORIGIN (decl);
2702 /* The new variable/label has no RTL, yet. */
2703 if (CODE_CONTAINS_STRUCT (TREE_CODE (copy), TS_DECL_WRTL)
2704 && !TREE_STATIC (copy) && !DECL_EXTERNAL (copy))
2705 SET_DECL_RTL (copy, NULL_RTX);
2707 /* These args would always appear unused, if not for this. */
2708 TREE_USED (copy) = 1;
2710 /* Set the context for the new declaration. */
2711 if (!DECL_CONTEXT (decl))
2712 /* Globals stay global. */
2714 else if (DECL_CONTEXT (decl) != from_fn)
2715 /* Things that weren't in the scope of the function we're inlining
2716 from aren't in the scope we're inlining to, either. */
2718 else if (TREE_STATIC (decl))
2719 /* Function-scoped static variables should stay in the original
2720 function. */
2722 else
2723 /* Ordinary automatic local variables are now in the scope of the
2724 new function. */
2725 DECL_CONTEXT (copy) = to_fn;
2727 return copy;
2730 /* Return a copy of the function's argument tree. */
2731 static tree
2732 copy_arguments_for_versioning (tree orig_parm, inline_data * id)
2734 tree *arg_copy, *parg;
2736 arg_copy = &orig_parm;
2737 for (parg = arg_copy; *parg; parg = &TREE_CHAIN (*parg))
2739 tree new = remap_decl (*parg, id);
2740 lang_hooks.dup_lang_specific_decl (new);
2741 TREE_CHAIN (new) = TREE_CHAIN (*parg);
2742 *parg = new;
2744 return orig_parm;
2747 /* Return a copy of the function's static chain. */
2748 static tree
2749 copy_static_chain (tree static_chain, inline_data * id)
2751 tree *chain_copy, *pvar;
2753 chain_copy = &static_chain;
2754 for (pvar = chain_copy; *pvar; pvar = &TREE_CHAIN (*pvar))
2756 tree new = remap_decl (*pvar, id);
2757 lang_hooks.dup_lang_specific_decl (new);
2758 TREE_CHAIN (new) = TREE_CHAIN (*pvar);
2759 *pvar = new;
2761 return static_chain;
2764 /* Return true if the function is allowed to be versioned.
2765 This is a guard for the versioning functionality. */
2766 bool
2767 tree_versionable_function_p (tree fndecl)
2769 if (fndecl == NULL_TREE)
2770 return false;
2771 /* ??? There are cases where a function is
2772 uninlinable but can be versioned. */
2773 if (!tree_inlinable_function_p (fndecl))
2774 return false;
2776 return true;
2779 /* Create a copy of a function's tree.
2780 OLD_DECL and NEW_DECL are FUNCTION_DECL tree nodes
2781 of the original function and the new copied function
2782 respectively. In case we want to replace a DECL
2783 tree with another tree while duplicating the function's
2784 body, TREE_MAP represents the mapping between these
2785 trees. */
2786 void
2787 tree_function_versioning (tree old_decl, tree new_decl, varray_type tree_map)
2789 struct cgraph_node *old_version_node;
2790 struct cgraph_node *new_version_node;
2791 inline_data id;
2792 tree p, new_fndecl;
2793 unsigned i;
2794 struct ipa_replace_map *replace_info;
2795 basic_block old_entry_block;
2796 tree t_step;
2798 gcc_assert (TREE_CODE (old_decl) == FUNCTION_DECL
2799 && TREE_CODE (new_decl) == FUNCTION_DECL);
2800 DECL_POSSIBLY_INLINED (old_decl) = 1;
2802 old_version_node = cgraph_node (old_decl);
2803 new_version_node = cgraph_node (new_decl);
2805 allocate_struct_function (new_decl);
2806 /* Cfun points to the new allocated function struct at this point. */
2807 cfun->function_end_locus = DECL_SOURCE_LOCATION (new_decl);
2809 DECL_ARTIFICIAL (new_decl) = 1;
2810 DECL_ABSTRACT_ORIGIN (new_decl) = DECL_ORIGIN (old_decl);
2812 /* Generate a new name for the new version. */
2813 DECL_NAME (new_decl) =
2814 create_tmp_var_name (NULL);
2815 /* Create a new SYMBOL_REF rtx for the new name. */
2816 if (DECL_RTL (old_decl) != NULL)
2818 SET_DECL_RTL (new_decl, copy_rtx (DECL_RTL (old_decl)));
2819 XEXP (DECL_RTL (new_decl), 0) =
2820 gen_rtx_SYMBOL_REF (GET_MODE (XEXP (DECL_RTL (old_decl), 0)),
2821 IDENTIFIER_POINTER (DECL_NAME (new_decl)));
2824 /* Prepare the data structures for the tree copy. */
2825 memset (&id, 0, sizeof (id));
2827 /* The new version. */
2828 id.node = new_version_node;
2830 /* The old version. */
2831 id.current_node = cgraph_node (old_decl);
2833 id.versioning_p = true;
2834 id.decl_map = splay_tree_new (splay_tree_compare_pointers, NULL, NULL);
2835 id.caller = new_decl;
2836 id.callee = old_decl;
2837 id.callee_cfun = DECL_STRUCT_FUNCTION (old_decl);
2839 current_function_decl = new_decl;
2841 /* Copy the function's static chain. */
2842 p = DECL_STRUCT_FUNCTION (old_decl)->static_chain_decl;
2843 if (p)
2844 DECL_STRUCT_FUNCTION (new_decl)->static_chain_decl =
2845 copy_static_chain (DECL_STRUCT_FUNCTION (old_decl)->static_chain_decl,
2846 &id);
2847 /* Copy the function's arguments. */
2848 if (DECL_ARGUMENTS (old_decl) != NULL_TREE)
2849 DECL_ARGUMENTS (new_decl) =
2850 copy_arguments_for_versioning (DECL_ARGUMENTS (old_decl), &id);
2852 /* If there's a tree_map, prepare for substitution. */
2853 if (tree_map)
2854 for (i = 0; i < VARRAY_ACTIVE_SIZE (tree_map); i++)
2856 replace_info = VARRAY_GENERIC_PTR (tree_map, i);
2857 if (replace_info->replace_p && !replace_info->ref_p)
2858 insert_decl_map (&id, replace_info->old_tree,
2859 replace_info->new_tree);
2860 else if (replace_info->replace_p && replace_info->ref_p)
2861 id.ipa_info = tree_map;
2864 DECL_INITIAL (new_decl) = remap_blocks (DECL_INITIAL (id.callee), &id);
2866 /* Renumber the lexical scoping (non-code) blocks consecutively. */
2867 number_blocks (id.caller);
2869 if (DECL_STRUCT_FUNCTION (old_decl)->unexpanded_var_list != NULL_TREE)
2870 /* Add local vars. */
2871 for (t_step = DECL_STRUCT_FUNCTION (old_decl)->unexpanded_var_list;
2872 t_step; t_step = TREE_CHAIN (t_step))
2874 tree var = TREE_VALUE (t_step);
2875 if (TREE_STATIC (var) && !TREE_ASM_WRITTEN (var))
2876 cfun->unexpanded_var_list = tree_cons (NULL_TREE, var,
2877 cfun->unexpanded_var_list);
2878 else
2879 cfun->unexpanded_var_list =
2880 tree_cons (NULL_TREE, remap_decl (var, &id),
2881 cfun->unexpanded_var_list);
2884 /* Copy the Function's body. */
2885 old_entry_block = ENTRY_BLOCK_PTR_FOR_FUNCTION
2886 (DECL_STRUCT_FUNCTION (old_decl));
2887 new_fndecl = copy_body (&id,
2888 old_entry_block->count,
2889 old_entry_block->frequency, NULL, NULL);
2891 DECL_SAVED_TREE (new_decl) = DECL_SAVED_TREE (new_fndecl);
2893 DECL_STRUCT_FUNCTION (new_decl)->cfg =
2894 DECL_STRUCT_FUNCTION (new_fndecl)->cfg;
2895 DECL_STRUCT_FUNCTION (new_decl)->eh = DECL_STRUCT_FUNCTION (new_fndecl)->eh;
2896 DECL_STRUCT_FUNCTION (new_decl)->ib_boundaries_block =
2897 DECL_STRUCT_FUNCTION (new_fndecl)->ib_boundaries_block;
2898 DECL_STRUCT_FUNCTION (new_decl)->last_label_uid =
2899 DECL_STRUCT_FUNCTION (new_fndecl)->last_label_uid;
2901 if (DECL_RESULT (old_decl) != NULL_TREE)
2903 tree *res_decl = &DECL_RESULT (old_decl);
2904 DECL_RESULT (new_decl) = remap_decl (*res_decl, &id);
2905 lang_hooks.dup_lang_specific_decl (DECL_RESULT (new_decl));
2908 current_function_decl = NULL;
2909 /* Renumber the lexical scoping (non-code) blocks consecutively. */
2910 number_blocks (new_decl);
2912 /* Clean up. */
2913 splay_tree_delete (id.decl_map);
2914 fold_cond_expr_cond ();
2915 return;
2918 /* Replace an INDIRECT_REF tree of a given DECL tree with a new
2919 given tree.
2920 ID->ipa_info keeps the old tree and the new tree.
2921 TP points to the INDIRECT REF tree. Return true if
2922 the trees were replaced. */
2923 static bool
2924 replace_ref_tree (inline_data * id, tree * tp)
2926 bool replaced = false;
2927 tree new;
2929 if (id->ipa_info && VARRAY_ACTIVE_SIZE (id->ipa_info) > 0)
2931 unsigned i;
2933 for (i = 0; i < VARRAY_ACTIVE_SIZE (id->ipa_info); i++)
2935 struct ipa_replace_map *replace_info;
2936 replace_info = VARRAY_GENERIC_PTR (id->ipa_info, i);
2938 if (replace_info->replace_p && replace_info->ref_p)
2940 tree old_tree = replace_info->old_tree;
2941 tree new_tree = replace_info->new_tree;
2943 if (TREE_CODE (*tp) == INDIRECT_REF
2944 && TREE_OPERAND (*tp, 0) == old_tree)
2946 new = copy_node (new_tree);
2947 *tp = new;
2948 replaced = true;
2953 return replaced;
2956 /* Return true if we are inlining. */
2957 static inline bool
2958 inlining_p (inline_data * id)
2960 return (!id->saving_p && !id->cloning_p && !id->versioning_p);