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