- inline_method moves copied constants to start block yet
[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 void copy_node_inline(ir_node *n, void *env) {
730         ir_node *nn;
731         ir_type *frame_tp = (ir_type *)env;
732
733         copy_node(n, NULL);
734         if (is_Sel(n)) {
735                 nn = get_new_node (n);
736                 assert(is_Sel(nn));
737                 if (get_entity_owner(get_Sel_entity(n)) == frame_tp) {
738                         set_Sel_entity(nn, get_entity_link(get_Sel_entity(n)));
739                 }
740         } else if (is_Block(n)) {
741                 nn = get_new_node (n);
742                 nn->attr.block.irg = current_ir_graph;
743         }
744 }
745
746 /**
747  * Copies new predecessors of old node and move constants to
748  * the Start Block.
749  */
750 static void copy_preds_inline(ir_node *n, void *env) {
751         ir_node *nn;
752
753         copy_preds(n, env);
754         nn = skip_Id(get_new_node(n));
755         if (is_irn_constlike(nn)) {
756                 /* move Constants into the start block */
757                 set_nodes_block(nn, get_irg_start_block(current_ir_graph));
758
759                 n = identify_remember(current_ir_graph->value_table, nn);
760                 if (nn != n) {
761                         exchange(nn, n);
762                 }
763         }
764 }
765
766 /**
767  * Walker: checks if P_value_arg_base is used.
768  */
769 static void find_addr(ir_node *node, void *env) {
770         int *allow_inline = env;
771         if (is_Proj(node) &&
772                         is_Start(get_Proj_pred(node)) &&
773                         get_Proj_proj(node) == pn_Start_P_value_arg_base) {
774                 *allow_inline = 0;
775         } else if (is_Alloc(node) && get_Alloc_where(node) == stack_alloc) {
776                 /* From GCC:
777                  * Refuse to inline alloca call unless user explicitly forced so as this
778                  * may change program's memory overhead drastically when the function
779                  * using alloca is called in loop.  In GCC present in SPEC2000 inlining
780                  * into schedule_block cause it to require 2GB of ram instead of 256MB.
781                  *
782                  * Sorryly this is true with our implementation also.
783                  * Moreover, we cannot differentiate between alloca() and VLA yet, so this
784                  * disables inlining of functions using VLA (with are completely save).
785                  *
786                  * 2 Solutions:
787                  * - add a flag to the Alloc node for "real" alloca() calls
788                  * - add a new Stack-Restore node at the end of a function using alloca()
789                  */
790                 *allow_inline = 0;
791         }
792 }
793
794 /**
795  * Check if we can inline a given call.
796  * Currently, we cannot inline two cases:
797  * - call with compound arguments
798  * - graphs that take the address of a parameter
799  *
800  * check these conditions here
801  */
802 static int can_inline(ir_node *call, ir_graph *called_graph) {
803         ir_type *call_type = get_Call_type(call);
804         int params, ress, i, res;
805         assert(is_Method_type(call_type));
806
807         params = get_method_n_params(call_type);
808         ress   = get_method_n_ress(call_type);
809
810         /* check parameters for compound arguments */
811         for (i = 0; i < params; ++i) {
812                 ir_type *p_type = get_method_param_type(call_type, i);
813
814                 if (is_compound_type(p_type))
815                         return 0;
816         }
817
818         /* check results for compound arguments */
819         for (i = 0; i < ress; ++i) {
820                 ir_type *r_type = get_method_res_type(call_type, i);
821
822                 if (is_compound_type(r_type))
823                         return 0;
824         }
825
826         res = 1;
827         irg_walk_graph(called_graph, find_addr, NULL, &res);
828
829         return res;
830 }
831
832 enum exc_mode {
833         exc_handler    = 0, /**< There is a handler. */
834         exc_to_end     = 1, /**< Branches to End. */
835         exc_no_handler = 2  /**< Exception handling not represented. */
836 };
837
838 /* Inlines a method at the given call site. */
839 int inline_method(ir_node *call, ir_graph *called_graph) {
840         ir_node             *pre_call;
841         ir_node             *post_call, *post_bl;
842         ir_node             *in[pn_Start_max];
843         ir_node             *end, *end_bl, *block;
844         ir_node             **res_pred;
845         ir_node             **cf_pred;
846         ir_node             **args_in;
847         ir_node             *ret, *phi;
848         int                 arity, n_ret, n_exc, n_res, i, n, j, rem_opt, irn_arity, n_params;
849         enum exc_mode       exc_handling;
850         ir_type             *called_frame, *curr_frame, *mtp, *ctp;
851         ir_entity           *ent;
852         ir_graph            *rem, *irg;
853         irg_inline_property prop = get_irg_inline_property(called_graph);
854
855         if (prop == irg_inline_forbidden)
856                 return 0;
857
858         ent = get_irg_entity(called_graph);
859
860         mtp = get_entity_type(ent);
861         ctp = get_Call_type(call);
862         if (get_method_n_params(mtp) > get_method_n_params(ctp)) {
863                 /* this is a bad feature of C: without a prototype, we can can call a function with less
864                 parameters than needed. Currently we don't support this, although it would be
865                 to use Unknown than. */
866                 return 0;
867         }
868
869         /* Argh, compiling C has some bad consequences:
870            the call type AND the method type might be different.
871            It is implementation defendant what happens in that case.
872            We support inlining, if the bitsize of the types matches AND
873            the same arithmetic is used. */
874         n_params = get_method_n_params(mtp);
875         for (i = n_params - 1; i >= 0; --i) {
876                 ir_type *param_tp = get_method_param_type(mtp, i);
877                 ir_type *arg_tp   = get_method_param_type(ctp, i);
878
879                 if (param_tp != arg_tp) {
880                         ir_mode *pmode = get_type_mode(param_tp);
881                         ir_mode *amode = get_type_mode(arg_tp);
882
883                         if (pmode == NULL || amode == NULL)
884                                 return 0;
885                         if (get_mode_size_bits(pmode) != get_mode_size_bits(amode))
886                                 return 0;
887                         if (get_mode_arithmetic(pmode) != get_mode_arithmetic(amode))
888                                 return 0;
889                         /* otherwise we can simply "reinterpret" the bits */
890                 }
891         }
892
893         irg = get_irn_irg(call);
894
895         /*
896          * We cannot inline a recursive call. The graph must be copied before
897          * the call the inline_method() using create_irg_copy().
898          */
899         if (called_graph == irg)
900                 return 0;
901
902         /*
903          * currently, we cannot inline two cases:
904          * - call with compound arguments
905          * - graphs that take the address of a parameter
906          */
907         if (! can_inline(call, called_graph))
908                 return 0;
909
910         rem = current_ir_graph;
911         current_ir_graph = irg;
912
913         DB((dbg, LEVEL_1, "Inlining %+F(%+F) into %+F\n", call, called_graph, irg));
914
915         /* --  Turn off optimizations, this can cause problems when allocating new nodes. -- */
916         rem_opt = get_opt_optimize();
917         set_optimize(0);
918
919         /* Handle graph state */
920         assert(get_irg_phase_state(irg) != phase_building);
921         assert(get_irg_pinned(irg) == op_pin_state_pinned);
922         assert(get_irg_pinned(called_graph) == op_pin_state_pinned);
923         set_irg_outs_inconsistent(irg);
924         set_irg_extblk_inconsistent(irg);
925         set_irg_doms_inconsistent(irg);
926         set_irg_loopinfo_inconsistent(irg);
927         set_irg_callee_info_state(irg, irg_callee_info_inconsistent);
928
929         /* -- Check preconditions -- */
930         assert(is_Call(call));
931
932         /* here we know we WILL inline, so inform the statistics */
933         hook_inline(call, called_graph);
934
935         /* -- Decide how to handle exception control flow: Is there a handler
936            for the Call node, or do we branch directly to End on an exception?
937            exc_handling:
938            0 There is a handler.
939            1 Branches to End.
940            2 Exception handling not represented in Firm. -- */
941         {
942                 ir_node *proj, *Mproj = NULL, *Xproj = NULL;
943                 for (proj = get_irn_link(call); proj; proj = get_irn_link(proj)) {
944                         long proj_nr = get_Proj_proj(proj);
945                         if (proj_nr == pn_Call_X_except) Xproj = proj;
946                         if (proj_nr == pn_Call_M_except) Mproj = proj;
947                 }
948                 if      (Mproj) { assert(Xproj); exc_handling = exc_handler; } /*  Mproj           */
949                 else if (Xproj) {                exc_handling = exc_to_end; } /* !Mproj &&  Xproj   */
950                 else            {                exc_handling = exc_no_handler; } /* !Mproj && !Xproj   */
951         }
952
953         /* create the argument tuple */
954         NEW_ARR_A(ir_type *, args_in, n_params);
955
956         block = get_nodes_block(call);
957         for (i = n_params - 1; i >= 0; --i) {
958                 ir_node *arg      = get_Call_param(call, i);
959                 ir_type *param_tp = get_method_param_type(mtp, i);
960                 ir_mode *mode     = get_type_mode(param_tp);
961
962                 if (mode != get_irn_mode(arg)) {
963                         arg = new_r_Conv(irg, block, arg, mode);
964                 }
965                 args_in[i] = arg;
966         }
967
968         /* --
969            the procedure and later replaces the Start node of the called graph.
970            Post_call is the old Call node and collects the results of the called
971            graph. Both will end up being a tuple.  -- */
972         post_bl = get_nodes_block(call);
973         set_irg_current_block(irg, post_bl);
974         /* XxMxPxPxPxT of Start + parameter of Call */
975         in[pn_Start_X_initial_exec]   = new_Jmp();
976         in[pn_Start_M]                = get_Call_mem(call);
977         in[pn_Start_P_frame_base]     = get_irg_frame(irg);
978         in[pn_Start_P_tls]            = get_irg_tls(irg);
979         in[pn_Start_T_args]           = new_Tuple(n_params, args_in);
980         /* in[pn_Start_P_value_arg_base] = ??? */
981         assert(pn_Start_P_value_arg_base == pn_Start_max - 1 && "pn_Start_P_value_arg_base not supported, fix");
982         pre_call = new_Tuple(pn_Start_max - 1, in);
983         post_call = call;
984
985         /* --
986            The new block gets the ins of the old block, pre_call and all its
987            predecessors and all Phi nodes. -- */
988         part_block(pre_call);
989
990         /* -- Prepare state for dead node elimination -- */
991         /* Visited flags in calling irg must be >= flag in called irg.
992            Else walker and arity computation will not work. */
993         if (get_irg_visited(irg) <= get_irg_visited(called_graph))
994                 set_irg_visited(irg, get_irg_visited(called_graph) + 1);
995         if (get_irg_block_visited(irg) < get_irg_block_visited(called_graph))
996                 set_irg_block_visited(irg, get_irg_block_visited(called_graph));
997         /* Set pre_call as new Start node in link field of the start node of
998            calling graph and pre_calls block as new block for the start block
999            of calling graph.
1000            Further mark these nodes so that they are not visited by the
1001            copying. */
1002         set_irn_link(get_irg_start(called_graph), pre_call);
1003         set_irn_visited(get_irg_start(called_graph), get_irg_visited(irg));
1004         set_irn_link(get_irg_start_block(called_graph), get_nodes_block(pre_call));
1005         set_irn_visited(get_irg_start_block(called_graph), get_irg_visited(irg));
1006         set_irn_link(get_irg_bad(called_graph), get_irg_bad(irg));
1007         set_irn_visited(get_irg_bad(called_graph), get_irg_visited(irg));
1008
1009         /* Initialize for compaction of in arrays */
1010         inc_irg_block_visited(irg);
1011
1012         /* -- Replicate local entities of the called_graph -- */
1013         /* copy the entities. */
1014         called_frame = get_irg_frame_type(called_graph);
1015         curr_frame   = get_irg_frame_type(irg);
1016         for (i = 0, n = get_class_n_members(called_frame); i < n; ++i) {
1017                 ir_entity *new_ent, *old_ent;
1018                 old_ent = get_class_member(called_frame, i);
1019                 new_ent = copy_entity_own(old_ent, curr_frame);
1020                 set_entity_link(old_ent, new_ent);
1021         }
1022
1023         /* visited is > than that of called graph.  With this trick visited will
1024            remain unchanged so that an outer walker, e.g., searching the call nodes
1025             to inline, calling this inline will not visit the inlined nodes. */
1026         set_irg_visited(irg, get_irg_visited(irg)-1);
1027
1028         /* -- Performing dead node elimination inlines the graph -- */
1029         /* Copies the nodes to the obstack of current_ir_graph. Updates links to new
1030            entities. */
1031         irg_walk(get_irg_end(called_graph), copy_node_inline, copy_preds_inline,
1032                  get_irg_frame_type(called_graph));
1033
1034         /* Repair called_graph */
1035         set_irg_visited(called_graph, get_irg_visited(irg));
1036         set_irg_block_visited(called_graph, get_irg_block_visited(irg));
1037         set_Block_block_visited(get_irg_start_block(called_graph), 0);
1038
1039         /* -- Merge the end of the inlined procedure with the call site -- */
1040         /* We will turn the old Call node into a Tuple with the following
1041            predecessors:
1042            -1:  Block of Tuple.
1043            0: Phi of all Memories of Return statements.
1044            1: Jmp from new Block that merges the control flow from all exception
1045            predecessors of the old end block.
1046            2: Tuple of all arguments.
1047            3: Phi of Exception memories.
1048            In case the old Call directly branches to End on an exception we don't
1049            need the block merging all exceptions nor the Phi of the exception
1050            memories.
1051         */
1052
1053         /* -- Precompute some values -- */
1054         end_bl = get_new_node(get_irg_end_block(called_graph));
1055         end = get_new_node(get_irg_end(called_graph));
1056         arity = get_irn_arity(end_bl);    /* arity = n_exc + n_ret  */
1057         n_res = get_method_n_ress(get_Call_type(call));
1058
1059         res_pred = xmalloc(n_res * sizeof(*res_pred));
1060         cf_pred  = xmalloc(arity * sizeof(*res_pred));
1061
1062         set_irg_current_block(irg, post_bl); /* just to make sure */
1063
1064         /* -- archive keepalives -- */
1065         irn_arity = get_irn_arity(end);
1066         for (i = 0; i < irn_arity; i++) {
1067                 ir_node *ka = get_End_keepalive(end, i);
1068                 if (! is_Bad(ka))
1069                         add_End_keepalive(get_irg_end(irg), ka);
1070         }
1071
1072         /* The new end node will die.  We need not free as the in array is on the obstack:
1073            copy_node() only generated 'D' arrays. */
1074
1075         /* -- Replace Return nodes by Jump nodes. -- */
1076         n_ret = 0;
1077         for (i = 0; i < arity; i++) {
1078                 ir_node *ret;
1079                 ret = get_irn_n(end_bl, i);
1080                 if (is_Return(ret)) {
1081                         cf_pred[n_ret] = new_r_Jmp(irg, get_nodes_block(ret));
1082                         n_ret++;
1083                 }
1084         }
1085         set_irn_in(post_bl, n_ret, cf_pred);
1086
1087         /* -- Build a Tuple for all results of the method.
1088            Add Phi node if there was more than one Return.  -- */
1089         turn_into_tuple(post_call, pn_Call_max);
1090         /* First the Memory-Phi */
1091         n_ret = 0;
1092         for (i = 0; i < arity; i++) {
1093                 ret = get_irn_n(end_bl, i);
1094                 if (is_Return(ret)) {
1095                         cf_pred[n_ret] = get_Return_mem(ret);
1096                         n_ret++;
1097                 }
1098         }
1099         phi = new_Phi(n_ret, cf_pred, mode_M);
1100         set_Tuple_pred(call, pn_Call_M_regular, phi);
1101         /* Conserve Phi-list for further inlinings -- but might be optimized */
1102         if (get_nodes_block(phi) == post_bl) {
1103                 set_irn_link(phi, get_irn_link(post_bl));
1104                 set_irn_link(post_bl, phi);
1105         }
1106         /* Now the real results */
1107         if (n_res > 0) {
1108                 for (j = 0; j < n_res; j++) {
1109                         n_ret = 0;
1110                         for (i = 0; i < arity; i++) {
1111                                 ret = get_irn_n(end_bl, i);
1112                                 if (is_Return(ret)) {
1113                                         cf_pred[n_ret] = get_Return_res(ret, j);
1114                                         n_ret++;
1115                                 }
1116                         }
1117                         if (n_ret > 0)
1118                                 phi = new_Phi(n_ret, cf_pred, get_irn_mode(cf_pred[0]));
1119                         else
1120                                 phi = new_Bad();
1121                         res_pred[j] = phi;
1122                         /* Conserve Phi-list for further inlinings -- but might be optimized */
1123                         if (get_nodes_block(phi) == post_bl) {
1124                                 set_Phi_next(phi, get_Block_phis(post_bl));
1125                                 set_Block_phis(post_bl, phi);
1126                         }
1127                 }
1128                 set_Tuple_pred(call, pn_Call_T_result, new_Tuple(n_res, res_pred));
1129         } else {
1130                 set_Tuple_pred(call, pn_Call_T_result, new_Bad());
1131         }
1132         /* handle the regular call */
1133         set_Tuple_pred(call, pn_Call_X_regular, new_Jmp());
1134
1135         /* For now, we cannot inline calls with value_base */
1136         set_Tuple_pred(call, pn_Call_P_value_res_base, new_Bad());
1137
1138         /* Finally the exception control flow.
1139            We have two (three) possible situations:
1140            First if the Call branches to an exception handler: We need to add a Phi node to
1141            collect the memory containing the exception objects.  Further we need
1142            to add another block to get a correct representation of this Phi.  To
1143            this block we add a Jmp that resolves into the X output of the Call
1144            when the Call is turned into a tuple.
1145            Second the Call branches to End, the exception is not handled.  Just
1146            add all inlined exception branches to the End node.
1147            Third: there is no Exception edge at all. Handle as case two. */
1148         if (exc_handling == exc_handler) {
1149                 n_exc = 0;
1150                 for (i = 0; i < arity; i++) {
1151                         ir_node *ret, *irn;
1152                         ret = get_irn_n(end_bl, i);
1153                         irn = skip_Proj(ret);
1154                         if (is_fragile_op(irn) || is_Raise(irn)) {
1155                                 cf_pred[n_exc] = ret;
1156                                 ++n_exc;
1157                         }
1158                 }
1159                 if (n_exc > 0) {
1160                         new_Block(n_exc, cf_pred);      /* watch it: current_block is changed! */
1161                         set_Tuple_pred(call, pn_Call_X_except, new_Jmp());
1162                         /* The Phi for the memories with the exception objects */
1163                         n_exc = 0;
1164                         for (i = 0; i < arity; i++) {
1165                                 ir_node *ret;
1166                                 ret = skip_Proj(get_irn_n(end_bl, i));
1167                                 if (is_Call(ret)) {
1168                                         cf_pred[n_exc] = new_r_Proj(irg, get_nodes_block(ret), ret, mode_M, 3);
1169                                         n_exc++;
1170                                 } else if (is_fragile_op(ret)) {
1171                                         /* We rely that all cfops have the memory output at the same position. */
1172                                         cf_pred[n_exc] = new_r_Proj(irg, get_nodes_block(ret), ret, mode_M, 0);
1173                                         n_exc++;
1174                                 } else if (is_Raise(ret)) {
1175                                         cf_pred[n_exc] = new_r_Proj(irg, get_nodes_block(ret), ret, mode_M, 1);
1176                                         n_exc++;
1177                                 }
1178                         }
1179                         set_Tuple_pred(call, pn_Call_M_except, new_Phi(n_exc, cf_pred, mode_M));
1180                 } else {
1181                         set_Tuple_pred(call, pn_Call_X_except, new_Bad());
1182                         set_Tuple_pred(call, pn_Call_M_except, new_Bad());
1183                 }
1184         } else {
1185                 ir_node *main_end_bl;
1186                 int main_end_bl_arity;
1187                 ir_node **end_preds;
1188
1189                 /* assert(exc_handling == 1 || no exceptions. ) */
1190                 n_exc = 0;
1191                 for (i = 0; i < arity; i++) {
1192                         ir_node *ret = get_irn_n(end_bl, i);
1193                         ir_node *irn = skip_Proj(ret);
1194
1195                         if (is_fragile_op(irn) || is_Raise(irn)) {
1196                                 cf_pred[n_exc] = ret;
1197                                 n_exc++;
1198                         }
1199                 }
1200                 main_end_bl = get_irg_end_block(irg);
1201                 main_end_bl_arity = get_irn_arity(main_end_bl);
1202                 end_preds =  xmalloc((n_exc + main_end_bl_arity) * sizeof(*end_preds));
1203
1204                 for (i = 0; i < main_end_bl_arity; ++i)
1205                         end_preds[i] = get_irn_n(main_end_bl, i);
1206                 for (i = 0; i < n_exc; ++i)
1207                         end_preds[main_end_bl_arity + i] = cf_pred[i];
1208                 set_irn_in(main_end_bl, n_exc + main_end_bl_arity, end_preds);
1209                 set_Tuple_pred(call, pn_Call_X_except,  new_Bad());
1210                 set_Tuple_pred(call, pn_Call_M_except,  new_Bad());
1211                 free(end_preds);
1212         }
1213         free(res_pred);
1214         free(cf_pred);
1215
1216         /* --  Turn CSE back on. -- */
1217         set_optimize(rem_opt);
1218         current_ir_graph = rem;
1219
1220         return 1;
1221 }
1222
1223 /********************************************************************/
1224 /* Apply inlineing to small methods.                                */
1225 /********************************************************************/
1226
1227 static struct obstack  temp_obst;
1228
1229 /** Represents a possible inlinable call in a graph. */
1230 typedef struct _call_entry call_entry;
1231 struct _call_entry {
1232         ir_node    *call;      /**< the Call node */
1233         ir_graph   *callee;    /**< the callee IR-graph called here */
1234         call_entry *next;      /**< for linking the next one */
1235         int        loop_depth; /**< the loop depth of this call */
1236 };
1237
1238 /**
1239  * environment for inlining small irgs
1240  */
1241 typedef struct _inline_env_t {
1242         struct obstack obst;  /**< an obstack where call_entries are allocated on. */
1243         call_entry *head;     /**< the head of the call entry list */
1244         call_entry *tail;     /**< the tail of the call entry list */
1245 } inline_env_t;
1246
1247 /**
1248  * Returns the irg called from a Call node. If the irg is not
1249  * known, NULL is returned.
1250  *
1251  * @param call  the call node
1252  */
1253 static ir_graph *get_call_called_irg(ir_node *call) {
1254         ir_node *addr;
1255
1256         addr = get_Call_ptr(call);
1257         if (is_Global(addr)) {
1258                 ir_entity *ent = get_Global_entity(addr);
1259                 return get_entity_irg(ent);
1260         }
1261
1262         return NULL;
1263 }
1264
1265 /**
1266  * Walker: Collect all calls to known graphs inside a graph.
1267  */
1268 static void collect_calls(ir_node *call, void *env) {
1269         if (is_Call(call)) {
1270                 ir_graph *called_irg = get_call_called_irg(call);
1271
1272                 if (called_irg != NULL) {
1273                         /* The Call node calls a locally defined method.  Remember to inline. */
1274                         inline_env_t *ienv  = env;
1275                         call_entry   *entry = obstack_alloc(&ienv->obst, sizeof(*entry));
1276                         entry->call       = call;
1277                         entry->callee     = called_irg;
1278                         entry->next       = NULL;
1279                         entry->loop_depth = 0;
1280
1281                         if (ienv->tail == NULL)
1282                                 ienv->head = entry;
1283                         else
1284                                 ienv->tail->next = entry;
1285                         ienv->tail = entry;
1286                 }
1287         }
1288 }
1289
1290 /**
1291  * Inlines all small methods at call sites where the called address comes
1292  * from a Const node that references the entity representing the called
1293  * method.
1294  * The size argument is a rough measure for the code size of the method:
1295  * Methods where the obstack containing the firm graph is smaller than
1296  * size are inlined.
1297  */
1298 void inline_small_irgs(ir_graph *irg, int size) {
1299         ir_graph *rem = current_ir_graph;
1300         inline_env_t env;
1301         call_entry *entry;
1302
1303         current_ir_graph = irg;
1304         /* Handle graph state */
1305         assert(get_irg_phase_state(irg) != phase_building);
1306         free_callee_info(irg);
1307
1308         /* Find Call nodes to inline.
1309            (We can not inline during a walk of the graph, as inlineing the same
1310            method several times changes the visited flag of the walked graph:
1311            after the first inlineing visited of the callee equals visited of
1312            the caller.  With the next inlineing both are increased.) */
1313         obstack_init(&env.obst);
1314         env.head = env.tail = NULL;
1315         irg_walk_graph(irg, NULL, collect_calls, &env);
1316
1317         if (env.head != NULL) {
1318                 /* There are calls to inline */
1319                 collect_phiprojs(irg);
1320                 for (entry = env.head; entry != NULL; entry = entry->next) {
1321                         ir_graph *callee = entry->callee;
1322                         if (((_obstack_memory_used(callee->obst) - (int)obstack_room(callee->obst)) < size) ||
1323                             (get_irg_inline_property(callee) >= irg_inline_forced)) {
1324                                 inline_method(entry->call, callee);
1325                         }
1326                 }
1327         }
1328         obstack_free(&env.obst, NULL);
1329         current_ir_graph = rem;
1330 }
1331
1332 /**
1333  * Environment for inlining irgs.
1334  */
1335 typedef struct {
1336         int n_nodes;             /**< Number of nodes in graph except Id, Tuple, Proj, Start, End. */
1337         int n_blocks;            /**< Number of Blocks in graph without Start and End block. */
1338         int n_nodes_orig;        /**< for statistics */
1339         int n_call_nodes;        /**< Number of Call nodes in the graph. */
1340         int n_call_nodes_orig;   /**< for statistics */
1341         int n_callers;           /**< Number of known graphs that call this graphs. */
1342         int n_callers_orig;      /**< for statistics */
1343         unsigned got_inline:1;   /**< Set, if at least one call inside this graph was inlined. */
1344         unsigned local_vars:1;   /**< Set, if a inlined function gets the address of an inlined variable. */
1345         unsigned recursive:1;    /**< Set, if this function is self recursive. */
1346         call_entry *call_head;   /**< The head of the list of all call nodes in this graph. */
1347         call_entry *call_tail;   /**< The tail of the list of all call nodes in this graph .*/
1348         unsigned *local_weights; /**< Once allocated, the beneficial weight for transmitting local addresses. */
1349 } inline_irg_env;
1350
1351 /**
1352  * Allocate a new environment for inlining.
1353  */
1354 static inline_irg_env *alloc_inline_irg_env(void) {
1355         inline_irg_env *env    = obstack_alloc(&temp_obst, sizeof(*env));
1356         env->n_nodes           = -2; /* do not count count Start, End */
1357         env->n_blocks          = -2; /* do not count count Start, End Block */
1358         env->n_nodes_orig      = -2; /* do not count Start, End */
1359         env->call_head         = NULL;
1360         env->call_tail         = NULL;
1361         env->n_call_nodes      = 0;
1362         env->n_call_nodes_orig = 0;
1363         env->n_callers         = 0;
1364         env->n_callers_orig    = 0;
1365         env->got_inline        = 0;
1366         env->local_vars        = 0;
1367         env->recursive         = 0;
1368         env->local_weights     = NULL;
1369         return env;
1370 }
1371
1372 typedef struct walker_env {
1373         inline_irg_env *x;     /**< the inline environment */
1374         call_entry *last_call; /**< points to the last inserted call */
1375         char ignore_runtime;   /**< the ignore runtime flag */
1376         char ignore_callers;   /**< if set, do change callers data */
1377 } wenv_t;
1378
1379 /**
1380  * post-walker: collect all calls in the inline-environment
1381  * of a graph and sum some statistics.
1382  */
1383 static void collect_calls2(ir_node *call, void *ctx) {
1384         wenv_t         *env = ctx;
1385         inline_irg_env *x = env->x;
1386         ir_opcode      code = get_irn_opcode(call);
1387         ir_graph       *callee;
1388         call_entry     *entry;
1389
1390         /* count meaningful nodes in irg */
1391         if (code != iro_Proj && code != iro_Tuple && code != iro_Sync) {
1392                 if (code != iro_Block) {
1393                         ++x->n_nodes;
1394                         ++x->n_nodes_orig;
1395                 } else {
1396                         ++x->n_blocks;
1397                 }
1398         }
1399
1400         if (code != iro_Call) return;
1401
1402         /* check, if it's a runtime call */
1403         if (env->ignore_runtime) {
1404                 ir_node *symc = get_Call_ptr(call);
1405
1406                 if (is_Global(symc)) {
1407                         ir_entity *ent = get_Global_entity(symc);
1408
1409                         if (get_entity_additional_properties(ent) & mtp_property_runtime)
1410                                 return;
1411                 }
1412         }
1413
1414         /* collect all call nodes */
1415         ++x->n_call_nodes;
1416         ++x->n_call_nodes_orig;
1417
1418         callee = get_call_called_irg(call);
1419         if (callee != NULL) {
1420                 if (! env->ignore_callers) {
1421                         inline_irg_env *callee_env = get_irg_link(callee);
1422                         /* count all static callers */
1423                         ++callee_env->n_callers;
1424                         ++callee_env->n_callers_orig;
1425                 }
1426                 if (callee == current_ir_graph)
1427                         x->recursive = 1;
1428
1429                 /* link it in the list of possible inlinable entries */
1430                 entry = obstack_alloc(&temp_obst, sizeof(*entry));
1431                 entry->call       = call;
1432                 entry->callee     = callee;
1433                 entry->next       = NULL;
1434                 entry->loop_depth = get_irn_loop(get_nodes_block(call))->depth;
1435
1436                 /* note: we use call_tail here as a pointer to the last inserted */
1437                 if (x->call_head == NULL) {
1438                         x->call_head = entry;
1439                 } else {
1440                         if (entry->loop_depth == env->last_call->loop_depth) {
1441                                 /* same depth as the last one, enqueue after it */
1442                                 entry->next          = env->last_call->next;
1443                                 env->last_call->next = entry;
1444                         } else if (entry->loop_depth > x->call_head->loop_depth) {
1445                                 /* put first */
1446                                 entry->next  = x->call_head;
1447                                 x->call_head = entry;
1448                         } else {
1449                                 /* search the insertion point */
1450                                 call_entry *p;
1451
1452                                 for (p = x->call_head; p->next != NULL; p = p->next)
1453                                         if (entry->loop_depth > p->next->loop_depth)
1454                                                 break;
1455                                 entry->next = p->next;
1456                                 p->next     = entry;
1457                         }
1458                 }
1459                 env->last_call = entry;
1460                 if (entry->next == NULL) {
1461                         /* keep tail up to date */
1462                         x->call_tail = entry;
1463                 }
1464         }
1465 }
1466
1467 /**
1468  * Returns TRUE if the number of callers is 0 in the irg's environment,
1469  * hence this irg is a leave.
1470  */
1471 INLINE static int is_leave(ir_graph *irg) {
1472         inline_irg_env *env = get_irg_link(irg);
1473         return env->n_call_nodes == 0;
1474 }
1475
1476 /**
1477  * Returns TRUE if the number of nodes in the callee is
1478  * smaller then size in the irg's environment.
1479  */
1480 INLINE static int is_smaller(ir_graph *callee, int size) {
1481         inline_irg_env *env = get_irg_link(callee);
1482         return env->n_nodes < size;
1483 }
1484
1485 /**
1486  * Append the nodes of the list src to the nodes of the list in environment dst.
1487  */
1488 static void append_call_list(inline_irg_env *dst, call_entry *src) {
1489         call_entry *entry, *nentry;
1490
1491         /* Note that the src list points to Call nodes in the inlined graph, but
1492            we need Call nodes in our graph. Luckily the inliner leaves this information
1493            in the link field. */
1494         for (entry = src; entry != NULL; entry = entry->next) {
1495                 nentry = obstack_alloc(&temp_obst, sizeof(*nentry));
1496                 nentry->call         = get_irn_link(entry->call);
1497                 nentry->callee       = entry->callee;
1498                 nentry->next         = NULL;
1499                 nentry->loop_depth   = entry->loop_depth;
1500                 dst->call_tail->next = nentry;
1501                 dst->call_tail       = nentry;
1502         }
1503 }
1504
1505 /**
1506  * Add the nodes of the list src in front to the nodes of the list dst.
1507  */
1508 static call_entry *replace_entry_by_call_list(call_entry *dst, call_entry *src) {
1509         call_entry *entry, *nentry, *head, *tail;
1510
1511         /* Note that the src list points to Call nodes in the inlined graph, but
1512            we need Call nodes in our graph. Luckily the inliner leaves this information
1513            in the link field. */
1514         head = tail = NULL;
1515         for (entry = src; entry != NULL; entry = entry->next) {
1516                 nentry = obstack_alloc(&temp_obst, sizeof(*nentry));
1517                 nentry->call         = get_irn_link(entry->call);
1518                 nentry->callee       = entry->callee;
1519                 nentry->next         = NULL;
1520                 nentry->loop_depth   = entry->loop_depth + dst->loop_depth;
1521                 if (head == NULL)
1522                         head = nentry;
1523                 else
1524                         tail->next = nentry;
1525                 tail = nentry;
1526         }
1527         /* skip the head of dst */
1528         if (head != NULL) {
1529                 tail->next = dst->next;
1530         } else {
1531                 head = dst->next;
1532         }
1533         return head;
1534 }
1535
1536 /*
1537  * Inlines small leave methods at call sites where the called address comes
1538  * from a Const node that references the entity representing the called
1539  * method.
1540  * The size argument is a rough measure for the code size of the method:
1541  * Methods where the obstack containing the firm graph is smaller than
1542  * size are inlined.
1543  */
1544 void inline_leave_functions(int maxsize, int leavesize, int size, int ignore_runtime) {
1545         inline_irg_env   *env;
1546         ir_graph         *irg;
1547         int              i, n_irgs;
1548         ir_graph         *rem;
1549         int              did_inline;
1550         wenv_t           wenv;
1551         call_entry       *entry, *tail;
1552         const call_entry *centry;
1553         pmap             *copied_graphs;
1554         pmap_entry       *pm_entry;
1555
1556         rem = current_ir_graph;
1557         obstack_init(&temp_obst);
1558
1559         /* a map for the copied graphs, used to inline recursive calls */
1560         copied_graphs = pmap_create();
1561
1562         /* extend all irgs by a temporary data structure for inlining. */
1563         n_irgs = get_irp_n_irgs();
1564         for (i = 0; i < n_irgs; ++i)
1565                 set_irg_link(get_irp_irg(i), alloc_inline_irg_env());
1566
1567         /* Precompute information in temporary data structure. */
1568         wenv.ignore_runtime = ignore_runtime;
1569         wenv.ignore_callers = 0;
1570         for (i = 0; i < n_irgs; ++i) {
1571                 ir_graph *irg = get_irp_irg(i);
1572
1573                 assert(get_irg_phase_state(irg) != phase_building);
1574                 free_callee_info(irg);
1575
1576                 assure_cf_loop(irg);
1577                 wenv.x = get_irg_link(irg);
1578                 irg_walk_graph(irg, NULL, collect_calls2, &wenv);
1579         }
1580
1581         /* -- and now inline. -- */
1582
1583         /* Inline leaves recursively -- we might construct new leaves. */
1584         do {
1585                 did_inline = 0;
1586
1587                 for (i = 0; i < n_irgs; ++i) {
1588                         ir_node *call;
1589                         int phiproj_computed = 0;
1590
1591                         current_ir_graph = get_irp_irg(i);
1592                         env = (inline_irg_env *)get_irg_link(current_ir_graph);
1593
1594                         tail = NULL;
1595                         for (entry = env->call_head; entry != NULL; entry = entry->next) {
1596                                 ir_graph *callee;
1597
1598                                 if (env->n_nodes > maxsize) break;
1599
1600                                 call   = entry->call;
1601                                 callee = entry->callee;
1602
1603                                 if (is_leave(callee) && (
1604                                     is_smaller(callee, leavesize) || (get_irg_inline_property(callee) >= irg_inline_forced))) {
1605                                         if (!phiproj_computed) {
1606                                                 phiproj_computed = 1;
1607                                                 collect_phiprojs(current_ir_graph);
1608                                         }
1609                                         did_inline = inline_method(call, callee);
1610
1611                                         if (did_inline) {
1612                                                 inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1613
1614                                                 /* was inlined, must be recomputed */
1615                                                 phiproj_computed = 0;
1616
1617                                                 /* Do some statistics */
1618                                                 env->got_inline = 1;
1619                                                 --env->n_call_nodes;
1620                                                 env->n_nodes += callee_env->n_nodes;
1621                                                 --callee_env->n_callers;
1622
1623                                                 /* remove this call from the list */
1624                                                 if (tail != NULL)
1625                                                         tail->next = entry->next;
1626                                                 else
1627                                                         env->call_head = entry->next;
1628                                                 continue;
1629                                         }
1630                                 }
1631                                 tail = entry;
1632                         }
1633                         env->call_tail = tail;
1634                 }
1635         } while (did_inline);
1636
1637         /* inline other small functions. */
1638         for (i = 0; i < n_irgs; ++i) {
1639                 ir_node *call;
1640                 int phiproj_computed = 0;
1641
1642                 current_ir_graph = get_irp_irg(i);
1643                 env = (inline_irg_env *)get_irg_link(current_ir_graph);
1644
1645                 /* note that the list of possible calls is updated during the process */
1646                 tail = NULL;
1647                 for (entry = env->call_head; entry != NULL; entry = entry->next) {
1648                         ir_graph   *callee;
1649                         pmap_entry *e;
1650
1651                         call   = entry->call;
1652                         callee = entry->callee;
1653
1654                         e = pmap_find(copied_graphs, callee);
1655                         if (e != NULL) {
1656                                 /*
1657                                  * Remap callee if we have a copy.
1658                                  * FIXME: Should we do this only for recursive Calls ?
1659                                  */
1660                                 callee = e->value;
1661                         }
1662
1663                         if (((is_smaller(callee, size) && (env->n_nodes < maxsize)) ||    /* small function */
1664                                 (get_irg_inline_property(callee) >= irg_inline_forced))) {
1665                                 if (current_ir_graph == callee) {
1666                                         /*
1667                                          * Recursive call: we cannot directly inline because we cannot walk
1668                                          * the graph and change it. So we have to make a copy of the graph
1669                                          * first.
1670                                          */
1671
1672                                         inline_irg_env *callee_env;
1673                                         ir_graph       *copy;
1674
1675                                         /*
1676                                          * No copy yet, create one.
1677                                          * Note that recursive methods are never leaves, so it is sufficient
1678                                          * to test this condition here.
1679                                          */
1680                                         copy = create_irg_copy(callee);
1681
1682                                         /* create_irg_copy() destroys the Proj links, recompute them */
1683                                         phiproj_computed = 0;
1684
1685                                         /* allocate new environment */
1686                                         callee_env = alloc_inline_irg_env();
1687                                         set_irg_link(copy, callee_env);
1688
1689                                         assure_cf_loop(copy);
1690                                         wenv.x              = callee_env;
1691                                         wenv.ignore_callers = 1;
1692                                         irg_walk_graph(copy, NULL, collect_calls2, &wenv);
1693
1694                                         /*
1695                                          * Enter the entity of the original graph. This is needed
1696                                          * for inline_method(). However, note that ent->irg still points
1697                                          * to callee, NOT to copy.
1698                                          */
1699                                         set_irg_entity(copy, get_irg_entity(callee));
1700
1701                                         pmap_insert(copied_graphs, callee, copy);
1702                                         callee = copy;
1703
1704                                         /* we have only one caller: the original graph */
1705                                         callee_env->n_callers      = 1;
1706                                         callee_env->n_callers_orig = 1;
1707                                 }
1708                                 if (! phiproj_computed) {
1709                                         phiproj_computed = 1;
1710                                         collect_phiprojs(current_ir_graph);
1711                                 }
1712                                 did_inline = inline_method(call, callee);
1713                                 if (did_inline) {
1714                                         inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1715
1716                                         /* was inlined, must be recomputed */
1717                                         phiproj_computed = 0;
1718
1719                                         /* callee was inline. Append it's call list. */
1720                                         env->got_inline = 1;
1721                                         --env->n_call_nodes;
1722                                         append_call_list(env, callee_env->call_head);
1723                                         env->n_call_nodes += callee_env->n_call_nodes;
1724                                         env->n_nodes += callee_env->n_nodes;
1725                                         --callee_env->n_callers;
1726
1727                                         /* after we have inlined callee, all called methods inside callee
1728                                            are now called once more */
1729                                         for (centry = callee_env->call_head; centry != NULL; centry = centry->next) {
1730                                                 inline_irg_env *penv = get_irg_link(centry->callee);
1731                                                 ++penv->n_callers;
1732                                         }
1733
1734                                         /* remove this call from the list */
1735                                         if (tail != NULL)
1736                                                 tail->next = entry->next;
1737                                         else
1738                                                 env->call_head = entry->next;
1739                                         continue;
1740                                 }
1741                         }
1742                         tail = entry;
1743                 }
1744                 env->call_tail = tail;
1745         }
1746
1747         for (i = 0; i < n_irgs; ++i) {
1748                 irg = get_irp_irg(i);
1749                 env = (inline_irg_env *)get_irg_link(irg);
1750
1751                 if (env->got_inline) {
1752                         optimize_graph_df(irg);
1753                         optimize_cf(irg);
1754                 }
1755                 if (env->got_inline || (env->n_callers_orig != env->n_callers)) {
1756                         DB((dbg, LEVEL_1, "Nodes:%3d ->%3d, calls:%3d ->%3d, callers:%3d ->%3d, -- %s\n",
1757                         env->n_nodes_orig, env->n_nodes, env->n_call_nodes_orig, env->n_call_nodes,
1758                         env->n_callers_orig, env->n_callers,
1759                         get_entity_name(get_irg_entity(irg))));
1760                 }
1761         }
1762
1763         /* kill the copied graphs: we don't need them anymore */
1764         foreach_pmap(copied_graphs, pm_entry) {
1765                 ir_graph *copy = pm_entry->value;
1766
1767                 /* reset the entity, otherwise it will be deleted in the next step ... */
1768                 set_irg_entity(copy, NULL);
1769                 free_ir_graph(copy);
1770         }
1771         pmap_destroy(copied_graphs);
1772
1773         obstack_free(&temp_obst, NULL);
1774         current_ir_graph = rem;
1775 }
1776
1777 /**
1778  * Calculate the parameter weights for transmitting the address of a local variable.
1779  */
1780 static unsigned calc_method_local_weight(ir_node *arg) {
1781         int      i, j, k;
1782         unsigned v, weight = 0;
1783
1784         for (i = get_irn_n_outs(arg) - 1; i >= 0; --i) {
1785                 ir_node *succ = get_irn_out(arg, i);
1786
1787                 switch (get_irn_opcode(succ)) {
1788                 case iro_Load:
1789                 case iro_Store:
1790                         /* Loads and Store can be removed */
1791                         weight += 3;
1792                         break;
1793                 case iro_Sel:
1794                         /* check if all args are constant */
1795                         for (j = get_Sel_n_indexs(succ) - 1; j >= 0; --j) {
1796                                 ir_node *idx = get_Sel_index(succ, j);
1797                                 if (! is_Const(idx))
1798                                         return 0;
1799                         }
1800                         /* Check users on this Sel. Note: if a 0 is returned here, there was
1801                            some unsupported node. */
1802                         v = calc_method_local_weight(succ);
1803                         if (v == 0)
1804                                 return 0;
1805                         /* we can kill one Sel with constant indexes, this is cheap */
1806                         weight += v + 1;
1807                         break;
1808                 case iro_Id:
1809                         /* when looking backward we might find Id nodes */
1810                         weight += calc_method_local_weight(succ);
1811                         break;
1812                 case iro_Tuple:
1813                         /* unoptimized tuple */
1814                         for (j = get_Tuple_n_preds(succ) - 1; j >= 0; --j) {
1815                                 ir_node *pred = get_Tuple_pred(succ, j);
1816                                 if (pred == arg) {
1817                                         /* look for Proj(j) */
1818                                         for (k = get_irn_n_outs(succ) - 1; k >= 0; --k) {
1819                                                 ir_node *succ_succ = get_irn_out(succ, k);
1820                                                 if (is_Proj(succ_succ)) {
1821                                                         if (get_Proj_proj(succ_succ) == j) {
1822                                                                 /* found */
1823                                                                 weight += calc_method_local_weight(succ_succ);
1824                                                         }
1825                                                 } else {
1826                                                         /* this should NOT happen */
1827                                                         return 0;
1828                                                 }
1829                                         }
1830                                 }
1831                         }
1832                         break;
1833                 default:
1834                         /* any other node: unsupported yet or bad. */
1835                         return 0;
1836                 }
1837         }
1838         return weight;
1839 }
1840
1841 /**
1842  * Calculate the parameter weights for transmitting the address of a local variable.
1843  */
1844 static void analyze_irg_local_weights(inline_irg_env *env, ir_graph *irg) {
1845         ir_entity *ent = get_irg_entity(irg);
1846         ir_type  *mtp;
1847         int      nparams, i, proj_nr;
1848         ir_node  *irg_args, *arg;
1849
1850         mtp      = get_entity_type(ent);
1851         nparams  = get_method_n_params(mtp);
1852
1853         /* allocate a new array. currently used as 'analysed' flag */
1854         env->local_weights = NEW_ARR_D(unsigned, &temp_obst, nparams);
1855
1856         /* If the method haven't parameters we have nothing to do. */
1857         if (nparams <= 0)
1858                 return;
1859
1860         assure_irg_outs(irg);
1861         irg_args = get_irg_args(irg);
1862         for (i = get_irn_n_outs(irg_args) - 1; i >= 0; --i) {
1863                 arg     = get_irn_out(irg_args, i);
1864                 proj_nr = get_Proj_proj(arg);
1865                 env->local_weights[proj_nr] = calc_method_local_weight(arg);
1866         }
1867 }
1868
1869 /**
1870  * Calculate the benefice for transmitting an local variable address.
1871  * After inlining, the local variable might be transformed into a
1872  * SSA variable by scalar_replacement().
1873  */
1874 static unsigned get_method_local_adress_weight(ir_graph *callee, int pos) {
1875         inline_irg_env *env = get_irg_link(callee);
1876
1877         if (env->local_weights != NULL) {
1878                 if (pos < ARR_LEN(env->local_weights))
1879                         return env->local_weights[pos];
1880                 return 0;
1881         }
1882
1883         analyze_irg_local_weights(env, callee);
1884
1885         if (pos < ARR_LEN(env->local_weights))
1886                 return env->local_weights[pos];
1887         return 0;
1888 }
1889
1890 /**
1891  * Calculate a benefice value for inlining the given call.
1892  *
1893  * @param call       the call node we have to inspect
1894  * @param callee     the called graph
1895  * @param local_adr  set after return if an address of a local variable is
1896  *                   transmitted as a parameter
1897  */
1898 static int calc_inline_benefice(ir_node *call, ir_graph *callee, unsigned *local_adr) {
1899         ir_entity *ent = get_irg_entity(callee);
1900         ir_node   *frame_ptr;
1901         ir_type   *mtp;
1902         int       weight = 0;
1903         int       i, n_params, all_const;
1904         unsigned  cc, v;
1905
1906         inline_irg_env *curr_env, *callee_env;
1907
1908         if (get_entity_additional_properties(ent) & mtp_property_noreturn) {
1909                 /* do NOT inline noreturn calls */
1910                 return INT_MIN;
1911         }
1912
1913         /* costs for every passed parameter */
1914         n_params = get_Call_n_params(call);
1915         mtp      = get_entity_type(ent);
1916         cc       = get_method_calling_convention(mtp);
1917         if (cc & cc_reg_param) {
1918                 /* register parameter, smaller costs for register parameters */
1919                 int max_regs = cc & ~cc_bits;
1920
1921                 if (max_regs < n_params)
1922                         weight += max_regs * 2 + (n_params - max_regs) * 5;
1923                 else
1924                         weight += n_params * 2;
1925         } else {
1926                 /* parameters are passed an stack */
1927                 weight += 5 * n_params;
1928         }
1929
1930         /* constant parameters improve the benefice */
1931         frame_ptr = get_irg_frame(current_ir_graph);
1932         all_const = 1;
1933         for (i = 0; i < n_params; ++i) {
1934                 ir_node *param = get_Call_param(call, i);
1935
1936                 if (is_Const(param)) {
1937                         weight += get_method_param_weight(ent, i);
1938                 } else {
1939                         all_const = 0;
1940                         if (is_SymConst(param))
1941                                 weight += get_method_param_weight(ent, i);
1942                         else if (is_Sel(param) && get_Sel_ptr(param) == frame_ptr) {
1943                                 /*
1944                                  * An address of a local variable is transmitted. After inlining,
1945                                  * scalar_replacement might be able to remove the local variable,
1946                                  * so honor this.
1947                                  */
1948                                 v = get_method_local_adress_weight(callee, i);
1949                                 weight += v;
1950                                 if (v > 0)
1951                                         *local_adr = 1;
1952                         }
1953                 }
1954         }
1955
1956         callee_env = get_irg_link(callee);
1957         if (get_entity_visibility(ent) == visibility_local &&
1958             callee_env->n_callers_orig == 1 &&
1959             callee != current_ir_graph) {
1960                 /* we are the only caller, give big bonus */
1961                 weight += 5000;
1962         }
1963
1964         /* do not inline big functions */
1965         weight -= callee_env->n_nodes;
1966
1967         /* reduce the benefice if the current function is already big */
1968         curr_env = get_irg_link(current_ir_graph);
1969         weight -= curr_env->n_nodes / 50;
1970
1971         /* give a bonus for functions with one block */
1972         if (callee_env->n_blocks == 1)
1973                 weight = weight * 3 / 2;
1974
1975         /* and one for small non-recursive functions: we want them to be inlined in mostly every case */
1976         else if (callee_env->n_nodes < 20 && !callee_env->recursive)
1977                 weight += 5000;
1978
1979         /* and finally for leaves: they do not increase the register pressure
1980            because of callee safe registers */
1981         else if (callee_env->n_call_nodes == 0)
1982                 weight += 25;
1983
1984         /*
1985          * Reduce the weight for recursive function IFF not all arguments are const.
1986          * inlining recursive functions is rarely good.
1987          */
1988         if (callee_env->recursive && !all_const)
1989                 weight -= 500;
1990
1991         /*
1992          * All arguments constant is probably a good sign, give an extra bonus
1993          */
1994         if (all_const)
1995                 weight += 100;
1996
1997         return weight;
1998 }
1999
2000 /**
2001  * Heuristic inliner. Calculates a benefice value for every call and inlines
2002  * those calls with a value higher than the threshold.
2003  */
2004 void inline_functions(int maxsize, int inline_threshold) {
2005         inline_irg_env   *env;
2006         int              i, n_irgs;
2007         ir_graph         *rem;
2008         int              did_inline;
2009         wenv_t           wenv;
2010         call_entry       *curr_call, **last_call;
2011         const call_entry *centry;
2012         pmap             *copied_graphs;
2013         pmap_entry       *pm_entry;
2014
2015         rem = current_ir_graph;
2016         obstack_init(&temp_obst);
2017
2018         /* a map for the copied graphs, used to inline recursive calls */
2019         copied_graphs = pmap_create();
2020
2021         /* extend all irgs by a temporary data structure for inlining. */
2022         n_irgs = get_irp_n_irgs();
2023         for (i = 0; i < n_irgs; ++i)
2024                 set_irg_link(get_irp_irg(i), alloc_inline_irg_env());
2025
2026         /* Precompute information in temporary data structure. */
2027         wenv.ignore_runtime = 0;
2028         wenv.ignore_callers = 0;
2029         for (i = 0; i < n_irgs; ++i) {
2030                 ir_graph *irg = get_irp_irg(i);
2031
2032                 assert(get_irg_phase_state(irg) != phase_building);
2033                 free_callee_info(irg);
2034
2035                 wenv.x         = get_irg_link(irg);
2036                 wenv.last_call = NULL;
2037                 assure_cf_loop(irg);
2038                 irg_walk_graph(irg, NULL, collect_calls2, &wenv);
2039         }
2040
2041         /* -- and now inline. -- */
2042         for (i = 0; i < n_irgs; ++i) {
2043                 int      phiproj_computed = 0;
2044                 ir_node  *call;
2045                 ir_graph *irg = get_irp_irg(i);
2046
2047                 current_ir_graph = irg;
2048                 env = get_irg_link(irg);
2049
2050                 /* note that the list of possible calls is updated during the process */
2051                 last_call = &env->call_head;
2052                 for (curr_call = env->call_head; curr_call != NULL;) {
2053                         ir_graph   *callee;
2054                         pmap_entry *e;
2055                         int        benefice;
2056                         unsigned   local_adr;
2057
2058                         if (env->n_nodes > maxsize) break;
2059
2060                         call   = curr_call->call;
2061                         callee = curr_call->callee;
2062
2063                         e = pmap_find(copied_graphs, callee);
2064                         if (e != NULL) {
2065                                 /*
2066                                 * Remap callee if we have a copy.
2067                                 * FIXME: Should we do this only for recursive Calls ?
2068                                 */
2069                                 callee = e->value;
2070                         }
2071
2072                         /* calculate the benefice on the original call to prevent excessive inlining */
2073                         local_adr = 0;
2074                         benefice = calc_inline_benefice(call, callee, &local_adr);
2075                         DB((dbg, LEVEL_2, "In %+F Call %+F has benefice %d\n", irg, callee, benefice));
2076
2077                         if (benefice > -inline_threshold ||
2078                                 (get_irg_inline_property(callee) >= irg_inline_forced)) {
2079                                 if (current_ir_graph == callee) {
2080                                         /*
2081                                          * Recursive call: we cannot directly inline because we cannot walk
2082                                          * the graph and change it. So we have to make a copy of the graph
2083                                          * first.
2084                                          */
2085
2086                                         inline_irg_env *callee_env;
2087                                         ir_graph       *copy;
2088
2089                                         /*
2090                                          * No copy yet, create one.
2091                                          * Note that recursive methods are never leaves, so it is sufficient
2092                                          * to test this condition here.
2093                                          */
2094                                         copy = create_irg_copy(callee);
2095
2096                                         /* create_irg_copy() destroys the Proj links, recompute them */
2097                                         phiproj_computed = 0;
2098
2099                                         /* allocate new environment */
2100                                         callee_env = alloc_inline_irg_env();
2101                                         set_irg_link(copy, callee_env);
2102
2103                                         assure_cf_loop(copy);
2104                                         wenv.x              = callee_env;
2105                                         wenv.ignore_callers = 1;
2106                                         irg_walk_graph(copy, NULL, collect_calls2, &wenv);
2107
2108                                         /*
2109                                          * Enter the entity of the original graph. This is needed
2110                                          * for inline_method(). However, note that ent->irg still points
2111                                          * to callee, NOT to copy.
2112                                          */
2113                                         set_irg_entity(copy, get_irg_entity(callee));
2114
2115                                         pmap_insert(copied_graphs, callee, copy);
2116                                         callee = copy;
2117
2118                                         /* we have only one caller: the original graph */
2119                                         callee_env->n_callers      = 1;
2120                                         callee_env->n_callers_orig = 1;
2121                                 }
2122                                 if (! phiproj_computed) {
2123                                         phiproj_computed = 1;
2124                                         collect_phiprojs(current_ir_graph);
2125                                 }
2126                                 did_inline = inline_method(call, callee);
2127                                 if (did_inline) {
2128                                         inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
2129
2130                                         /* was inlined, must be recomputed */
2131                                         phiproj_computed = 0;
2132
2133                                         /* after we have inlined callee, all called methods inside callee
2134                                         are now called once more */
2135                                         for (centry = callee_env->call_head; centry != NULL; centry = centry->next) {
2136                                                 inline_irg_env *penv = get_irg_link(centry->callee);
2137                                                 ++penv->n_callers;
2138                                         }
2139
2140                                         /* callee was inline. Append it's call list. */
2141                                         env->got_inline = 1;
2142                                         if (local_adr)
2143                                                 env->local_vars = 1;
2144                                         --env->n_call_nodes;
2145                                         curr_call = replace_entry_by_call_list(curr_call, callee_env->call_head);
2146                                         env->n_call_nodes += callee_env->n_call_nodes;
2147                                         env->n_nodes += callee_env->n_nodes;
2148                                         --callee_env->n_callers;
2149
2150                                         /* remove the current call entry from the list */
2151                                         *last_call = curr_call;
2152                                         continue;
2153                                 }
2154                         }
2155                         last_call = &curr_call->next;
2156                         curr_call = curr_call->next;
2157                 }
2158
2159                 if (env->got_inline) {
2160                         /* this irg got calls inlined: optimize it */
2161
2162                         /* scalar replacement does not work well with Tuple nodes, so optimize them away */
2163                         optimize_graph_df(irg);
2164
2165                         if (env->local_vars) {
2166                                 if (scalar_replacement_opt(irg)) {
2167                                         optimize_graph_df(irg);
2168                                 }
2169                         }
2170                         optimize_cf(irg);
2171                 }
2172                 if (env->got_inline || (env->n_callers_orig != env->n_callers)) {
2173                         DB((dbg, LEVEL_1, "Nodes:%3d ->%3d, calls:%3d ->%3d, callers:%3d ->%3d, -- %s\n",
2174                         env->n_nodes_orig, env->n_nodes, env->n_call_nodes_orig, env->n_call_nodes,
2175                         env->n_callers_orig, env->n_callers,
2176                         get_entity_name(get_irg_entity(irg))));
2177                 }
2178         }
2179
2180         /* kill the copied graphs: we don't need them anymore */
2181         foreach_pmap(copied_graphs, pm_entry) {
2182                 ir_graph *copy = pm_entry->value;
2183
2184                 /* reset the entity, otherwise it will be deleted in the next step ... */
2185                 set_irg_entity(copy, NULL);
2186                 free_ir_graph(copy);
2187         }
2188         pmap_destroy(copied_graphs);
2189
2190         obstack_free(&temp_obst, NULL);
2191         current_ir_graph = rem;
2192 }
2193
2194 void firm_init_inline(void) {
2195         FIRM_DBG_REGISTER(dbg, "firm.opt.inline");
2196 }