Remove duplicate macro.
[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  */
26 #include "config.h"
27
28 #include "iredges.h"
29 #include "irgmod.h"
30 #include "irop.h"
31 #include "irnode_t.h"
32 #include "ircons.h"
33 #include "irprog_t.h"
34 #include "iroptimize.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         foreach_out_edge_safe(resproj, edge) {
77                 ir_node *proj = get_edge_src_irn(edge);
78                 long    pn    = get_Proj_proj(proj);
79
80                 if (pn == 0) {
81                         edges_reroute(proj, l_res);
82                 } else if (pn == 1 && h_res != NULL) {
83                         edges_reroute(proj, h_res);
84                 } else {
85                         panic("Unsupported Result-Proj from Call found");
86                 }
87         }
88 }
89
90 /**
91  * Replace a call be a tuple of l_res, h_res.
92  *
93  * @param call   the call node to replace
94  * @param l_res  the lower 32 bit result
95  * @param h_res  the upper 32 bit result or NULL
96  * @param irg    the graph to replace on
97  * @param block  the block to replace on (always the call block)
98  */
99 static void resolve_call(ir_node *call, ir_node *l_res, ir_node *h_res, ir_graph *irg, ir_node *block)
100 {
101         ir_node *jmp, *res, *in[2];
102         ir_node *nomem = get_irg_no_mem(irg);
103         int     old_cse;
104
105         if (edges_activated(irg)) {
106                 /* use rerouting to prevent some warning in the backend */
107                 foreach_out_edge_safe(call, edge) {
108                         ir_node *proj = get_edge_src_irn(edge);
109                         pn_Call pn    = (pn_Call)get_Proj_proj(proj);
110
111                         switch (pn) {
112                         case pn_Call_X_regular:
113                                 /* Beware:
114                                  * We do not check here if this call really has exception and regular Proj's.
115                                  * new_r_Jmp might than be CSEd with the real exit jmp and then bad things happen
116                                  * (in movgen.c from 186.crafty for example).
117                                  * So be sure the newly created Jmp cannot CSE.
118                                  */
119                                 old_cse = get_opt_cse();
120                                 set_opt_cse(0);
121                                 jmp = new_r_Jmp(block);
122                                 set_opt_cse(old_cse);
123                                 edges_reroute(proj, jmp);
124                                 break;
125
126                         case pn_Call_X_except:
127                                 /* should not happen here */
128                                 edges_reroute(proj, new_r_Bad(irg, mode_X));
129                                 break;
130                         case pn_Call_M:
131                                 /* should not happen here */
132                                 edges_reroute(proj, nomem);
133                                 break;
134                         case pn_Call_T_result:
135                                 reroute_result(proj, l_res, h_res);
136                                 break;
137                         default:
138                                 panic("Wrong Proj from Call");
139                         }
140                         kill_node(proj);
141                 }
142                 kill_node(call);
143         } else {
144                 /* no edges, build Tuple */
145                 if (h_res == NULL)
146                         res = l_res;
147                 else {
148                         in[0] = l_res;
149                         in[1] = h_res;
150                         res = new_r_Tuple(block, 2, in);
151                 }
152
153                 /*
154                  * Beware:
155                  * We do not check here if this call really has exception and regular Proj's.
156                  * new_r_Jmp might than be CSEd with the real exit jmp and then bad things happen
157                  * (in movgen.c from 186.crafty for example).
158                  * So be sure the newly created Jmp cannot CSE.
159                  */
160                 old_cse = get_opt_cse();
161                 set_opt_cse(0);
162                 jmp = new_r_Jmp(block);
163                 set_opt_cse(old_cse);
164
165                 turn_into_tuple(call, pn_Call_max+1);
166                 set_Tuple_pred(call, pn_Call_M,         nomem);
167                 set_Tuple_pred(call, pn_Call_X_regular, jmp);
168                 set_Tuple_pred(call, pn_Call_X_except,  new_r_Bad(irg, mode_X));
169                 set_Tuple_pred(call, pn_Call_T_result,  res);
170         }
171 }
172
173 /**
174  * Map an Add (a_l, a_h, b_l, b_h)
175  */
176 static int map_Add(ir_node *call, void *ctx)
177 {
178         dbg_info *dbg        = get_irn_dbg_info(call);
179         ir_node  *block      = get_nodes_block(call);
180         ir_node  **params    = get_Call_param_arr(call);
181         ir_type  *method     = get_Call_type(call);
182         ir_node  *a_l        = params[BINOP_Left_Low];
183         ir_node  *a_h        = params[BINOP_Left_High];
184         ir_node  *b_l        = params[BINOP_Right_Low];
185         ir_node  *b_h        = params[BINOP_Right_High];
186         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
187         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
188         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
189         ir_node  *add_low, *add_high, *flags;
190         ir_node  *l_res, *h_res;
191         (void) ctx;
192
193         /* l_res = a_l + b_l */
194         /* h_res = a_h + b_h + carry */
195
196         add_low  = new_bd_ia32_l_Add(dbg, block, a_l, b_l, mode_T);
197         flags    = new_r_Proj(add_low, mode_flags, pn_ia32_flags);
198         add_high = new_bd_ia32_l_Adc(dbg, block, a_h, b_h, flags, h_mode);
199
200         l_res = new_r_Proj(add_low, l_mode, pn_ia32_res);
201         h_res = add_high;
202
203         resolve_call(call, l_res, h_res, current_ir_graph, block);
204         return 1;
205 }
206
207 /**
208  * Map a Sub (a_l, a_h, b_l, b_h)
209  */
210 static int map_Sub(ir_node *call, void *ctx)
211 {
212         dbg_info *dbg        = get_irn_dbg_info(call);
213         ir_node  *block      = get_nodes_block(call);
214         ir_node  **params    = get_Call_param_arr(call);
215         ir_type  *method     = get_Call_type(call);
216         ir_node  *a_l        = params[BINOP_Left_Low];
217         ir_node  *a_h        = params[BINOP_Left_High];
218         ir_node  *b_l        = params[BINOP_Right_Low];
219         ir_node  *b_h        = params[BINOP_Right_High];
220         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
221         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
222         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
223         ir_node  *sub_low, *sub_high, *flags;
224         ir_node  *l_res, *h_res;
225         (void) ctx;
226
227         /* l_res = a_l - b_l */
228         /* h_res = a_h - b_h - carry */
229
230         sub_low  = new_bd_ia32_l_Sub(dbg, block, a_l, b_l, mode_T);
231         flags    = new_r_Proj(sub_low, mode_flags, pn_ia32_flags);
232         sub_high = new_bd_ia32_l_Sbb(dbg, block, a_h, b_h, flags, h_mode);
233
234         l_res = new_r_Proj(sub_low, l_mode, pn_ia32_res);
235         h_res = sub_high;
236
237         resolve_call(call, l_res, h_res, current_ir_graph, block);
238         return 1;
239 }
240
241 /**
242  * Checks where node high is a sign extension of low.
243  */
244 static int is_sign_extend(ir_node *low, ir_node *high)
245 {
246         if (is_Shrs(high)) {
247                 ir_node   *high_l;
248                 ir_node   *high_r;
249                 ir_tarval *shift_count;
250
251                 high_r = get_Shrs_right(high);
252                 if (!is_Const(high_r)) return 0;
253
254                 shift_count = get_Const_tarval(high_r);
255                 if (!tarval_is_long(shift_count))       return 0;
256                 if (get_tarval_long(shift_count) != 31) return 0;
257
258                 high_l = get_Shrs_left(high);
259
260                 if (is_Conv(low)    && get_Conv_op(low)    == high_l) return 1;
261                 if (is_Conv(high_l) && get_Conv_op(high_l) == low)    return 1;
262         } else if (is_Const(low) && is_Const(high)) {
263                 ir_tarval *tl = get_Const_tarval(low);
264                 ir_tarval *th = get_Const_tarval(high);
265
266                 if (tarval_is_long(th) && tarval_is_long(tl)) {
267                         long l = get_tarval_long(tl);
268                         long h = get_tarval_long(th);
269
270                         return (h == 0  && l >= 0) || (h == -1 && l <  0);
271                 }
272         }
273
274         return 0;
275 }
276
277 /**
278  * Map a Mul (a_l, a_h, b_l, b_h)
279  */
280 static int map_Mul(ir_node *call, void *ctx)
281 {
282         dbg_info *dbg     = get_irn_dbg_info(call);
283         ir_node  *block   = get_nodes_block(call);
284         ir_node  **params = get_Call_param_arr(call);
285         ir_type  *method  = get_Call_type(call);
286         ir_node  *a_l     = params[BINOP_Left_Low];
287         ir_node  *a_h     = params[BINOP_Left_High];
288         ir_node  *b_l     = params[BINOP_Right_Low];
289         ir_node  *b_h     = params[BINOP_Right_High];
290         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
291         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
292         ir_node  *l_res, *h_res, *mul, *pEDX, *add;
293         (void) ctx;
294
295         /*
296                 EDX:EAX = a_l * b_l
297                 l_res   = EAX
298
299                 t1 = b_l * a_h
300                 t2 = t1 + EDX
301                 t3 = a_l * b_h
302                 h_res = t2 + t3
303         */
304
305         /* handle the often used case of 32x32=64 mul */
306         if (is_sign_extend(a_l, a_h) && is_sign_extend(b_l, b_h)) {
307                 mul   = new_bd_ia32_l_IMul(dbg, block, a_l, b_l);
308                 h_res = new_rd_Proj(dbg, mul, h_mode, pn_ia32_l_IMul_res_high);
309                 l_res = new_rd_Proj(dbg, mul, l_mode, pn_ia32_l_IMul_res_low);
310         } else {
311                 /* note that zero extension is handled hare efficiently */
312                 mul   = new_bd_ia32_l_Mul(dbg, block, a_l, b_l);
313                 pEDX  = new_rd_Proj(dbg, mul, h_mode, pn_ia32_l_Mul_res_high);
314                 l_res = new_rd_Proj(dbg, mul, l_mode, pn_ia32_l_Mul_res_low);
315
316                 b_l   = new_rd_Conv(dbg, block, b_l, h_mode);
317                 mul   = new_rd_Mul( dbg, block, a_h, b_l, h_mode);
318                 add   = new_rd_Add( dbg, block, mul, pEDX, h_mode);
319                 a_l   = new_rd_Conv(dbg, block, a_l, h_mode);
320                 mul   = new_rd_Mul( dbg, block, a_l, b_h, h_mode);
321                 h_res = new_rd_Add( dbg, block, add, mul, h_mode);
322         }
323         resolve_call(call, l_res, h_res, current_ir_graph, block);
324
325         return 1;
326 }
327
328 /**
329  * Map a Minus (a_l, a_h)
330  */
331 static int map_Minus(ir_node *call, void *ctx)
332 {
333         dbg_info *dbg     = get_irn_dbg_info(call);
334         ir_node  *block   = get_nodes_block(call);
335         ir_node  **params = get_Call_param_arr(call);
336         ir_type  *method  = get_Call_type(call);
337         ir_node  *a_l     = params[BINOP_Left_Low];
338         ir_node  *a_h     = params[BINOP_Left_High];
339         ir_mode  *l_mode  = get_type_mode(get_method_res_type(method, 0));
340         ir_mode  *h_mode  = get_type_mode(get_method_res_type(method, 1));
341         ir_node  *l_res, *h_res, *res;
342         (void) ctx;
343
344         res   = new_bd_ia32_Minus64Bit(dbg, block, a_l, a_h);
345         l_res = new_r_Proj(res, l_mode, pn_ia32_Minus64Bit_low_res);
346         h_res = new_r_Proj(res, h_mode, pn_ia32_Minus64Bit_high_res);
347
348         resolve_call(call, l_res, h_res, current_ir_graph, block);
349
350         return 1;
351 }
352
353 #if 0
354 /**
355  * Map a Abs (a_l, a_h)
356  */
357 static int map_Abs(ir_node *call, void *ctx)
358 {
359         dbg_info *dbg        = get_irn_dbg_info(call);
360         ir_node  *block      = get_nodes_block(call);
361         ir_node  **params    = get_Call_param_arr(call);
362         ir_type  *method     = get_Call_type(call);
363         ir_node  *a_l        = params[BINOP_Left_Low];
364         ir_node  *a_h        = params[BINOP_Left_High];
365         ir_mode  *l_mode     = get_type_mode(get_method_res_type(method, 0));
366         ir_mode  *h_mode     = get_type_mode(get_method_res_type(method, 1));
367         ir_mode  *mode_flags = ia32_reg_classes[CLASS_ia32_flags].mode;
368         ir_node  *l_res, *h_res, *sign, *sub_l, *sub_h;
369         ir_node  *sign_l;
370         ir_node  *l_sub;
371         ir_node  *flags;
372         (void) ctx;
373
374         /*
375                 Code inspired by gcc output :) (although gcc doubles the
376                 operation for t1 as t2 and uses t1 for operations with low part
377                 and t2 for operations with high part which is actually unnecessary
378                 because t1 and t2 represent the same value)
379
380                 t1    = SHRS a_h, 31
381                 t2    = a_l ^ t1
382                 t3    = a_h ^ t1
383                 l_res = t2 - t1
384                 h_res = t3 - t1 - carry
385
386         */
387
388         /* TODO: give a hint to the backend somehow to not create a cltd here... */
389         sign   = new_rd_Shrs(dbg, block, a_h, new_r_Const_long(irg, l_mode, 31), h_mode);
390         sign_l = new_rd_Conv(dbg, block, sign, l_mode);
391         sub_l  = new_rd_Eor(dbg, block, a_l, sign_l, l_mode);
392         sub_h  = new_rd_Eor(dbg, block, a_h, sign,   h_mode);
393
394         l_sub  = new_bd_ia32_l_Sub(dbg, block, sub_l, sign_l, mode_T);
395         l_res  = new_r_Proj(l_sub, l_mode,     pn_ia32_res);
396         flags  = new_r_Proj(l_sub, mode_flags, pn_ia32_flags);
397         h_res  = new_bd_ia32_l_Sbb(dbg, block, sub_h, sign, flags, h_mode);
398
399         resolve_call(call, l_res, h_res, current_ir_graph, block);
400
401         return 1;
402 }
403 #endif
404
405 #define ID(x) new_id_from_chars(x, sizeof(x)-1)
406
407 /**
408  * Maps a Div. Change into a library call.
409  */
410 static int map_Div(ir_node *call, void *ctx)
411 {
412         ia32_intrinsic_env_t *env = (ia32_intrinsic_env_t*)ctx;
413         ir_type   *method    = get_Call_type(call);
414         ir_mode   *h_mode    = get_type_mode(get_method_res_type(method, 1));
415         ir_node   *ptr;
416         ir_entity *ent;
417         ir_graph  *irg = get_irn_irg(call);
418         symconst_symbol sym;
419
420         if (mode_is_signed(h_mode)) {
421                 /* 64bit signed Division */
422                 ent = env->divdi3;
423                 if (ent == NULL) {
424                         /* create library entity */
425                         ident *id = ID("__divdi3");
426                         ent = env->divdi3 = create_compilerlib_entity(id, method);
427                 }
428         } else {
429                 /* 64bit unsigned Division */
430                 ent = env->udivdi3;
431                 if (ent == NULL) {
432                         /* create library entity */
433                         ident *id = ID("__udivdi3");
434                         ent = env->udivdi3 = create_compilerlib_entity(id, method);
435                 }
436         }
437
438         ptr = get_Call_ptr(call);
439         sym.entity_p = ent;
440         ptr = new_r_SymConst(irg, get_irn_mode(ptr), sym, symconst_addr_ent);
441         set_Call_ptr(call, ptr);
442
443         return 1;
444 }
445
446 /**
447  * Maps a Mod. Change into a library call
448  */
449 static int map_Mod(ir_node *call, void *ctx)
450 {
451         ia32_intrinsic_env_t *env = (ia32_intrinsic_env_t*)ctx;
452         ir_type   *method    = get_Call_type(call);
453         ir_mode   *h_mode    = get_type_mode(get_method_res_type(method, 1));
454         ir_node   *ptr;
455         ir_entity *ent;
456         ir_graph  *irg = get_irn_irg(call);
457         symconst_symbol sym;
458
459         if (mode_is_signed(h_mode)) {
460                 /* 64bit signed Modulo */
461                 ent = env->moddi3;
462                 if (ent == NULL) {
463                         /* create library entity */
464                         ident *id = ID("__moddi3");
465                         ent = env->moddi3 = create_compilerlib_entity(id, method);
466                 }
467         } else {
468                 /* 64bit signed Modulo */
469                 ent = env->umoddi3;
470                 if (ent == NULL) {
471                         /* create library entity */
472                         ident *id = ID("__umoddi3");
473                         ent = env->umoddi3 = create_compilerlib_entity(id, method);
474                 }
475         }
476
477         ptr = get_Call_ptr(call);
478         sym.entity_p = ent;
479         ptr = new_r_SymConst(irg, get_irn_mode(ptr), sym, symconst_addr_ent);
480         set_Call_ptr(call, ptr);
481
482         return 1;
483 }
484
485 /**
486  * Maps a Conv.
487  */
488 static int map_Conv(ir_node *call, void *ctx)
489 {
490         ir_graph  *irg     = current_ir_graph;
491         dbg_info  *dbg     = get_irn_dbg_info(call);
492         ir_node   *block   = get_nodes_block(call);
493         ir_node   **params = get_Call_param_arr(call);
494         ir_type   *method  = get_Call_type(call);
495         int       n        = get_Call_n_params(call);
496         ir_node   *l_res, *h_res;
497         (void) ctx;
498
499         if (n == 1) {
500                 ir_node *float_to_ll;
501
502                 /* We have a Conv float -> long long here */
503                 ir_node *a_f        = params[0];
504                 ir_mode *l_res_mode = get_type_mode(get_method_res_type(method, 0));
505                 ir_mode *h_res_mode = get_type_mode(get_method_res_type(method, 1));
506
507                 assert(mode_is_float(get_irn_mode(a_f)) && "unexpected Conv call");
508
509                 if (mode_is_signed(h_res_mode)) {
510                         /* convert from float to signed 64bit */
511                         float_to_ll = new_bd_ia32_l_FloattoLL(dbg, block, a_f);
512
513                         l_res = new_r_Proj(float_to_ll, l_res_mode,
514                                            pn_ia32_l_FloattoLL_res_low);
515                         h_res = new_r_Proj(float_to_ll, h_res_mode,
516                                                            pn_ia32_l_FloattoLL_res_high);
517                 } else {
518                         /* Convert from float to unsigned 64bit. */
519                         ir_tarval *flt_tv   = new_tarval_from_str("9223372036854775808", 19, ia32_mode_E);
520                         ir_node   *flt_corr = new_r_Const(irg, flt_tv);
521                         ir_node   *lower_blk = block;
522                         ir_node   *upper_blk;
523                         ir_node   *cmp, *proj, *cond, *blk, *int_phi, *flt_phi;
524                         ir_node   *in[2];
525
526                         part_block(call);
527                         upper_blk = get_nodes_block(call);
528
529                         a_f   = new_rd_Conv(dbg, upper_blk, a_f, ia32_mode_E);
530                         cmp   = new_rd_Cmp(dbg, upper_blk, a_f, flt_corr, ir_relation_less);
531                         cond  = new_rd_Cond(dbg, upper_blk, cmp);
532                         in[0] = new_r_Proj(cond, mode_X, pn_Cond_true);
533                         in[1] = new_r_Proj(cond, mode_X, pn_Cond_false);
534                         blk   = new_r_Block(irg, 1, &in[1]);
535                         in[1] = new_r_Jmp(blk);
536
537                         set_irn_in(lower_blk, 2, in);
538
539                         /* create to Phis */
540                         in[0] = new_r_Const(irg, get_mode_null(h_res_mode));
541                         in[1] = new_r_Const_long(irg, h_res_mode, 0x80000000);
542
543                         int_phi = new_r_Phi(lower_blk, 2, in, h_res_mode);
544
545                         in[0] = a_f;
546                         in[1] = new_rd_Sub(dbg, upper_blk, a_f, flt_corr, ia32_mode_E);
547
548                         flt_phi = new_r_Phi(lower_blk, 2, in, ia32_mode_E);
549
550                         /* fix Phi links for next part_block() */
551                         if (is_Phi(int_phi))
552                                 add_Block_phi(lower_blk, int_phi);
553                         if (is_Phi(flt_phi))
554                                 add_Block_phi(lower_blk, flt_phi);
555
556                         float_to_ll = new_bd_ia32_l_FloattoLL(dbg, lower_blk, flt_phi);
557
558                         l_res = new_r_Proj(float_to_ll, l_res_mode,
559                                                            pn_ia32_l_FloattoLL_res_low);
560                         h_res = new_r_Proj(float_to_ll, h_res_mode,
561                                                            pn_ia32_l_FloattoLL_res_high);
562
563                         h_res = new_rd_Add(dbg, lower_blk, h_res, int_phi, h_res_mode);
564
565                         /* move the call and its Proj's to the lower block */
566                         set_nodes_block(call, lower_blk);
567
568                         for (proj = (ir_node*)get_irn_link(call); proj != NULL;
569                              proj = (ir_node*)get_irn_link(proj)) {
570                                 set_nodes_block(proj, lower_blk);
571                         }
572                         block = lower_blk;
573                 }
574                 /* lower the call */
575                 resolve_call(call, l_res, h_res, irg, block);
576         } else if (n == 2) {
577                 ir_node *ll_to_float;
578
579                 /* We have a Conv long long -> float here */
580                 ir_node *a_l       = params[BINOP_Left_Low];
581                 ir_node *a_h       = params[BINOP_Left_High];
582                 ir_mode *fres_mode = get_type_mode(get_method_res_type(method, 0));
583
584                 assert(! mode_is_float(get_irn_mode(a_l))
585                                 && ! mode_is_float(get_irn_mode(a_h)));
586
587                 ll_to_float = new_bd_ia32_l_LLtoFloat(dbg, block, a_h, a_l, fres_mode);
588
589                 /* lower the call */
590                 resolve_call(call, ll_to_float, NULL, irg, block);
591         } else {
592                 panic("unexpected Conv call %+F", call);
593         }
594
595         return 1;
596 }
597
598 /* Ia32 implementation of intrinsic mapping. */
599 ir_entity *ia32_create_intrinsic_fkt(ir_type *method, const ir_op *op,
600                                      const ir_mode *imode, const ir_mode *omode,
601                                      void *context)
602 {
603         i_record      elt;
604         ir_entity     **ent = NULL;
605         i_mapper_func mapper;
606
607         if (! intrinsics)
608                 intrinsics = NEW_ARR_F(i_record, 0);
609
610         switch (get_op_code(op)) {
611         case iro_Add:
612                 ent    = &i_ents[iro_Add];
613                 mapper = map_Add;
614                 break;
615         case iro_Sub:
616                 ent    = &i_ents[iro_Sub];
617                 mapper = map_Sub;
618                 break;
619         case iro_Mul:
620                 ent    = &i_ents[iro_Mul];
621                 mapper = map_Mul;
622                 break;
623         case iro_Minus:
624                 ent    = &i_ents[iro_Minus];
625                 mapper = map_Minus;
626                 break;
627         case iro_Div:
628                 ent    = &i_ents[iro_Div];
629                 mapper = map_Div;
630                 break;
631         case iro_Mod:
632                 ent    = &i_ents[iro_Mod];
633                 mapper = map_Mod;
634                 break;
635         case iro_Conv:
636                 ent    = &i_ents[iro_Conv];
637                 mapper = map_Conv;
638                 break;
639         default:
640                 fprintf(stderr, "FIXME: unhandled op for ia32 intrinsic function %s\n", get_id_str(op->name));
641                 return def_create_intrinsic_fkt(method, op, imode, omode, context);
642         }
643
644         if (ent && ! *ent) {
645                 ident *id = id_mangle(ID("L"), get_op_ident(op));
646                 *ent = new_entity(get_glob_type(), id, method);
647                 set_entity_visibility(*ent, ir_visibility_private);
648         }
649
650         elt.i_call.kind     = INTRINSIC_CALL;
651         elt.i_call.i_ent    = *ent;
652         elt.i_call.i_mapper = mapper;
653         elt.i_call.ctx      = context;
654         elt.i_call.link     = NULL;
655
656         ARR_APP1(i_record, intrinsics, elt);
657         return *ent;
658 }