Remove pointless local variables.
[libfirm] / ir / ir / irprofile.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       Code instrumentation and execution count profiling.
23  * @author      Adam M. Szalkowski, Steven Schaefer
24  * @date        06.04.2006, 11.11.2010
25  * @version     $Id$
26  */
27 #include "config.h"
28
29 #include <math.h>
30 #include <stdio.h>
31
32 #include "hashptr.h"
33 #include "debug.h"
34 #include "obst.h"
35 #include "xmalloc.h"
36 #include "set.h"
37 #include "irtools.h"
38
39 #include "irgwalk.h"
40 #include "irdump_t.h"
41 #include "irnode_t.h"
42 #include "ircons_t.h"
43 #include "execfreq.h"
44 #include "typerep.h"
45
46 #include "irprofile.h"
47
48 /* Instrument blocks walker. */
49 typedef struct block_id_walker_data_t {
50         unsigned int id;   /**< current block id number */
51         ir_node *symconst; /**< the SymConst representing the counter array */
52 } block_id_walker_data_t;
53
54 /* Associate counters with blocks. */
55 typedef struct block_assoc_t {
56         unsigned int i;          /**< current block id number */
57         unsigned int *counters;  /**< block execution counts */
58 } block_assoc_t;
59
60 typedef struct intialize_execfreq_env_t {
61         ir_graph *irg;
62         ir_exec_freq *execfreqs;
63         double freq_factor;
64 } initialize_execfreq_env_t;
65
66 /* maximal filename size */
67 #define MAX_NAME_SIZE 0x100
68
69 /* minimal execution frequency (an execfreq of 0 confuses algos) */
70 #define MIN_EXECFREQ 0.00001
71
72 /* keep the execcounts here because they are only read once per compiler run */
73 static set *profile = NULL;
74
75 /* Hook for vcg output. */
76 DEBUG_ONLY(static void *hook;)
77
78 /* The debug module handle. */
79 DEBUG_ONLY(static firm_dbg_module_t *dbg;)
80
81 /* Since the backend creates a new firm graph we cannot associate counts with
82  * blocks directly. Instead we associate them with the block ids, which are
83  * maintained.
84  */
85 typedef struct execcount_t {
86         unsigned long block; /**< block id */
87         unsigned int  count; /**< execution count */
88 } execcount_t;
89
90 /**
91  * Compare two execcount_t entries.
92  */
93 static int cmp_execcount(const void *a, const void *b, size_t size)
94 {
95         const execcount_t *ea = (const execcount_t*)a;
96         const execcount_t *eb = (const execcount_t*)b;
97         (void) size;
98         return ea->block != eb->block;
99 }
100
101 /**
102  * Block walker, count number of blocks.
103  */
104 static void block_counter(ir_node *bb, void *data)
105 {
106         unsigned *count = (unsigned*) data;
107         (void) bb;
108         ++(*count);
109 }
110
111 /**
112  * Returns the number of blocks the given graph.
113  */
114 static unsigned int get_irg_n_blocks(ir_graph *irg)
115 {
116         unsigned int count = 0;
117         irg_block_walk_graph(irg, block_counter, NULL, &count);
118         return count;
119 }
120
121 /**
122  * Returns the number of basic blocks in the current ir program.
123  */
124 static unsigned int get_irp_n_blocks(void)
125 {
126         int i, n = get_irp_n_irgs();
127         unsigned int count = 0;
128
129         for (i = 0; i < n; i++) {
130                 ir_graph *irg = get_irp_irg(i);
131                 count += get_irg_n_blocks(irg);
132         }
133
134         return count;
135 }
136
137 /* vcg helper */
138 static void dump_profile_node_info(void *ctx, FILE *f, const ir_node *irn)
139 {
140         (void) ctx;
141         if (is_Block(irn)) {
142                 unsigned int execcount = ir_profile_get_block_execcount(irn);
143                 fprintf(f, "profiled execution count: %u\n", execcount);
144         }
145 }
146
147 /**
148  * Add the given method entity as a constructor.
149  */
150 static void add_constructor(ir_entity *method)
151 {
152     ir_type   *method_type  = get_entity_type(method);
153     ir_type   *ptr_type     = new_type_pointer(method_type);
154
155     ir_type   *constructors = get_segment_type(IR_SEGMENT_CONSTRUCTORS);
156         /* Mach-O does not like labels in the constructor segment, but with ELF
157          * the linker dies horribly if there is no label. */
158         ident     *ide = id_unique("constructor_ptr.%u");
159     ir_entity *ptr = new_entity(constructors, ide, ptr_type);
160     ir_graph  *irg = get_const_code_irg();
161     ir_node   *val = new_rd_SymConst_addr_ent(NULL, irg, mode_P_code, method);
162
163         set_entity_ld_ident(ptr, new_id_from_chars("", 0));
164     set_entity_compiler_generated(ptr, 1);
165     set_entity_linkage(ptr, IR_LINKAGE_CONSTANT | IR_LINKAGE_HIDDEN_USER);
166     set_entity_visibility(ptr, ir_visibility_private);
167     set_atomic_ent_value(ptr, val);
168 }
169
170 /**
171  * Returns an entity representing the __init_firmprof function from libfirmprof
172  * This is the equivalent of:
173  * extern void __init_firmprof(char *filename, uint *counters, uint size)
174  */
175 static ir_entity *get_init_firmprof_ref(void)
176 {
177         ident   *init_name = new_id_from_str("__init_firmprof");
178         ir_type *init_type = new_type_method(3, 0);
179         ir_type *uint      = new_type_primitive(mode_Iu);
180         ir_type *uintptr   = new_type_pointer(uint);
181         ir_type *string    = new_type_pointer(new_type_primitive(mode_Bs));
182         ir_entity *result;
183
184         set_method_param_type(init_type, 0, string);
185         set_method_param_type(init_type, 1, uintptr);
186         set_method_param_type(init_type, 2, uint);
187
188         result = new_entity(get_glob_type(), init_name, init_type);
189         set_entity_visibility(result, ir_visibility_external);
190
191         return result;
192 }
193
194 /**
195  * Generates a new irg which calls the initializer
196  *
197  * Pseudocode:
198  *    static void __firmprof_initializer(void) __attribute__ ((constructor))
199  *    {
200  *        __init_firmprof(ent_filename, bblock_counts, n_blocks);
201  *    }
202  */
203 static ir_graph *gen_initializer_irg(ir_entity *ent_filename,
204                                      ir_entity *bblock_counts, int n_blocks)
205 {
206         ir_graph *irg;
207         ir_node  *ins[3];
208         ir_node  *bb, *ret, *call, *symconst;
209         ir_type  *empty_frame_type;
210         symconst_symbol sym;
211
212         ir_entity *init_ent = get_init_firmprof_ref();
213
214         ident     *name = new_id_from_str("__firmprof_initializer");
215         ir_entity *ent  = new_entity(get_glob_type(), name, new_type_method(0, 0));
216         set_entity_visibility(ent, ir_visibility_local);
217         set_entity_ld_ident(ent, name);
218
219         /* create the new ir_graph */
220         irg = new_ir_graph(ent, 0);
221         set_current_ir_graph(irg);
222         empty_frame_type = get_irg_frame_type(irg);
223         set_type_size_bytes(empty_frame_type, 0);
224         set_type_state(empty_frame_type, layout_fixed);
225
226         bb = get_r_cur_block(irg);
227
228         sym.entity_p = init_ent;
229         symconst     = new_r_SymConst(irg, mode_P_data, sym, symconst_addr_ent);
230
231         sym.entity_p = ent_filename;
232         ins[0] = new_r_SymConst(irg, mode_P_data, sym, symconst_addr_ent);
233         sym.entity_p = bblock_counts;
234         ins[1] = new_r_SymConst(irg, mode_P_data, sym, symconst_addr_ent);
235         ins[2] = new_r_Const_long(irg, mode_Iu, n_blocks);
236
237         call = new_r_Call(bb, get_irg_initial_mem(irg), symconst, 3, ins,
238                 get_entity_type(init_ent));
239         ret  = new_r_Return(bb, new_r_Proj(call, mode_M, pn_Call_M), 0, NULL);
240         mature_immBlock(bb);
241
242         add_immBlock_pred(get_irg_end_block(irg), ret);
243         mature_immBlock(get_irg_end_block(irg));
244
245         irg_finalize_cons(irg);
246
247         /* add a pointer to the new function in the constructor section */
248         add_constructor(ent);
249
250         return irg;
251 }
252
253 /**
254  * Instrument a block with code needed for profiling.
255  * This just inserts the instruction nodes, it doesn't connect the memory
256  * nodes in a meaningful way.
257  */
258 static void instrument_block(ir_node *bb, ir_node *address, unsigned int id)
259 {
260         ir_graph *irg = get_irn_irg(bb);
261         ir_node  *load, *store, *offset, *add, *projm, *proji, *unknown, *cnst;
262
263         /* We can't instrument the end block */
264         if (bb == get_irg_end_block(irg))
265                 return;
266
267         unknown = new_r_Unknown(irg, mode_M);
268         cnst    = new_r_Const_long(irg, mode_Iu, get_mode_size_bytes(mode_Iu) * id);
269         offset  = new_r_Add(bb, address, cnst, get_modeP_data());
270         load    = new_r_Load(bb, unknown, offset, mode_Iu, cons_none);
271         projm   = new_r_Proj(load, mode_M, pn_Load_M);
272         proji   = new_r_Proj(load, mode_Iu, pn_Load_res);
273         cnst    = new_r_Const_long(irg, mode_Iu, 1);
274         add     = new_r_Add(bb, proji, cnst, mode_Iu);
275         store   = new_r_Store(bb, projm, offset, add, cons_none);
276         projm   = new_r_Proj(store, mode_M, pn_Store_M);
277
278         set_irn_link(bb, projm);
279         set_irn_link(projm, load);
280 }
281
282 /**
283  * SSA Construction for instrumentation code memory.
284  *
285  * This introduces a new memory node and connects it to the instrumentation
286  * codes, inserting phiM nodes as necessary. Note that afterwards, the new
287  * memory is not connected to any return nodes and thus still dead.
288  */
289 static void fix_ssa(ir_node *bb, void *data)
290 {
291         ir_graph *irg = get_irn_irg(bb);
292         ir_node *mem, *proj, *load;
293         int n, arity = get_Block_n_cfgpreds(bb);
294
295         (void) data;
296
297         /* end blocks are not instrumented, skip! */
298         if (bb == get_irg_end_block(irg))
299                 return;
300
301         if (bb == get_irg_start_block(irg)) {
302                 mem = get_irg_initial_mem(irg);
303         } else if (arity == 1) {
304                 ir_node *pred = get_Block_cfgpred_block(bb, 0);
305                 if (!is_Bad(pred))
306                         mem = (ir_node*) get_irn_link(pred);
307                 else
308                         mem = new_r_NoMem(irg);
309         } else {
310                 ir_node **ins = ALLOCAN(ir_node*, arity);
311                 for (n = arity - 1; n >= 0; --n) {
312                         ir_node *pred = get_Block_cfgpred_block(bb, n);
313                         if (!is_Bad(pred))
314                                 ins[n] = (ir_node*) get_irn_link(pred);
315                         else
316                                 ins[n] = new_r_NoMem(irg);
317                 }
318                 mem = new_r_Phi(bb, arity, ins, mode_M);
319         }
320
321         /* The block link fields point to the projm from the instrumentation code,
322          * the projm in turn links to the initial load which lacks a memory
323          * argument at this point. */
324         proj = (ir_node*) get_irn_link(bb);
325         load = (ir_node*) get_irn_link(proj);
326         set_Load_mem(load, mem);
327 }
328
329 /**
330  * Instrument a single block.
331  */
332 static void block_instrument_walker(ir_node *bb, void *data)
333 {
334         block_id_walker_data_t *wd = (block_id_walker_data_t*)data;
335         instrument_block(bb, wd->symconst, wd->id);
336         ++wd->id;
337 }
338
339 /**
340  * Synchronize the original memory input of node with the additional operand
341  * from the profiling code.
342  */
343 static ir_node *sync_mem(ir_node *bb, ir_node *mem)
344 {
345         ir_node *ins[2];
346         ins[0] = (ir_node*) get_irn_link(bb);
347         ins[1] = mem;
348         return new_r_Sync(bb, 2, ins);
349 }
350
351 /**
352  * Instrument a single ir_graph, counters should point to the bblock
353  * counters array.
354  */
355 static void instrument_irg(ir_graph *irg, ir_entity *counters,
356                            block_id_walker_data_t *wd)
357 {
358         ir_node *end   = get_irg_end(irg);
359         ir_node *endbb = get_irg_end_block(irg);
360         int i;
361
362         /* generate a symbolic constant pointing to the count array */
363         symconst_symbol sym;
364         sym.entity_p = counters;
365         wd->symconst = new_r_SymConst(irg, mode_P_data, sym, symconst_addr_ent);
366
367         /* instrument each block in the current irg */
368         irg_block_walk_graph(irg, block_instrument_walker, NULL, wd);
369         irg_block_walk_graph(irg, fix_ssa, NULL, NULL);
370
371         /* connect the new memory nodes to the return nodes */
372         for (i = get_Block_n_cfgpreds(endbb) - 1; i >= 0; --i) {
373                 ir_node *node = skip_Proj(get_Block_cfgpred(endbb, i));
374                 ir_node *bb   = get_Block_cfgpred_block(endbb, i);
375                 ir_node *mem;
376
377                 switch (get_irn_opcode(node)) {
378                 case iro_Return:
379                         mem = get_Return_mem(node);
380                         set_Return_mem(node, sync_mem(bb, mem));
381                         break;
382                 case iro_Raise:
383                         mem = get_Raise_mem(node);
384                         set_Raise_mem(node, sync_mem(bb, mem));
385                         break;
386                 case iro_Bad:
387                         break;
388                 default:
389                         /* A fragile's op exception. There should be another path to End,
390                          * so ignore it.
391                          */
392                         assert(is_fragile_op(node) && \
393                                 "unexpected End control flow predecessor");
394                 }
395         }
396
397         /* as well as calls with attribute noreturn */
398         for (i = get_End_n_keepalives(end) - 1; i >= 0; --i) {
399                 ir_node *node = get_End_keepalive(end, i);
400                 if (is_Call(node)) {
401                         ir_node *bb  = get_nodes_block(node);
402                         ir_node *mem = get_Call_mem(node);
403                         set_Call_mem(node, sync_mem(bb, mem));
404                 }
405         }
406 }
407
408 /**
409  * Creates a new entity representing the equivalent of
410  * static unsigned int name[size]
411  */
412 static ir_entity *new_array_entity(ident *name, int size)
413 {
414         ir_entity *result;
415         ir_type *uint_type, *array_type;
416
417         uint_type = new_type_primitive(mode_Iu);
418         set_type_alignment_bytes(uint_type, get_type_size_bytes(uint_type));
419
420         array_type = new_type_array(1, uint_type);
421         set_array_bounds_int(array_type, 0, 0, size);
422         set_type_size_bytes(array_type, size * get_mode_size_bytes(mode_Iu));
423         set_type_alignment_bytes(array_type, get_mode_size_bytes(mode_Iu));
424         set_type_state(array_type, layout_fixed);
425
426         result = new_entity(get_glob_type(), name, array_type);
427         set_entity_visibility(result, ir_visibility_local);
428         set_entity_compiler_generated(result, 1);
429
430         return result;
431 }
432
433 /**
434  * Creates a new entity representing the equivalent of
435  * static const char name[strlen(string)+1] = string
436  */
437 static ir_entity *new_static_string_entity(ident *name, const char *string)
438 {
439         ir_entity *result;
440
441         ir_type *char_type   = new_type_primitive(mode_Bs);
442         ir_type *string_type = new_type_array(1, char_type);
443
444         ir_initializer_t *contents;
445
446         size_t i, length = strlen(string)+1;
447
448         /* Create the type for a fixed-length string */
449         set_array_bounds_int(string_type, 0, 0, length);
450         set_type_size_bytes(string_type, length);
451         set_type_alignment_bytes(string_type, 1);
452         set_type_state(string_type, layout_fixed);
453
454         result = new_entity(get_glob_type(), name, string_type);
455         set_entity_visibility(result, ir_visibility_local);
456         set_entity_linkage(result, IR_LINKAGE_CONSTANT);
457         set_entity_compiler_generated(result, 1);
458
459         /* There seems to be no simpler way to do this. Or at least, cparser
460          * does exactly the same thing... */
461         contents = create_initializer_compound(length);
462         for (i = 0; i < length; i++) {
463                 ir_tarval *c = new_tarval_from_long(string[i], mode_Bs);
464                 ir_initializer_t *init = create_initializer_tarval(c);
465                 set_initializer_compound_value(contents, i, init);
466         }
467         set_entity_initializer(result, contents);
468
469         return result;
470 }
471
472 /**
473  * Instrument all ir_graphs in the current ir_program. Currently this only
474  * works for graphs in the backend. Additionally, the resulting program
475  * has to be linked with libfirmprof.
476  *
477  * @param filename the name of the profile file (usually module_name.prof)
478  * @returns the module initializer, may be NULL
479  */
480 ir_graph *ir_profile_instrument(const char *filename)
481 {
482         int n, n_blocks = 0;
483         ident *counter_id, *filename_id;
484         ir_entity *bblock_counts, *ent_filename;
485         block_id_walker_data_t wd;
486         FIRM_DBG_REGISTER(dbg, "firm.ir.profile");
487
488         /* Don't do anything for modules without code. Else the linker will
489          * complain. */
490         if (get_irp_n_irgs() == 0)
491                 return NULL;
492
493         /* count the number of block first */
494         n_blocks = get_irp_n_blocks();
495
496         /* create all the necessary types and entities. Note that the
497          * types must have a fixed layout, because we are already running in the
498          * backend */
499         counter_id    = new_id_from_str("__FIRMPROF__BLOCK_COUNTS");
500         bblock_counts = new_array_entity(counter_id, n_blocks);
501
502         filename_id  = new_id_from_str("__FIRMPROF__FILE_NAME");
503         ent_filename = new_static_string_entity(filename_id, filename);
504
505         /* initialize block id array and instrument blocks */
506         wd.id  = 0;
507         for (n = get_irp_n_irgs() - 1; n >= 0; --n) {
508                 ir_graph *irg = get_irp_irg(n);
509                 instrument_irg(irg, bblock_counts, &wd);
510         }
511
512         return gen_initializer_irg(ent_filename, bblock_counts, n_blocks);
513 }
514
515 static unsigned int *
516 parse_profile(const char *filename, unsigned int num_blocks)
517 {
518         unsigned int *result = NULL;
519         char buf[8];
520         size_t ret;
521
522         FILE *f = fopen(filename, "rb");
523         if (!f) {
524                 DBG((dbg, LEVEL_2, "Failed to open profile file (%s)\n", filename));
525                 return NULL;
526         }
527
528         /* check header */
529         ret = fread(buf, 8, 1, f);
530         if (ret == 0 || strncmp(buf, "firmprof", 8) != 0) {
531                 DBG((dbg, LEVEL_2, "Broken fileheader in profile\n"));
532                 goto end;
533         }
534
535         result = XMALLOCN(unsigned int, num_blocks);
536         if (fread(result, sizeof(unsigned int) * num_blocks, 1, f) < 1) {
537                 DBG((dbg, LEVEL_4, "Failed to read counters... (size: %u)\n",
538                     sizeof(unsigned int) * num_blocks));
539                 xfree(result);
540                 result = NULL;
541         }
542
543 end:
544         fclose(f);
545         return result;
546 }
547
548 /**
549  * Reads the corresponding profile info file if it exists.
550  */
551
552 static void block_associate_walker(ir_node *bb, void *env)
553 {
554         block_assoc_t *b = (block_assoc_t*) env;
555         execcount_t query;
556
557         query.block = get_irn_node_nr(bb);
558         query.count = b->counters[(b->i)++];
559         DBG((dbg, LEVEL_4, "execcount(%+F, %u): %u\n", bb, query.block,
560             query.count));
561         set_insert(profile, &query, sizeof(query), query.block);
562 }
563
564 static void irp_associate_blocks(block_assoc_t *env)
565 {
566         int n;
567         for (n = get_irp_n_irgs() - 1; n >= 0; --n) {
568                 ir_graph *irg = get_irp_irg(n);
569                 irg_block_walk_graph(irg, block_associate_walker, NULL, env);
570         }
571 }
572
573 bool ir_profile_read(const char *filename)
574 {
575         block_assoc_t env;
576         FIRM_DBG_REGISTER(dbg, "firm.ir.profile");
577
578         env.i = 0;
579         env.counters = parse_profile(filename, get_irp_n_blocks());
580         if (!env.counters)
581                 return false;
582
583         if (profile)
584                 ir_profile_free();
585         profile = new_set(cmp_execcount, 16);
586
587         irp_associate_blocks(&env);
588         xfree(env.counters);
589
590         /* register the vcg hook */
591         hook = dump_add_node_info_callback(dump_profile_node_info, NULL);
592         return true;
593 }
594
595 /**
596  * Frees the profile info
597  */
598 void ir_profile_free(void)
599 {
600         if (profile) {
601                 del_set(profile);
602                 profile = NULL;
603         }
604
605         if (hook != NULL) {
606                 dump_remove_node_info_callback(hook);
607                 hook = NULL;
608         }
609 }
610
611 /**
612  * Tells whether profile module has acquired data
613  */
614 bool ir_profile_has_data(void)
615 {
616         return profile != NULL;
617 }
618
619 /**
620  * Get block execution count as determined by profiling
621  */
622 unsigned int ir_profile_get_block_execcount(const ir_node *block)
623 {
624         execcount_t *ec, query;
625
626         if (!ir_profile_has_data())
627                 return 1;
628
629         query.block = get_irn_node_nr(block);
630         ec = (execcount_t*)set_find(profile, &query, sizeof(query), query.block);
631
632         if (ec != NULL) {
633                 return ec->count;
634         } else {
635                 DBG((dbg, LEVEL_3,
636                         "Warning: Profile contains no data for %+F\n", block));
637                 return 1;
638         }
639 }
640
641 static void initialize_execfreq(ir_node *block, void *data)
642 {
643         initialize_execfreq_env_t *env = (initialize_execfreq_env_t*)data;
644         double freq;
645
646         if (block == get_irg_start_block(env->irg)
647            || block == get_irg_end_block(env->irg)) {
648                 freq = 1.0;
649         } else {
650                 freq = ir_profile_get_block_execcount(block);
651                 freq *= env->freq_factor;
652                 if (freq < MIN_EXECFREQ)
653                         freq = MIN_EXECFREQ;
654         }
655
656         set_execfreq(env->execfreqs, block, freq);
657 }
658
659 ir_exec_freq *ir_create_execfreqs_from_profile(ir_graph *irg)
660 {
661         ir_node *start_block;
662         initialize_execfreq_env_t env;
663         unsigned count;
664
665         env.irg = irg;
666         env.execfreqs = create_execfreq(irg);
667
668         /* Find the first block containing instructions */
669         start_block = get_irg_start_block(irg);
670         count = ir_profile_get_block_execcount(start_block);
671         if (count == 0) {
672                 /* the function was never executed, so fallback to estimated freqs */
673                 free_execfreq(env.execfreqs);
674                 return compute_execfreq(irg, 10);
675         }
676
677         env.freq_factor = 1.0 / count;
678         irg_block_walk_graph(irg, initialize_execfreq, NULL, &env);
679
680         return env.execfreqs;
681 }