cleanup iredges API a bit
[libfirm] / ir / be / ia32 / ia32_intrinsics.c
1 /*
2  * Copyright (C) 1995-2008 University of Karlsruhe.  All right reserved.
3  *
4  * This file is part of libFirm.
5  *
6  * This file may be distributed and/or modified under the terms of the
7  * GNU General Public License version 2 as published by the Free Software
8  * Foundation and appearing in the file LICENSE.GPL included in the
9  * packaging of this file.
10  *
11  * Licensees holding valid libFirm Professional Edition licenses may use
12  * this file in accordance with the libFirm Commercial License.
13  * Agreement provided with the Software.
14  *
15  * This file is provided AS IS with NO WARRANTY OF ANY KIND, INCLUDING THE
16  * WARRANTY OF DESIGN, MERCHANTABILITY AND FITNESS FOR A PARTICULAR
17  * PURPOSE.
18  */
19
20 /**
21  * @file
22  * @brief       This file implements the mapping of 64Bit intrinsic
23  *              functions to code or library calls.
24  * @author      Michael Beck
25  * @version     $Id$
26  */
27 #include "config.h"
28
29 #include "iredges.h"
30 #include "irgmod.h"
31 #include "irop.h"
32 #include "irnode_t.h"
33 #include "ircons.h"
34 #include "irprog_t.h"
35 #include "lowering.h"
36 #include "array.h"
37 #include "error.h"
38
39 #include "ia32_new_nodes.h"
40 #include "bearch_ia32_t.h"
41 #include "gen_ia32_regalloc_if.h"
42 #include "begnuas.h"
43
44 /** The array of all intrinsics that must be mapped. */
45 static i_record *intrinsics;
46
47 /** An array to cache all entities. */
48 static ir_entity *i_ents[iro_Last + 1];
49
50 /*
51  * Maps all intrinsic calls that the backend support
52  * and map all instructions the backend did not support
53  * to runtime calls.
54  */
55 void ia32_handle_intrinsics(void)
56 {
57         if (intrinsics && ARR_LEN(intrinsics) > 0) {
58                 lower_intrinsics(intrinsics, ARR_LEN(intrinsics), /*part_block_used=*/1);
59         }
60 }
61
62 #define BINOP_Left_Low   0
63 #define BINOP_Left_High  1
64 #define BINOP_Right_Low  2
65 #define BINOP_Right_High 3
66
67 /**
68  * Reroute edges from the pn_Call_T_result proj of a call.
69  *
70  * @param proj   the pn_Call_T_result Proj
71  * @param l_res  the lower 32 bit result
72  * @param h_res  the upper 32 bit result or NULL
73  */
74 static void reroute_result(ir_node *proj, ir_node *l_res, ir_node *h_res)
75 {
76         const ir_edge_t *edge, *next;
77
78         foreach_out_edge_safe(proj, edge, next) {
79                 ir_node *proj = get_edge_src_irn(edge);
80                 long    pn    = get_Proj_proj(proj);
81
82                 if (pn == 0) {
83                         edges_reroute(proj, l_res);
84                 } else if (pn == 1 && h_res != NULL) {
85                         edges_reroute(proj, h_res);
86                 } else {
87                         panic("Unsupported Result-Proj from Call found");
88                 }
89         }
90 }
91
92 /**
93  * Replace a call be a tuple of l_res, h_res.
94  *
95  * @param call   the call node to replace
96  * @param l_res  the lower 32 bit result
97  * @param h_res  the upper 32 bit result or NULL
98  * @param irg    the graph to replace on
99  * @param block  the block to replace on (always the call block)
100  */
101 static void resolve_call(ir_node *call, ir_node *l_res, ir_node *h_res, ir_graph *irg, ir_node *block)
102 {
103         ir_node *jmp, *res, *in[2];
104         ir_node *bad   = get_irg_bad(irg);
105         ir_node *nomem = get_irg_no_mem(irg);
106         int     old_cse;
107
108         if (edges_activated(irg)) {
109                 /* use rerouting to prevent some warning in the backend */
110                 const ir_edge_t *edge, *next;
111
112                 foreach_out_edge_safe(call, edge, next) {
113                         ir_node *proj = get_edge_src_irn(edge);
114                         pn_Call pn    = (pn_Call)get_Proj_proj(proj);
115
116                         switch (pn) {
117                         case pn_Call_X_regular:
118                                 /* Beware:
119                                  * We do not check here if this call really has exception and regular Proj's.
120                                  * new_r_Jmp might than be CSEd with the real exit jmp and then bad things happen
121                                  * (in movgen.c from 186.crafty for example).
122                                  * So be sure the newly created Jmp cannot CSE.
123                                  */
124                                 old_cse = get_opt_cse();
125                                 set_opt_cse(0);
126                                 jmp = new_r_Jmp(block);
127                                 set_opt_cse(old_cse);
128                                 edges_reroute(proj, jmp);
129                                 break;
130
131                         case pn_Call_X_except:
132                                 /* should not happen here */
133                                 edges_reroute(proj, bad);
134                                 break;
135                         case pn_Call_M:
136                                 /* should not happen here */
137                                 edges_reroute(proj, nomem);
138                                 break;
139                         case pn_Call_T_result:
140                                 reroute_result(proj, l_res, h_res);
141                                 break;
142                         default:
143                                 panic("Wrong Proj from Call");
144                         }
145                         kill_node(proj);
146                 }
147                 kill_node(call);
148         } else {
149                 /* no edges, build Tuple */
150                 if (h_res == NULL)
151                         res = l_res;
152                 else {
153                         in[0] = l_res;
154                         in[1] = h_res;
155                         res = new_r_Tuple(block, 2, in);
156                 }
157
158                 turn_into_tuple(call, pn_Call_max);
159                 /*
160                  * Beware:
161                  * We do not check here if this call really has exception and regular Proj's.
162                  * new_r_Jmp might than be CSEd with the real exit jmp and then bad things happen
163                  * (in movgen.c from 186.crafty for example).
164                  * So be sure the newly created Jmp cannot CSE.
165                  */
166                 old_cse = get_opt_cse();
167                 set_opt_cse(0);
168                 jmp = new_r_Jmp(block);
169                 set_opt_cse(old_cse);
170
171                 set_Tuple_pred(call, pn_Call_M,                nomem);
172                 set_Tuple_pred(call, pn_Call_X_regular,        jmp);
173                 set_Tuple_pred(call, pn_Call_X_except,         bad);
174                 set_Tuple_pred(call, pn_Call_T_result,         res);
175         }
176 }
177
178 /**
179  * Map an Add (a_l, a_h, b_l, b_h)
180  */
181 static int map_Add(ir_node *call, void *ctx)
182 {
183         dbg_info *dbg        = get_irn_dbg_info(call);
184         ir_node  *block      = get_nodes_block(call);
185         ir_node  **params    = get_Call_param_arr(call);
186         ir_type  *method     = get_Call_type(call);
187         ir_node  *a_l        = params[BINOP_Left_Low];
188         ir_node  *a_h        = params[BINOP_Left_High];
189         ir_node  *b_l        = params[BINOP_Right_Low];
190         ir_node  *b_h        = params[BINOP_Right_High];
191         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
192         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
193         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
194         ir_node  *add_low, *add_high, *flags;
195         ir_node  *l_res, *h_res;
196         (void) ctx;
197
198         /* l_res = a_l + b_l */
199         /* h_res = a_h + b_h + carry */
200
201         add_low  = new_bd_ia32_l_Add(dbg, block, a_l, b_l, mode_T);
202         flags    = new_r_Proj(add_low, mode_flags, pn_ia32_flags);
203         add_high = new_bd_ia32_l_Adc(dbg, block, a_h, b_h, flags, h_mode);
204
205         l_res = new_r_Proj(add_low, l_mode, pn_ia32_res);
206         h_res = add_high;
207
208         resolve_call(call, l_res, h_res, current_ir_graph, block);
209         return 1;
210 }
211
212 /**
213  * Map a Sub (a_l, a_h, b_l, b_h)
214  */
215 static int map_Sub(ir_node *call, void *ctx)
216 {
217         dbg_info *dbg        = get_irn_dbg_info(call);
218         ir_node  *block      = get_nodes_block(call);
219         ir_node  **params    = get_Call_param_arr(call);
220         ir_type  *method     = get_Call_type(call);
221         ir_node  *a_l        = params[BINOP_Left_Low];
222         ir_node  *a_h        = params[BINOP_Left_High];
223         ir_node  *b_l        = params[BINOP_Right_Low];
224         ir_node  *b_h        = params[BINOP_Right_High];
225         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
226         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
227         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
228         ir_node  *sub_low, *sub_high, *flags;
229         ir_node  *l_res, *h_res;
230         (void) ctx;
231
232         /* l_res = a_l - b_l */
233         /* h_res = a_h - b_h - carry */
234
235         sub_low  = new_bd_ia32_l_Sub(dbg, block, a_l, b_l, mode_T);
236         flags    = new_r_Proj(sub_low, mode_flags, pn_ia32_flags);
237         sub_high = new_bd_ia32_l_Sbb(dbg, block, a_h, b_h, flags, h_mode);
238
239         l_res = new_r_Proj(sub_low, l_mode, pn_ia32_res);
240         h_res = sub_high;
241
242         resolve_call(call, l_res, h_res, current_ir_graph, block);
243         return 1;
244 }
245
246 /**
247  * Map a Shl (a_l, a_h, count)
248  */
249 static int map_Shl(ir_node *call, void *ctx)
250 {
251         ir_graph *irg     = current_ir_graph;
252         dbg_info *dbg     = get_irn_dbg_info(call);
253         ir_node  *block   = get_nodes_block(call);
254         ir_node  **params = get_Call_param_arr(call);
255         ir_type  *method  = get_Call_type(call);
256         ir_node  *a_l     = params[BINOP_Left_Low];
257         ir_node  *a_h     = params[BINOP_Left_High];
258         ir_node  *cnt     = params[BINOP_Right_Low];
259         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
260         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
261         ir_mode  *c_mode;
262         ir_node  *l_res, *h_res, *irn, *cond, *upper, *n_block, *l1, *l2, *h1, *h2, *in[2];
263         (void) ctx;
264
265         if (is_Const(cnt)) {
266                 /* the shift count is a const, create better code */
267                 ir_tarval *tv = get_Const_tarval(cnt);
268
269                 if (tarval_cmp(tv, new_tarval_from_long(32, l_mode))
270                                 & (ir_relation_greater_equal)) {
271                         /* simplest case: shift only the lower bits. Note that there is no
272                            need to reduce the constant here, this is done by the hardware.  */
273                         ir_node *conv = new_rd_Conv(dbg, block, a_l, h_mode);
274                         h_res = new_rd_Shl(dbg, block, conv, cnt, h_mode);
275                         l_res = new_rd_Const(dbg, irg, get_mode_null(l_mode));
276
277                 } else {
278                         /* h_res = SHLD a_h, a_l, cnt */
279                         h_res = new_bd_ia32_l_ShlD(dbg, block, a_h, a_l, cnt, h_mode);
280
281                         /* l_res = SHL a_l, cnt */
282                         l_res = new_bd_ia32_l_ShlDep(dbg, block, a_l, cnt, h_res, l_mode);
283                 }
284
285                 resolve_call(call, l_res, h_res, irg, block);
286                 return 1;
287         }
288
289         part_block(call);
290         upper = get_nodes_block(call);
291
292         /* h_res = SHLD a_h, a_l, cnt */
293         h1 = new_bd_ia32_l_ShlD(dbg, upper, a_h, a_l, cnt, h_mode);
294
295         /* l_res = SHL a_l, cnt */
296         l1 = new_bd_ia32_l_ShlDep(dbg, upper, a_l, cnt, h1, l_mode);
297
298         c_mode = get_irn_mode(cnt);
299         irn    = new_r_Const_long(irg, c_mode, 32);
300         irn    = new_rd_And(dbg, upper, cnt, irn, c_mode);
301         irn    = new_rd_Cmp(dbg, upper, irn, new_r_Const(irg, get_mode_null(c_mode)), ir_relation_equal);
302         cond   = new_rd_Cond(dbg, upper, irn);
303
304         in[0]  = new_r_Proj(cond, mode_X, pn_Cond_true);
305         in[1]  = new_r_Proj(cond, mode_X, pn_Cond_false);
306
307         /* the block for cnt >= 32 */
308         n_block = new_rd_Block(dbg, irg, 1, &in[1]);
309         h2      = new_rd_Conv(dbg, n_block, l1, h_mode);
310         l2      = new_r_Const(irg, get_mode_null(l_mode));
311         in[1]   = new_r_Jmp(n_block);
312
313         set_irn_in(block, 2, in);
314
315         in[0] = l1;
316         in[1] = l2;
317         l_res = new_r_Phi(block, 2, in, l_mode);
318         set_Block_phis(block, l_res);
319
320         in[0] = h1;
321         in[1] = h2;
322         h_res = new_r_Phi(block, 2, in, h_mode);
323         set_Phi_next(l_res, h_res);
324         set_Phi_next(h_res, NULL);
325
326         /* move it down */
327         set_nodes_block(call, block);
328         for (irn = (ir_node*)get_irn_link(call); irn != NULL;
329              irn = (ir_node*)get_irn_link(irn)) {
330                 set_nodes_block(irn, block);
331         }
332
333         resolve_call(call, l_res, h_res, irg, block);
334         return 1;
335 }
336
337 /**
338  * Map a Shr (a_l, a_h, count)
339  */
340 static int map_Shr(ir_node *call, void *ctx)
341 {
342         ir_graph *irg     = current_ir_graph;
343         dbg_info *dbg     = get_irn_dbg_info(call);
344         ir_node  *block   = get_nodes_block(call);
345         ir_node  **params = get_Call_param_arr(call);
346         ir_type  *method  = get_Call_type(call);
347         ir_node  *a_l     = params[BINOP_Left_Low];
348         ir_node  *a_h     = params[BINOP_Left_High];
349         ir_node  *cnt     = params[BINOP_Right_Low];
350         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
351         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
352         ir_mode  *c_mode;
353         ir_node  *l_res, *h_res, *irn, *cond, *upper, *n_block, *l1, *l2, *h1, *h2, *in[2];
354         (void) ctx;
355
356         if (is_Const(cnt)) {
357                 /* the shift count is a const, create better code */
358                 ir_tarval *tv = get_Const_tarval(cnt);
359
360                 if (tarval_cmp(tv, new_tarval_from_long(32, l_mode)) & (ir_relation_greater_equal)) {
361                         /* simplest case: shift only the higher bits. Note that there is no
362                            need to reduce the constant here, this is done by the hardware.  */
363                         ir_node *conv = new_rd_Conv(dbg, block, a_h, l_mode);
364                         h_res = new_rd_Const(dbg, irg, get_mode_null(h_mode));
365                         l_res = new_rd_Shr(dbg, block, conv, cnt, l_mode);
366                 } else {
367                         /* l_res = SHRD a_h:a_l, cnt */
368                         l_res = new_bd_ia32_l_ShrD(dbg, block, a_l, a_h, cnt, l_mode);
369
370                         /* h_res = SHR a_h, cnt */
371                         h_res = new_bd_ia32_l_ShrDep(dbg, block, a_h, cnt, l_res, h_mode);
372                 }
373                 resolve_call(call, l_res, h_res, irg, block);
374                 return 1;
375         }
376
377         part_block(call);
378         upper = get_nodes_block(call);
379
380         /* l_res = SHRD a_h:a_l, cnt */
381         l1 = new_bd_ia32_l_ShrD(dbg, upper, a_l, a_h, cnt, l_mode);
382
383         /* h_res = SHR a_h, cnt */
384         h1 = new_bd_ia32_l_ShrDep(dbg, upper, a_h, cnt, l1, h_mode);
385
386         c_mode = get_irn_mode(cnt);
387         irn    = new_r_Const_long(irg, c_mode, 32);
388         irn    = new_rd_And(dbg, upper, cnt, irn, c_mode);
389         irn    = new_rd_Cmp(dbg, upper, irn, new_r_Const(irg, get_mode_null(c_mode)), ir_relation_equal);
390         cond   = new_rd_Cond(dbg, upper, irn);
391
392         in[0]  = new_r_Proj(cond, mode_X, pn_Cond_true);
393         in[1]  = new_r_Proj(cond, mode_X, pn_Cond_false);
394
395         /* the block for cnt >= 32 */
396         n_block = new_rd_Block(dbg, irg, 1, &in[1]);
397         l2      = new_rd_Conv(dbg, n_block, h1, l_mode);
398         h2      = new_r_Const(irg, get_mode_null(h_mode));
399         in[1]   = new_r_Jmp(n_block);
400
401         set_irn_in(block, 2, in);
402
403         in[0] = l1;
404         in[1] = l2;
405         l_res = new_r_Phi(block, 2, in, l_mode);
406         set_Block_phis(block, l_res);
407
408         in[0] = h1;
409         in[1] = h2;
410         h_res = new_r_Phi(block, 2, in, h_mode);
411         set_Phi_next(l_res, h_res);
412         set_Phi_next(h_res, NULL);
413
414         /* move it down */
415         set_nodes_block(call, block);
416         for (irn = (ir_node*)get_irn_link(call); irn != NULL;
417              irn = (ir_node*)get_irn_link(irn)) {
418                 set_nodes_block(irn, block);
419         }
420
421         resolve_call(call, l_res, h_res, irg, block);
422         return 1;
423 }
424
425 /**
426  * Map a Shrs (a_l, a_h, count)
427  */
428 static int map_Shrs(ir_node *call, void *ctx)
429 {
430         ir_graph *irg     = current_ir_graph;
431         dbg_info *dbg     = get_irn_dbg_info(call);
432         ir_node  *block   = get_nodes_block(call);
433         ir_node  **params = get_Call_param_arr(call);
434         ir_type  *method  = get_Call_type(call);
435         ir_node  *a_l     = params[BINOP_Left_Low];
436         ir_node  *a_h     = params[BINOP_Left_High];
437         ir_node  *cnt     = params[BINOP_Right_Low];
438         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
439         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
440         ir_mode  *c_mode;
441         ir_node  *l_res, *h_res, *irn, *cond, *upper, *n_block, *l1, *l2, *h1, *h2, *in[2];
442         (void) ctx;
443
444         if (is_Const(cnt)) {
445                 /* the shift count is a const, create better code */
446                 ir_tarval *tv = get_Const_tarval(cnt);
447
448                 if (tarval_cmp(tv, new_tarval_from_long(32, l_mode)) & (ir_relation_greater_equal)) {
449                         /* simplest case: shift only the higher bits. Note that there is no
450                            need to reduce the constant here, this is done by the hardware.  */
451                         ir_node *conv    = new_rd_Conv(dbg, block, a_h, l_mode);
452                         ir_mode *c_mode  = get_irn_mode(cnt);
453
454                         h_res = new_rd_Shrs(dbg, block, a_h, new_r_Const_long(irg, c_mode, 31), h_mode);
455                         l_res = new_rd_Shrs(dbg, block, conv, cnt, l_mode);
456                 } else {
457                         /* l_res = SHRD a_h:a_l, cnt */
458                         l_res = new_bd_ia32_l_ShrD(dbg, block, a_l, a_h, cnt, l_mode);
459
460                         /* h_res = SAR a_h, cnt */
461                         h_res = new_bd_ia32_l_SarDep(dbg, block, a_h, cnt, l_res, h_mode);
462                 }
463                 resolve_call(call, l_res, h_res, irg, block);
464                 return 1;
465         }
466
467         part_block(call);
468         upper = get_nodes_block(call);
469
470         /* l_res = SHRD a_h:a_l, cnt */
471         l1 = new_bd_ia32_l_ShrD(dbg, upper, a_l, a_h, cnt, l_mode);
472
473         /* h_res = SAR a_h, cnt */
474         h1 = new_bd_ia32_l_SarDep(dbg, upper, a_h, cnt, l1, h_mode);
475
476         c_mode = get_irn_mode(cnt);
477         irn    = new_r_Const_long(irg, c_mode, 32);
478         irn    = new_rd_And(dbg, upper, cnt, irn, c_mode);
479         irn    = new_rd_Cmp(dbg, upper, irn, new_r_Const(irg, get_mode_null(c_mode)), ir_relation_equal);
480         cond   = new_rd_Cond(dbg, upper, irn);
481
482         in[0]  = new_r_Proj(cond, mode_X, pn_Cond_true);
483         in[1]  = new_r_Proj(cond, mode_X, pn_Cond_false);
484
485         /* the block for cnt >= 32 */
486         n_block = new_rd_Block(dbg, irg, 1, &in[1]);
487         l2      = new_rd_Conv(dbg, n_block, h1, l_mode);
488         h2      = new_rd_Shrs(dbg, n_block, a_h, new_r_Const_long(irg, c_mode, 31), h_mode);
489         in[1]   = new_r_Jmp(n_block);
490
491         set_irn_in(block, 2, in);
492
493         in[0] = l1;
494         in[1] = l2;
495         l_res = new_r_Phi(block, 2, in, l_mode);
496         set_Block_phis(block, l_res);
497
498         in[0] = h1;
499         in[1] = h2;
500         h_res = new_r_Phi(block, 2, in, h_mode);
501         set_Phi_next(l_res, h_res);
502         set_Phi_next(h_res, NULL);
503
504         /* move it down */
505         set_nodes_block(call, block);
506         for (irn = (ir_node*)get_irn_link(call); irn != NULL;
507              irn = (ir_node*)get_irn_link(irn)) {
508                 set_nodes_block(irn, block);
509         }
510
511         resolve_call(call, l_res, h_res, irg, block);
512         return 1;
513 }
514
515 /**
516  * Checks where node high is a sign extension of low.
517  */
518 static int is_sign_extend(ir_node *low, ir_node *high)
519 {
520         if (is_Shrs(high)) {
521                 ir_node   *high_l;
522                 ir_node   *high_r;
523                 ir_tarval *shift_count;
524
525                 high_r = get_Shrs_right(high);
526                 if (!is_Const(high_r)) return 0;
527
528                 shift_count = get_Const_tarval(high_r);
529                 if (!tarval_is_long(shift_count))       return 0;
530                 if (get_tarval_long(shift_count) != 31) return 0;
531
532                 high_l = get_Shrs_left(high);
533
534                 if (is_Conv(low)    && get_Conv_op(low)    == high_l) return 1;
535                 if (is_Conv(high_l) && get_Conv_op(high_l) == low)    return 1;
536         } else if (is_Const(low) && is_Const(high)) {
537                 ir_tarval *tl = get_Const_tarval(low);
538                 ir_tarval *th = get_Const_tarval(high);
539
540                 if (tarval_is_long(th) && tarval_is_long(tl)) {
541                         long l = get_tarval_long(tl);
542                         long h = get_tarval_long(th);
543
544                         return (h == 0  && l >= 0) || (h == -1 && l <  0);
545                 }
546         }
547
548         return 0;
549 }
550
551 /**
552  * Map a Mul (a_l, a_h, b_l, b_h)
553  */
554 static int map_Mul(ir_node *call, void *ctx)
555 {
556         dbg_info *dbg     = get_irn_dbg_info(call);
557         ir_node  *block   = get_nodes_block(call);
558         ir_node  **params = get_Call_param_arr(call);
559         ir_type  *method  = get_Call_type(call);
560         ir_node  *a_l     = params[BINOP_Left_Low];
561         ir_node  *a_h     = params[BINOP_Left_High];
562         ir_node  *b_l     = params[BINOP_Right_Low];
563         ir_node  *b_h     = params[BINOP_Right_High];
564         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
565         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
566         ir_node  *l_res, *h_res, *mul, *pEDX, *add;
567         (void) ctx;
568
569         /*
570                 EDX:EAX = a_l * b_l
571                 l_res   = EAX
572
573                 t1 = b_l * a_h
574                 t2 = t1 + EDX
575                 t3 = a_l * b_h
576                 h_res = t2 + t3
577         */
578
579         /* handle the often used case of 32x32=64 mul */
580         if (is_sign_extend(a_l, a_h) && is_sign_extend(b_l, b_h)) {
581                 mul   = new_bd_ia32_l_IMul(dbg, block, a_l, b_l);
582                 h_res = new_rd_Proj(dbg, mul, h_mode, pn_ia32_l_IMul_res_high);
583                 l_res = new_rd_Proj(dbg, mul, l_mode, pn_ia32_l_IMul_res_low);
584         } else {
585                 /* note that zero extension is handled hare efficiently */
586                 mul   = new_bd_ia32_l_Mul(dbg, block, a_l, b_l);
587                 pEDX  = new_rd_Proj(dbg, mul, h_mode, pn_ia32_l_Mul_res_high);
588                 l_res = new_rd_Proj(dbg, mul, l_mode, pn_ia32_l_Mul_res_low);
589
590                 b_l   = new_rd_Conv(dbg, block, b_l, h_mode);
591                 mul   = new_rd_Mul( dbg, block, a_h, b_l, h_mode);
592                 add   = new_rd_Add( dbg, block, mul, pEDX, h_mode);
593                 a_l   = new_rd_Conv(dbg, block, a_l, h_mode);
594                 mul   = new_rd_Mul( dbg, block, a_l, b_h, h_mode);
595                 h_res = new_rd_Add( dbg, block, add, mul, h_mode);
596         }
597         resolve_call(call, l_res, h_res, current_ir_graph, block);
598
599         return 1;
600 }
601
602 /**
603  * Map a Minus (a_l, a_h)
604  */
605 static int map_Minus(ir_node *call, void *ctx)
606 {
607         dbg_info *dbg     = get_irn_dbg_info(call);
608         ir_node  *block   = get_nodes_block(call);
609         ir_node  **params = get_Call_param_arr(call);
610         ir_type  *method  = get_Call_type(call);
611         ir_node  *a_l     = params[BINOP_Left_Low];
612         ir_node  *a_h     = params[BINOP_Left_High];
613         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
614         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
615         ir_node  *l_res, *h_res, *res;
616         (void) ctx;
617
618         res   = new_bd_ia32_Minus64Bit(dbg, block, a_l, a_h);
619         l_res = new_r_Proj(res, l_mode, pn_ia32_Minus64Bit_low_res);
620         h_res = new_r_Proj(res, h_mode, pn_ia32_Minus64Bit_high_res);
621
622         resolve_call(call, l_res, h_res, current_ir_graph, block);
623
624         return 1;
625 }
626
627 #if 0
628 /**
629  * Map a Abs (a_l, a_h)
630  */
631 static int map_Abs(ir_node *call, void *ctx)
632 {
633         dbg_info *dbg        = get_irn_dbg_info(call);
634         ir_node  *block      = get_nodes_block(call);
635         ir_node  **params    = get_Call_param_arr(call);
636         ir_type  *method     = get_Call_type(call);
637         ir_node  *a_l        = params[BINOP_Left_Low];
638         ir_node  *a_h        = params[BINOP_Left_High];
639         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
640         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
641         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
642         ir_node  *l_res, *h_res, *sign, *sub_l, *sub_h;
643         ir_node  *sign_l;
644         ir_node  *l_sub;
645         ir_node  *flags;
646         (void) ctx;
647
648         /*
649                 Code inspired by gcc output :) (although gcc doubles the
650                 operation for t1 as t2 and uses t1 for operations with low part
651                 and t2 for operations with high part which is actually unnecessary
652                 because t1 and t2 represent the same value)
653
654                 t1    = SHRS a_h, 31
655                 t2    = a_l ^ t1
656                 t3    = a_h ^ t1
657                 l_res = t2 - t1
658                 h_res = t3 - t1 - carry
659
660         */
661
662         /* TODO: give a hint to the backend somehow to not create a cltd here... */
663         sign   = new_rd_Shrs(dbg, block, a_h, new_r_Const_long(irg, l_mode, 31), h_mode);
664         sign_l = new_rd_Conv(dbg, block, sign, l_mode);
665         sub_l  = new_rd_Eor(dbg, block, a_l, sign_l, l_mode);
666         sub_h  = new_rd_Eor(dbg, block, a_h, sign,   h_mode);
667
668         l_sub  = new_bd_ia32_l_Sub(dbg, block, sub_l, sign_l, mode_T);
669         l_res  = new_r_Proj(l_sub, l_mode,     pn_ia32_res);
670         flags  = new_r_Proj(l_sub, mode_flags, pn_ia32_flags);
671         h_res  = new_bd_ia32_l_Sbb(dbg, block, sub_h, sign, flags, h_mode);
672
673         resolve_call(call, l_res, h_res, current_ir_graph, block);
674
675         return 1;
676 }
677 #endif
678
679 #define ID(x) new_id_from_chars(x, sizeof(x)-1)
680
681 static ir_entity *create_compiler_lib_entity(const char *name, ir_type *type)
682 {
683         ir_type   *glob   = get_glob_type();
684         ident     *id     = new_id_from_str(name);
685         ir_entity *entity;
686
687         /* Hack: we need to know the type of runtime library we use. Strictly
688            speaking it's not the same as the object-file-format. But in practice
689            the following should be enough */
690         if (be_gas_object_file_format == OBJECT_FILE_FORMAT_MACH_O
691                         || be_gas_object_file_format == OBJECT_FILE_FORMAT_COFF) {
692                 id = id_mangle3("___", id, "");
693         } else {
694                 id = id_mangle3("__", id, "");
695         }
696         entity = new_entity(glob, id, type);
697         set_entity_visibility(entity, ir_visibility_local);
698         set_entity_ld_ident(entity, id);
699         return entity;
700 }
701
702 /**
703  * Maps a Div. Change into a library call.
704  */
705 static int map_Div(ir_node *call, void *ctx)
706 {
707         ia32_intrinsic_env_t *env = (ia32_intrinsic_env_t*)ctx;
708         ir_type   *method    = get_Call_type(call);
709         ir_mode   *h_mode    = get_type_mode(get_method_res_type(method, 1));
710         ir_node   *ptr;
711         ir_entity *ent;
712         ir_graph  *irg = get_irn_irg(call);
713         symconst_symbol sym;
714
715         if (mode_is_signed(h_mode)) {
716                 /* 64bit signed Division */
717                 ent = env->divdi3;
718                 if (ent == NULL) {
719                         ent = env->divdi3 = create_compiler_lib_entity("divdi3", method);
720                 }
721         } else {
722                 /* 64bit unsigned Division */
723                 ent = env->udivdi3;
724                 if (ent == NULL) {
725                         /* create library entity */
726                         ent = env->udivdi3 = create_compiler_lib_entity("udivdi3", method);
727                 }
728         }
729
730         ptr = get_Call_ptr(call);
731         sym.entity_p = ent;
732         ptr = new_r_SymConst(irg, get_irn_mode(ptr), sym, symconst_addr_ent);
733         set_Call_ptr(call, ptr);
734
735         return 1;
736 }
737
738 /**
739  * Maps a Mod. Change into a library call
740  */
741 static int map_Mod(ir_node *call, void *ctx)
742 {
743         ia32_intrinsic_env_t *env = (ia32_intrinsic_env_t*)ctx;
744         ir_type   *method    = get_Call_type(call);
745         ir_mode   *h_mode    = get_type_mode(get_method_res_type(method, 1));
746         ir_node   *ptr;
747         ir_entity *ent;
748         ir_graph  *irg = get_irn_irg(call);
749         symconst_symbol sym;
750
751         if (mode_is_signed(h_mode)) {
752                 /* 64bit signed Modulo */
753                 ent = env->moddi3;
754                 if (ent == NULL) {
755                         /* create library entity */
756                         ent = env->moddi3 = create_compiler_lib_entity("moddi3", method);
757                 }
758         } else {
759                 /* 64bit signed Modulo */
760                 ent = env->umoddi3;
761                 if (ent == NULL) {
762                         /* create library entity */
763                         ent = env->umoddi3 = create_compiler_lib_entity("umoddi3", method);
764                 }
765         }
766
767         ptr = get_Call_ptr(call);
768         sym.entity_p = ent;
769         ptr = new_r_SymConst(irg, get_irn_mode(ptr), sym, symconst_addr_ent);
770         set_Call_ptr(call, ptr);
771
772         return 1;
773 }
774
775 /**
776  * Maps a Conv.
777  */
778 static int map_Conv(ir_node *call, void *ctx)
779 {
780         ir_graph  *irg     = current_ir_graph;
781         dbg_info  *dbg     = get_irn_dbg_info(call);
782         ir_node   *block   = get_nodes_block(call);
783         ir_node   **params = get_Call_param_arr(call);
784         ir_type   *method  = get_Call_type(call);
785         int       n        = get_Call_n_params(call);
786         ir_node   *l_res, *h_res;
787         (void) ctx;
788
789         if (n == 1) {
790                 ir_node *float_to_ll;
791
792                 /* We have a Conv float -> long long here */
793                 ir_node *a_f        = params[0];
794                 ir_mode *l_res_mode = get_type_mode(get_method_res_type(method, 0));
795                 ir_mode *h_res_mode = get_type_mode(get_method_res_type(method, 1));
796
797                 assert(mode_is_float(get_irn_mode(a_f)) && "unexpected Conv call");
798
799                 if (mode_is_signed(h_res_mode)) {
800                         /* convert from float to signed 64bit */
801                         float_to_ll = new_bd_ia32_l_FloattoLL(dbg, block, a_f);
802
803                         l_res = new_r_Proj(float_to_ll, l_res_mode,
804                                            pn_ia32_l_FloattoLL_res_low);
805                         h_res = new_r_Proj(float_to_ll, h_res_mode,
806                                                            pn_ia32_l_FloattoLL_res_high);
807                 } else {
808                         /* convert from float to signed 64bit */
809                         ir_mode   *flt_mode = get_irn_mode(a_f);
810                         ir_tarval *flt_tv   = new_tarval_from_str("9223372036854775808", 19, flt_mode);
811                         ir_node   *flt_corr = new_r_Const(irg, flt_tv);
812                         ir_node   *lower_blk = block;
813                         ir_node   *upper_blk;
814                         ir_node   *cmp, *proj, *cond, *blk, *int_phi, *flt_phi;
815                         ir_node   *in[2];
816
817                         part_block(call);
818                         upper_blk = get_nodes_block(call);
819
820                         cmp   = new_rd_Cmp(dbg, upper_blk, a_f, flt_corr, ir_relation_less);
821                         cond  = new_rd_Cond(dbg, upper_blk, cmp);
822                         in[0] = new_r_Proj(cond, mode_X, pn_Cond_true);
823                         in[1] = new_r_Proj(cond, mode_X, pn_Cond_false);
824                         blk   = new_r_Block(irg, 1, &in[1]);
825                         in[1] = new_r_Jmp(blk);
826
827                         set_irn_in(lower_blk, 2, in);
828
829                         /* create to Phis */
830                         in[0] = new_r_Const(irg, get_mode_null(h_res_mode));
831                         in[1] = new_r_Const_long(irg, h_res_mode, 0x80000000);
832
833                         int_phi = new_r_Phi(lower_blk, 2, in, h_res_mode);
834
835                         in[0] = a_f;
836                         in[1] = new_rd_Sub(dbg, upper_blk, a_f, flt_corr, flt_mode);
837
838                         flt_phi = new_r_Phi(lower_blk, 2, in, flt_mode);
839
840                         /* fix Phi links for next part_block() */
841                         set_Block_phis(lower_blk, int_phi);
842                         set_Phi_next(int_phi, flt_phi);
843                         set_Phi_next(flt_phi, NULL);
844
845                         float_to_ll = new_bd_ia32_l_FloattoLL(dbg, lower_blk, flt_phi);
846
847                         l_res = new_r_Proj(float_to_ll, l_res_mode,
848                                                            pn_ia32_l_FloattoLL_res_low);
849                         h_res = new_r_Proj(float_to_ll, h_res_mode,
850                                                            pn_ia32_l_FloattoLL_res_high);
851
852                         h_res = new_rd_Add(dbg, lower_blk, h_res, int_phi, h_res_mode);
853
854                         /* move the call and its Proj's to the lower block */
855                         set_nodes_block(call, lower_blk);
856
857                         for (proj = (ir_node*)get_irn_link(call); proj != NULL;
858                              proj = (ir_node*)get_irn_link(proj)) {
859                                 set_nodes_block(proj, lower_blk);
860                         }
861                         block = lower_blk;
862                 }
863                 /* lower the call */
864                 resolve_call(call, l_res, h_res, irg, block);
865         } else if (n == 2) {
866                 ir_node *ll_to_float;
867
868                 /* We have a Conv long long -> float here */
869                 ir_node *a_l       = params[BINOP_Left_Low];
870                 ir_node *a_h       = params[BINOP_Left_High];
871                 ir_mode *fres_mode = get_type_mode(get_method_res_type(method, 0));
872
873                 assert(! mode_is_float(get_irn_mode(a_l))
874                                 && ! mode_is_float(get_irn_mode(a_h)));
875
876                 ll_to_float = new_bd_ia32_l_LLtoFloat(dbg, block, a_h, a_l, fres_mode);
877
878                 /* lower the call */
879                 resolve_call(call, ll_to_float, NULL, irg, block);
880         } else {
881                 panic("unexpected Conv call %+F", call);
882         }
883
884         return 1;
885 }
886
887 /* Ia32 implementation of intrinsic mapping. */
888 ir_entity *ia32_create_intrinsic_fkt(ir_type *method, const ir_op *op,
889                                      const ir_mode *imode, const ir_mode *omode,
890                                      void *context)
891 {
892         i_record      elt;
893         ir_entity     **ent = NULL;
894         i_mapper_func mapper;
895
896         if (! intrinsics)
897                 intrinsics = NEW_ARR_F(i_record, 0);
898
899         switch (get_op_code(op)) {
900         case iro_Add:
901                 ent    = &i_ents[iro_Add];
902                 mapper = map_Add;
903                 break;
904         case iro_Sub:
905                 ent    = &i_ents[iro_Sub];
906                 mapper = map_Sub;
907                 break;
908         case iro_Shl:
909                 ent    = &i_ents[iro_Shl];
910                 mapper = map_Shl;
911                 break;
912         case iro_Shr:
913                 ent    = &i_ents[iro_Shr];
914                 mapper = map_Shr;
915                 break;
916         case iro_Shrs:
917                 ent    = &i_ents[iro_Shrs];
918                 mapper = map_Shrs;
919                 break;
920         case iro_Mul:
921                 ent    = &i_ents[iro_Mul];
922                 mapper = map_Mul;
923                 break;
924         case iro_Minus:
925                 ent    = &i_ents[iro_Minus];
926                 mapper = map_Minus;
927                 break;
928         case iro_Div:
929                 ent    = &i_ents[iro_Div];
930                 mapper = map_Div;
931                 break;
932         case iro_Mod:
933                 ent    = &i_ents[iro_Mod];
934                 mapper = map_Mod;
935                 break;
936         case iro_Conv:
937                 ent    = &i_ents[iro_Conv];
938                 mapper = map_Conv;
939                 break;
940         default:
941                 fprintf(stderr, "FIXME: unhandled op for ia32 intrinsic function %s\n", get_id_str(op->name));
942                 return def_create_intrinsic_fkt(method, op, imode, omode, context);
943         }
944
945         if (ent && ! *ent) {
946 #define IDENT(s)  new_id_from_chars(s, sizeof(s)-1)
947
948                 ident *id = id_mangle(IDENT("L"), get_op_ident(op));
949                 *ent = new_entity(get_glob_type(), id, method);
950                 set_entity_visibility(*ent, ir_visibility_private);
951         }
952
953         elt.i_call.kind     = INTRINSIC_CALL;
954         elt.i_call.i_ent    = *ent;
955         elt.i_call.i_mapper = mapper;
956         elt.i_call.ctx      = context;
957         elt.i_call.link     = NULL;
958
959         ARR_APP1(i_record, intrinsics, elt);
960         return *ent;
961 }