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