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