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