Correct comment.
[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 resproj  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 *resproj, ir_node *l_res, ir_node *h_res)
75 {
76         const ir_edge_t *edge, *next;
77
78         foreach_out_edge_safe(resproj, 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                 /*
158                  * Beware:
159                  * We do not check here if this call really has exception and regular Proj's.
160                  * new_r_Jmp might than be CSEd with the real exit jmp and then bad things happen
161                  * (in movgen.c from 186.crafty for example).
162                  * So be sure the newly created Jmp cannot CSE.
163                  */
164                 old_cse = get_opt_cse();
165                 set_opt_cse(0);
166                 jmp = new_r_Jmp(block);
167                 set_opt_cse(old_cse);
168
169                 turn_into_tuple(call, pn_Call_max+1);
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  * Checks where node high is a sign extension of low.
247  */
248 static int is_sign_extend(ir_node *low, ir_node *high)
249 {
250         if (is_Shrs(high)) {
251                 ir_node   *high_l;
252                 ir_node   *high_r;
253                 ir_tarval *shift_count;
254
255                 high_r = get_Shrs_right(high);
256                 if (!is_Const(high_r)) return 0;
257
258                 shift_count = get_Const_tarval(high_r);
259                 if (!tarval_is_long(shift_count))       return 0;
260                 if (get_tarval_long(shift_count) != 31) return 0;
261
262                 high_l = get_Shrs_left(high);
263
264                 if (is_Conv(low)    && get_Conv_op(low)    == high_l) return 1;
265                 if (is_Conv(high_l) && get_Conv_op(high_l) == low)    return 1;
266         } else if (is_Const(low) && is_Const(high)) {
267                 ir_tarval *tl = get_Const_tarval(low);
268                 ir_tarval *th = get_Const_tarval(high);
269
270                 if (tarval_is_long(th) && tarval_is_long(tl)) {
271                         long l = get_tarval_long(tl);
272                         long h = get_tarval_long(th);
273
274                         return (h == 0  && l >= 0) || (h == -1 && l <  0);
275                 }
276         }
277
278         return 0;
279 }
280
281 /**
282  * Map a Mul (a_l, a_h, b_l, b_h)
283  */
284 static int map_Mul(ir_node *call, void *ctx)
285 {
286         dbg_info *dbg     = get_irn_dbg_info(call);
287         ir_node  *block   = get_nodes_block(call);
288         ir_node  **params = get_Call_param_arr(call);
289         ir_type  *method  = get_Call_type(call);
290         ir_node  *a_l     = params[BINOP_Left_Low];
291         ir_node  *a_h     = params[BINOP_Left_High];
292         ir_node  *b_l     = params[BINOP_Right_Low];
293         ir_node  *b_h     = params[BINOP_Right_High];
294         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
295         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
296         ir_node  *l_res, *h_res, *mul, *pEDX, *add;
297         (void) ctx;
298
299         /*
300                 EDX:EAX = a_l * b_l
301                 l_res   = EAX
302
303                 t1 = b_l * a_h
304                 t2 = t1 + EDX
305                 t3 = a_l * b_h
306                 h_res = t2 + t3
307         */
308
309         /* handle the often used case of 32x32=64 mul */
310         if (is_sign_extend(a_l, a_h) && is_sign_extend(b_l, b_h)) {
311                 mul   = new_bd_ia32_l_IMul(dbg, block, a_l, b_l);
312                 h_res = new_rd_Proj(dbg, mul, h_mode, pn_ia32_l_IMul_res_high);
313                 l_res = new_rd_Proj(dbg, mul, l_mode, pn_ia32_l_IMul_res_low);
314         } else {
315                 /* note that zero extension is handled hare efficiently */
316                 mul   = new_bd_ia32_l_Mul(dbg, block, a_l, b_l);
317                 pEDX  = new_rd_Proj(dbg, mul, h_mode, pn_ia32_l_Mul_res_high);
318                 l_res = new_rd_Proj(dbg, mul, l_mode, pn_ia32_l_Mul_res_low);
319
320                 b_l   = new_rd_Conv(dbg, block, b_l, h_mode);
321                 mul   = new_rd_Mul( dbg, block, a_h, b_l, h_mode);
322                 add   = new_rd_Add( dbg, block, mul, pEDX, h_mode);
323                 a_l   = new_rd_Conv(dbg, block, a_l, h_mode);
324                 mul   = new_rd_Mul( dbg, block, a_l, b_h, h_mode);
325                 h_res = new_rd_Add( dbg, block, add, mul, h_mode);
326         }
327         resolve_call(call, l_res, h_res, current_ir_graph, block);
328
329         return 1;
330 }
331
332 /**
333  * Map a Minus (a_l, a_h)
334  */
335 static int map_Minus(ir_node *call, void *ctx)
336 {
337         dbg_info *dbg     = get_irn_dbg_info(call);
338         ir_node  *block   = get_nodes_block(call);
339         ir_node  **params = get_Call_param_arr(call);
340         ir_type  *method  = get_Call_type(call);
341         ir_node  *a_l     = params[BINOP_Left_Low];
342         ir_node  *a_h     = params[BINOP_Left_High];
343         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
344         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
345         ir_node  *l_res, *h_res, *res;
346         (void) ctx;
347
348         res   = new_bd_ia32_Minus64Bit(dbg, block, a_l, a_h);
349         l_res = new_r_Proj(res, l_mode, pn_ia32_Minus64Bit_low_res);
350         h_res = new_r_Proj(res, h_mode, pn_ia32_Minus64Bit_high_res);
351
352         resolve_call(call, l_res, h_res, current_ir_graph, block);
353
354         return 1;
355 }
356
357 #if 0
358 /**
359  * Map a Abs (a_l, a_h)
360  */
361 static int map_Abs(ir_node *call, void *ctx)
362 {
363         dbg_info *dbg        = get_irn_dbg_info(call);
364         ir_node  *block      = get_nodes_block(call);
365         ir_node  **params    = get_Call_param_arr(call);
366         ir_type  *method     = get_Call_type(call);
367         ir_node  *a_l        = params[BINOP_Left_Low];
368         ir_node  *a_h        = params[BINOP_Left_High];
369         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
370         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
371         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
372         ir_node  *l_res, *h_res, *sign, *sub_l, *sub_h;
373         ir_node  *sign_l;
374         ir_node  *l_sub;
375         ir_node  *flags;
376         (void) ctx;
377
378         /*
379                 Code inspired by gcc output :) (although gcc doubles the
380                 operation for t1 as t2 and uses t1 for operations with low part
381                 and t2 for operations with high part which is actually unnecessary
382                 because t1 and t2 represent the same value)
383
384                 t1    = SHRS a_h, 31
385                 t2    = a_l ^ t1
386                 t3    = a_h ^ t1
387                 l_res = t2 - t1
388                 h_res = t3 - t1 - carry
389
390         */
391
392         /* TODO: give a hint to the backend somehow to not create a cltd here... */
393         sign   = new_rd_Shrs(dbg, block, a_h, new_r_Const_long(irg, l_mode, 31), h_mode);
394         sign_l = new_rd_Conv(dbg, block, sign, l_mode);
395         sub_l  = new_rd_Eor(dbg, block, a_l, sign_l, l_mode);
396         sub_h  = new_rd_Eor(dbg, block, a_h, sign,   h_mode);
397
398         l_sub  = new_bd_ia32_l_Sub(dbg, block, sub_l, sign_l, mode_T);
399         l_res  = new_r_Proj(l_sub, l_mode,     pn_ia32_res);
400         flags  = new_r_Proj(l_sub, mode_flags, pn_ia32_flags);
401         h_res  = new_bd_ia32_l_Sbb(dbg, block, sub_h, sign, flags, h_mode);
402
403         resolve_call(call, l_res, h_res, current_ir_graph, block);
404
405         return 1;
406 }
407 #endif
408
409 #define ID(x) new_id_from_chars(x, sizeof(x)-1)
410
411 static ir_entity *create_compiler_lib_entity(const char *name, ir_type *type)
412 {
413         ir_type   *glob   = get_glob_type();
414         ident     *id     = new_id_from_str(name);
415         ir_entity *entity;
416
417         /* Hack: we need to know the type of runtime library we use. Strictly
418            speaking it's not the same as the object-file-format. But in practice
419            the following should be enough */
420         if (be_gas_object_file_format == OBJECT_FILE_FORMAT_MACH_O
421                         || be_gas_object_file_format == OBJECT_FILE_FORMAT_COFF) {
422                 id = id_mangle3("___", id, "");
423         } else {
424                 id = id_mangle3("__", id, "");
425         }
426         entity = new_entity(glob, id, type);
427         set_entity_visibility(entity, ir_visibility_external);
428         set_entity_ld_ident(entity, id);
429         return entity;
430 }
431
432 /**
433  * Maps a Div. Change into a library call.
434  */
435 static int map_Div(ir_node *call, void *ctx)
436 {
437         ia32_intrinsic_env_t *env = (ia32_intrinsic_env_t*)ctx;
438         ir_type   *method    = get_Call_type(call);
439         ir_mode   *h_mode    = get_type_mode(get_method_res_type(method, 1));
440         ir_node   *ptr;
441         ir_entity *ent;
442         ir_graph  *irg = get_irn_irg(call);
443         symconst_symbol sym;
444
445         if (mode_is_signed(h_mode)) {
446                 /* 64bit signed Division */
447                 ent = env->divdi3;
448                 if (ent == NULL) {
449                         ent = env->divdi3 = create_compiler_lib_entity("divdi3", method);
450                 }
451         } else {
452                 /* 64bit unsigned Division */
453                 ent = env->udivdi3;
454                 if (ent == NULL) {
455                         /* create library entity */
456                         ent = env->udivdi3 = create_compiler_lib_entity("udivdi3", method);
457                 }
458         }
459
460         ptr = get_Call_ptr(call);
461         sym.entity_p = ent;
462         ptr = new_r_SymConst(irg, get_irn_mode(ptr), sym, symconst_addr_ent);
463         set_Call_ptr(call, ptr);
464
465         return 1;
466 }
467
468 /**
469  * Maps a Mod. Change into a library call
470  */
471 static int map_Mod(ir_node *call, void *ctx)
472 {
473         ia32_intrinsic_env_t *env = (ia32_intrinsic_env_t*)ctx;
474         ir_type   *method    = get_Call_type(call);
475         ir_mode   *h_mode    = get_type_mode(get_method_res_type(method, 1));
476         ir_node   *ptr;
477         ir_entity *ent;
478         ir_graph  *irg = get_irn_irg(call);
479         symconst_symbol sym;
480
481         if (mode_is_signed(h_mode)) {
482                 /* 64bit signed Modulo */
483                 ent = env->moddi3;
484                 if (ent == NULL) {
485                         /* create library entity */
486                         ent = env->moddi3 = create_compiler_lib_entity("moddi3", method);
487                 }
488         } else {
489                 /* 64bit signed Modulo */
490                 ent = env->umoddi3;
491                 if (ent == NULL) {
492                         /* create library entity */
493                         ent = env->umoddi3 = create_compiler_lib_entity("umoddi3", method);
494                 }
495         }
496
497         ptr = get_Call_ptr(call);
498         sym.entity_p = ent;
499         ptr = new_r_SymConst(irg, get_irn_mode(ptr), sym, symconst_addr_ent);
500         set_Call_ptr(call, ptr);
501
502         return 1;
503 }
504
505 /**
506  * Maps a Conv.
507  */
508 static int map_Conv(ir_node *call, void *ctx)
509 {
510         ir_graph  *irg     = current_ir_graph;
511         dbg_info  *dbg     = get_irn_dbg_info(call);
512         ir_node   *block   = get_nodes_block(call);
513         ir_node   **params = get_Call_param_arr(call);
514         ir_type   *method  = get_Call_type(call);
515         int       n        = get_Call_n_params(call);
516         ir_node   *l_res, *h_res;
517         (void) ctx;
518
519         if (n == 1) {
520                 ir_node *float_to_ll;
521
522                 /* We have a Conv float -> long long here */
523                 ir_node *a_f        = params[0];
524                 ir_mode *l_res_mode = get_type_mode(get_method_res_type(method, 0));
525                 ir_mode *h_res_mode = get_type_mode(get_method_res_type(method, 1));
526
527                 assert(mode_is_float(get_irn_mode(a_f)) && "unexpected Conv call");
528
529                 if (mode_is_signed(h_res_mode)) {
530                         /* convert from float to signed 64bit */
531                         float_to_ll = new_bd_ia32_l_FloattoLL(dbg, block, a_f);
532
533                         l_res = new_r_Proj(float_to_ll, l_res_mode,
534                                            pn_ia32_l_FloattoLL_res_low);
535                         h_res = new_r_Proj(float_to_ll, h_res_mode,
536                                                            pn_ia32_l_FloattoLL_res_high);
537                 } else {
538                         /* Convert from float to unsigned 64bit. */
539                         ir_mode   *flt_mode = get_irn_mode(a_f);
540                         ir_tarval *flt_tv   = new_tarval_from_str("9223372036854775808", 19, flt_mode);
541                         ir_node   *flt_corr = new_r_Const(irg, flt_tv);
542                         ir_node   *lower_blk = block;
543                         ir_node   *upper_blk;
544                         ir_node   *cmp, *proj, *cond, *blk, *int_phi, *flt_phi;
545                         ir_node   *in[2];
546
547                         part_block(call);
548                         upper_blk = get_nodes_block(call);
549
550                         cmp   = new_rd_Cmp(dbg, upper_blk, a_f, flt_corr, ir_relation_less);
551                         cond  = new_rd_Cond(dbg, upper_blk, cmp);
552                         in[0] = new_r_Proj(cond, mode_X, pn_Cond_true);
553                         in[1] = new_r_Proj(cond, mode_X, pn_Cond_false);
554                         blk   = new_r_Block(irg, 1, &in[1]);
555                         in[1] = new_r_Jmp(blk);
556
557                         set_irn_in(lower_blk, 2, in);
558
559                         /* create to Phis */
560                         in[0] = new_r_Const(irg, get_mode_null(h_res_mode));
561                         in[1] = new_r_Const_long(irg, h_res_mode, 0x80000000);
562
563                         int_phi = new_r_Phi(lower_blk, 2, in, h_res_mode);
564
565                         in[0] = a_f;
566                         in[1] = new_rd_Sub(dbg, upper_blk, a_f, flt_corr, flt_mode);
567
568                         flt_phi = new_r_Phi(lower_blk, 2, in, flt_mode);
569
570                         /* fix Phi links for next part_block() */
571                         set_Block_phis(lower_blk, int_phi);
572                         set_Phi_next(int_phi, flt_phi);
573                         set_Phi_next(flt_phi, NULL);
574
575                         float_to_ll = new_bd_ia32_l_FloattoLL(dbg, lower_blk, flt_phi);
576
577                         l_res = new_r_Proj(float_to_ll, l_res_mode,
578                                                            pn_ia32_l_FloattoLL_res_low);
579                         h_res = new_r_Proj(float_to_ll, h_res_mode,
580                                                            pn_ia32_l_FloattoLL_res_high);
581
582                         h_res = new_rd_Add(dbg, lower_blk, h_res, int_phi, h_res_mode);
583
584                         /* move the call and its Proj's to the lower block */
585                         set_nodes_block(call, lower_blk);
586
587                         for (proj = (ir_node*)get_irn_link(call); proj != NULL;
588                              proj = (ir_node*)get_irn_link(proj)) {
589                                 set_nodes_block(proj, lower_blk);
590                         }
591                         block = lower_blk;
592                 }
593                 /* lower the call */
594                 resolve_call(call, l_res, h_res, irg, block);
595         } else if (n == 2) {
596                 ir_node *ll_to_float;
597
598                 /* We have a Conv long long -> float here */
599                 ir_node *a_l       = params[BINOP_Left_Low];
600                 ir_node *a_h       = params[BINOP_Left_High];
601                 ir_mode *fres_mode = get_type_mode(get_method_res_type(method, 0));
602
603                 assert(! mode_is_float(get_irn_mode(a_l))
604                                 && ! mode_is_float(get_irn_mode(a_h)));
605
606                 ll_to_float = new_bd_ia32_l_LLtoFloat(dbg, block, a_h, a_l, fres_mode);
607
608                 /* lower the call */
609                 resolve_call(call, ll_to_float, NULL, irg, block);
610         } else {
611                 panic("unexpected Conv call %+F", call);
612         }
613
614         return 1;
615 }
616
617 /* Ia32 implementation of intrinsic mapping. */
618 ir_entity *ia32_create_intrinsic_fkt(ir_type *method, const ir_op *op,
619                                      const ir_mode *imode, const ir_mode *omode,
620                                      void *context)
621 {
622         i_record      elt;
623         ir_entity     **ent = NULL;
624         i_mapper_func mapper;
625
626         if (! intrinsics)
627                 intrinsics = NEW_ARR_F(i_record, 0);
628
629         switch (get_op_code(op)) {
630         case iro_Add:
631                 ent    = &i_ents[iro_Add];
632                 mapper = map_Add;
633                 break;
634         case iro_Sub:
635                 ent    = &i_ents[iro_Sub];
636                 mapper = map_Sub;
637                 break;
638         case iro_Mul:
639                 ent    = &i_ents[iro_Mul];
640                 mapper = map_Mul;
641                 break;
642         case iro_Minus:
643                 ent    = &i_ents[iro_Minus];
644                 mapper = map_Minus;
645                 break;
646         case iro_Div:
647                 ent    = &i_ents[iro_Div];
648                 mapper = map_Div;
649                 break;
650         case iro_Mod:
651                 ent    = &i_ents[iro_Mod];
652                 mapper = map_Mod;
653                 break;
654         case iro_Conv:
655                 ent    = &i_ents[iro_Conv];
656                 mapper = map_Conv;
657                 break;
658         default:
659                 fprintf(stderr, "FIXME: unhandled op for ia32 intrinsic function %s\n", get_id_str(op->name));
660                 return def_create_intrinsic_fkt(method, op, imode, omode, context);
661         }
662
663         if (ent && ! *ent) {
664 #define IDENT(s)  new_id_from_chars(s, sizeof(s)-1)
665
666                 ident *id = id_mangle(IDENT("L"), get_op_ident(op));
667                 *ent = new_entity(get_glob_type(), id, method);
668                 set_entity_visibility(*ent, ir_visibility_private);
669         }
670
671         elt.i_call.kind     = INTRINSIC_CALL;
672         elt.i_call.i_ent    = *ent;
673         elt.i_call.i_mapper = mapper;
674         elt.i_call.ctx      = context;
675         elt.i_call.link     = NULL;
676
677         ARR_APP1(i_record, intrinsics, elt);
678         return *ent;
679 }