ia32: Clean up ia32_get_op_estimated_cost().
[libfirm] / ir / be / ia32 / ia32_intrinsics.c
1 /*
2  * This file is part of libFirm.
3  * Copyright (C) 2012 University of Karlsruhe.
4  */
5
6 /**
7  * @file
8  * @brief       This file implements the mapping of 64Bit intrinsic
9  *              functions to code or library calls.
10  * @author      Michael Beck
11  */
12 #include "config.h"
13
14 #include "iredges.h"
15 #include "irgmod.h"
16 #include "irop.h"
17 #include "irnode_t.h"
18 #include "ircons.h"
19 #include "irprog_t.h"
20 #include "iroptimize.h"
21 #include "lower_dw.h"
22 #include "array.h"
23 #include "error.h"
24 #include "util.h"
25
26 #include "ia32_new_nodes.h"
27 #include "bearch_ia32_t.h"
28 #include "gen_ia32_regalloc_if.h"
29 #include "begnuas.h"
30
31 /** The array of all intrinsics that must be mapped. */
32 static i_record *intrinsics;
33
34 /** An array to cache all entities. */
35 static ir_entity *i_ents[iro_Last + 1];
36
37 /*
38  * Maps all intrinsic calls that the backend support
39  * and map all instructions the backend did not support
40  * to runtime calls.
41  */
42 void ia32_handle_intrinsics(void)
43 {
44         if (intrinsics && ARR_LEN(intrinsics) > 0) {
45                 lower_intrinsics(intrinsics, ARR_LEN(intrinsics), /*part_block_used=*/1);
46         }
47 }
48
49 #define BINOP_Left_Low   0
50 #define BINOP_Left_High  1
51 #define BINOP_Right_Low  2
52 #define BINOP_Right_High 3
53
54 /**
55  * Reroute edges from the pn_Call_T_result proj of a call.
56  *
57  * @param resproj  the pn_Call_T_result Proj
58  * @param l_res    the lower 32 bit result
59  * @param h_res    the upper 32 bit result or NULL
60  */
61 static void reroute_result(ir_node *resproj, ir_node *l_res, ir_node *h_res)
62 {
63         foreach_out_edge_safe(resproj, edge) {
64                 ir_node *proj = get_edge_src_irn(edge);
65                 long    pn    = get_Proj_proj(proj);
66
67                 if (pn == 0) {
68                         edges_reroute(proj, l_res);
69                 } else if (pn == 1 && h_res != NULL) {
70                         edges_reroute(proj, h_res);
71                 } else {
72                         panic("Unsupported Result-Proj from Call found");
73                 }
74         }
75 }
76
77 /**
78  * Replace a call be a tuple of l_res, h_res.
79  *
80  * @param call   the call node to replace
81  * @param l_res  the lower 32 bit result
82  * @param h_res  the upper 32 bit result or NULL
83  * @param irg    the graph to replace on
84  * @param block  the block to replace on (always the call block)
85  */
86 static void resolve_call(ir_node *call, ir_node *l_res, ir_node *h_res, ir_graph *irg, ir_node *block)
87 {
88         ir_node *jmp, *res, *in[2];
89         ir_node *nomem = get_irg_no_mem(irg);
90         int     old_cse;
91
92         if (edges_activated(irg)) {
93                 /* use rerouting to prevent some warning in the backend */
94                 foreach_out_edge_safe(call, edge) {
95                         ir_node *proj = get_edge_src_irn(edge);
96                         pn_Call pn    = (pn_Call)get_Proj_proj(proj);
97
98                         switch (pn) {
99                         case pn_Call_X_regular:
100                                 /* Beware:
101                                  * We do not check here if this call really has exception and regular Proj's.
102                                  * new_r_Jmp might than be CSEd with the real exit jmp and then bad things happen
103                                  * (in movgen.c from 186.crafty for example).
104                                  * So be sure the newly created Jmp cannot CSE.
105                                  */
106                                 old_cse = get_opt_cse();
107                                 set_opt_cse(0);
108                                 jmp = new_r_Jmp(block);
109                                 set_opt_cse(old_cse);
110                                 edges_reroute(proj, jmp);
111                                 break;
112
113                         case pn_Call_X_except:
114                                 /* should not happen here */
115                                 edges_reroute(proj, new_r_Bad(irg, mode_X));
116                                 break;
117                         case pn_Call_M:
118                                 /* should not happen here */
119                                 edges_reroute(proj, nomem);
120                                 break;
121                         case pn_Call_T_result:
122                                 reroute_result(proj, l_res, h_res);
123                                 break;
124                         default:
125                                 panic("Wrong Proj from Call");
126                         }
127                         kill_node(proj);
128                 }
129                 kill_node(call);
130         } else {
131                 /* no edges, build Tuple */
132                 if (h_res == NULL)
133                         res = l_res;
134                 else {
135                         in[0] = l_res;
136                         in[1] = h_res;
137                         res = new_r_Tuple(block, 2, in);
138                 }
139
140                 /*
141                  * Beware:
142                  * We do not check here if this call really has exception and regular Proj's.
143                  * new_r_Jmp might than be CSEd with the real exit jmp and then bad things happen
144                  * (in movgen.c from 186.crafty for example).
145                  * So be sure the newly created Jmp cannot CSE.
146                  */
147                 old_cse = get_opt_cse();
148                 set_opt_cse(0);
149                 jmp = new_r_Jmp(block);
150                 set_opt_cse(old_cse);
151
152                 ir_node *const in[] = {
153                         [pn_Call_M]         = nomem,
154                         [pn_Call_T_result]  = res,
155                         [pn_Call_X_regular] = jmp,
156                         [pn_Call_X_except]  = new_r_Bad(irg, mode_X),
157                 };
158                 turn_into_tuple(call, ARRAY_SIZE(in), in);
159         }
160 }
161
162 /**
163  * Map an Add (a_l, a_h, b_l, b_h)
164  */
165 static int map_Add(ir_node *call, void *ctx)
166 {
167         dbg_info *dbg        = get_irn_dbg_info(call);
168         ir_node  *block      = get_nodes_block(call);
169         ir_node  **params    = get_Call_param_arr(call);
170         ir_type  *method     = get_Call_type(call);
171         ir_node  *a_l        = params[BINOP_Left_Low];
172         ir_node  *a_h        = params[BINOP_Left_High];
173         ir_node  *b_l        = params[BINOP_Right_Low];
174         ir_node  *b_h        = params[BINOP_Right_High];
175         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
176         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
177         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
178         ir_node  *add_low, *add_high, *flags;
179         ir_node  *l_res, *h_res;
180         (void) ctx;
181
182         /* l_res = a_l + b_l */
183         /* h_res = a_h + b_h + carry */
184
185         add_low  = new_bd_ia32_l_Add(dbg, block, a_l, b_l, mode_T);
186         flags    = new_r_Proj(add_low, mode_flags, pn_ia32_flags);
187         add_high = new_bd_ia32_l_Adc(dbg, block, a_h, b_h, flags, h_mode);
188
189         l_res = new_r_Proj(add_low, l_mode, pn_ia32_res);
190         h_res = add_high;
191
192         resolve_call(call, l_res, h_res, current_ir_graph, block);
193         return 1;
194 }
195
196 /**
197  * Map a Sub (a_l, a_h, b_l, b_h)
198  */
199 static int map_Sub(ir_node *call, void *ctx)
200 {
201         dbg_info *dbg        = get_irn_dbg_info(call);
202         ir_node  *block      = get_nodes_block(call);
203         ir_node  **params    = get_Call_param_arr(call);
204         ir_type  *method     = get_Call_type(call);
205         ir_node  *a_l        = params[BINOP_Left_Low];
206         ir_node  *a_h        = params[BINOP_Left_High];
207         ir_node  *b_l        = params[BINOP_Right_Low];
208         ir_node  *b_h        = params[BINOP_Right_High];
209         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
210         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
211         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
212         ir_node  *sub_low, *sub_high, *flags;
213         ir_node  *l_res, *h_res;
214         (void) ctx;
215
216         /* l_res = a_l - b_l */
217         /* h_res = a_h - b_h - carry */
218
219         sub_low  = new_bd_ia32_l_Sub(dbg, block, a_l, b_l, mode_T);
220         flags    = new_r_Proj(sub_low, mode_flags, pn_ia32_flags);
221         sub_high = new_bd_ia32_l_Sbb(dbg, block, a_h, b_h, flags, h_mode);
222
223         l_res = new_r_Proj(sub_low, l_mode, pn_ia32_res);
224         h_res = sub_high;
225
226         resolve_call(call, l_res, h_res, current_ir_graph, block);
227         return 1;
228 }
229
230 /**
231  * Checks where node high is a sign extension of low.
232  */
233 static int is_sign_extend(ir_node *low, ir_node *high)
234 {
235         if (is_Shrs(high)) {
236                 ir_node   *high_l;
237                 ir_node   *high_r;
238                 ir_tarval *shift_count;
239
240                 high_r = get_Shrs_right(high);
241                 if (!is_Const(high_r)) return 0;
242
243                 shift_count = get_Const_tarval(high_r);
244                 if (!tarval_is_long(shift_count))       return 0;
245                 if (get_tarval_long(shift_count) != 31) return 0;
246
247                 high_l = get_Shrs_left(high);
248
249                 if (is_Conv(low)    && get_Conv_op(low)    == high_l) return 1;
250                 if (is_Conv(high_l) && get_Conv_op(high_l) == low)    return 1;
251         } else if (is_Const(low) && is_Const(high)) {
252                 ir_tarval *tl = get_Const_tarval(low);
253                 ir_tarval *th = get_Const_tarval(high);
254
255                 if (tarval_is_long(th) && tarval_is_long(tl)) {
256                         long l = get_tarval_long(tl);
257                         long h = get_tarval_long(th);
258
259                         return (h == 0  && l >= 0) || (h == -1 && l <  0);
260                 }
261         }
262
263         return 0;
264 }
265
266 /**
267  * Map a Mul (a_l, a_h, b_l, b_h)
268  */
269 static int map_Mul(ir_node *call, void *ctx)
270 {
271         dbg_info *dbg     = get_irn_dbg_info(call);
272         ir_node  *block   = get_nodes_block(call);
273         ir_node  **params = get_Call_param_arr(call);
274         ir_type  *method  = get_Call_type(call);
275         ir_node  *a_l     = params[BINOP_Left_Low];
276         ir_node  *a_h     = params[BINOP_Left_High];
277         ir_node  *b_l     = params[BINOP_Right_Low];
278         ir_node  *b_h     = params[BINOP_Right_High];
279         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
280         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
281         ir_node  *l_res, *h_res, *mul, *pEDX, *add;
282         (void) ctx;
283
284         /*
285                 EDX:EAX = a_l * b_l
286                 l_res   = EAX
287
288                 t1 = b_l * a_h
289                 t2 = t1 + EDX
290                 t3 = a_l * b_h
291                 h_res = t2 + t3
292         */
293
294         /* handle the often used case of 32x32=64 mul */
295         if (is_sign_extend(a_l, a_h) && is_sign_extend(b_l, b_h)) {
296                 mul   = new_bd_ia32_l_IMul(dbg, block, a_l, b_l);
297                 h_res = new_rd_Proj(dbg, mul, h_mode, pn_ia32_l_IMul_res_high);
298                 l_res = new_rd_Proj(dbg, mul, l_mode, pn_ia32_l_IMul_res_low);
299         } else {
300                 /* note that zero extension is handled hare efficiently */
301                 mul   = new_bd_ia32_l_Mul(dbg, block, a_l, b_l);
302                 pEDX  = new_rd_Proj(dbg, mul, h_mode, pn_ia32_l_Mul_res_high);
303                 l_res = new_rd_Proj(dbg, mul, l_mode, pn_ia32_l_Mul_res_low);
304
305                 b_l   = new_rd_Conv(dbg, block, b_l, h_mode);
306                 mul   = new_rd_Mul( dbg, block, a_h, b_l, h_mode);
307                 add   = new_rd_Add( dbg, block, mul, pEDX, h_mode);
308                 a_l   = new_rd_Conv(dbg, block, a_l, h_mode);
309                 mul   = new_rd_Mul( dbg, block, a_l, b_h, h_mode);
310                 h_res = new_rd_Add( dbg, block, add, mul, h_mode);
311         }
312         resolve_call(call, l_res, h_res, current_ir_graph, block);
313
314         return 1;
315 }
316
317 /**
318  * Map a Minus (a_l, a_h)
319  */
320 static int map_Minus(ir_node *call, void *ctx)
321 {
322         dbg_info *dbg     = get_irn_dbg_info(call);
323         ir_node  *block   = get_nodes_block(call);
324         ir_node  **params = get_Call_param_arr(call);
325         ir_type  *method  = get_Call_type(call);
326         ir_node  *a_l     = params[BINOP_Left_Low];
327         ir_node  *a_h     = params[BINOP_Left_High];
328         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
329         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
330         ir_node  *l_res, *h_res, *res;
331         (void) ctx;
332
333         res   = new_bd_ia32_Minus64Bit(dbg, block, a_l, a_h);
334         l_res = new_r_Proj(res, l_mode, pn_ia32_Minus64Bit_low_res);
335         h_res = new_r_Proj(res, h_mode, pn_ia32_Minus64Bit_high_res);
336
337         resolve_call(call, l_res, h_res, current_ir_graph, block);
338
339         return 1;
340 }
341
342 #define ID(x) new_id_from_chars(x, sizeof(x)-1)
343
344 /**
345  * Maps a Div. Change into a library call.
346  */
347 static int map_Div(ir_node *call, void *ctx)
348 {
349         ia32_intrinsic_env_t *env = (ia32_intrinsic_env_t*)ctx;
350         ir_type   *method    = get_Call_type(call);
351         ir_mode   *h_mode    = get_type_mode(get_method_res_type(method, 1));
352         ir_node   *ptr;
353         ir_entity *ent;
354         ir_graph  *irg = get_irn_irg(call);
355         symconst_symbol sym;
356
357         if (mode_is_signed(h_mode)) {
358                 /* 64bit signed Division */
359                 ent = env->divdi3;
360                 if (ent == NULL) {
361                         /* create library entity */
362                         ident *id = ID("__divdi3");
363                         ent = env->divdi3 = create_compilerlib_entity(id, method);
364                 }
365         } else {
366                 /* 64bit unsigned Division */
367                 ent = env->udivdi3;
368                 if (ent == NULL) {
369                         /* create library entity */
370                         ident *id = ID("__udivdi3");
371                         ent = env->udivdi3 = create_compilerlib_entity(id, method);
372                 }
373         }
374
375         ptr = get_Call_ptr(call);
376         sym.entity_p = ent;
377         ptr = new_r_SymConst(irg, get_irn_mode(ptr), sym, symconst_addr_ent);
378         set_Call_ptr(call, ptr);
379
380         return 1;
381 }
382
383 /**
384  * Maps a Mod. Change into a library call
385  */
386 static int map_Mod(ir_node *call, void *ctx)
387 {
388         ia32_intrinsic_env_t *env = (ia32_intrinsic_env_t*)ctx;
389         ir_type   *method    = get_Call_type(call);
390         ir_mode   *h_mode    = get_type_mode(get_method_res_type(method, 1));
391         ir_node   *ptr;
392         ir_entity *ent;
393         ir_graph  *irg = get_irn_irg(call);
394         symconst_symbol sym;
395
396         if (mode_is_signed(h_mode)) {
397                 /* 64bit signed Modulo */
398                 ent = env->moddi3;
399                 if (ent == NULL) {
400                         /* create library entity */
401                         ident *id = ID("__moddi3");
402                         ent = env->moddi3 = create_compilerlib_entity(id, method);
403                 }
404         } else {
405                 /* 64bit signed Modulo */
406                 ent = env->umoddi3;
407                 if (ent == NULL) {
408                         /* create library entity */
409                         ident *id = ID("__umoddi3");
410                         ent = env->umoddi3 = create_compilerlib_entity(id, method);
411                 }
412         }
413
414         ptr = get_Call_ptr(call);
415         sym.entity_p = ent;
416         ptr = new_r_SymConst(irg, get_irn_mode(ptr), sym, symconst_addr_ent);
417         set_Call_ptr(call, ptr);
418
419         return 1;
420 }
421
422 /**
423  * Maps a Conv.
424  */
425 static int map_Conv(ir_node *call, void *ctx)
426 {
427         ir_graph  *irg     = current_ir_graph;
428         dbg_info  *dbg     = get_irn_dbg_info(call);
429         ir_node   *block   = get_nodes_block(call);
430         ir_node   **params = get_Call_param_arr(call);
431         ir_type   *method  = get_Call_type(call);
432         int       n        = get_Call_n_params(call);
433         ir_node   *l_res, *h_res;
434         (void) ctx;
435
436         if (n == 1) {
437                 ir_node *float_to_ll;
438
439                 /* We have a Conv float -> long long here */
440                 ir_node *a_f        = params[0];
441                 ir_mode *l_res_mode = get_type_mode(get_method_res_type(method, 0));
442                 ir_mode *h_res_mode = get_type_mode(get_method_res_type(method, 1));
443
444                 assert(mode_is_float(get_irn_mode(a_f)) && "unexpected Conv call");
445
446                 if (mode_is_signed(h_res_mode)) {
447                         /* convert from float to signed 64bit */
448                         float_to_ll = new_bd_ia32_l_FloattoLL(dbg, block, a_f);
449
450                         l_res = new_r_Proj(float_to_ll, l_res_mode,
451                                            pn_ia32_l_FloattoLL_res_low);
452                         h_res = new_r_Proj(float_to_ll, h_res_mode,
453                                                            pn_ia32_l_FloattoLL_res_high);
454                 } else {
455                         /* Convert from float to unsigned 64bit. */
456                         ir_tarval *flt_tv   = new_tarval_from_str("9223372036854775808", 19, ia32_mode_E);
457                         ir_node   *flt_corr = new_r_Const(irg, flt_tv);
458                         ir_node   *lower_blk = block;
459                         ir_node   *upper_blk;
460                         ir_node   *cmp, *proj, *cond, *blk, *int_phi, *flt_phi;
461                         ir_node   *in[2];
462
463                         part_block(call);
464                         upper_blk = get_nodes_block(call);
465
466                         a_f   = new_rd_Conv(dbg, upper_blk, a_f, ia32_mode_E);
467                         cmp   = new_rd_Cmp(dbg, upper_blk, a_f, flt_corr, ir_relation_less);
468                         cond  = new_rd_Cond(dbg, upper_blk, cmp);
469                         in[0] = new_r_Proj(cond, mode_X, pn_Cond_true);
470                         in[1] = new_r_Proj(cond, mode_X, pn_Cond_false);
471                         blk   = new_r_Block(irg, 1, &in[1]);
472                         in[1] = new_r_Jmp(blk);
473
474                         set_irn_in(lower_blk, 2, in);
475
476                         /* create to Phis */
477                         in[0] = new_r_Const(irg, get_mode_null(h_res_mode));
478                         in[1] = new_r_Const_long(irg, h_res_mode, 0x80000000);
479
480                         int_phi = new_r_Phi(lower_blk, 2, in, h_res_mode);
481
482                         in[0] = a_f;
483                         in[1] = new_rd_Sub(dbg, upper_blk, a_f, flt_corr, ia32_mode_E);
484
485                         flt_phi = new_r_Phi(lower_blk, 2, in, ia32_mode_E);
486
487                         /* fix Phi links for next part_block() */
488                         if (is_Phi(int_phi))
489                                 add_Block_phi(lower_blk, int_phi);
490                         if (is_Phi(flt_phi))
491                                 add_Block_phi(lower_blk, flt_phi);
492
493                         float_to_ll = new_bd_ia32_l_FloattoLL(dbg, lower_blk, flt_phi);
494
495                         l_res = new_r_Proj(float_to_ll, l_res_mode,
496                                                            pn_ia32_l_FloattoLL_res_low);
497                         h_res = new_r_Proj(float_to_ll, h_res_mode,
498                                                            pn_ia32_l_FloattoLL_res_high);
499
500                         h_res = new_rd_Add(dbg, lower_blk, h_res, int_phi, h_res_mode);
501
502                         /* move the call and its Proj's to the lower block */
503                         set_nodes_block(call, lower_blk);
504
505                         for (proj = (ir_node*)get_irn_link(call); proj != NULL;
506                              proj = (ir_node*)get_irn_link(proj)) {
507                                 set_nodes_block(proj, lower_blk);
508                         }
509                         block = lower_blk;
510                 }
511                 /* lower the call */
512                 resolve_call(call, l_res, h_res, irg, block);
513         } else if (n == 2) {
514                 ir_node *ll_to_float;
515
516                 /* We have a Conv long long -> float here */
517                 ir_node *a_l       = params[BINOP_Left_Low];
518                 ir_node *a_h       = params[BINOP_Left_High];
519                 ir_mode *fres_mode = get_type_mode(get_method_res_type(method, 0));
520
521                 assert(! mode_is_float(get_irn_mode(a_l))
522                                 && ! mode_is_float(get_irn_mode(a_h)));
523
524                 ll_to_float = new_bd_ia32_l_LLtoFloat(dbg, block, a_h, a_l, fres_mode);
525
526                 /* lower the call */
527                 resolve_call(call, ll_to_float, NULL, irg, block);
528         } else {
529                 panic("unexpected Conv call %+F", call);
530         }
531
532         return 1;
533 }
534
535 /* Ia32 implementation of intrinsic mapping. */
536 ir_entity *ia32_create_intrinsic_fkt(ir_type *method, const ir_op *op,
537                                      const ir_mode *imode, const ir_mode *omode,
538                                      void *context)
539 {
540         i_record      elt;
541         ir_entity     **ent = NULL;
542         i_mapper_func mapper;
543
544         if (! intrinsics)
545                 intrinsics = NEW_ARR_F(i_record, 0);
546
547         switch (get_op_code(op)) {
548         case iro_Add:
549                 ent    = &i_ents[iro_Add];
550                 mapper = map_Add;
551                 break;
552         case iro_Sub:
553                 ent    = &i_ents[iro_Sub];
554                 mapper = map_Sub;
555                 break;
556         case iro_Mul:
557                 ent    = &i_ents[iro_Mul];
558                 mapper = map_Mul;
559                 break;
560         case iro_Minus:
561                 ent    = &i_ents[iro_Minus];
562                 mapper = map_Minus;
563                 break;
564         case iro_Div:
565                 ent    = &i_ents[iro_Div];
566                 mapper = map_Div;
567                 break;
568         case iro_Mod:
569                 ent    = &i_ents[iro_Mod];
570                 mapper = map_Mod;
571                 break;
572         case iro_Conv:
573                 ent    = &i_ents[iro_Conv];
574                 mapper = map_Conv;
575                 break;
576         default:
577                 fprintf(stderr, "FIXME: unhandled op for ia32 intrinsic function %s\n", get_id_str(op->name));
578                 return def_create_intrinsic_fkt(method, op, imode, omode, context);
579         }
580
581         if (ent && ! *ent) {
582                 ident *id = id_mangle(ID("L"), get_op_ident(op));
583                 *ent = new_entity(get_glob_type(), id, method);
584                 set_entity_visibility(*ent, ir_visibility_private);
585         }
586
587         elt.i_call.kind     = INTRINSIC_CALL;
588         elt.i_call.i_ent    = *ent;
589         elt.i_call.i_mapper = mapper;
590         elt.i_call.ctx      = context;
591         elt.i_call.link     = NULL;
592
593         ARR_APP1(i_record, intrinsics, elt);
594         return *ent;
595 }