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