issue a debug output when inlining
[libfirm] / ir / opt / opt_inline.c
1 /*
2  * Copyright (C) 1995-2008 University of Karlsruhe.  All right reserved.
3  *
4  * This file is part of libFirm.
5  *
6  * This file may be distributed and/or modified under the terms of the
7  * GNU General Public License version 2 as published by the Free Software
8  * Foundation and appearing in the file LICENSE.GPL included in the
9  * packaging of this file.
10  *
11  * Licensees holding valid libFirm Professional Edition licenses may use
12  * this file in accordance with the libFirm Commercial License.
13  * Agreement provided with the Software.
14  *
15  * This file is provided AS IS with NO WARRANTY OF ANY KIND, INCLUDING THE
16  * WARRANTY OF DESIGN, MERCHANTABILITY AND FITNESS FOR A PARTICULAR
17  * PURPOSE.
18  */
19
20 /**
21  * @file
22  * @brief    Dead node elimination and Procedure Inlining.
23  * @author   Michael Beck, Goetz Lindenmaier
24  * @version  $Id$
25  */
26 #ifdef HAVE_CONFIG_H
27 # include "config.h"
28 #endif
29
30 #include <limits.h>
31 #include <assert.h>
32
33 #include "irnode_t.h"
34 #include "irgraph_t.h"
35 #include "irprog_t.h"
36
37 #include "iroptimize.h"
38 #include "ircons_t.h"
39 #include "iropt_t.h"
40 #include "irgopt.h"
41 #include "irgmod.h"
42 #include "irgwalk.h"
43
44 #include "adt/array.h"
45 #include "adt/pset.h"
46 #include "adt/pmap.h"
47 #include "adt/pdeq.h"
48 #include "adt/xmalloc.h"
49
50 #include "irouts.h"
51 #include "irloop_t.h"
52 #include "irbackedge_t.h"
53 #include "opt_inline_t.h"
54 #include "cgana.h"
55 #include "trouts.h"
56 #include "error.h"
57
58 #include "analyze_irg_args.h"
59 #include "iredges_t.h"
60 #include "irflag_t.h"
61 #include "irhooks.h"
62 #include "irtools.h"
63
64 DEBUG_ONLY(static firm_dbg_module_t *dbg;)
65
66 /*------------------------------------------------------------------*/
67 /* Routines for dead node elimination / copying garbage collection  */
68 /* of the obstack.                                                  */
69 /*------------------------------------------------------------------*/
70
71 /**
72  * Remember the new node in the old node by using a field all nodes have.
73  */
74 #define set_new_node(oldn, newn)  set_irn_link(oldn, newn)
75
76 /**
77  * Get this new node, before the old node is forgotten.
78  */
79 #define get_new_node(oldn) get_irn_link(oldn)
80
81 /**
82  * Check if a new node was set.
83  */
84 #define has_new_node(n) (get_new_node(n) != NULL)
85
86 /**
87  * We use the block_visited flag to mark that we have computed the
88  * number of useful predecessors for this block.
89  * Further we encode the new arity in this flag in the old blocks.
90  * Remembering the arity is useful, as it saves a lot of pointer
91  * accesses.  This function is called for all Phi and Block nodes
92  * in a Block.
93  */
94 static INLINE int
95 compute_new_arity(ir_node *b) {
96         int i, res, irn_arity;
97         int irg_v, block_v;
98
99         irg_v = get_irg_block_visited(current_ir_graph);
100         block_v = get_Block_block_visited(b);
101         if (block_v >= irg_v) {
102                 /* we computed the number of preds for this block and saved it in the
103                    block_v flag */
104                 return block_v - irg_v;
105         } else {
106                 /* compute the number of good predecessors */
107                 res = irn_arity = get_irn_arity(b);
108                 for (i = 0; i < irn_arity; i++)
109                         if (is_Bad(get_irn_n(b, i))) res--;
110                         /* save it in the flag. */
111                         set_Block_block_visited(b, irg_v + res);
112                         return res;
113         }
114 }
115
116 /**
117  * Copies the node to the new obstack. The Ins of the new node point to
118  * the predecessors on the old obstack.  For block/phi nodes not all
119  * predecessors might be copied.  n->link points to the new node.
120  * For Phi and Block nodes the function allocates in-arrays with an arity
121  * only for useful predecessors.  The arity is determined by counting
122  * the non-bad predecessors of the block.
123  *
124  * @param n    The node to be copied
125  * @param env  if non-NULL, the node number attribute will be copied to the new node
126  *
127  * Note: Also used for loop unrolling.
128  */
129 static void copy_node(ir_node *n, void *env) {
130         ir_node *nn, *block;
131         int new_arity;
132         ir_op *op = get_irn_op(n);
133         (void) env;
134
135         if (op == op_Bad) {
136                 /* node copied already */
137                 return;
138         } else if (op == op_Block) {
139                 block = NULL;
140                 new_arity = compute_new_arity(n);
141                 n->attr.block.graph_arr = NULL;
142         } else {
143                 block = get_nodes_block(n);
144                 if (op == op_Phi) {
145                         new_arity = compute_new_arity(block);
146                 } else {
147                         new_arity = get_irn_arity(n);
148                 }
149         }
150         nn = new_ir_node(get_irn_dbg_info(n),
151                 current_ir_graph,
152                 block,
153                 op,
154                 get_irn_mode(n),
155                 new_arity,
156                 get_irn_in(n) + 1);
157         /* Copy the attributes.  These might point to additional data.  If this
158            was allocated on the old obstack the pointers now are dangling.  This
159            frees e.g. the memory of the graph_arr allocated in new_immBlock. */
160         if (op == op_Block) {
161                 /* we cannot allow blocks WITHOUT macroblock input */
162                 set_Block_MacroBlock(nn, get_Block_MacroBlock(n));
163         }
164         copy_node_attr(n, nn);
165
166 #ifdef DEBUG_libfirm
167         {
168                 int copy_node_nr = env != NULL;
169                 if (copy_node_nr) {
170                         /* for easier debugging, we want to copy the node numbers too */
171                         nn->node_nr = n->node_nr;
172                 }
173         }
174 #endif
175
176         set_new_node(n, nn);
177         hook_dead_node_elim_subst(current_ir_graph, n, nn);
178 }
179
180 /**
181  * Copies new predecessors of old node to new node remembered in link.
182  * Spare the Bad predecessors of Phi and Block nodes.
183  */
184 static void copy_preds(ir_node *n, void *env) {
185         ir_node *nn, *block;
186         int i, j, irn_arity;
187         (void) env;
188
189         nn = get_new_node(n);
190
191         if (is_Block(n)) {
192                 /* copy the macro block header */
193                 ir_node *mbh = get_Block_MacroBlock(n);
194
195                 if (mbh == n) {
196                         /* this block is a macroblock header */
197                         set_Block_MacroBlock(nn, nn);
198                 } else {
199                         /* get the macro block header */
200                         ir_node *nmbh = get_new_node(mbh);
201                         assert(nmbh != NULL);
202                         set_Block_MacroBlock(nn, nmbh);
203                 }
204
205                 /* Don't copy Bad nodes. */
206                 j = 0;
207                 irn_arity = get_irn_arity(n);
208                 for (i = 0; i < irn_arity; i++) {
209                         if (! is_Bad(get_irn_n(n, i))) {
210                                 ir_node *pred = get_irn_n(n, i);
211                                 set_irn_n(nn, j, get_new_node(pred));
212                                 j++;
213                         }
214                 }
215                 /* repair the block visited flag from above misuse. Repair it in both
216                    graphs so that the old one can still be used. */
217                 set_Block_block_visited(nn, 0);
218                 set_Block_block_visited(n, 0);
219                 /* Local optimization could not merge two subsequent blocks if
220                    in array contained Bads.  Now it's possible.
221                    We don't call optimize_in_place as it requires
222                    that the fields in ir_graph are set properly. */
223                 if ((get_opt_control_flow_straightening()) &&
224                         (get_Block_n_cfgpreds(nn) == 1) &&
225                         is_Jmp(get_Block_cfgpred(nn, 0))) {
226                         ir_node *old = get_nodes_block(get_Block_cfgpred(nn, 0));
227                         if (nn == old) {
228                                 /* Jmp jumps into the block it is in -- deal self cycle. */
229                                 assert(is_Bad(get_new_node(get_irg_bad(current_ir_graph))));
230                                 exchange(nn, get_new_node(get_irg_bad(current_ir_graph)));
231                         } else {
232                                 exchange(nn, old);
233                         }
234                 }
235         } else if (is_Phi(n) && get_irn_arity(n) > 0) {
236                 /* Don't copy node if corresponding predecessor in block is Bad.
237                    The Block itself should not be Bad. */
238                 block = get_nodes_block(n);
239                 set_nodes_block(nn, get_new_node(block));
240                 j = 0;
241                 irn_arity = get_irn_arity(n);
242                 for (i = 0; i < irn_arity; i++) {
243                         if (! is_Bad(get_irn_n(block, i))) {
244                                 ir_node *pred = get_irn_n(n, i);
245                                 set_irn_n(nn, j, get_new_node(pred));
246                                 /*if (is_backedge(n, i)) set_backedge(nn, j);*/
247                                 j++;
248                         }
249                 }
250                 /* If the pre walker reached this Phi after the post walker visited the
251                    block block_visited is > 0. */
252                 set_Block_block_visited(get_nodes_block(n), 0);
253                 /* Compacting the Phi's ins might generate Phis with only one
254                    predecessor. */
255                 if (get_irn_arity(nn) == 1)
256                         exchange(nn, get_irn_n(nn, 0));
257         } else {
258                 irn_arity = get_irn_arity(n);
259                 for (i = -1; i < irn_arity; i++)
260                         set_irn_n(nn, i, get_new_node(get_irn_n(n, i)));
261         }
262         /* Now the new node is complete.  We can add it to the hash table for CSE.
263            @@@ inlining aborts if we identify End. Why? */
264         if (!is_End(nn))
265                 add_identities(current_ir_graph->value_table, nn);
266 }
267
268 /**
269  * Copies the graph recursively, compacts the keep-alives of the end node.
270  *
271  * @param irg           the graph to be copied
272  * @param copy_node_nr  If non-zero, the node number will be copied
273  */
274 static void copy_graph(ir_graph *irg, int copy_node_nr) {
275         ir_node *oe, *ne, *ob, *nb, *om, *nm; /* old end, new end, old bad, new bad, old NoMem, new NoMem */
276         ir_node *ka;      /* keep alive */
277         int i, irn_arity;
278         unsigned long vfl;
279
280         /* Some nodes must be copied by hand, sigh */
281         vfl = get_irg_visited(irg);
282         set_irg_visited(irg, vfl + 1);
283
284         oe = get_irg_end(irg);
285         mark_irn_visited(oe);
286         /* copy the end node by hand, allocate dynamic in array! */
287         ne = new_ir_node(get_irn_dbg_info(oe),
288                 irg,
289                 NULL,
290                 op_End,
291                 mode_X,
292                 -1,
293                 NULL);
294         /* Copy the attributes.  Well, there might be some in the future... */
295         copy_node_attr(oe, ne);
296         set_new_node(oe, ne);
297
298         /* copy the Bad node */
299         ob = get_irg_bad(irg);
300         mark_irn_visited(ob);
301         nb = new_ir_node(get_irn_dbg_info(ob),
302                 irg,
303                 NULL,
304                 op_Bad,
305                 mode_T,
306                 0,
307                 NULL);
308         copy_node_attr(ob, nb);
309         set_new_node(ob, nb);
310
311         /* copy the NoMem node */
312         om = get_irg_no_mem(irg);
313         mark_irn_visited(om);
314         nm = new_ir_node(get_irn_dbg_info(om),
315                 irg,
316                 NULL,
317                 op_NoMem,
318                 mode_M,
319                 0,
320                 NULL);
321         copy_node_attr(om, nm);
322         set_new_node(om, nm);
323
324         /* copy the live nodes */
325         set_irg_visited(irg, vfl);
326         irg_walk(get_nodes_block(oe), copy_node, copy_preds, INT_TO_PTR(copy_node_nr));
327
328         /* Note: from yet, the visited flag of the graph is equal to vfl + 1 */
329
330         /* visit the anchors as well */
331         for (i = get_irg_n_anchors(irg) - 1; i >= 0; --i) {
332                 ir_node *n = get_irg_anchor(irg, i);
333
334                 if (n && (get_irn_visited(n) <= vfl)) {
335                         set_irg_visited(irg, vfl);
336                         irg_walk(n, copy_node, copy_preds, INT_TO_PTR(copy_node_nr));
337                 }
338         }
339
340         /* copy_preds for the end node ... */
341         set_nodes_block(ne, get_new_node(get_nodes_block(oe)));
342
343         /*- ... and now the keep alives. -*/
344         /* First pick the not marked block nodes and walk them.  We must pick these
345            first as else we will oversee blocks reachable from Phis. */
346         irn_arity = get_End_n_keepalives(oe);
347         for (i = 0; i < irn_arity; i++) {
348                 ka = get_End_keepalive(oe, i);
349                 if (is_Block(ka)) {
350                         if (get_irn_visited(ka) <= vfl) {
351                                 /* We must keep the block alive and copy everything reachable */
352                                 set_irg_visited(irg, vfl);
353                                 irg_walk(ka, copy_node, copy_preds, INT_TO_PTR(copy_node_nr));
354                         }
355                         add_End_keepalive(ne, get_new_node(ka));
356                 }
357         }
358
359         /* Now pick other nodes.  Here we will keep all! */
360         irn_arity = get_End_n_keepalives(oe);
361         for (i = 0; i < irn_arity; i++) {
362                 ka = get_End_keepalive(oe, i);
363                 if (!is_Block(ka)) {
364                         if (get_irn_visited(ka) <= vfl) {
365                                 /* We didn't copy the node yet.  */
366                                 set_irg_visited(irg, vfl);
367                                 irg_walk(ka, copy_node, copy_preds, INT_TO_PTR(copy_node_nr));
368                         }
369                         add_End_keepalive(ne, get_new_node(ka));
370                 }
371         }
372
373         /* start block sometimes only reached after keep alives */
374         set_nodes_block(nb, get_new_node(get_nodes_block(ob)));
375         set_nodes_block(nm, get_new_node(get_nodes_block(om)));
376 }
377
378 /**
379  * Copies the graph reachable from current_ir_graph->end to the obstack
380  * in current_ir_graph and fixes the environment.
381  * Then fixes the fields in current_ir_graph containing nodes of the
382  * graph.
383  *
384  * @param copy_node_nr  If non-zero, the node number will be copied
385  */
386 static void
387 copy_graph_env(int copy_node_nr) {
388         ir_graph *irg = current_ir_graph;
389         ir_node *old_end, *new_anchor;
390         int i;
391
392         /* remove end_except and end_reg nodes */
393         old_end = get_irg_end(irg);
394         set_irg_end_except (irg, old_end);
395         set_irg_end_reg    (irg, old_end);
396
397         /* Not all nodes remembered in irg might be reachable
398            from the end node.  Assure their link is set to NULL, so that
399            we can test whether new nodes have been computed. */
400         for (i = get_irg_n_anchors(irg) - 1; i >= 0; --i) {
401                 ir_node *n = get_irg_anchor(irg, i);
402                 if (n != NULL)
403                         set_new_node(n, NULL);
404         }
405         /* we use the block walk flag for removing Bads from Blocks ins. */
406         inc_irg_block_visited(irg);
407
408         /* copy the graph */
409         copy_graph(irg, copy_node_nr);
410
411         /* fix the anchor */
412         old_end    = get_irg_end(irg);
413         new_anchor = new_Anchor(irg);
414
415         for (i = get_irg_n_anchors(irg) - 1; i >= 0; --i) {
416                 ir_node *n = get_irg_anchor(irg, i);
417                 if (n)
418                         set_irn_n(new_anchor, i, get_new_node(n));
419         }
420         free_End(old_end);
421         irg->anchor = new_anchor;
422
423         /* ensure the new anchor is placed in the endblock */
424         set_nodes_block(new_anchor, get_irg_end_block(irg));
425 }
426
427 /**
428  * Copies all reachable nodes to a new obstack.  Removes bad inputs
429  * from block nodes and the corresponding inputs from Phi nodes.
430  * Merges single exit blocks with single entry blocks and removes
431  * 1-input Phis.
432  * Adds all new nodes to a new hash table for CSE.  Does not
433  * perform CSE, so the hash table might contain common subexpressions.
434  */
435 void dead_node_elimination(ir_graph *irg) {
436         ir_graph *rem;
437 #ifdef INTERPROCEDURAL_VIEW
438         int rem_ipview = get_interprocedural_view();
439 #endif
440         struct obstack *graveyard_obst = NULL;
441         struct obstack *rebirth_obst   = NULL;
442         assert(! edges_activated(irg) && "dead node elimination requires disabled edges");
443
444         /* inform statistics that we started a dead-node elimination run */
445         hook_dead_node_elim(irg, 1);
446
447         /* Remember external state of current_ir_graph. */
448         rem = current_ir_graph;
449         current_ir_graph = irg;
450 #ifdef INTERPROCEDURAL_VIEW
451         set_interprocedural_view(0);
452 #endif
453
454         assert(get_irg_phase_state(irg) != phase_building);
455
456         /* Handle graph state */
457         free_callee_info(irg);
458         free_irg_outs(irg);
459         free_trouts();
460
461         /* @@@ so far we loose loops when copying */
462         free_loop_information(irg);
463
464         set_irg_doms_inconsistent(irg);
465
466         /* A quiet place, where the old obstack can rest in peace,
467            until it will be cremated. */
468         graveyard_obst = irg->obst;
469
470         /* A new obstack, where the reachable nodes will be copied to. */
471         rebirth_obst = xmalloc(sizeof(*rebirth_obst));
472         irg->obst = rebirth_obst;
473         obstack_init(irg->obst);
474         irg->last_node_idx = 0;
475
476         /* We also need a new value table for CSE */
477         del_identities(irg->value_table);
478         irg->value_table = new_identities();
479
480         /* Copy the graph from the old to the new obstack */
481         copy_graph_env(/*copy_node_nr=*/1);
482
483         /* Free memory from old unoptimized obstack */
484         obstack_free(graveyard_obst, 0);  /* First empty the obstack ... */
485         xfree(graveyard_obst);            /* ... then free it.           */
486
487         /* inform statistics that the run is over */
488         hook_dead_node_elim(irg, 0);
489
490         current_ir_graph = rem;
491 #ifdef INTERPROCEDURAL_VIEW
492         set_interprocedural_view(rem_ipview);
493 #endif
494 }
495
496 /**
497  * Relink bad predecessors of a block and store the old in array to the
498  * link field. This function is called by relink_bad_predecessors().
499  * The array of link field starts with the block operand at position 0.
500  * If block has bad predecessors, create a new in array without bad preds.
501  * Otherwise let in array untouched.
502  */
503 static void relink_bad_block_predecessors(ir_node *n, void *env) {
504         ir_node **new_in, *irn;
505         int i, new_irn_n, old_irn_arity, new_irn_arity = 0;
506         (void) env;
507
508         /* if link field of block is NULL, look for bad predecessors otherwise
509            this is already done */
510         if (is_Block(n) && get_irn_link(n) == NULL) {
511                 /* save old predecessors in link field (position 0 is the block operand)*/
512                 set_irn_link(n, get_irn_in(n));
513
514                 /* count predecessors without bad nodes */
515                 old_irn_arity = get_irn_arity(n);
516                 for (i = 0; i < old_irn_arity; i++)
517                         if (!is_Bad(get_irn_n(n, i)))
518                                 ++new_irn_arity;
519
520                 /* arity changing: set new predecessors without bad nodes */
521                 if (new_irn_arity < old_irn_arity) {
522                         /* Get new predecessor array. We do not resize the array, as we must
523                            keep the old one to update Phis. */
524                         new_in = NEW_ARR_D(ir_node *, current_ir_graph->obst, (new_irn_arity+1));
525
526                         /* set new predecessors in array */
527                         new_in[0] = NULL;
528                         new_irn_n = 1;
529                         for (i = 0; i < old_irn_arity; i++) {
530                                 irn = get_irn_n(n, i);
531                                 if (!is_Bad(irn)) {
532                                         new_in[new_irn_n] = irn;
533                                         is_backedge(n, i) ? set_backedge(n, new_irn_n-1) : set_not_backedge(n, new_irn_n-1);
534                                         ++new_irn_n;
535                                 }
536                         }
537                         /* ARR_SETLEN(int, n->attr.block.backedge, new_irn_arity); */
538                         ARR_SHRINKLEN(n->attr.block.backedge, new_irn_arity);
539                         n->in = new_in;
540                 } /* ir node has bad predecessors */
541         } /* Block is not relinked */
542 }
543
544 /**
545  * Relinks Bad predecessors from Blocks and Phis called by walker
546  * remove_bad_predecesors(). If n is a Block, call
547  * relink_bad_block_redecessors(). If n is a Phi-node, call also the relinking
548  * function of Phi's Block. If this block has bad predecessors, relink preds
549  * of the Phi-node.
550  */
551 static void relink_bad_predecessors(ir_node *n, void *env) {
552         ir_node *block, **old_in;
553         int i, old_irn_arity, new_irn_arity;
554
555         /* relink bad predecessors of a block */
556         if (is_Block(n))
557                 relink_bad_block_predecessors(n, env);
558
559         /* If Phi node relink its block and its predecessors */
560         if (is_Phi(n)) {
561                 /* Relink predecessors of phi's block */
562                 block = get_nodes_block(n);
563                 if (get_irn_link(block) == NULL)
564                         relink_bad_block_predecessors(block, env);
565
566                 old_in = (ir_node **)get_irn_link(block); /* Of Phi's Block */
567                 old_irn_arity = ARR_LEN(old_in);
568
569                 /* Relink Phi predecessors if count of predecessors changed */
570                 if (old_irn_arity != ARR_LEN(get_irn_in(block))) {
571                         /* set new predecessors in array
572                            n->in[0] remains the same block */
573                         new_irn_arity = 1;
574                         for(i = 1; i < old_irn_arity; i++)
575                                 if (!is_Bad(old_in[i])) {
576                                         n->in[new_irn_arity] = n->in[i];
577                                         is_backedge(n, i) ? set_backedge(n, new_irn_arity) : set_not_backedge(n, new_irn_arity);
578                                         ++new_irn_arity;
579                                 }
580
581                                 ARR_SETLEN(ir_node *, n->in, new_irn_arity);
582                                 ARR_SETLEN(int, n->attr.phi.u.backedge, new_irn_arity);
583                 }
584         } /* n is a Phi node */
585 }
586
587 /*
588  * Removes Bad Bad predecessors from Blocks and the corresponding
589  * inputs to Phi nodes as in dead_node_elimination but without
590  * copying the graph.
591  * On walking up set the link field to NULL, on walking down call
592  * relink_bad_predecessors() (This function stores the old in array
593  * to the link field and sets a new in array if arity of predecessors
594  * changes).
595  */
596 void remove_bad_predecessors(ir_graph *irg) {
597         panic("Fix backedge handling first");
598         irg_walk_graph(irg, firm_clear_link, relink_bad_predecessors, NULL);
599 }
600
601
602 /*
603    __                      _  __ __
604   (_     __    o     _    | \/  |_
605   __)|_| | \_/ | \_/(/_   |_/\__|__
606
607   The following stuff implements a facility that automatically patches
608   registered ir_node pointers to the new node when a dead node elimination occurs.
609 */
610
611 struct _survive_dce_t {
612         struct obstack obst;
613         pmap *places;
614         pmap *new_places;
615         hook_entry_t dead_node_elim;
616         hook_entry_t dead_node_elim_subst;
617 };
618
619 typedef struct _survive_dce_list_t {
620         struct _survive_dce_list_t *next;
621         ir_node **place;
622 } survive_dce_list_t;
623
624 static void dead_node_hook(void *context, ir_graph *irg, int start) {
625         survive_dce_t *sd = context;
626         (void) irg;
627
628         /* Create a new map before the dead node elimination is performed. */
629         if (start) {
630                 sd->new_places = pmap_create_ex(pmap_count(sd->places));
631         } else {
632                 /* Patch back all nodes if dead node elimination is over and something is to be done. */
633                 pmap_destroy(sd->places);
634                 sd->places     = sd->new_places;
635                 sd->new_places = NULL;
636         }
637 }
638
639 /**
640  * Hook called when dead node elimination replaces old by nw.
641  */
642 static void dead_node_subst_hook(void *context, ir_graph *irg, ir_node *old, ir_node *nw) {
643         survive_dce_t *sd = context;
644         survive_dce_list_t *list = pmap_get(sd->places, old);
645         (void) irg;
646
647         /* If the node is to be patched back, write the new address to all registered locations. */
648         if (list) {
649                 survive_dce_list_t *p;
650
651                 for (p = list; p; p = p->next)
652                         *(p->place) = nw;
653
654                 pmap_insert(sd->new_places, nw, list);
655         }
656 }
657
658 /**
659  * Make a new Survive DCE environment.
660  */
661 survive_dce_t *new_survive_dce(void) {
662         survive_dce_t *res = xmalloc(sizeof(res[0]));
663         obstack_init(&res->obst);
664         res->places     = pmap_create();
665         res->new_places = NULL;
666
667         res->dead_node_elim.hook._hook_dead_node_elim = dead_node_hook;
668         res->dead_node_elim.context                   = res;
669         res->dead_node_elim.next                      = NULL;
670
671         res->dead_node_elim_subst.hook._hook_dead_node_elim_subst = dead_node_subst_hook;
672         res->dead_node_elim_subst.context = res;
673         res->dead_node_elim_subst.next    = NULL;
674
675 #ifndef FIRM_ENABLE_HOOKS
676         assert(0 && "need hooks enabled");
677 #endif
678
679         register_hook(hook_dead_node_elim, &res->dead_node_elim);
680         register_hook(hook_dead_node_elim_subst, &res->dead_node_elim_subst);
681         return res;
682 }
683
684 /**
685  * Free a Survive DCE environment.
686  */
687 void free_survive_dce(survive_dce_t *sd) {
688         obstack_free(&sd->obst, NULL);
689         pmap_destroy(sd->places);
690         unregister_hook(hook_dead_node_elim, &sd->dead_node_elim);
691         unregister_hook(hook_dead_node_elim_subst, &sd->dead_node_elim_subst);
692         xfree(sd);
693 }
694
695 /**
696  * Register a node pointer to be patched upon DCE.
697  * When DCE occurs, the node pointer specified by @p place will be
698  * patched to the new address of the node it is pointing to.
699  *
700  * @param sd    The Survive DCE environment.
701  * @param place The address of the node pointer.
702  */
703 void survive_dce_register_irn(survive_dce_t *sd, ir_node **place) {
704         if (*place != NULL) {
705                 ir_node *irn      = *place;
706                 survive_dce_list_t *curr = pmap_get(sd->places, irn);
707                 survive_dce_list_t *nw   = obstack_alloc(&sd->obst, sizeof(nw[0]));
708
709                 nw->next  = curr;
710                 nw->place = place;
711
712                 pmap_insert(sd->places, irn, nw);
713         }
714 }
715
716 /*--------------------------------------------------------------------*/
717 /*  Functionality for inlining                                         */
718 /*--------------------------------------------------------------------*/
719
720 /**
721  * Copy node for inlineing.  Updates attributes that change when
722  * inlineing but not for dead node elimination.
723  *
724  * Copies the node by calling copy_node() and then updates the entity if
725  * it's a local one.  env must be a pointer of the frame type of the
726  * inlined procedure. The new entities must be in the link field of
727  * the entities.
728  */
729 static INLINE void
730 copy_node_inline(ir_node *n, void *env) {
731         ir_node *nn;
732         ir_type *frame_tp = (ir_type *)env;
733
734         copy_node(n, NULL);
735         if (is_Sel(n)) {
736                 nn = get_new_node (n);
737                 assert(is_Sel(nn));
738                 if (get_entity_owner(get_Sel_entity(n)) == frame_tp) {
739                         set_Sel_entity(nn, get_entity_link(get_Sel_entity(n)));
740                 }
741         } else if (is_Block(n)) {
742                 nn = get_new_node (n);
743                 nn->attr.block.irg = current_ir_graph;
744         }
745 }
746
747 /**
748  * Walker: checks if P_value_arg_base is used.
749  */
750 static void find_addr(ir_node *node, void *env) {
751         int *allow_inline = env;
752         if (is_Proj(node) &&
753                         is_Start(get_Proj_pred(node)) &&
754                         get_Proj_proj(node) == pn_Start_P_value_arg_base) {
755                 *allow_inline = 0;
756         }
757 }
758
759 /**
760  * Check if we can inline a given call.
761  * Currently, we cannot inline two cases:
762  * - call with compound arguments
763  * - graphs that take the address of a parameter
764  *
765  * check these conditions here
766  */
767 static int can_inline(ir_node *call, ir_graph *called_graph) {
768         ir_type *call_type = get_Call_type(call);
769         int params, ress, i, res;
770         assert(is_Method_type(call_type));
771
772         params = get_method_n_params(call_type);
773         ress   = get_method_n_ress(call_type);
774
775         /* check parameters for compound arguments */
776         for (i = 0; i < params; ++i) {
777                 ir_type *p_type = get_method_param_type(call_type, i);
778
779                 if (is_compound_type(p_type))
780                         return 0;
781         }
782
783         /* check results for compound arguments */
784         for (i = 0; i < ress; ++i) {
785                 ir_type *r_type = get_method_res_type(call_type, i);
786
787                 if (is_compound_type(r_type))
788                         return 0;
789         }
790
791         res = 1;
792         irg_walk_graph(called_graph, find_addr, NULL, &res);
793
794         return res;
795 }
796
797 enum exc_mode {
798         exc_handler    = 0, /**< There is a handler. */
799         exc_to_end     = 1, /**< Branches to End. */
800         exc_no_handler = 2  /**< Exception handling not represented. */
801 };
802
803 /* Inlines a method at the given call site. */
804 int inline_method(ir_node *call, ir_graph *called_graph) {
805         ir_node *pre_call;
806         ir_node *post_call, *post_bl;
807         ir_node *in[pn_Start_max];
808         ir_node *end, *end_bl;
809         ir_node **res_pred;
810         ir_node **cf_pred;
811         ir_node *ret, *phi;
812         int arity, n_ret, n_exc, n_res, i, n, j, rem_opt, irn_arity;
813         enum exc_mode exc_handling;
814         ir_type *called_frame, *curr_frame;
815         irg_inline_property prop = get_irg_inline_property(called_graph);
816         ir_entity *ent;
817
818         if (prop == irg_inline_forbidden)
819                 return 0;
820
821         ent = get_irg_entity(called_graph);
822
823         /* Do not inline variadic functions. */
824         if (get_method_variadicity(get_entity_type(ent)) == variadicity_variadic)
825                 return 0;
826
827         assert(get_method_n_params(get_entity_type(ent)) ==
828                get_method_n_params(get_Call_type(call)));
829
830         /*
831          * We cannot inline a recursive call. The graph must be copied before
832          * the call the inline_method() using create_irg_copy().
833          */
834         if (called_graph == current_ir_graph)
835                 return 0;
836
837         /*
838          * currently, we cannot inline two cases:
839          * - call with compound arguments
840          * - graphs that take the address of a parameter
841          */
842         if (! can_inline(call, called_graph))
843                 return 0;
844
845         DB((dbg, SET_LEVEL_1, "Inlining %+F(%+F) into %+F\n", call, called_graph, current_ir_graph));
846
847         /* --  Turn off optimizations, this can cause problems when allocating new nodes. -- */
848         rem_opt = get_opt_optimize();
849         set_optimize(0);
850
851         /* Handle graph state */
852         assert(get_irg_phase_state(current_ir_graph) != phase_building);
853         assert(get_irg_pinned(current_ir_graph) == op_pin_state_pinned);
854         assert(get_irg_pinned(called_graph) == op_pin_state_pinned);
855         set_irg_outs_inconsistent(current_ir_graph);
856         set_irg_extblk_inconsistent(current_ir_graph);
857         set_irg_doms_inconsistent(current_ir_graph);
858         set_irg_loopinfo_inconsistent(current_ir_graph);
859         set_irg_callee_info_state(current_ir_graph, irg_callee_info_inconsistent);
860
861         /* -- Check preconditions -- */
862         assert(is_Call(call));
863
864         /* here we know we WILL inline, so inform the statistics */
865         hook_inline(call, called_graph);
866
867         /* -- Decide how to handle exception control flow: Is there a handler
868            for the Call node, or do we branch directly to End on an exception?
869            exc_handling:
870            0 There is a handler.
871            1 Branches to End.
872            2 Exception handling not represented in Firm. -- */
873         {
874                 ir_node *proj, *Mproj = NULL, *Xproj = NULL;
875                 for (proj = get_irn_link(call); proj; proj = get_irn_link(proj)) {
876                         long proj_nr = get_Proj_proj(proj);
877                         if (proj_nr == pn_Call_X_except) Xproj = proj;
878                         if (proj_nr == pn_Call_M_except) Mproj = proj;
879                 }
880                 if      (Mproj) { assert(Xproj); exc_handling = exc_handler; } /*  Mproj           */
881                 else if (Xproj) {                exc_handling = exc_to_end; } /* !Mproj &&  Xproj   */
882                 else            {                exc_handling = exc_no_handler; } /* !Mproj && !Xproj   */
883         }
884
885         /* --
886            the procedure and later replaces the Start node of the called graph.
887            Post_call is the old Call node and collects the results of the called
888            graph. Both will end up being a tuple.  -- */
889         post_bl = get_nodes_block(call);
890         set_irg_current_block(current_ir_graph, post_bl);
891         /* XxMxPxPxPxT of Start + parameter of Call */
892         in[pn_Start_X_initial_exec]   = new_Jmp();
893         in[pn_Start_M]                = get_Call_mem(call);
894         in[pn_Start_P_frame_base]     = get_irg_frame(current_ir_graph);
895         in[pn_Start_P_globals]        = get_irg_globals(current_ir_graph);
896         in[pn_Start_P_tls]            = get_irg_tls(current_ir_graph);
897         in[pn_Start_T_args]           = new_Tuple(get_Call_n_params(call), get_Call_param_arr(call));
898         /* in[pn_Start_P_value_arg_base] = ??? */
899         assert(pn_Start_P_value_arg_base == pn_Start_max - 1 && "pn_Start_P_value_arg_base not supported, fix");
900         pre_call = new_Tuple(pn_Start_max - 1, in);
901         post_call = call;
902
903         /* --
904            The new block gets the ins of the old block, pre_call and all its
905            predecessors and all Phi nodes. -- */
906         part_block(pre_call);
907
908         /* -- Prepare state for dead node elimination -- */
909         /* Visited flags in calling irg must be >= flag in called irg.
910            Else walker and arity computation will not work. */
911         if (get_irg_visited(current_ir_graph) <= get_irg_visited(called_graph))
912                 set_irg_visited(current_ir_graph, get_irg_visited(called_graph)+1);
913         if (get_irg_block_visited(current_ir_graph)< get_irg_block_visited(called_graph))
914                 set_irg_block_visited(current_ir_graph, get_irg_block_visited(called_graph));
915         /* Set pre_call as new Start node in link field of the start node of
916            calling graph and pre_calls block as new block for the start block
917            of calling graph.
918            Further mark these nodes so that they are not visited by the
919            copying. */
920         set_irn_link(get_irg_start(called_graph), pre_call);
921         set_irn_visited(get_irg_start(called_graph), get_irg_visited(current_ir_graph));
922         set_irn_link(get_irg_start_block(called_graph), get_nodes_block(pre_call));
923         set_irn_visited(get_irg_start_block(called_graph), get_irg_visited(current_ir_graph));
924         set_irn_link(get_irg_bad(called_graph), get_irg_bad(current_ir_graph));
925         set_irn_visited(get_irg_bad(called_graph), get_irg_visited(current_ir_graph));
926
927         /* Initialize for compaction of in arrays */
928         inc_irg_block_visited(current_ir_graph);
929
930         /* -- Replicate local entities of the called_graph -- */
931         /* copy the entities. */
932         called_frame = get_irg_frame_type(called_graph);
933         curr_frame   = get_irg_frame_type(current_ir_graph);
934         for (i = 0, n = get_class_n_members(called_frame); i < n; ++i) {
935                 ir_entity *new_ent, *old_ent;
936                 old_ent = get_class_member(called_frame, i);
937                 new_ent = copy_entity_own(old_ent, curr_frame);
938                 set_entity_link(old_ent, new_ent);
939         }
940
941         /* visited is > than that of called graph.  With this trick visited will
942            remain unchanged so that an outer walker, e.g., searching the call nodes
943             to inline, calling this inline will not visit the inlined nodes. */
944         set_irg_visited(current_ir_graph, get_irg_visited(current_ir_graph)-1);
945
946         /* -- Performing dead node elimination inlines the graph -- */
947         /* Copies the nodes to the obstack of current_ir_graph. Updates links to new
948            entities. */
949         irg_walk(get_irg_end(called_graph), copy_node_inline, copy_preds,
950                  get_irg_frame_type(called_graph));
951
952         /* Repair called_graph */
953         set_irg_visited(called_graph, get_irg_visited(current_ir_graph));
954         set_irg_block_visited(called_graph, get_irg_block_visited(current_ir_graph));
955         set_Block_block_visited(get_irg_start_block(called_graph), 0);
956
957         /* -- Merge the end of the inlined procedure with the call site -- */
958         /* We will turn the old Call node into a Tuple with the following
959            predecessors:
960            -1:  Block of Tuple.
961            0: Phi of all Memories of Return statements.
962            1: Jmp from new Block that merges the control flow from all exception
963            predecessors of the old end block.
964            2: Tuple of all arguments.
965            3: Phi of Exception memories.
966            In case the old Call directly branches to End on an exception we don't
967            need the block merging all exceptions nor the Phi of the exception
968            memories.
969         */
970
971         /* -- Precompute some values -- */
972         end_bl = get_new_node(get_irg_end_block(called_graph));
973         end = get_new_node(get_irg_end(called_graph));
974         arity = get_irn_arity(end_bl);    /* arity = n_exc + n_ret  */
975         n_res = get_method_n_ress(get_Call_type(call));
976
977         res_pred = xmalloc(n_res * sizeof(*res_pred));
978         cf_pred  = xmalloc(arity * sizeof(*res_pred));
979
980         set_irg_current_block(current_ir_graph, post_bl); /* just to make sure */
981
982         /* -- archive keepalives -- */
983         irn_arity = get_irn_arity(end);
984         for (i = 0; i < irn_arity; i++) {
985                 ir_node *ka = get_End_keepalive(end, i);
986                 if (! is_Bad(ka))
987                         add_End_keepalive(get_irg_end(current_ir_graph), ka);
988         }
989
990         /* The new end node will die.  We need not free as the in array is on the obstack:
991            copy_node() only generated 'D' arrays. */
992
993         /* -- Replace Return nodes by Jump nodes. -- */
994         n_ret = 0;
995         for (i = 0; i < arity; i++) {
996                 ir_node *ret;
997                 ret = get_irn_n(end_bl, i);
998                 if (is_Return(ret)) {
999                         cf_pred[n_ret] = new_r_Jmp(current_ir_graph, get_nodes_block(ret));
1000                         n_ret++;
1001                 }
1002         }
1003         set_irn_in(post_bl, n_ret, cf_pred);
1004
1005         /* -- Build a Tuple for all results of the method.
1006            Add Phi node if there was more than one Return.  -- */
1007         turn_into_tuple(post_call, pn_Call_max);
1008         /* First the Memory-Phi */
1009         n_ret = 0;
1010         for (i = 0; i < arity; i++) {
1011                 ret = get_irn_n(end_bl, i);
1012                 if (is_Return(ret)) {
1013                         cf_pred[n_ret] = get_Return_mem(ret);
1014                         n_ret++;
1015                 }
1016         }
1017         phi = new_Phi(n_ret, cf_pred, mode_M);
1018         set_Tuple_pred(call, pn_Call_M_regular, phi);
1019         /* Conserve Phi-list for further inlinings -- but might be optimized */
1020         if (get_nodes_block(phi) == post_bl) {
1021                 set_irn_link(phi, get_irn_link(post_bl));
1022                 set_irn_link(post_bl, phi);
1023         }
1024         /* Now the real results */
1025         if (n_res > 0) {
1026                 for (j = 0; j < n_res; j++) {
1027                         n_ret = 0;
1028                         for (i = 0; i < arity; i++) {
1029                                 ret = get_irn_n(end_bl, i);
1030                                 if (is_Return(ret)) {
1031                                         cf_pred[n_ret] = get_Return_res(ret, j);
1032                                         n_ret++;
1033                                 }
1034                         }
1035                         if (n_ret > 0)
1036                                 phi = new_Phi(n_ret, cf_pred, get_irn_mode(cf_pred[0]));
1037                         else
1038                                 phi = new_Bad();
1039                         res_pred[j] = phi;
1040                         /* Conserve Phi-list for further inlinings -- but might be optimized */
1041                         if (get_nodes_block(phi) == post_bl) {
1042                                 set_Phi_next(phi, get_Block_phis(post_bl));
1043                                 set_Block_phis(post_bl, phi);
1044                         }
1045                 }
1046                 set_Tuple_pred(call, pn_Call_T_result, new_Tuple(n_res, res_pred));
1047         } else {
1048                 set_Tuple_pred(call, pn_Call_T_result, new_Bad());
1049         }
1050         /* handle the regular call */
1051         set_Tuple_pred(call, pn_Call_X_regular, new_Jmp());
1052
1053         /* For now, we cannot inline calls with value_base */
1054         set_Tuple_pred(call, pn_Call_P_value_res_base, new_Bad());
1055
1056         /* Finally the exception control flow.
1057            We have two (three) possible situations:
1058            First if the Call branches to an exception handler: We need to add a Phi node to
1059            collect the memory containing the exception objects.  Further we need
1060            to add another block to get a correct representation of this Phi.  To
1061            this block we add a Jmp that resolves into the X output of the Call
1062            when the Call is turned into a tuple.
1063            Second the Call branches to End, the exception is not handled.  Just
1064            add all inlined exception branches to the End node.
1065            Third: there is no Exception edge at all. Handle as case two. */
1066         if (exc_handling == exc_handler) {
1067                 n_exc = 0;
1068                 for (i = 0; i < arity; i++) {
1069                         ir_node *ret, *irn;
1070                         ret = get_irn_n(end_bl, i);
1071                         irn = skip_Proj(ret);
1072                         if (is_fragile_op(irn) || is_Raise(irn)) {
1073                                 cf_pred[n_exc] = ret;
1074                                 ++n_exc;
1075                         }
1076                 }
1077                 if (n_exc > 0) {
1078                         new_Block(n_exc, cf_pred);      /* watch it: current_block is changed! */
1079                         set_Tuple_pred(call, pn_Call_X_except, new_Jmp());
1080                         /* The Phi for the memories with the exception objects */
1081                         n_exc = 0;
1082                         for (i = 0; i < arity; i++) {
1083                                 ir_node *ret;
1084                                 ret = skip_Proj(get_irn_n(end_bl, i));
1085                                 if (is_Call(ret)) {
1086                                         cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 3);
1087                                         n_exc++;
1088                                 } else if (is_fragile_op(ret)) {
1089                                         /* We rely that all cfops have the memory output at the same position. */
1090                                         cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 0);
1091                                         n_exc++;
1092                                 } else if (is_Raise(ret)) {
1093                                         cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 1);
1094                                         n_exc++;
1095                                 }
1096                         }
1097                         set_Tuple_pred(call, pn_Call_M_except, new_Phi(n_exc, cf_pred, mode_M));
1098                 } else {
1099                         set_Tuple_pred(call, pn_Call_X_except, new_Bad());
1100                         set_Tuple_pred(call, pn_Call_M_except, new_Bad());
1101                 }
1102         } else {
1103                 ir_node *main_end_bl;
1104                 int main_end_bl_arity;
1105                 ir_node **end_preds;
1106
1107                 /* assert(exc_handling == 1 || no exceptions. ) */
1108                 n_exc = 0;
1109                 for (i = 0; i < arity; i++) {
1110                         ir_node *ret = get_irn_n(end_bl, i);
1111                         ir_node *irn = skip_Proj(ret);
1112
1113                         if (is_fragile_op(irn) || is_Raise(irn)) {
1114                                 cf_pred[n_exc] = ret;
1115                                 n_exc++;
1116                         }
1117                 }
1118                 main_end_bl = get_irg_end_block(current_ir_graph);
1119                 main_end_bl_arity = get_irn_arity(main_end_bl);
1120                 end_preds =  xmalloc((n_exc + main_end_bl_arity) * sizeof(*end_preds));
1121
1122                 for (i = 0; i < main_end_bl_arity; ++i)
1123                         end_preds[i] = get_irn_n(main_end_bl, i);
1124                 for (i = 0; i < n_exc; ++i)
1125                         end_preds[main_end_bl_arity + i] = cf_pred[i];
1126                 set_irn_in(main_end_bl, n_exc + main_end_bl_arity, end_preds);
1127                 set_Tuple_pred(call, pn_Call_X_except,  new_Bad());
1128                 set_Tuple_pred(call, pn_Call_M_except,  new_Bad());
1129                 free(end_preds);
1130         }
1131         free(res_pred);
1132         free(cf_pred);
1133
1134         /* --  Turn CSE back on. -- */
1135         set_optimize(rem_opt);
1136
1137         return 1;
1138 }
1139
1140 /********************************************************************/
1141 /* Apply inlineing to small methods.                                */
1142 /********************************************************************/
1143
1144 static struct obstack  temp_obst;
1145
1146 /** Represents a possible inlinable call in a graph. */
1147 typedef struct _call_entry call_entry;
1148 struct _call_entry {
1149         ir_node    *call;   /**< the Call */
1150         ir_graph   *callee; /**< the callee called here */
1151         call_entry *next;   /**< for linking the next one */
1152         unsigned   weight;  /**< the weight of the call */
1153 };
1154
1155 /**
1156  * environment for inlining small irgs
1157  */
1158 typedef struct _inline_env_t {
1159         struct obstack obst;  /**< an obstack where call_entries are allocated on. */
1160         call_entry *head;     /**< the head of the call entry list */
1161         call_entry *tail;     /**< the tail of the call entry list */
1162 } inline_env_t;
1163
1164 /**
1165  * Returns the irg called from a Call node. If the irg is not
1166  * known, NULL is returned.
1167  *
1168  * @param call  the call node
1169  */
1170 static ir_graph *get_call_called_irg(ir_node *call) {
1171         ir_node *addr;
1172
1173         addr = get_Call_ptr(call);
1174         if (is_Global(addr)) {
1175                 ir_entity *ent = get_Global_entity(addr);
1176                 return get_entity_irg(ent);
1177         }
1178
1179         return NULL;
1180 }
1181
1182 /**
1183  * Walker: Collect all calls to known graphs inside a graph.
1184  */
1185 static void collect_calls(ir_node *call, void *env) {
1186         if (is_Call(call)) {
1187                 ir_graph *called_irg = get_call_called_irg(call);
1188
1189                 if (called_irg != NULL) {
1190                         /* The Call node calls a locally defined method.  Remember to inline. */
1191                         inline_env_t *ienv  = env;
1192                         call_entry   *entry = obstack_alloc(&ienv->obst, sizeof(*entry));
1193                         entry->call   = call;
1194                         entry->callee = called_irg;
1195                         entry->next   = NULL;
1196                         entry->weight = 0;
1197
1198                         if (ienv->tail == NULL)
1199                                 ienv->head = entry;
1200                         else
1201                                 ienv->tail->next = entry;
1202                         ienv->tail = entry;
1203                 }
1204         }
1205 }
1206
1207 /**
1208  * Inlines all small methods at call sites where the called address comes
1209  * from a Const node that references the entity representing the called
1210  * method.
1211  * The size argument is a rough measure for the code size of the method:
1212  * Methods where the obstack containing the firm graph is smaller than
1213  * size are inlined.
1214  */
1215 void inline_small_irgs(ir_graph *irg, int size) {
1216   ir_graph *rem = current_ir_graph;
1217         inline_env_t env;
1218         call_entry *entry;
1219
1220         current_ir_graph = irg;
1221         /* Handle graph state */
1222         assert(get_irg_phase_state(irg) != phase_building);
1223         free_callee_info(irg);
1224
1225         /* Find Call nodes to inline.
1226            (We can not inline during a walk of the graph, as inlineing the same
1227            method several times changes the visited flag of the walked graph:
1228            after the first inlineing visited of the callee equals visited of
1229            the caller.  With the next inlineing both are increased.) */
1230         obstack_init(&env.obst);
1231         env.head = env.tail = NULL;
1232         irg_walk_graph(irg, NULL, collect_calls, &env);
1233
1234         if (env.head != NULL) {
1235                 int did_inline = 0;
1236
1237                 /* There are calls to inline */
1238                 collect_phiprojs(irg);
1239                 for (entry = env.head; entry != NULL; entry = entry->next) {
1240                         ir_graph *callee = entry->callee;
1241                         if (((_obstack_memory_used(callee->obst) - (int)obstack_room(callee->obst)) < size) ||
1242                             (get_irg_inline_property(callee) >= irg_inline_forced)) {
1243                                 did_inline |= inline_method(entry->call, callee);
1244                         }
1245                 }
1246                 if (did_inline != 0) {
1247                         /* this irg got calls inlined */
1248                         set_irg_outs_inconsistent(irg);
1249                         set_irg_doms_inconsistent(irg);
1250                         set_irg_loopinfo_inconsistent(irg);
1251                 }
1252         }
1253         obstack_free(&env.obst, NULL);
1254         current_ir_graph = rem;
1255 }
1256
1257 /**
1258  * Environment for inlining irgs.
1259  */
1260 typedef struct {
1261         int n_nodes;             /**< Number of nodes in graph except Id, Tuple, Proj, Start, End. */
1262         int n_blocks;            /**< Number of Blocks in graph without Start and End block. */
1263         int n_nodes_orig;        /**< for statistics */
1264         call_entry *call_head;   /**< The head of the list of all call nodes in this graph. */
1265         call_entry *call_tail;   /**< The tail of the list of all call nodes in this graph .*/
1266         int n_call_nodes;        /**< Number of Call nodes in the graph. */
1267         int n_call_nodes_orig;   /**< for statistics */
1268         int n_callers;           /**< Number of known graphs that call this graphs. */
1269         int n_callers_orig;      /**< for statistics */
1270         unsigned got_inline:1;   /**< Set, if at least one call inside this graph was inlined. */
1271         unsigned local_vars:1;   /**< Set, if a inlined function gets the address of an inlined variable. */
1272         unsigned *local_weights; /**< Once allocated, the beneficial weight for transmitting local addresses. */
1273 } inline_irg_env;
1274
1275 /**
1276  * Allocate a new environment for inlining.
1277  */
1278 static inline_irg_env *alloc_inline_irg_env(void) {
1279         inline_irg_env *env    = obstack_alloc(&temp_obst, sizeof(*env));
1280         env->n_nodes           = -2; /* do not count count Start, End */
1281         env->n_blocks          = -2; /* do not count count Start, End Block */
1282         env->n_nodes_orig      = -2; /* do not count Start, End */
1283         env->call_head         = NULL;
1284         env->call_tail         = NULL;
1285         env->n_call_nodes      = 0;
1286         env->n_call_nodes_orig = 0;
1287         env->n_callers         = 0;
1288         env->n_callers_orig    = 0;
1289         env->got_inline        = 0;
1290         env->local_vars        = 0;
1291         env->local_weights     = NULL;
1292         return env;
1293 }
1294
1295 typedef struct walker_env {
1296         inline_irg_env *x;    /**< the inline environment */
1297         char ignore_runtime;  /**< the ignore runtime flag */
1298         char ignore_callers;  /**< if set, do change callers data */
1299 } wenv_t;
1300
1301 /**
1302  * post-walker: collect all calls in the inline-environment
1303  * of a graph and sum some statistics.
1304  */
1305 static void collect_calls2(ir_node *call, void *ctx) {
1306         wenv_t         *env = ctx;
1307         inline_irg_env *x = env->x;
1308         ir_opcode      code = get_irn_opcode(call);
1309         ir_graph       *callee;
1310         call_entry     *entry;
1311
1312         /* count meaningful nodes in irg */
1313         if (code != iro_Proj && code != iro_Tuple && code != iro_Sync) {
1314                 if (code != iro_Block) {
1315                         ++x->n_nodes;
1316                         ++x->n_nodes_orig;
1317                 } else {
1318                         ++x->n_blocks;
1319                 }
1320         }
1321
1322         if (code != iro_Call) return;
1323
1324         /* check, if it's a runtime call */
1325         if (env->ignore_runtime) {
1326                 ir_node *symc = get_Call_ptr(call);
1327
1328                 if (is_Global(symc)) {
1329                         ir_entity *ent = get_Global_entity(symc);
1330
1331                         if (get_entity_additional_properties(ent) & mtp_property_runtime)
1332                                 return;
1333                 }
1334         }
1335
1336         /* collect all call nodes */
1337         ++x->n_call_nodes;
1338         ++x->n_call_nodes_orig;
1339
1340         callee = get_call_called_irg(call);
1341         if (callee != NULL) {
1342                 if (! env->ignore_callers) {
1343                         inline_irg_env *callee_env = get_irg_link(callee);
1344                         /* count all static callers */
1345                         ++callee_env->n_callers;
1346                         ++callee_env->n_callers_orig;
1347                 }
1348
1349                 /* link it in the list of possible inlinable entries */
1350                 entry = obstack_alloc(&temp_obst, sizeof(*entry));
1351                 entry->call   = call;
1352                 entry->callee = callee;
1353                 entry->next   = NULL;
1354                 if (x->call_tail == NULL)
1355                         x->call_head = entry;
1356                 else
1357                         x->call_tail->next = entry;
1358                 x->call_tail = entry;
1359         }
1360 }
1361
1362 /**
1363  * Returns TRUE if the number of callers is 0 in the irg's environment,
1364  * hence this irg is a leave.
1365  */
1366 INLINE static int is_leave(ir_graph *irg) {
1367         inline_irg_env *env = get_irg_link(irg);
1368         return env->n_call_nodes == 0;
1369 }
1370
1371 /**
1372  * Returns TRUE if the number of nodes in the callee is
1373  * smaller then size in the irg's environment.
1374  */
1375 INLINE static int is_smaller(ir_graph *callee, int size) {
1376         inline_irg_env *env = get_irg_link(callee);
1377         return env->n_nodes < size;
1378 }
1379
1380 /**
1381  * Append the nodes of the list src to the nodes of the list in environment dst.
1382  */
1383 static void append_call_list(inline_irg_env *dst, call_entry *src) {
1384         call_entry *entry, *nentry;
1385
1386         /* Note that the src list points to Call nodes in the inlined graph, but
1387            we need Call nodes in our graph. Luckily the inliner leaves this information
1388            in the link field. */
1389         for (entry = src; entry != NULL; entry = entry->next) {
1390                 nentry = obstack_alloc(&temp_obst, sizeof(*nentry));
1391                 nentry->call   = get_irn_link(entry->call);
1392                 nentry->callee = entry->callee;
1393                 nentry->next   = NULL;
1394                 dst->call_tail->next = nentry;
1395                 dst->call_tail       = nentry;
1396         }
1397 }
1398
1399 /*
1400  * Inlines small leave methods at call sites where the called address comes
1401  * from a Const node that references the entity representing the called
1402  * method.
1403  * The size argument is a rough measure for the code size of the method:
1404  * Methods where the obstack containing the firm graph is smaller than
1405  * size are inlined.
1406  */
1407 void inline_leave_functions(int maxsize, int leavesize, int size, int ignore_runtime) {
1408         inline_irg_env   *env;
1409         ir_graph         *irg;
1410         int              i, n_irgs;
1411         ir_graph         *rem;
1412         int              did_inline;
1413         wenv_t           wenv;
1414         call_entry       *entry, *tail;
1415         const call_entry *centry;
1416         pmap             *copied_graphs;
1417         pmap_entry       *pm_entry;
1418
1419         rem = current_ir_graph;
1420         obstack_init(&temp_obst);
1421
1422         /* a map for the copied graphs, used to inline recursive calls */
1423         copied_graphs = pmap_create();
1424
1425         /* extend all irgs by a temporary data structure for inlining. */
1426         n_irgs = get_irp_n_irgs();
1427         for (i = 0; i < n_irgs; ++i)
1428                 set_irg_link(get_irp_irg(i), alloc_inline_irg_env());
1429
1430         /* Precompute information in temporary data structure. */
1431         wenv.ignore_runtime = ignore_runtime;
1432         wenv.ignore_callers = 0;
1433         for (i = 0; i < n_irgs; ++i) {
1434                 ir_graph *irg = get_irp_irg(i);
1435
1436                 assert(get_irg_phase_state(irg) != phase_building);
1437                 free_callee_info(irg);
1438
1439                 wenv.x = get_irg_link(irg);
1440                 irg_walk_graph(irg, NULL, collect_calls2, &wenv);
1441         }
1442
1443         /* -- and now inline. -- */
1444
1445         /* Inline leaves recursively -- we might construct new leaves. */
1446         do {
1447                 did_inline = 0;
1448
1449                 for (i = 0; i < n_irgs; ++i) {
1450                         ir_node *call;
1451                         int phiproj_computed = 0;
1452
1453                         current_ir_graph = get_irp_irg(i);
1454                         env = (inline_irg_env *)get_irg_link(current_ir_graph);
1455
1456                         tail = NULL;
1457                         for (entry = env->call_head; entry != NULL; entry = entry->next) {
1458                                 ir_graph *callee;
1459
1460                                 if (env->n_nodes > maxsize) break;
1461
1462                                 call   = entry->call;
1463                                 callee = entry->callee;
1464
1465                                 if (is_leave(callee) && (
1466                                     is_smaller(callee, leavesize) || (get_irg_inline_property(callee) >= irg_inline_forced))) {
1467                                         if (!phiproj_computed) {
1468                                                 phiproj_computed = 1;
1469                                                 collect_phiprojs(current_ir_graph);
1470                                         }
1471                                         did_inline = inline_method(call, callee);
1472
1473                                         if (did_inline) {
1474                                                 inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1475
1476                                                 /* was inlined, must be recomputed */
1477                                                 phiproj_computed = 0;
1478
1479                                                 /* Do some statistics */
1480                                                 env->got_inline = 1;
1481                                                 --env->n_call_nodes;
1482                                                 env->n_nodes += callee_env->n_nodes;
1483                                                 --callee_env->n_callers;
1484
1485                                                 /* remove this call from the list */
1486                                                 if (tail != NULL)
1487                                                         tail->next = entry->next;
1488                                                 else
1489                                                         env->call_head = entry->next;
1490                                                 continue;
1491                                         }
1492                                 }
1493                                 tail = entry;
1494                         }
1495                         env->call_tail = tail;
1496                 }
1497         } while (did_inline);
1498
1499         /* inline other small functions. */
1500         for (i = 0; i < n_irgs; ++i) {
1501                 ir_node *call;
1502                 int phiproj_computed = 0;
1503
1504                 current_ir_graph = get_irp_irg(i);
1505                 env = (inline_irg_env *)get_irg_link(current_ir_graph);
1506
1507                 /* note that the list of possible calls is updated during the process */
1508                 tail = NULL;
1509                 for (entry = env->call_head; entry != NULL; entry = entry->next) {
1510                         ir_graph   *callee;
1511                         pmap_entry *e;
1512
1513                         call   = entry->call;
1514                         callee = entry->callee;
1515
1516                         e = pmap_find(copied_graphs, callee);
1517                         if (e != NULL) {
1518                                 /*
1519                                  * Remap callee if we have a copy.
1520                                  * FIXME: Should we do this only for recursive Calls ?
1521                                  */
1522                                 callee = e->value;
1523                         }
1524
1525                         if (((is_smaller(callee, size) && (env->n_nodes < maxsize)) ||    /* small function */
1526                                 (get_irg_inline_property(callee) >= irg_inline_forced))) {
1527                                 if (current_ir_graph == callee) {
1528                                         /*
1529                                          * Recursive call: we cannot directly inline because we cannot walk
1530                                          * the graph and change it. So we have to make a copy of the graph
1531                                          * first.
1532                                          */
1533
1534                                         inline_irg_env *callee_env;
1535                                         ir_graph       *copy;
1536
1537                                         /*
1538                                          * No copy yet, create one.
1539                                          * Note that recursive methods are never leaves, so it is sufficient
1540                                          * to test this condition here.
1541                                          */
1542                                         copy = create_irg_copy(callee);
1543
1544                                         /* create_irg_copy() destroys the Proj links, recompute them */
1545                                         phiproj_computed = 0;
1546
1547                                         /* allocate new environment */
1548                                         callee_env = alloc_inline_irg_env();
1549                                         set_irg_link(copy, callee_env);
1550
1551                                         wenv.x              = callee_env;
1552                                         wenv.ignore_callers = 1;
1553                                         irg_walk_graph(copy, NULL, collect_calls2, &wenv);
1554
1555                                         /*
1556                                          * Enter the entity of the original graph. This is needed
1557                                          * for inline_method(). However, note that ent->irg still points
1558                                          * to callee, NOT to copy.
1559                                          */
1560                                         set_irg_entity(copy, get_irg_entity(callee));
1561
1562                                         pmap_insert(copied_graphs, callee, copy);
1563                                         callee = copy;
1564
1565                                         /* we have only one caller: the original graph */
1566                                         callee_env->n_callers      = 1;
1567                                         callee_env->n_callers_orig = 1;
1568                                 }
1569                                 if (! phiproj_computed) {
1570                                         phiproj_computed = 1;
1571                                         collect_phiprojs(current_ir_graph);
1572                                 }
1573                                 did_inline = inline_method(call, callee);
1574                                 if (did_inline) {
1575                                         inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1576
1577                                         /* was inlined, must be recomputed */
1578                                         phiproj_computed = 0;
1579
1580                                         /* callee was inline. Append it's call list. */
1581                                         env->got_inline = 1;
1582                                         --env->n_call_nodes;
1583                                         append_call_list(env, callee_env->call_head);
1584                                         env->n_call_nodes += callee_env->n_call_nodes;
1585                                         env->n_nodes += callee_env->n_nodes;
1586                                         --callee_env->n_callers;
1587
1588                                         /* after we have inlined callee, all called methods inside callee
1589                                            are now called once more */
1590                                         for (centry = callee_env->call_head; centry != NULL; centry = centry->next) {
1591                                                 inline_irg_env *penv = get_irg_link(centry->callee);
1592                                                 ++penv->n_callers;
1593                                         }
1594
1595                                         /* remove this call from the list */
1596                                         if (tail != NULL)
1597                                                 tail->next = entry->next;
1598                                         else
1599                                                 env->call_head = entry->next;
1600                                         continue;
1601                                 }
1602                         }
1603                         tail = entry;
1604                 }
1605                 env->call_tail = tail;
1606         }
1607
1608         for (i = 0; i < n_irgs; ++i) {
1609                 irg = get_irp_irg(i);
1610                 env = (inline_irg_env *)get_irg_link(irg);
1611
1612                 if (env->got_inline) {
1613                         /* this irg got calls inlined */
1614                         set_irg_outs_inconsistent(irg);
1615                         set_irg_doms_inconsistent(irg);
1616                         set_irg_loopinfo_inconsistent(irg);
1617
1618                         optimize_graph_df(irg);
1619                         optimize_cf(irg);
1620                 }
1621                 if (env->got_inline || (env->n_callers_orig != env->n_callers)) {
1622                         DB((dbg, SET_LEVEL_1, "Nodes:%3d ->%3d, calls:%3d ->%3d, callers:%3d ->%3d, -- %s\n",
1623                         env->n_nodes_orig, env->n_nodes, env->n_call_nodes_orig, env->n_call_nodes,
1624                         env->n_callers_orig, env->n_callers,
1625                         get_entity_name(get_irg_entity(irg))));
1626                 }
1627         }
1628
1629         /* kill the copied graphs: we don't need them anymore */
1630         foreach_pmap(copied_graphs, pm_entry) {
1631                 ir_graph *copy = pm_entry->value;
1632
1633                 /* reset the entity, otherwise it will be deleted in the next step ... */
1634                 set_irg_entity(copy, NULL);
1635                 free_ir_graph(copy);
1636         }
1637         pmap_destroy(copied_graphs);
1638
1639         obstack_free(&temp_obst, NULL);
1640         current_ir_graph = rem;
1641 }
1642
1643 /**
1644  * Calculate the parameter weights for transmitting the address of a local variable.
1645  */
1646 static unsigned calc_method_local_weight(ir_node *arg) {
1647         int      i, j, k;
1648         unsigned v, weight = 0;
1649
1650         for (i = get_irn_n_outs(arg) - 1; i >= 0; --i) {
1651                 ir_node *succ = get_irn_out(arg, i);
1652
1653                 switch (get_irn_opcode(succ)) {
1654                 case iro_Load:
1655                 case iro_Store:
1656                         /* Loads and Store can be removed */
1657                         weight += 3;
1658                         break;
1659                 case iro_Sel:
1660                         /* check if all args are constant */
1661                         for (j = get_Sel_n_indexs(succ) - 1; j >= 0; --j) {
1662                                 ir_node *idx = get_Sel_index(succ, j);
1663                                 if (! is_Const(idx))
1664                                         return 0;
1665                         }
1666                         /* Check users on this Sel. Note: if a 0 is returned here, there was
1667                            some unsupported node. */
1668                         v = calc_method_local_weight(succ);
1669                         if (v == 0)
1670                                 return 0;
1671                         /* we can kill one Sel with constant indexes, this is cheap */
1672                         weight += v + 1;
1673                         break;
1674                 case iro_Id:
1675                         /* when looking backward we might find Id nodes */
1676                         weight += calc_method_local_weight(succ);
1677                         break;
1678                 case iro_Tuple:
1679                         /* unoptimized tuple */
1680                         for (j = get_Tuple_n_preds(succ) - 1; j >= 0; --j) {
1681                                 ir_node *pred = get_Tuple_pred(succ, j);
1682                                 if (pred == arg) {
1683                                         /* look for Proj(j) */
1684                                         for (k = get_irn_n_outs(succ) - 1; k >= 0; --k) {
1685                                                 ir_node *succ_succ = get_irn_out(succ, k);
1686                                                 if (is_Proj(succ_succ)) {
1687                                                         if (get_Proj_proj(succ_succ) == j) {
1688                                                                 /* found */
1689                                                                 weight += calc_method_local_weight(succ_succ);
1690                                                         }
1691                                                 } else {
1692                                                         /* this should NOT happen */
1693                                                         return 0;
1694                                                 }
1695                                         }
1696                                 }
1697                         }
1698                 default:
1699                         /* any other node: unsupported yet or bad. */
1700                         return 0;
1701                 }
1702         }
1703         return weight;
1704 }
1705
1706 /**
1707  * Calculate the parameter weights for transmitting the address of a local variable.
1708  */
1709 static void analyze_irg_local_weights(inline_irg_env *env, ir_graph *irg) {
1710         ir_entity *ent = get_irg_entity(irg);
1711         ir_type  *mtp;
1712         int      nparams, i, proj_nr;
1713         ir_node  *irg_args, *arg;
1714
1715         mtp      = get_entity_type(ent);
1716         nparams  = get_method_n_params(mtp);
1717
1718         /* allocate a new array. currently used as 'analysed' flag */
1719         env->local_weights = NEW_ARR_D(unsigned, &temp_obst, nparams);
1720
1721         /* If the method haven't parameters we have nothing to do. */
1722         if (nparams <= 0)
1723                 return;
1724
1725         assure_irg_outs(irg);
1726         irg_args = get_irg_args(irg);
1727         for (i = get_irn_n_outs(irg_args) - 1; i >= 0; --i) {
1728                 arg     = get_irn_out(irg_args, i);
1729                 proj_nr = get_Proj_proj(arg);
1730                 env->local_weights[proj_nr] = calc_method_local_weight(arg);
1731         }
1732 }
1733
1734 /**
1735  * Calculate the benefice for transmitting an local variable address.
1736  * After inlining, the local variable might be transformed into a
1737  * SSA variable by scalar_replacement().
1738  */
1739 static unsigned get_method_local_adress_weight(ir_graph *callee, int pos) {
1740         inline_irg_env *env = get_irg_link(callee);
1741
1742         if (env->local_weights != NULL) {
1743                 if (pos < ARR_LEN(env->local_weights))
1744                         return env->local_weights[pos];
1745                 return 0;
1746         }
1747
1748         analyze_irg_local_weights(env, callee);
1749
1750         if (pos < ARR_LEN(env->local_weights))
1751                 return env->local_weights[pos];
1752         return 0;
1753 }
1754
1755 /**
1756  * calculate a benefice value for inlining the given call.
1757  */
1758 static int calc_inline_benefice(ir_node *call, ir_graph *callee, unsigned *local_adr) {
1759         ir_entity *ent = get_irg_entity(callee);
1760         ir_node   *frame_ptr;
1761         ir_type   *mtp;
1762         int       weight = 0;
1763         int       i, n_params;
1764         unsigned  cc, v;
1765
1766         inline_irg_env *curr_env, *callee_env;
1767
1768         if (get_entity_additional_properties(ent) & mtp_property_noreturn) {
1769                 /* do NOT inline noreturn calls */
1770                 return INT_MIN;
1771         }
1772
1773         /* costs for every passed parameter */
1774         n_params = get_Call_n_params(call);
1775         mtp      = get_entity_type(ent);
1776         cc       = get_method_calling_convention(mtp);
1777         if (cc & cc_reg_param) {
1778                 /* register parameter, smaller costs for register parameters */
1779                 int max_regs = cc & ~cc_bits;
1780
1781                 if (max_regs < n_params)
1782                         weight += max_regs * 2 + (n_params - max_regs) * 5;
1783                 else
1784                         weight += n_params * 2;
1785         } else {
1786                 /* parameters are passed an stack */
1787                 weight += 5 * n_params;
1788         }
1789
1790         /* constant parameters improve the benefice */
1791         frame_ptr = get_irg_frame(current_ir_graph);
1792         for (i = 0; i < n_params; ++i) {
1793                 ir_node *param = get_Call_param(call, i);
1794
1795                 if (is_Const(param) || is_SymConst(param))
1796                         weight += get_method_param_weight(ent, i);
1797                 else if (is_Sel(param) && get_Sel_ptr(param) == frame_ptr) {
1798                         /*
1799                          * An address of a local variable is transmitted. After inlining,
1800                          * scalar_replacement might be able to remove the local variable,
1801                          * so honor this.
1802                          */
1803                         v = get_method_local_adress_weight(callee, i);
1804                         weight += v;
1805                         if (v > 0)
1806                                 *local_adr = 1;
1807                 }
1808         }
1809
1810         callee_env = get_irg_link(callee);
1811         if (get_entity_visibility(ent) == visibility_local &&
1812             callee_env->n_callers_orig == 1 &&
1813             callee != current_ir_graph) {
1814                 /* we are the only caller, give big bonus */
1815                 weight += 5000;
1816         }
1817
1818         /* do not inline big functions */
1819         weight -= callee_env->n_nodes;
1820
1821         /* reduce the benefice if the current function is already big */
1822         curr_env = get_irg_link(current_ir_graph);
1823         weight -= curr_env->n_nodes / 100;
1824
1825         /* give a bonus for functions with one block */
1826         if (callee_env->n_blocks == 1)
1827                 weight = weight * 3 / 2;
1828
1829         return weight;
1830 }
1831
1832 /**
1833  * Heuristic inliner. Calculates a benifice value for every call and inlines
1834  * those calls with a value higher than the threshold.
1835  */
1836 void inline_functions(int inline_threshold) {
1837         inline_irg_env   *env;
1838         ir_graph         *irg;
1839         int              i, n_irgs;
1840         ir_graph         *rem;
1841         int              did_inline;
1842         wenv_t           wenv;
1843         call_entry       *entry, *tail;
1844         const call_entry *centry;
1845         pmap             *copied_graphs;
1846         pmap_entry       *pm_entry;
1847
1848         rem = current_ir_graph;
1849         obstack_init(&temp_obst);
1850
1851         /* a map for the copied graphs, used to inline recursive calls */
1852         copied_graphs = pmap_create();
1853
1854         /* extend all irgs by a temporary data structure for inlining. */
1855         n_irgs = get_irp_n_irgs();
1856         for (i = 0; i < n_irgs; ++i)
1857                 set_irg_link(get_irp_irg(i), alloc_inline_irg_env());
1858
1859         /* Precompute information in temporary data structure. */
1860         wenv.ignore_runtime = 0;
1861         wenv.ignore_callers = 0;
1862         for (i = 0; i < n_irgs; ++i) {
1863                 ir_graph *irg = get_irp_irg(i);
1864
1865                 assert(get_irg_phase_state(irg) != phase_building);
1866                 free_callee_info(irg);
1867
1868                 wenv.x = get_irg_link(irg);
1869                 irg_walk_graph(irg, NULL, collect_calls2, &wenv);
1870         }
1871
1872         /* -- and now inline. -- */
1873         for (i = 0; i < n_irgs; ++i) {
1874                 ir_node *call;
1875                 int phiproj_computed = 0;
1876
1877                 current_ir_graph = get_irp_irg(i);
1878                 env = get_irg_link(current_ir_graph);
1879
1880                 /* note that the list of possible calls is updated during the process */
1881                 tail = NULL;
1882                 for (entry = env->call_head; entry != NULL; entry = entry->next) {
1883                         ir_graph   *callee;
1884                         pmap_entry *e;
1885                         int        benefice;
1886                         unsigned   local_adr;
1887
1888                         call   = entry->call;
1889                         callee = entry->callee;
1890
1891                         /* calculate the benifice on the original call to prevent excessive inlining */
1892                         local_adr = 0;
1893                         benefice = calc_inline_benefice(call, callee, &local_adr);
1894                         DB((dbg, SET_LEVEL_2, "In %+F Call %+F has benefice %d\n", current_ir_graph, callee, benefice));
1895
1896                         e = pmap_find(copied_graphs, callee);
1897                         if (e != NULL) {
1898                                 /*
1899                                  * Remap callee if we have a copy.
1900                                  * FIXME: Should we do this only for recursive Calls ?
1901                                  */
1902                                 callee = e->value;
1903                         }
1904
1905                         if (benefice > -inline_threshold ||
1906                                 (get_irg_inline_property(callee) >= irg_inline_forced)) {
1907                                 if (current_ir_graph == callee) {
1908                                         /*
1909                                          * Recursive call: we cannot directly inline because we cannot walk
1910                                          * the graph and change it. So we have to make a copy of the graph
1911                                          * first.
1912                                          */
1913
1914                                         inline_irg_env *callee_env;
1915                                         ir_graph       *copy;
1916
1917                                         /*
1918                                          * No copy yet, create one.
1919                                          * Note that recursive methods are never leaves, so it is sufficient
1920                                          * to test this condition here.
1921                                          */
1922                                         copy = create_irg_copy(callee);
1923
1924                                         /* create_irg_copy() destroys the Proj links, recompute them */
1925                                         phiproj_computed = 0;
1926
1927                                         /* allocate new environment */
1928                                         callee_env = alloc_inline_irg_env();
1929                                         set_irg_link(copy, callee_env);
1930
1931                                         wenv.x              = callee_env;
1932                                         wenv.ignore_callers = 1;
1933                                         irg_walk_graph(copy, NULL, collect_calls2, &wenv);
1934
1935                                         /*
1936                                          * Enter the entity of the original graph. This is needed
1937                                          * for inline_method(). However, note that ent->irg still points
1938                                          * to callee, NOT to copy.
1939                                          */
1940                                         set_irg_entity(copy, get_irg_entity(callee));
1941
1942                                         pmap_insert(copied_graphs, callee, copy);
1943                                         callee = copy;
1944
1945                                         /* we have only one caller: the original graph */
1946                                         callee_env->n_callers      = 1;
1947                                         callee_env->n_callers_orig = 1;
1948                                 }
1949                                 if (! phiproj_computed) {
1950                                         phiproj_computed = 1;
1951                                         collect_phiprojs(current_ir_graph);
1952                                 }
1953                                 did_inline = inline_method(call, callee);
1954                                 if (did_inline) {
1955                                         inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1956
1957                                         /* was inlined, must be recomputed */
1958                                         phiproj_computed = 0;
1959
1960                                         /* callee was inline. Append it's call list. */
1961                                         env->got_inline = 1;
1962                                         if (local_adr)
1963                                                 env->local_vars = 1;
1964                                         --env->n_call_nodes;
1965                                         append_call_list(env, callee_env->call_head);
1966                                         env->n_call_nodes += callee_env->n_call_nodes;
1967                                         env->n_nodes += callee_env->n_nodes;
1968                                         --callee_env->n_callers;
1969
1970                                         /* after we have inlined callee, all called methods inside callee
1971                                            are now called once more */
1972                                         for (centry = callee_env->call_head; centry != NULL; centry = centry->next) {
1973                                                 inline_irg_env *penv = get_irg_link(centry->callee);
1974                                                 ++penv->n_callers;
1975                                         }
1976
1977                                         /* remove this call from the list */
1978                                         if (tail != NULL)
1979                                                 tail->next = entry->next;
1980                                         else
1981                                                 env->call_head = entry->next;
1982                                         continue;
1983                                 }
1984                         }
1985                         tail = entry;
1986                 }
1987                 env->call_tail = tail;
1988         }
1989
1990         for (i = 0; i < n_irgs; ++i) {
1991                 irg = get_irp_irg(i);
1992                 env = (inline_irg_env *)get_irg_link(irg);
1993
1994                 if (env->got_inline) {
1995                         /* this irg got calls inlined */
1996                         set_irg_outs_inconsistent(irg);
1997                         set_irg_doms_inconsistent(irg);
1998                         set_irg_loopinfo_inconsistent(irg);
1999
2000                         /* scalar replacement does not work well with Tuple nodes, so optimize them away */
2001                         optimize_graph_df(irg);
2002
2003                         if (env->local_vars) {
2004                                 if (scalar_replacement_opt(irg))
2005                                         optimize_graph_df(irg);
2006                         }
2007
2008                         optimize_cf(irg);
2009                 }
2010                 if (env->got_inline || (env->n_callers_orig != env->n_callers)) {
2011                         DB((dbg, SET_LEVEL_1, "Nodes:%3d ->%3d, calls:%3d ->%3d, callers:%3d ->%3d, -- %s\n",
2012                         env->n_nodes_orig, env->n_nodes, env->n_call_nodes_orig, env->n_call_nodes,
2013                         env->n_callers_orig, env->n_callers,
2014                         get_entity_name(get_irg_entity(irg))));
2015                 }
2016         }
2017
2018         /* kill the copied graphs: we don't need them anymore */
2019         foreach_pmap(copied_graphs, pm_entry) {
2020                 ir_graph *copy = pm_entry->value;
2021
2022                 /* reset the entity, otherwise it will be deleted in the next step ... */
2023                 set_irg_entity(copy, NULL);
2024                 free_ir_graph(copy);
2025         }
2026         pmap_destroy(copied_graphs);
2027
2028         obstack_free(&temp_obst, NULL);
2029         current_ir_graph = rem;
2030 }
2031
2032 void firm_init_inline(void) {
2033         FIRM_DBG_REGISTER(dbg, "firm.opt.inline");
2034 }