verify: Clarify assertion message.
[libfirm] / ir / opt / opt_inline.c
1 /*
2  * Copyright (C) 1995-2011 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  */
25 #include "config.h"
26
27 #include <limits.h>
28 #include <stdbool.h>
29 #include <assert.h>
30
31 #include "irnode_t.h"
32 #include "irgraph_t.h"
33 #include "irprog_t.h"
34
35 #include "iroptimize.h"
36 #include "ircons_t.h"
37 #include "iropt_t.h"
38 #include "irgopt.h"
39 #include "irgmod.h"
40 #include "irgwalk.h"
41
42 #include "array_t.h"
43 #include "list.h"
44 #include "pset.h"
45 #include "pmap.h"
46 #include "pdeq.h"
47 #include "xmalloc.h"
48 #include "pqueue.h"
49
50 #include "irouts.h"
51 #include "irloop_t.h"
52 #include "irbackedge_t.h"
53 #include "opt_init.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 #include "iropt_dbg.h"
64 #include "irpass_t.h"
65 #include "irnodemap.h"
66
67 DEBUG_ONLY(static firm_dbg_module_t *dbg;)
68
69 /*------------------------------------------------------------------*/
70 /* Routines for dead node elimination / copying garbage collection  */
71 /* of the obstack.                                                  */
72 /*------------------------------------------------------------------*/
73
74 /**
75  * Remember the new node in the old node by using a field all nodes have.
76  */
77 static void set_new_node(ir_node *node, ir_node *new_node)
78 {
79         set_irn_link(node, new_node);
80 }
81
82 /**
83  * Get this new node, before the old node is forgotten.
84  */
85 static inline ir_node *get_new_node(ir_node *old_node)
86 {
87         assert(irn_visited(old_node));
88         return (ir_node*) get_irn_link(old_node);
89 }
90
91 /*--------------------------------------------------------------------*/
92 /*  Functionality for inlining                                         */
93 /*--------------------------------------------------------------------*/
94
95 /**
96  * Copy node for inlineing.  Updates attributes that change when
97  * inlineing but not for dead node elimination.
98  *
99  * Copies the node by calling copy_node() and then updates the entity if
100  * it's a local one.  env must be a pointer of the frame type of the
101  * inlined procedure. The new entities must be in the link field of
102  * the entities.
103  */
104 static void copy_node_inline(ir_node *node, void *env)
105 {
106         ir_graph *new_irg  = (ir_graph*) env;
107         ir_node  *new_node = irn_copy_into_irg(node, new_irg);
108
109         set_new_node(node, new_node);
110         if (is_Sel(node)) {
111                 ir_graph  *old_irg        = get_irn_irg(node);
112                 ir_type   *old_frame_type = get_irg_frame_type(old_irg);
113                 ir_entity *old_entity     = get_Sel_entity(node);
114                 assert(is_Sel(new_node));
115                 /* use copied entities from the new frame */
116                 if (get_entity_owner(old_entity) == old_frame_type) {
117                         ir_entity *new_entity = (ir_entity*)get_entity_link(old_entity);
118                         assert(new_entity != NULL);
119                         set_Sel_entity(new_node, new_entity);
120                 }
121         } else if (is_Block(new_node)) {
122                 new_node->attr.block.irg.irg = new_irg;
123         }
124 }
125
126 static void set_preds_inline(ir_node *node, void *env)
127 {
128         ir_node *new_node;
129
130         irn_rewire_inputs(node);
131
132         /* move constants into start block */
133         new_node = get_new_node(node);
134         if (is_irn_start_block_placed(new_node)) {
135                 ir_graph *new_irg     = (ir_graph *) env;
136                 ir_node  *start_block = get_irg_start_block(new_irg);
137                 set_nodes_block(new_node, start_block);
138         }
139 }
140
141 /**
142  * Walker: checks if P_value_arg_base is used.
143  */
144 static void find_addr(ir_node *node, void *env)
145 {
146         bool *allow_inline = (bool*)env;
147
148         if (is_Block(node) && get_Block_entity(node)) {
149                 /**
150                  * Currently we can't handle blocks whose address was taken correctly
151                  * when inlining
152                  */
153                 *allow_inline = false;
154         } else if (is_Sel(node)) {
155                 ir_graph *irg = current_ir_graph;
156                 if (get_Sel_ptr(node) == get_irg_frame(irg)) {
157                         /* access to frame */
158                         ir_entity *ent = get_Sel_entity(node);
159                         if (get_entity_owner(ent) != get_irg_frame_type(irg)) {
160                                 /* access to value_type */
161                                 *allow_inline = false;
162                         }
163                         if (is_parameter_entity(ent)) {
164                                 *allow_inline = false;
165                         }
166                 }
167         } else if (is_Alloc(node) && get_Alloc_where(node) == stack_alloc) {
168                 /* From GCC:
169                  * Refuse to inline alloca call unless user explicitly forced so as this
170                  * may change program's memory overhead drastically when the function
171                  * using alloca is called in loop.  In GCC present in SPEC2000 inlining
172                  * into schedule_block cause it to require 2GB of ram instead of 256MB.
173                  *
174                  * Sorrily this is true with our implementation also.
175                  * Moreover, we cannot differentiate between alloca() and VLA yet, so
176                  * this disables inlining of functions using VLA (which are completely
177                  * save).
178                  *
179                  * 2 Solutions:
180                  * - add a flag to the Alloc node for "real" alloca() calls
181                  * - add a new Stack-Restore node at the end of a function using
182                  *   alloca()
183                  */
184                 *allow_inline = false;
185         }
186 }
187
188 /**
189  * Check if we can inline a given call.
190  * Currently, we cannot inline two cases:
191  * - call with compound arguments
192  * - graphs that take the address of a parameter
193  *
194  * check these conditions here
195  */
196 static bool can_inline(ir_node *call, ir_graph *called_graph)
197 {
198         ir_entity          *called      = get_irg_entity(called_graph);
199         ir_type            *called_type = get_entity_type(called);
200         ir_type            *call_type   = get_Call_type(call);
201         size_t              n_params    = get_method_n_params(called_type);
202         size_t              n_arguments = get_method_n_params(call_type);
203         size_t              n_res       = get_method_n_ress(called_type);
204         mtp_additional_properties props = get_entity_additional_properties(called);
205         size_t              i;
206         bool                res;
207
208         if (props & mtp_property_noinline)
209                 return false;
210
211         if (n_arguments != n_params) {
212                 /* this is a bad feature of C: without a prototype, we can
213                  * call a function with less parameters than needed. Currently
214                  * we don't support this, although we could use Unknown than. */
215                 return false;
216         }
217         if (n_res != get_method_n_ress(call_type)) {
218                 return false;
219         }
220
221         /* Argh, compiling C has some bad consequences:
222          * It is implementation dependent what happens in that case.
223          * We support inlining, if the bitsize of the types matches AND
224          * the same arithmetic is used. */
225         for (i = 0; i < n_params; ++i) {
226                 ir_type *param_tp = get_method_param_type(called_type, i);
227                 ir_type *arg_tp   = get_method_param_type(call_type, i);
228
229                 if (param_tp != arg_tp) {
230                         ir_mode *pmode = get_type_mode(param_tp);
231                         ir_mode *amode = get_type_mode(arg_tp);
232
233                         if (pmode == NULL || amode == NULL)
234                                 return false;
235                         if (get_mode_size_bits(pmode) != get_mode_size_bits(amode))
236                                 return false;
237                         if (get_mode_arithmetic(pmode) != get_mode_arithmetic(amode))
238                                 return false;
239                         /* otherwise we can simply "reinterpret" the bits */
240                 }
241         }
242         for (i = 0; i < n_res; ++i) {
243                 ir_type *decl_res_tp = get_method_res_type(called_type, i);
244                 ir_type *used_res_tp = get_method_res_type(call_type, i);
245
246                 if (decl_res_tp != used_res_tp) {
247                         ir_mode *decl_mode = get_type_mode(decl_res_tp);
248                         ir_mode *used_mode = get_type_mode(used_res_tp);
249                         if (decl_mode == NULL || used_mode == NULL)
250                                 return false;
251                         if (get_mode_size_bits(decl_mode) != get_mode_size_bits(used_mode))
252                                 return false;
253                         if (get_mode_arithmetic(decl_mode) != get_mode_arithmetic(used_mode))
254                                 return false;
255                         /* otherwise we can "reinterpret" the bits */
256                 }
257         }
258
259         /* check parameters for compound arguments */
260         for (i = 0; i < n_params; ++i) {
261                 ir_type *p_type = get_method_param_type(call_type, i);
262
263                 if (is_compound_type(p_type) || is_Array_type(p_type))
264                         return false;
265         }
266
267         /* check results for compound arguments */
268         for (i = 0; i < n_res; ++i) {
269                 ir_type *r_type = get_method_res_type(call_type, i);
270
271                 if (is_compound_type(r_type) || is_Array_type(r_type))
272                         return false;
273         }
274
275         res = true;
276         irg_walk_graph(called_graph, find_addr, NULL, &res);
277
278         return res;
279 }
280
281 enum exc_mode {
282         exc_handler,    /**< There is a handler. */
283         exc_no_handler  /**< Exception handling not represented. */
284 };
285
286 /**
287  * copy all entities on the stack frame on 1 irg to the stackframe of another.
288  * Sets entity links of the old entities to the copies
289  */
290 static void copy_frame_entities(ir_graph *from, ir_graph *to)
291 {
292         ir_type *from_frame = get_irg_frame_type(from);
293         ir_type *to_frame   = get_irg_frame_type(to);
294         size_t   n_members  = get_class_n_members(from_frame);
295         size_t   i;
296         assert(from_frame != to_frame);
297
298         for (i = 0; i < n_members; ++i) {
299                 ir_entity *old_ent = get_class_member(from_frame, i);
300                 ir_entity *new_ent = copy_entity_own(old_ent, to_frame);
301                 set_entity_link(old_ent, new_ent);
302                 assert (!is_parameter_entity(old_ent));
303         }
304 }
305
306 /* Inlines a method at the given call site. */
307 int inline_method(ir_node *const call, ir_graph *called_graph)
308 {
309         /* we cannot inline some types of calls */
310         if (! can_inline(call, called_graph))
311                 return 0;
312
313         /* We cannot inline a recursive call. The graph must be copied before
314          * the call the inline_method() using create_irg_copy(). */
315         ir_graph *irg = get_irn_irg(call);
316         if (called_graph == irg)
317                 return 0;
318
319         ir_entity *ent      = get_irg_entity(called_graph);
320         ir_type   *mtp      = get_entity_type(ent);
321         ir_type   *ctp      = get_Call_type(call);
322         int        n_params = get_method_n_params(mtp);
323
324         ir_graph *rem = current_ir_graph;
325         current_ir_graph = irg;
326
327         DB((dbg, LEVEL_1, "Inlining %+F(%+F) into %+F\n", call, called_graph, irg));
328
329         /* optimizations can cause problems when allocating new nodes */
330         int rem_opt = get_opt_optimize();
331         set_optimize(0);
332
333         /* Handle graph state */
334         assert(get_irg_pinned(irg) == op_pin_state_pinned);
335         assert(get_irg_pinned(called_graph) == op_pin_state_pinned);
336         clear_irg_properties(irg, IR_GRAPH_PROPERTY_CONSISTENT_DOMINANCE
337                            | IR_GRAPH_PROPERTY_CONSISTENT_ENTITY_USAGE);
338         set_irg_callee_info_state(irg, irg_callee_info_inconsistent);
339         clear_irg_properties(irg, IR_GRAPH_PROPERTY_CONSISTENT_ENTITY_USAGE);
340         edges_deactivate(irg);
341
342         /* here we know we WILL inline, so inform the statistics */
343         hook_inline(call, called_graph);
344
345         /* -- Decide how to handle exception control flow: Is there a handler
346            for the Call node, or do we branch directly to End on an exception?
347            exc_handling:
348            0 There is a handler.
349            2 Exception handling not represented in Firm. -- */
350         ir_node *Xproj = NULL;
351         for (ir_node *proj = (ir_node*)get_irn_link(call); proj != NULL;
352                  proj = (ir_node*)get_irn_link(proj)) {
353                 long proj_nr = get_Proj_proj(proj);
354                 if (proj_nr == pn_Call_X_except) Xproj = proj;
355         }
356         enum exc_mode exc_handling = Xproj != NULL ? exc_handler : exc_no_handler;
357
358         /* create the argument tuple */
359         ir_node **args_in = ALLOCAN(ir_node*, n_params);
360
361         ir_node *block = get_nodes_block(call);
362         for (int i = n_params - 1; i >= 0; --i) {
363                 ir_node *arg      = get_Call_param(call, i);
364                 ir_type *param_tp = get_method_param_type(mtp, i);
365                 ir_mode *mode     = get_type_mode(param_tp);
366
367                 if (mode != get_irn_mode(arg)) {
368                         arg = new_r_Conv(block, arg, mode);
369                 }
370                 args_in[i] = arg;
371         }
372
373         /* the procedure and later replaces the Start node of the called graph.
374          * Post_call is the old Call node and collects the results of the called
375          * graph. Both will end up being a tuple. */
376         ir_node *post_bl = get_nodes_block(call);
377         /* XxMxPxPxPxT of Start + parameter of Call */
378         ir_node *in[pn_Start_max+1];
379         in[pn_Start_M]              = get_Call_mem(call);
380         in[pn_Start_X_initial_exec] = new_r_Jmp(post_bl);
381         in[pn_Start_P_frame_base]   = get_irg_frame(irg);
382         in[pn_Start_T_args]         = new_r_Tuple(post_bl, n_params, args_in);
383         ir_node *pre_call = new_r_Tuple(post_bl, pn_Start_max+1, in);
384
385         /* --
386            The new block gets the ins of the old block, pre_call and all its
387            predecessors and all Phi nodes. -- */
388         part_block(pre_call);
389
390         /* increment visited flag for later walk */
391         inc_irg_visited(called_graph);
392
393         /* link some nodes to nodes in the current graph so instead of copying
394          * the linked nodes will get used.
395          * So the copier will use the created Tuple instead of copying the start
396          * node, similar for singleton nodes like NoMem and Bad.
397          * Note: this will prohibit predecessors to be copied - only do it for
398          *       nodes without predecessors */
399         ir_node *start_block = get_irg_start_block(called_graph);
400         set_new_node(start_block, get_nodes_block(pre_call));
401         mark_irn_visited(start_block);
402
403         ir_node *start = get_irg_start(called_graph);
404         set_new_node(start, pre_call);
405         mark_irn_visited(start);
406
407         ir_node *nomem = get_irg_no_mem(called_graph);
408         set_new_node(nomem, get_irg_no_mem(irg));
409         mark_irn_visited(nomem);
410
411         /* entitiy link is used to link entities on old stackframe to the
412          * new stackframe */
413         irp_reserve_resources(irp, IRP_RESOURCE_ENTITY_LINK);
414
415         /* copy entities and nodes */
416         assert(!irn_visited(get_irg_end(called_graph)));
417         copy_frame_entities(called_graph, irg);
418         irg_walk_core(get_irg_end(called_graph), copy_node_inline, set_preds_inline,
419                       irg);
420
421         irp_free_resources(irp, IRP_RESOURCE_ENTITY_LINK);
422
423         /* -- Merge the end of the inlined procedure with the call site -- */
424         /* We will turn the old Call node into a Tuple with the following
425            predecessors:
426            -1:  Block of Tuple.
427            0: Phi of all Memories of Return statements.
428            1: Jmp from new Block that merges the control flow from all exception
429            predecessors of the old end block.
430            2: Tuple of all arguments.
431            3: Phi of Exception memories.
432            In case the old Call directly branches to End on an exception we don't
433            need the block merging all exceptions nor the Phi of the exception
434            memories.
435         */
436
437         /* Precompute some values */
438         ir_node *end_bl = get_new_node(get_irg_end_block(called_graph));
439         ir_node *end    = get_new_node(get_irg_end(called_graph));
440         int      arity  = get_Block_n_cfgpreds(end_bl); /* arity = n_exc + n_ret  */
441         int      n_res  = get_method_n_ress(get_Call_type(call));
442
443         ir_node **res_pred = XMALLOCN(ir_node*, n_res);
444         ir_node **cf_pred  = XMALLOCN(ir_node*, arity);
445
446         /* archive keepalives */
447         int irn_arity = get_irn_arity(end);
448         for (int i = 0; i < irn_arity; i++) {
449                 ir_node *ka = get_End_keepalive(end, i);
450                 if (! is_Bad(ka))
451                         add_End_keepalive(get_irg_end(irg), ka);
452         }
453
454         /* replace Return nodes by Jump nodes */
455         int n_ret = 0;
456         for (int i = 0; i < arity; i++) {
457                 ir_node *ret = get_Block_cfgpred(end_bl, i);
458                 if (is_Return(ret)) {
459                         ir_node *block = get_nodes_block(ret);
460                         cf_pred[n_ret] = new_r_Jmp(block);
461                         n_ret++;
462                 }
463         }
464         set_irn_in(post_bl, n_ret, cf_pred);
465
466         /* build a Tuple for all results of the method.
467          * add Phi node if there was more than one Return. */
468         /* First the Memory-Phi */
469         int n_mem_phi = 0;
470         for (int i = 0; i < arity; i++) {
471                 ir_node *ret = get_Block_cfgpred(end_bl, i);
472                 if (is_Return(ret)) {
473                         cf_pred[n_mem_phi++] = get_Return_mem(ret);
474                 }
475                 /* memory output for some exceptions is directly connected to End */
476                 if (is_Call(ret)) {
477                         cf_pred[n_mem_phi++] = new_r_Proj(ret, mode_M, 3);
478                 } else if (is_fragile_op(ret)) {
479                         /* We rely that all cfops have the memory output at the same position. */
480                         cf_pred[n_mem_phi++] = new_r_Proj(ret, mode_M, 0);
481                 } else if (is_Raise(ret)) {
482                         cf_pred[n_mem_phi++] = new_r_Proj(ret, mode_M, 1);
483                 }
484         }
485         ir_node *const call_mem = new_r_Phi(post_bl, n_mem_phi, cf_pred, mode_M);
486         /* Conserve Phi-list for further inlinings -- but might be optimized */
487         if (get_nodes_block(call_mem) == post_bl) {
488                 set_irn_link(call_mem, get_irn_link(post_bl));
489                 set_irn_link(post_bl, call_mem);
490         }
491         /* Now the real results */
492         ir_node *call_res;
493         if (n_res > 0) {
494                 for (int j = 0; j < n_res; j++) {
495                         ir_type *res_type = get_method_res_type(ctp, j);
496                         ir_mode *res_mode = get_type_mode(res_type);
497                         int n_ret = 0;
498                         for (int i = 0; i < arity; i++) {
499                                 ir_node *ret = get_Block_cfgpred(end_bl, i);
500                                 if (is_Return(ret)) {
501                                         ir_node *res = get_Return_res(ret, j);
502                                         if (get_irn_mode(res) != res_mode) {
503                                                 ir_node *block = get_nodes_block(res);
504                                                 res = new_r_Conv(block, res, res_mode);
505                                         }
506                                         cf_pred[n_ret] = res;
507                                         n_ret++;
508                                 }
509                         }
510                         ir_node *const phi = n_ret > 0
511                                 ? new_r_Phi(post_bl, n_ret, cf_pred, res_mode)
512                                 : new_r_Bad(irg, res_mode);
513                         res_pred[j] = phi;
514                         /* Conserve Phi-list for further inlinings -- but might be optimized */
515                         if (get_nodes_block(phi) == post_bl) {
516                                 set_Phi_next(phi, get_Block_phis(post_bl));
517                                 set_Block_phis(post_bl, phi);
518                         }
519                 }
520                 call_res = new_r_Tuple(post_bl, n_res, res_pred);
521         } else {
522                 call_res = new_r_Bad(irg, mode_T);
523         }
524         /* handle the regular call */
525         ir_node *const call_x_reg = new_r_Jmp(post_bl);
526
527         /* Finally the exception control flow.
528            We have two possible situations:
529            First if the Call branches to an exception handler:
530            We need to add a Phi node to
531            collect the memory containing the exception objects.  Further we need
532            to add another block to get a correct representation of this Phi.  To
533            this block we add a Jmp that resolves into the X output of the Call
534            when the Call is turned into a tuple.
535            Second: There is no exception edge. Just add all inlined exception
536            branches to the End node.
537          */
538         ir_node *call_x_exc;
539         if (exc_handling == exc_handler) {
540                 int n_exc = 0;
541                 for (int i = 0; i < arity; i++) {
542                         ir_node *ret = get_Block_cfgpred(end_bl, i);
543                         ir_node *irn = skip_Proj(ret);
544                         if (is_fragile_op(irn) || is_Raise(irn)) {
545                                 cf_pred[n_exc] = ret;
546                                 ++n_exc;
547                         }
548                 }
549                 if (n_exc > 0) {
550                         if (n_exc == 1) {
551                                 /* simple fix */
552                                 call_x_exc = cf_pred[0];
553                         } else {
554                                 ir_node *block = new_r_Block(irg, n_exc, cf_pred);
555                                 call_x_exc = new_r_Jmp(block);
556                         }
557                 } else {
558                         call_x_exc = new_r_Bad(irg, mode_X);
559                 }
560         } else {
561                 /* assert(exc_handling == 1 || no exceptions. ) */
562                 int n_exc = 0;
563                 for (int i = 0; i < arity; i++) {
564                         ir_node *ret = get_Block_cfgpred(end_bl, i);
565                         ir_node *irn = skip_Proj(ret);
566
567                         if (is_fragile_op(irn) || is_Raise(irn)) {
568                                 cf_pred[n_exc] = ret;
569                                 n_exc++;
570                         }
571                 }
572                 ir_node  *main_end_bl       = get_irg_end_block(irg);
573                 int       main_end_bl_arity = get_irn_arity(main_end_bl);
574                 ir_node **end_preds         = XMALLOCN(ir_node*, n_exc+main_end_bl_arity);
575
576                 for (int i = 0; i < main_end_bl_arity; ++i)
577                         end_preds[i] = get_irn_n(main_end_bl, i);
578                 for (int i = 0; i < n_exc; ++i)
579                         end_preds[main_end_bl_arity + i] = cf_pred[i];
580                 set_irn_in(main_end_bl, n_exc + main_end_bl_arity, end_preds);
581                 call_x_exc = new_r_Bad(irg, mode_X);
582                 free(end_preds);
583         }
584         free(res_pred);
585         free(cf_pred);
586
587         ir_node *const call_in[] = {
588                 [pn_Call_M]         = call_mem,
589                 [pn_Call_T_result]  = call_res,
590                 [pn_Call_X_regular] = call_x_reg,
591                 [pn_Call_X_except]  = call_x_exc,
592         };
593         turn_into_tuple(call, ARRAY_SIZE(call_in), call_in);
594
595         /* --  Turn CSE back on. -- */
596         set_optimize(rem_opt);
597         current_ir_graph = rem;
598
599         return 1;
600 }
601
602 /********************************************************************/
603 /* Apply inlining to small methods.                                 */
604 /********************************************************************/
605
606 static struct obstack  temp_obst;
607
608 /** Represents a possible inlinable call in a graph. */
609 typedef struct call_entry {
610         ir_node    *call;       /**< The Call node. */
611         ir_graph   *callee;     /**< The callee IR-graph. */
612         list_head  list;        /**< List head for linking the next one. */
613         int        loop_depth;  /**< The loop depth of this call. */
614         int        benefice;    /**< The calculated benefice of this call. */
615         unsigned   local_adr:1; /**< Set if this call gets an address of a local variable. */
616         unsigned   all_const:1; /**< Set if this call has only constant parameters. */
617 } call_entry;
618
619 /**
620  * Returns the irg called from a Call node. If the irg is not
621  * known, NULL is returned.
622  *
623  * @param call  the call node
624  */
625 static ir_graph *get_call_called_irg(ir_node *call)
626 {
627         ir_node *addr;
628
629         addr = get_Call_ptr(call);
630         if (is_SymConst_addr_ent(addr)) {
631                 ir_entity *ent = get_SymConst_entity(addr);
632                 /* we don't know which function gets finally bound to a weak symbol */
633                 if (get_entity_linkage(ent) & IR_LINKAGE_WEAK)
634                         return NULL;
635
636                 return get_entity_irg(ent);
637         }
638
639         return NULL;
640 }
641
642 /**
643  * Environment for inlining irgs.
644  */
645 typedef struct {
646         list_head calls;             /**< List of of all call nodes in this graph. */
647         unsigned  *local_weights;    /**< Once allocated, the beneficial weight for transmitting local addresses. */
648         unsigned  n_nodes;           /**< Number of nodes in graph except Id, Tuple, Proj, Start, End. */
649         unsigned  n_blocks;          /**< Number of Blocks in graph without Start and End block. */
650         unsigned  n_nodes_orig;      /**< for statistics */
651         unsigned  n_call_nodes;      /**< Number of Call nodes in the graph. */
652         unsigned  n_call_nodes_orig; /**< for statistics */
653         unsigned  n_callers;         /**< Number of known graphs that call this graphs. */
654         unsigned  n_callers_orig;    /**< for statistics */
655         unsigned  got_inline:1;      /**< Set, if at least one call inside this graph was inlined. */
656         unsigned  recursive:1;       /**< Set, if this function is self recursive. */
657 } inline_irg_env;
658
659 /**
660  * Allocate a new environment for inlining.
661  */
662 static inline_irg_env *alloc_inline_irg_env(void)
663 {
664         inline_irg_env *env    = OALLOC(&temp_obst, inline_irg_env);
665         INIT_LIST_HEAD(&env->calls);
666         env->local_weights     = NULL;
667         env->n_nodes           = -2; /* do not count count Start, End */
668         env->n_blocks          = -2; /* do not count count Start, End Block */
669         env->n_nodes_orig      = -2; /* do not count Start, End */
670         env->n_call_nodes      = 0;
671         env->n_call_nodes_orig = 0;
672         env->n_callers         = 0;
673         env->n_callers_orig    = 0;
674         env->got_inline        = 0;
675         env->recursive         = 0;
676         return env;
677 }
678
679 typedef struct walker_env {
680         inline_irg_env *x;     /**< the inline environment */
681         char ignore_runtime;   /**< the ignore runtime flag */
682         char ignore_callers;   /**< if set, do change callers data */
683 } wenv_t;
684
685 /**
686  * post-walker: collect all calls in the inline-environment
687  * of a graph and sum some statistics.
688  */
689 static void collect_calls2(ir_node *call, void *ctx)
690 {
691         wenv_t         *env = (wenv_t*)ctx;
692         inline_irg_env *x = env->x;
693         unsigned        code = get_irn_opcode(call);
694         ir_graph       *callee;
695         call_entry     *entry;
696
697         /* count meaningful nodes in irg */
698         if (code != iro_Proj && code != iro_Tuple && code != iro_Sync) {
699                 if (code != iro_Block) {
700                         ++x->n_nodes;
701                         ++x->n_nodes_orig;
702                 } else {
703                         ++x->n_blocks;
704                 }
705         }
706
707         if (code != iro_Call) return;
708
709         /* check, if it's a runtime call */
710         if (env->ignore_runtime) {
711                 ir_node *symc = get_Call_ptr(call);
712
713                 if (is_SymConst_addr_ent(symc)) {
714                         ir_entity *ent = get_SymConst_entity(symc);
715
716                         if (get_entity_additional_properties(ent) & mtp_property_runtime)
717                                 return;
718                 }
719         }
720
721         /* collect all call nodes */
722         ++x->n_call_nodes;
723         ++x->n_call_nodes_orig;
724
725         callee = get_call_called_irg(call);
726         if (callee != NULL) {
727                 if (! env->ignore_callers) {
728                         inline_irg_env *callee_env = (inline_irg_env*)get_irg_link(callee);
729                         /* count all static callers */
730                         ++callee_env->n_callers;
731                         ++callee_env->n_callers_orig;
732                 }
733                 if (callee == current_ir_graph)
734                         x->recursive = 1;
735
736                 /* link it in the list of possible inlinable entries */
737                 entry = OALLOC(&temp_obst, call_entry);
738                 entry->call       = call;
739                 entry->callee     = callee;
740                 entry->loop_depth = get_irn_loop(get_nodes_block(call))->depth;
741                 entry->benefice   = 0;
742                 entry->local_adr  = 0;
743                 entry->all_const  = 0;
744
745                 list_add_tail(&entry->list, &x->calls);
746         }
747 }
748
749 /**
750  * Duplicate a call entry.
751  *
752  * @param entry     the original entry to duplicate
753  * @param new_call  the new call node
754  * @param loop_depth_delta
755  *                  delta value for the loop depth
756  */
757 static call_entry *duplicate_call_entry(const call_entry *entry,
758                                         ir_node *new_call, int loop_depth_delta)
759 {
760         call_entry *nentry = OALLOC(&temp_obst, call_entry);
761         nentry->call       = new_call;
762         nentry->callee     = entry->callee;
763         nentry->benefice   = entry->benefice;
764         nentry->loop_depth = entry->loop_depth + loop_depth_delta;
765         nentry->local_adr  = entry->local_adr;
766         nentry->all_const  = entry->all_const;
767
768         return nentry;
769 }
770
771 /**
772  * Calculate the parameter weights for transmitting the address of a local variable.
773  */
774 static unsigned calc_method_local_weight(ir_node *arg)
775 {
776         int      j;
777         unsigned v, weight = 0;
778
779         for (unsigned i = get_irn_n_outs(arg); i-- > 0; ) {
780                 ir_node *succ = get_irn_out(arg, i);
781
782                 switch (get_irn_opcode(succ)) {
783                 case iro_Load:
784                 case iro_Store:
785                         /* Loads and Store can be removed */
786                         weight += 3;
787                         break;
788                 case iro_Sel:
789                         /* check if all args are constant */
790                         for (j = get_Sel_n_indexs(succ) - 1; j >= 0; --j) {
791                                 ir_node *idx = get_Sel_index(succ, j);
792                                 if (! is_Const(idx))
793                                         return 0;
794                         }
795                         /* Check users on this Sel. Note: if a 0 is returned here, there was
796                            some unsupported node. */
797                         v = calc_method_local_weight(succ);
798                         if (v == 0)
799                                 return 0;
800                         /* we can kill one Sel with constant indexes, this is cheap */
801                         weight += v + 1;
802                         break;
803                 case iro_Id:
804                         /* when looking backward we might find Id nodes */
805                         weight += calc_method_local_weight(succ);
806                         break;
807                 case iro_Tuple:
808                         /* unoptimized tuple */
809                         for (j = get_Tuple_n_preds(succ) - 1; j >= 0; --j) {
810                                 ir_node *pred = get_Tuple_pred(succ, j);
811                                 if (pred == arg) {
812                                         /* look for Proj(j) */
813                                         for (unsigned k = get_irn_n_outs(succ); k-- > 0; ) {
814                                                 ir_node *succ_succ = get_irn_out(succ, k);
815                                                 if (is_Proj(succ_succ)) {
816                                                         if (get_Proj_proj(succ_succ) == j) {
817                                                                 /* found */
818                                                                 weight += calc_method_local_weight(succ_succ);
819                                                         }
820                                                 } else {
821                                                         /* this should NOT happen */
822                                                         return 0;
823                                                 }
824                                         }
825                                 }
826                         }
827                         break;
828                 default:
829                         /* any other node: unsupported yet or bad. */
830                         return 0;
831                 }
832         }
833         return weight;
834 }
835
836 /**
837  * Calculate the parameter weights for transmitting the address of a local variable.
838  */
839 static void analyze_irg_local_weights(inline_irg_env *env, ir_graph *irg)
840 {
841         ir_entity *ent = get_irg_entity(irg);
842         ir_type  *mtp;
843         size_t   nparams;
844         long     proj_nr;
845         ir_node  *irg_args, *arg;
846
847         mtp      = get_entity_type(ent);
848         nparams  = get_method_n_params(mtp);
849
850         /* allocate a new array. currently used as 'analysed' flag */
851         env->local_weights = NEW_ARR_D(unsigned, &temp_obst, nparams);
852
853         /* If the method haven't parameters we have nothing to do. */
854         if (nparams <= 0)
855                 return;
856
857         assure_irg_outs(irg);
858         irg_args = get_irg_args(irg);
859         for (unsigned i = get_irn_n_outs(irg_args); i-- > 0; ) {
860                 arg     = get_irn_out(irg_args, i);
861                 proj_nr = get_Proj_proj(arg);
862                 env->local_weights[proj_nr] = calc_method_local_weight(arg);
863         }
864 }
865
866 /**
867  * Calculate the benefice for transmitting an local variable address.
868  * After inlining, the local variable might be transformed into a
869  * SSA variable by scalar_replacement().
870  */
871 static unsigned get_method_local_adress_weight(ir_graph *callee, size_t pos)
872 {
873         inline_irg_env *env = (inline_irg_env*)get_irg_link(callee);
874
875         if (env->local_weights == NULL)
876                 analyze_irg_local_weights(env, callee);
877
878         if (pos < ARR_LEN(env->local_weights))
879                 return env->local_weights[pos];
880         return 0;
881 }
882
883 /**
884  * Calculate a benefice value for inlining the given call.
885  *
886  * @param call       the call node we have to inspect
887  * @param callee     the called graph
888  */
889 static int calc_inline_benefice(call_entry *entry, ir_graph *callee)
890 {
891         ir_node   *call = entry->call;
892         ir_entity *ent  = get_irg_entity(callee);
893         ir_type   *callee_frame;
894         size_t    i, n_members, n_params;
895         ir_node   *frame_ptr;
896         ir_type   *mtp;
897         int       weight = 0;
898         int       all_const;
899         unsigned  cc, v;
900
901         inline_irg_env *callee_env;
902
903         mtp_additional_properties props = get_entity_additional_properties(ent);
904         if (props & mtp_property_noinline) {
905                 DB((dbg, LEVEL_2, "In %+F Call to %+F: inlining forbidden\n",
906                     call, callee));
907                 return entry->benefice = INT_MIN;
908         }
909
910         callee_frame = get_irg_frame_type(callee);
911         n_members = get_class_n_members(callee_frame);
912         for (i = 0; i < n_members; ++i) {
913                 ir_entity *frame_ent = get_class_member(callee_frame, i);
914                 if (is_parameter_entity(frame_ent)) {
915                         // TODO inliner should handle parameter entities by inserting Store operations
916                         DB((dbg, LEVEL_2, "In %+F Call to %+F: inlining forbidden due to parameter entity\n", call, callee));
917                         add_entity_additional_properties(ent, mtp_property_noinline);
918                         return entry->benefice = INT_MIN;
919                 }
920         }
921
922         if (props & mtp_property_noreturn) {
923                 DB((dbg, LEVEL_2, "In %+F Call to %+F: not inlining noreturn or weak\n",
924                     call, callee));
925                 return entry->benefice = INT_MIN;
926         }
927
928         /* costs for every passed parameter */
929         n_params = get_Call_n_params(call);
930         mtp      = get_entity_type(ent);
931         cc       = get_method_calling_convention(mtp);
932         if (cc & cc_reg_param) {
933                 /* register parameter, smaller costs for register parameters */
934                 size_t max_regs = cc & ~cc_bits;
935
936                 if (max_regs < n_params)
937                         weight += max_regs * 2 + (n_params - max_regs) * 5;
938                 else
939                         weight += n_params * 2;
940         } else {
941                 /* parameters are passed an stack */
942                 weight += 5 * n_params;
943         }
944
945         /* constant parameters improve the benefice */
946         frame_ptr = get_irg_frame(current_ir_graph);
947         all_const = 1;
948         for (i = 0; i < n_params; ++i) {
949                 ir_node *param = get_Call_param(call, i);
950
951                 if (is_Const(param)) {
952                         weight += get_method_param_weight(ent, i);
953                 } else {
954                         all_const = 0;
955                         if (is_SymConst(param))
956                                 weight += get_method_param_weight(ent, i);
957                         else if (is_Sel(param) && get_Sel_ptr(param) == frame_ptr) {
958                                 /*
959                                  * An address of a local variable is transmitted. After
960                                  * inlining, scalar_replacement might be able to remove the
961                                  * local variable, so honor this.
962                                  */
963                                 v = get_method_local_adress_weight(callee, i);
964                                 weight += v;
965                                 if (v > 0)
966                                         entry->local_adr = 1;
967                         }
968                 }
969         }
970         entry->all_const = all_const;
971
972         callee_env = (inline_irg_env*)get_irg_link(callee);
973         if (callee_env->n_callers == 1 &&
974             callee != current_ir_graph &&
975             !entity_is_externally_visible(ent)) {
976                 weight += 700;
977         }
978
979         /* give a bonus for functions with one block */
980         if (callee_env->n_blocks == 1)
981                 weight = weight * 3 / 2;
982
983         /* and one for small non-recursive functions: we want them to be inlined in mostly every case */
984         if (callee_env->n_nodes < 30 && !callee_env->recursive)
985                 weight += 2000;
986
987         /* and finally for leafs: they do not increase the register pressure
988            because of callee safe registers */
989         if (callee_env->n_call_nodes == 0)
990                 weight += 400;
991
992         /** it's important to inline inner loops first */
993         if (entry->loop_depth > 30)
994                 weight += 30 * 1024;
995         else
996                 weight += entry->loop_depth * 1024;
997
998         /*
999          * All arguments constant is probably a good sign, give an extra bonus
1000          */
1001         if (all_const)
1002                 weight += 1024;
1003
1004         return entry->benefice = weight;
1005 }
1006
1007 typedef struct walk_env_t {
1008         ir_graph **irgs;
1009         size_t   last_irg;
1010 } walk_env_t;
1011
1012 /**
1013  * Callgraph walker, collect all visited graphs.
1014  */
1015 static void callgraph_walker(ir_graph *irg, void *data)
1016 {
1017         walk_env_t *env = (walk_env_t *)data;
1018         env->irgs[env->last_irg++] = irg;
1019 }
1020
1021 /**
1022  * Creates an inline order for all graphs.
1023  *
1024  * @return the list of graphs.
1025  */
1026 static ir_graph **create_irg_list(void)
1027 {
1028         ir_entity  **free_methods;
1029         size_t     n_irgs = get_irp_n_irgs();
1030         walk_env_t env;
1031
1032         cgana(&free_methods);
1033         xfree(free_methods);
1034
1035         compute_callgraph();
1036
1037         env.irgs     = XMALLOCNZ(ir_graph*, n_irgs);
1038         env.last_irg = 0;
1039
1040         callgraph_walk(NULL, callgraph_walker, &env);
1041         assert(n_irgs == env.last_irg);
1042
1043         free_callgraph();
1044
1045         return env.irgs;
1046 }
1047
1048 /**
1049  * Push a call onto the priority list if its benefice is big enough.
1050  *
1051  * @param pqueue   the priority queue of calls
1052  * @param call     the call entry
1053  * @param inlien_threshold
1054  *                 the threshold value
1055  */
1056 static void maybe_push_call(pqueue_t *pqueue, call_entry *call,
1057                             int inline_threshold)
1058 {
1059         ir_graph *callee   = call->callee;
1060         int       benefice = calc_inline_benefice(call, callee);
1061
1062         DB((dbg, LEVEL_2, "In %+F Call %+F to %+F has benefice %d\n",
1063             get_irn_irg(call->call), call->call, callee, benefice));
1064
1065         ir_entity                *ent   = get_irg_entity(callee);
1066         mtp_additional_properties props = get_entity_additional_properties(ent);
1067         if (!(props & mtp_property_always_inline) && benefice < inline_threshold) {
1068                 return;
1069         }
1070
1071         pqueue_put(pqueue, call, benefice);
1072 }
1073
1074 /**
1075  * Try to inline calls into a graph.
1076  *
1077  * @param irg      the graph into which we inline
1078  * @param maxsize  do NOT inline if the size of irg gets
1079  *                 bigger than this amount
1080  * @param inline_threshold
1081  *                 threshold value for inline decision
1082  * @param copied_graphs
1083  *                 map containing copied of recursive graphs
1084  */
1085 static void inline_into(ir_graph *irg, unsigned maxsize,
1086                         int inline_threshold, pmap *copied_graphs)
1087 {
1088         int            phiproj_computed = 0;
1089         inline_irg_env *env = (inline_irg_env*)get_irg_link(irg);
1090         wenv_t         wenv;
1091         pqueue_t       *pqueue;
1092
1093         if (env->n_call_nodes == 0)
1094                 return;
1095
1096         if (env->n_nodes > maxsize) {
1097                 DB((dbg, LEVEL_2, "%+F: too big (%d)\n", irg, env->n_nodes));
1098                 return;
1099         }
1100
1101         current_ir_graph = irg;
1102         ir_reserve_resources(irg, IR_RESOURCE_IRN_LINK|IR_RESOURCE_PHI_LIST);
1103
1104         /* put irgs into the pqueue */
1105         pqueue = new_pqueue();
1106
1107         list_for_each_entry(call_entry, curr_call, &env->calls, list) {
1108                 assert(is_Call(curr_call->call));
1109                 maybe_push_call(pqueue, curr_call, inline_threshold);
1110         }
1111
1112         /* note that the list of possible calls is updated during the process */
1113         while (!pqueue_empty(pqueue)) {
1114                 int                 did_inline;
1115                 call_entry          *curr_call  = (call_entry*)pqueue_pop_front(pqueue);
1116                 ir_graph            *callee     = curr_call->callee;
1117                 ir_node             *call_node  = curr_call->call;
1118                 inline_irg_env      *callee_env = (inline_irg_env*)get_irg_link(callee);
1119                 ir_entity           *ent        = get_irg_entity(callee);
1120                 mtp_additional_properties props
1121                         = get_entity_additional_properties(ent);
1122                 ir_graph            *calleee;
1123                 int                 loop_depth;
1124
1125                 if (!(props & mtp_property_always_inline)
1126                     && env->n_nodes + callee_env->n_nodes > maxsize) {
1127                         DB((dbg, LEVEL_2, "%+F: too big (%d) + %+F (%d)\n", irg,
1128                                                 env->n_nodes, callee, callee_env->n_nodes));
1129                         continue;
1130                 }
1131
1132                 calleee = pmap_get(ir_graph, copied_graphs, callee);
1133                 if (calleee != NULL) {
1134                         int benefice = curr_call->benefice;
1135                         /*
1136                          * Reduce the weight for recursive function IFF not all arguments are const.
1137                          * inlining recursive functions is rarely good.
1138                          */
1139                         if (!curr_call->all_const)
1140                                 benefice -= 2000;
1141                         if (benefice < inline_threshold)
1142                                 continue;
1143
1144                         /*
1145                          * Remap callee if we have a copy.
1146                          */
1147                         callee     = calleee;
1148                         callee_env = (inline_irg_env*)get_irg_link(callee);
1149                 }
1150
1151                 if (current_ir_graph == callee) {
1152                         /*
1153                          * Recursive call: we cannot directly inline because we cannot
1154                          * walk the graph and change it. So we have to make a copy of
1155                          * the graph first.
1156                          */
1157                         int benefice = curr_call->benefice;
1158                         ir_graph *copy;
1159
1160                         /*
1161                          * Reduce the weight for recursive function IFF not all arguments are const.
1162                          * inlining recursive functions is rarely good.
1163                          */
1164                         if (!curr_call->all_const)
1165                                 benefice -= 2000;
1166                         if (benefice < inline_threshold)
1167                                 continue;
1168
1169                         ir_free_resources(irg, IR_RESOURCE_IRN_LINK|IR_RESOURCE_PHI_LIST);
1170
1171                         /*
1172                          * No copy yet, create one.
1173                          * Note that recursive methods are never leafs, so it is
1174                          * sufficient to test this condition here.
1175                          */
1176                         copy = create_irg_copy(callee);
1177
1178                         /* create_irg_copy() destroys the Proj links, recompute them */
1179                         phiproj_computed = 0;
1180
1181                         ir_reserve_resources(irg, IR_RESOURCE_IRN_LINK|IR_RESOURCE_PHI_LIST);
1182
1183                         /* allocate a new environment */
1184                         callee_env = alloc_inline_irg_env();
1185                         set_irg_link(copy, callee_env);
1186
1187                         assure_irg_properties(copy, IR_GRAPH_PROPERTY_CONSISTENT_LOOPINFO);
1188                         memset(&wenv, 0, sizeof(wenv));
1189                         wenv.x              = callee_env;
1190                         wenv.ignore_callers = 1;
1191                         irg_walk_graph(copy, NULL, collect_calls2, &wenv);
1192
1193                         /*
1194                          * Enter the entity of the original graph. This is needed
1195                          * for inline_method(). However, note that ent->irg still points
1196                          * to callee, NOT to copy.
1197                          */
1198                         set_irg_entity(copy, get_irg_entity(callee));
1199
1200                         pmap_insert(copied_graphs, callee, copy);
1201                         callee = copy;
1202
1203                         /* we have only one caller: the original graph */
1204                         callee_env->n_callers      = 1;
1205                         callee_env->n_callers_orig = 1;
1206                 }
1207                 if (! phiproj_computed) {
1208                         phiproj_computed = 1;
1209                         collect_phiprojs(current_ir_graph);
1210                 }
1211                 did_inline = inline_method(call_node, callee);
1212                 if (!did_inline)
1213                         continue;
1214
1215                 /* call was inlined, Phi/Projs for current graph must be recomputed */
1216                 phiproj_computed = 0;
1217
1218                 /* remove it from the caller list */
1219                 list_del(&curr_call->list);
1220
1221                 /* callee was inline. Append its call list. */
1222                 env->got_inline = 1;
1223                 --env->n_call_nodes;
1224
1225                 /* we just generate a bunch of new calls */
1226                 loop_depth = curr_call->loop_depth;
1227                 list_for_each_entry(call_entry, centry, &callee_env->calls, list) {
1228                         inline_irg_env *penv = (inline_irg_env*)get_irg_link(centry->callee);
1229                         ir_node        *new_call;
1230                         call_entry     *new_entry;
1231
1232                         /* after we have inlined callee, all called methods inside
1233                          * callee are now called once more */
1234                         ++penv->n_callers;
1235
1236                         /* Note that the src list points to Call nodes in the inlined graph,
1237                          * but we need Call nodes in our graph. Luckily the inliner leaves
1238                          * this information in the link field. */
1239                         new_call = (ir_node*)get_irn_link(centry->call);
1240                         if (get_irn_irg(new_call) != irg) {
1241                                 /* centry->call has not been copied, which means it is dead.
1242                                  * This might happen during inlining, if a const function,
1243                                  * which cannot be inlined is only used as an unused argument
1244                                  * of another function, which is inlined. */
1245                                 continue;
1246                         }
1247                         assert(is_Call(new_call));
1248
1249                         new_entry = duplicate_call_entry(centry, new_call, loop_depth);
1250                         list_add_tail(&new_entry->list, &env->calls);
1251                         maybe_push_call(pqueue, new_entry, inline_threshold);
1252                 }
1253
1254                 env->n_call_nodes += callee_env->n_call_nodes;
1255                 env->n_nodes += callee_env->n_nodes;
1256                 --callee_env->n_callers;
1257         }
1258         ir_free_resources(irg, IR_RESOURCE_IRN_LINK|IR_RESOURCE_PHI_LIST);
1259         del_pqueue(pqueue);
1260 }
1261
1262 /*
1263  * Heuristic inliner. Calculates a benefice value for every call and inlines
1264  * those calls with a value higher than the threshold.
1265  */
1266 void inline_functions(unsigned maxsize, int inline_threshold,
1267                       opt_ptr after_inline_opt)
1268 {
1269         inline_irg_env   *env;
1270         size_t           i, n_irgs;
1271         ir_graph         *rem;
1272         wenv_t           wenv;
1273         pmap             *copied_graphs;
1274         pmap_entry       *pm_entry;
1275         ir_graph         **irgs;
1276
1277         rem = current_ir_graph;
1278         obstack_init(&temp_obst);
1279
1280         irgs = create_irg_list();
1281
1282         /* a map for the copied graphs, used to inline recursive calls */
1283         copied_graphs = pmap_create();
1284
1285         /* extend all irgs by a temporary data structure for inlining. */
1286         n_irgs = get_irp_n_irgs();
1287         for (i = 0; i < n_irgs; ++i)
1288                 set_irg_link(irgs[i], alloc_inline_irg_env());
1289
1290         /* Pre-compute information in temporary data structure. */
1291         wenv.ignore_runtime = 0;
1292         wenv.ignore_callers = 0;
1293         for (i = 0; i < n_irgs; ++i) {
1294                 ir_graph *irg = irgs[i];
1295
1296                 free_callee_info(irg);
1297
1298                 wenv.x = (inline_irg_env*)get_irg_link(irg);
1299                 assure_loopinfo(irg);
1300                 irg_walk_graph(irg, NULL, collect_calls2, &wenv);
1301         }
1302
1303         /* -- and now inline. -- */
1304         for (i = 0; i < n_irgs; ++i) {
1305                 ir_graph *irg = irgs[i];
1306
1307                 inline_into(irg, maxsize, inline_threshold, copied_graphs);
1308         }
1309
1310         for (i = 0; i < n_irgs; ++i) {
1311                 ir_graph *irg = irgs[i];
1312
1313                 env = (inline_irg_env*)get_irg_link(irg);
1314                 if (env->got_inline && after_inline_opt != NULL) {
1315                         /* this irg got calls inlined: optimize it */
1316                         after_inline_opt(irg);
1317                 }
1318                 if (env->got_inline || (env->n_callers_orig != env->n_callers)) {
1319                         DB((dbg, LEVEL_1, "Nodes:%3d ->%3d, calls:%3d ->%3d, callers:%3d ->%3d, -- %s\n",
1320                         env->n_nodes_orig, env->n_nodes, env->n_call_nodes_orig, env->n_call_nodes,
1321                         env->n_callers_orig, env->n_callers,
1322                         get_entity_name(get_irg_entity(irg))));
1323                 }
1324         }
1325
1326         /* kill the copied graphs: we don't need them anymore */
1327         foreach_pmap(copied_graphs, pm_entry) {
1328                 ir_graph *copy = (ir_graph*)pm_entry->value;
1329
1330                 /* reset the entity, otherwise it will be deleted in the next step ... */
1331                 set_irg_entity(copy, NULL);
1332                 free_ir_graph(copy);
1333         }
1334         pmap_destroy(copied_graphs);
1335
1336         xfree(irgs);
1337
1338         obstack_free(&temp_obst, NULL);
1339         current_ir_graph = rem;
1340 }
1341
1342 typedef struct inline_functions_pass_t {
1343         ir_prog_pass_t pass;
1344         unsigned       maxsize;
1345         int            inline_threshold;
1346         opt_ptr        after_inline_opt;
1347 } inline_functions_pass_t;
1348
1349 /**
1350  * Wrapper to run inline_functions() as a ir_prog pass.
1351  */
1352 static int inline_functions_wrapper(ir_prog *irp, void *context)
1353 {
1354         inline_functions_pass_t *pass = (inline_functions_pass_t*)context;
1355
1356         (void)irp;
1357         inline_functions(pass->maxsize, pass->inline_threshold,
1358                          pass->after_inline_opt);
1359         return 0;
1360 }
1361
1362 /* create a ir_prog pass for inline_functions */
1363 ir_prog_pass_t *inline_functions_pass(
1364           const char *name, unsigned maxsize, int inline_threshold,
1365           opt_ptr after_inline_opt)
1366 {
1367         inline_functions_pass_t *pass = XMALLOCZ(inline_functions_pass_t);
1368
1369         pass->maxsize          = maxsize;
1370         pass->inline_threshold = inline_threshold;
1371         pass->after_inline_opt = after_inline_opt;
1372
1373         return def_prog_pass_constructor(
1374                 &pass->pass, name ? name : "inline_functions",
1375                 inline_functions_wrapper);
1376 }
1377
1378 void firm_init_inline(void)
1379 {
1380         FIRM_DBG_REGISTER(dbg, "firm.opt.inline");
1381 }