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