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