blob: 1c275702466f50e869068cb7e7ab381f91f2db32 [file] [log] [blame]
sewardj2019a972011-03-07 16:04:07 +00001/* -*- mode: C; c-basic-offset: 3; -*- */
2
3/*---------------------------------------------------------------*/
4/*--- begin host_s390_isel.c ---*/
5/*---------------------------------------------------------------*/
6
7/*
8 This file is part of Valgrind, a dynamic binary instrumentation
9 framework.
10
florian61f23c12012-08-06 18:33:21 +000011 Copyright IBM Corp. 2010-2012
florian2c74d242012-09-12 19:38:42 +000012 Copyright (C) 2012-2012 Florian Krohm (britzel@acm.org)
sewardj2019a972011-03-07 16:04:07 +000013
14 This program is free software; you can redistribute it and/or
15 modify it under the terms of the GNU General Public License as
16 published by the Free Software Foundation; either version 2 of the
17 License, or (at your option) any later version.
18
19 This program is distributed in the hope that it will be useful, but
20 WITHOUT ANY WARRANTY; without even the implied warranty of
21 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
22 General Public License for more details.
23
24 You should have received a copy of the GNU General Public License
25 along with this program; if not, write to the Free Software
26 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
27 02110-1301, USA.
28
29 The GNU General Public License is contained in the file COPYING.
30*/
31
32/* Contributed by Florian Krohm */
33
34#include "libvex_basictypes.h"
35#include "libvex_ir.h"
36#include "libvex.h"
37#include "libvex_s390x_common.h"
38
sewardj2019a972011-03-07 16:04:07 +000039#include "main_util.h"
40#include "main_globals.h"
florian9f42ab42012-12-23 01:09:16 +000041#include "guest_s390_defs.h" /* S390X_GUEST_OFFSET */
sewardj2019a972011-03-07 16:04:07 +000042#include "host_generic_regs.h"
43#include "host_s390_defs.h"
44
45/*---------------------------------------------------------*/
46/*--- ISelEnv ---*/
47/*---------------------------------------------------------*/
48
49/* This carries around:
50
51 - A mapping from IRTemp to IRType, giving the type of any IRTemp we
52 might encounter. This is computed before insn selection starts,
53 and does not change.
54
55 - A mapping from IRTemp to HReg. This tells the insn selector
56 which virtual register(s) are associated with each IRTemp
57 temporary. This is computed before insn selection starts, and
58 does not change. We expect this mapping to map precisely the
59 same set of IRTemps as the type mapping does.
60
61 - vregmap holds the primary register for the IRTemp.
62 - vregmapHI holds the secondary register for the IRTemp,
63 if any is needed. That's only for Ity_I64 temps
64 in 32 bit mode or Ity_I128 temps in 64-bit mode.
65
66 - The code array, that is, the insns selected so far.
67
68 - A counter, for generating new virtual registers.
69
70 - The host subarchitecture we are selecting insns for.
71 This is set at the start and does not change.
florianad43b3a2012-02-20 15:01:14 +000072
florian8844a632012-04-13 04:04:06 +000073 - A Bool for indicating whether we may generate chain-me
74 instructions for control flow transfers, or whether we must use
75 XAssisted.
76
77 - The maximum guest address of any guest insn in this block.
78 Actually, the address of the highest-addressed byte from any insn
79 in this block. Is set at the start and does not change. This is
80 used for detecting jumps which are definitely forward-edges from
81 this block, and therefore can be made (chained) to the fast entry
82 point of the destination, thereby avoiding the destination's
83 event check.
84
florianad43b3a2012-02-20 15:01:14 +000085 - Values of certain guest registers which are often assigned constants.
sewardj2019a972011-03-07 16:04:07 +000086*/
87
florianad43b3a2012-02-20 15:01:14 +000088/* Symbolic names for guest registers whose value we're tracking */
89enum {
90 GUEST_IA,
91 GUEST_CC_OP,
92 GUEST_CC_DEP1,
93 GUEST_CC_DEP2,
94 GUEST_CC_NDEP,
95 GUEST_SYSNO,
florian7d117ba2012-05-06 03:34:55 +000096 GUEST_COUNTER,
florianad43b3a2012-02-20 15:01:14 +000097 GUEST_UNKNOWN /* must be the last entry */
98};
99
100/* Number of registers we're tracking. */
101#define NUM_TRACKED_REGS GUEST_UNKNOWN
102
103
sewardj2019a972011-03-07 16:04:07 +0000104typedef struct {
105 IRTypeEnv *type_env;
106
florian8844a632012-04-13 04:04:06 +0000107 HInstrArray *code;
sewardj2019a972011-03-07 16:04:07 +0000108 HReg *vregmap;
109 HReg *vregmapHI;
110 UInt n_vregmap;
florian8844a632012-04-13 04:04:06 +0000111 UInt vreg_ctr;
112 UInt hwcaps;
sewardj2019a972011-03-07 16:04:07 +0000113
florian2c74d242012-09-12 19:38:42 +0000114 IRExpr *previous_bfp_rounding_mode;
florianc8e4f562012-10-27 16:19:31 +0000115 IRExpr *previous_dfp_rounding_mode;
florian2c74d242012-09-12 19:38:42 +0000116
florianad43b3a2012-02-20 15:01:14 +0000117 ULong old_value[NUM_TRACKED_REGS];
sewardj2019a972011-03-07 16:04:07 +0000118
florian8844a632012-04-13 04:04:06 +0000119 /* The next two are for translation chaining */
120 Addr64 max_ga;
121 Bool chaining_allowed;
122
florianad43b3a2012-02-20 15:01:14 +0000123 Bool old_value_valid[NUM_TRACKED_REGS];
sewardj2019a972011-03-07 16:04:07 +0000124} ISelEnv;
125
126
127/* Forward declarations */
128static HReg s390_isel_int_expr(ISelEnv *, IRExpr *);
129static s390_amode *s390_isel_amode(ISelEnv *, IRExpr *);
130static s390_cc_t s390_isel_cc(ISelEnv *, IRExpr *);
131static s390_opnd_RMI s390_isel_int_expr_RMI(ISelEnv *, IRExpr *);
132static void s390_isel_int128_expr(HReg *, HReg *, ISelEnv *, IRExpr *);
133static HReg s390_isel_float_expr(ISelEnv *, IRExpr *);
134static void s390_isel_float128_expr(HReg *, HReg *, ISelEnv *, IRExpr *);
florian12390202012-11-10 22:34:14 +0000135static HReg s390_isel_dfp_expr(ISelEnv *, IRExpr *);
floriane38f6412012-12-21 17:32:12 +0000136static void s390_isel_dfp128_expr(HReg *, HReg *, ISelEnv *, IRExpr *);
sewardj2019a972011-03-07 16:04:07 +0000137
138
florianad43b3a2012-02-20 15:01:14 +0000139static Int
140get_guest_reg(Int offset)
141{
142 switch (offset) {
florian428dfdd2012-03-27 03:09:49 +0000143 case S390X_GUEST_OFFSET(guest_IA): return GUEST_IA;
144 case S390X_GUEST_OFFSET(guest_CC_OP): return GUEST_CC_OP;
145 case S390X_GUEST_OFFSET(guest_CC_DEP1): return GUEST_CC_DEP1;
146 case S390X_GUEST_OFFSET(guest_CC_DEP2): return GUEST_CC_DEP2;
147 case S390X_GUEST_OFFSET(guest_CC_NDEP): return GUEST_CC_NDEP;
148 case S390X_GUEST_OFFSET(guest_SYSNO): return GUEST_SYSNO;
florian7d117ba2012-05-06 03:34:55 +0000149 case S390X_GUEST_OFFSET(guest_counter): return GUEST_COUNTER;
florianad43b3a2012-02-20 15:01:14 +0000150
151 /* Also make sure there is never a partial write to one of
152 these registers. That would complicate matters. */
florian428dfdd2012-03-27 03:09:49 +0000153 case S390X_GUEST_OFFSET(guest_IA)+1 ... S390X_GUEST_OFFSET(guest_IA)+7:
154 case S390X_GUEST_OFFSET(guest_CC_OP)+1 ... S390X_GUEST_OFFSET(guest_CC_OP)+7:
155 case S390X_GUEST_OFFSET(guest_CC_DEP1)+1 ... S390X_GUEST_OFFSET(guest_CC_DEP1)+7:
156 case S390X_GUEST_OFFSET(guest_CC_DEP2)+1 ... S390X_GUEST_OFFSET(guest_CC_DEP2)+7:
157 case S390X_GUEST_OFFSET(guest_CC_NDEP)+1 ... S390X_GUEST_OFFSET(guest_CC_NDEP)+7:
florian7d117ba2012-05-06 03:34:55 +0000158 case S390X_GUEST_OFFSET(guest_SYSNO)+1 ... S390X_GUEST_OFFSET(guest_SYSNO)+7:
159 /* counter is used both as 4-byte and as 8-byte entity */
160 case S390X_GUEST_OFFSET(guest_counter)+1 ... S390X_GUEST_OFFSET(guest_counter)+3:
161 case S390X_GUEST_OFFSET(guest_counter)+5 ... S390X_GUEST_OFFSET(guest_counter)+7:
florianaf50a192012-07-13 14:13:06 +0000162 vpanic("partial update of this guest state register is not allowed");
florianad43b3a2012-02-20 15:01:14 +0000163 break;
164
165 default: break;
166 }
167
168 return GUEST_UNKNOWN;
169}
170
sewardj2019a972011-03-07 16:04:07 +0000171/* Add an instruction */
172static void
173addInstr(ISelEnv *env, s390_insn *insn)
174{
175 addHInstr(env->code, insn);
176
177 if (vex_traceflags & VEX_TRACE_VCODE) {
178 vex_printf("%s\n", s390_insn_as_string(insn));
179 }
180}
181
182
183static __inline__ IRExpr *
184mkU64(ULong value)
185{
186 return IRExpr_Const(IRConst_U64(value));
187}
188
189
190/*---------------------------------------------------------*/
191/*--- Registers ---*/
192/*---------------------------------------------------------*/
193
194/* Return the virtual register to which a given IRTemp is mapped. */
195static HReg
196lookupIRTemp(ISelEnv *env, IRTemp tmp)
197{
198 vassert(tmp < env->n_vregmap);
199 vassert(env->vregmap[tmp] != INVALID_HREG);
200
201 return env->vregmap[tmp];
202}
203
204
205/* Return the two virtual registers to which the IRTemp is mapped. */
206static void
207lookupIRTemp128(HReg *hi, HReg *lo, ISelEnv *env, IRTemp tmp)
208{
209 vassert(tmp < env->n_vregmap);
210 vassert(env->vregmapHI[tmp] != INVALID_HREG);
211
212 *lo = env->vregmap[tmp];
213 *hi = env->vregmapHI[tmp];
214}
215
216
217/* Allocate a new integer register */
218static HReg
219newVRegI(ISelEnv *env)
220{
221 HReg reg = mkHReg(env->vreg_ctr, HRcInt64, True /* virtual */ );
222 env->vreg_ctr++;
223
224 return reg;
225}
226
227
228/* Allocate a new floating point register */
229static HReg
230newVRegF(ISelEnv *env)
231{
232 HReg reg = mkHReg(env->vreg_ctr, HRcFlt64, True /* virtual */ );
233
234 env->vreg_ctr++;
235
236 return reg;
237}
238
239
240/* Construct a non-virtual general purpose register */
241static __inline__ HReg
florian297b6062012-05-08 20:16:17 +0000242make_gpr(UInt regno)
sewardj2019a972011-03-07 16:04:07 +0000243{
244 return mkHReg(regno, HRcInt64, False /* virtual */ );
245}
246
247
248/* Construct a non-virtual floating point register */
249static __inline__ HReg
250make_fpr(UInt regno)
251{
252 return mkHReg(regno, HRcFlt64, False /* virtual */ );
253}
254
255
256/*---------------------------------------------------------*/
257/*--- Amode ---*/
258/*---------------------------------------------------------*/
259
260static __inline__ Bool
261ulong_fits_unsigned_12bit(ULong val)
262{
263 return (val & 0xFFFu) == val;
264}
265
266
267static __inline__ Bool
268ulong_fits_signed_20bit(ULong val)
269{
270 Long v = val & 0xFFFFFu;
271
272 v = (v << 44) >> 44; /* sign extend */
273
274 return val == (ULong)v;
275}
276
277
florianad43b3a2012-02-20 15:01:14 +0000278static __inline__ Bool
279ulong_fits_signed_8bit(ULong val)
280{
281 Long v = val & 0xFFu;
282
283 v = (v << 56) >> 56; /* sign extend */
284
285 return val == (ULong)v;
286}
287
sewardj2019a972011-03-07 16:04:07 +0000288/* EXPR is an expression that is used as an address. Return an s390_amode
289 for it. */
290static s390_amode *
291s390_isel_amode_wrk(ISelEnv *env, IRExpr *expr)
292{
293 if (expr->tag == Iex_Binop && expr->Iex.Binop.op == Iop_Add64) {
294 IRExpr *arg1 = expr->Iex.Binop.arg1;
295 IRExpr *arg2 = expr->Iex.Binop.arg2;
296
297 /* Move constant into right subtree */
298 if (arg1->tag == Iex_Const) {
299 IRExpr *tmp;
300 tmp = arg1;
301 arg1 = arg2;
302 arg2 = tmp;
303 }
304
305 /* r + constant: Check for b12 first, then b20 */
306 if (arg2->tag == Iex_Const && arg2->Iex.Const.con->tag == Ico_U64) {
307 ULong value = arg2->Iex.Const.con->Ico.U64;
308
309 if (ulong_fits_unsigned_12bit(value)) {
310 return s390_amode_b12((Int)value, s390_isel_int_expr(env, arg1));
311 }
sewardj652b56a2011-04-13 15:38:17 +0000312 /* If long-displacement is not available, do not construct B20 or
313 BX20 amodes because code generation cannot handle them. */
314 if (s390_host_has_ldisp && ulong_fits_signed_20bit(value)) {
sewardj2019a972011-03-07 16:04:07 +0000315 return s390_amode_b20((Int)value, s390_isel_int_expr(env, arg1));
316 }
317 }
318 }
319
320 /* Doesn't match anything in particular. Generate it into
321 a register and use that. */
322 return s390_amode_b12(0, s390_isel_int_expr(env, expr));
323}
324
325
326static s390_amode *
327s390_isel_amode(ISelEnv *env, IRExpr *expr)
328{
florian35da8612011-06-25 02:25:41 +0000329 s390_amode *am;
sewardj2019a972011-03-07 16:04:07 +0000330
331 /* Address computation should yield a 64-bit value */
332 vassert(typeOfIRExpr(env->type_env, expr) == Ity_I64);
333
334 am = s390_isel_amode_wrk(env, expr);
335
336 /* Check post-condition */
337 vassert(s390_amode_is_sane(am));
338
339 return am;
340}
341
342
343/*---------------------------------------------------------*/
344/*--- Helper functions ---*/
345/*---------------------------------------------------------*/
346
347/* Constants and memory accesses should be right operands */
348#define order_commutative_operands(left, right) \
349 do { \
350 if (left->tag == Iex_Const || left->tag == Iex_Load || \
351 left->tag == Iex_Get) { \
352 IRExpr *tmp; \
353 tmp = left; \
354 left = right; \
355 right = tmp; \
356 } \
357 } while (0)
358
359
360/* Copy an RMI operand to the DST register */
361static s390_insn *
362s390_opnd_copy(UChar size, HReg dst, s390_opnd_RMI opnd)
363{
364 switch (opnd.tag) {
365 case S390_OPND_AMODE:
366 return s390_insn_load(size, dst, opnd.variant.am);
367
368 case S390_OPND_REG:
369 return s390_insn_move(size, dst, opnd.variant.reg);
370
371 case S390_OPND_IMMEDIATE:
372 return s390_insn_load_immediate(size, dst, opnd.variant.imm);
373
374 default:
375 vpanic("s390_opnd_copy");
376 }
377}
378
379
380/* Construct a RMI operand for a register */
381static __inline__ s390_opnd_RMI
382s390_opnd_reg(HReg reg)
383{
384 s390_opnd_RMI opnd;
385
386 opnd.tag = S390_OPND_REG;
387 opnd.variant.reg = reg;
388
389 return opnd;
390}
391
392
393/* Construct a RMI operand for an immediate constant */
394static __inline__ s390_opnd_RMI
395s390_opnd_imm(ULong value)
396{
397 s390_opnd_RMI opnd;
398
399 opnd.tag = S390_OPND_IMMEDIATE;
400 opnd.variant.imm = value;
401
402 return opnd;
403}
404
405
florianffbd84d2012-12-09 02:06:29 +0000406/* Return 1, if EXPR represents the constant 0 */
407static Bool
sewardj2019a972011-03-07 16:04:07 +0000408s390_expr_is_const_zero(IRExpr *expr)
409{
410 ULong value;
411
412 if (expr->tag == Iex_Const) {
413 switch (expr->Iex.Const.con->tag) {
414 case Ico_U1: value = expr->Iex.Const.con->Ico.U1; break;
415 case Ico_U8: value = expr->Iex.Const.con->Ico.U8; break;
416 case Ico_U16: value = expr->Iex.Const.con->Ico.U16; break;
417 case Ico_U32: value = expr->Iex.Const.con->Ico.U32; break;
418 case Ico_U64: value = expr->Iex.Const.con->Ico.U64; break;
419 default:
420 vpanic("s390_expr_is_const_zero");
421 }
422 return value == 0;
423 }
424
425 return 0;
426}
427
428
florianb93348d2012-12-27 00:59:43 +0000429/* Return the value of CON as a sign-exteded ULong value */
430static ULong
431get_const_value_as_ulong(const IRConst *con)
432{
433 Long value;
434
435 switch (con->tag) {
436 case Ico_U1: value = con->Ico.U1; return (ULong) ((value << 63) >> 63);
437 case Ico_U8: value = con->Ico.U8; return (ULong) ((value << 56) >> 56);
438 case Ico_U16: value = con->Ico.U16; return (ULong) ((value << 48) >> 48);
439 case Ico_U32: value = con->Ico.U32; return (ULong) ((value << 32) >> 32);
440 case Ico_U64: return con->Ico.U64;
441 default:
442 vpanic("get_const_value_as_ulong");
443 }
444}
445
446
sewardj2019a972011-03-07 16:04:07 +0000447/* Call a helper (clean or dirty)
448 Arguments must satisfy the following conditions:
floriane0654362012-05-09 13:31:09 +0000449
sewardj2019a972011-03-07 16:04:07 +0000450 (a) they are expressions yielding an integer result
451 (b) there can be no more than S390_NUM_GPRPARMS arguments
floriane0654362012-05-09 13:31:09 +0000452
453 guard is a Ity_Bit expression indicating whether or not the
454 call happens. If guard == NULL, the call is unconditional.
florian52af7bc2012-05-12 03:44:49 +0000455
456 Calling the helper function proceeds as follows:
457
458 (1) The helper arguments are evaluated and their value stored in
459 virtual registers.
460 (2) The condition code is evaluated
461 (3) The argument values are copied from the virtual registers to the
462 registers mandated by the ABI.
463 (4) Call the helper function.
464
465 This is not the most efficient way as step 3 generates register-to-register
466 moves. But it is the least fragile way as the only hidden dependency here
467 is that register-to-register moves (step 3) must not clobber the condition
468 code. Other schemes (e.g. VEX r2326) that attempt to avoid the register-
469 to-register add more such dependencies. Not good. Besides, it's the job
470 of the register allocator to throw out those reg-to-reg moves.
sewardj2019a972011-03-07 16:04:07 +0000471*/
472static void
473doHelperCall(ISelEnv *env, Bool passBBP, IRExpr *guard,
florian01ed6e72012-05-27 16:52:43 +0000474 IRCallee *callee, IRExpr **args, HReg dst)
sewardj2019a972011-03-07 16:04:07 +0000475{
florian52af7bc2012-05-12 03:44:49 +0000476 UInt n_args, i, argreg, size;
sewardj2019a972011-03-07 16:04:07 +0000477 ULong target;
478 HReg tmpregs[S390_NUM_GPRPARMS];
479 s390_cc_t cc;
480
481 n_args = 0;
482 for (i = 0; args[i]; i++)
483 ++n_args;
484
485 if (n_args > (S390_NUM_GPRPARMS - (passBBP ? 1 : 0))) {
486 vpanic("doHelperCall: too many arguments");
487 }
488
florian11b8ee82012-08-06 13:35:33 +0000489 /* All arguments must have Ity_I64. For two reasons:
490 (1) We do not handle floating point arguments.
491 (2) The ABI requires that integer values are sign- or zero-extended
492 to 64 bit.
493 */
494 Int arg_errors = 0;
495 for (i = 0; i < n_args; ++i) {
496 IRType type = typeOfIRExpr(env->type_env, args[i]);
497 if (type != Ity_I64) {
498 ++arg_errors;
499 vex_printf("calling %s: argument #%d has type ", callee->name, i);
500 ppIRType(type);
501 vex_printf("; Ity_I64 is required\n");
502 }
503 }
504
505 if (arg_errors)
506 vpanic("cannot continue due to errors in argument passing");
507
florian52af7bc2012-05-12 03:44:49 +0000508 argreg = 0;
509
510 /* If we need the guest state pointer put it in a temporary arg reg */
511 if (passBBP) {
512 tmpregs[argreg] = newVRegI(env);
513 addInstr(env, s390_insn_move(sizeof(ULong), tmpregs[argreg],
514 s390_hreg_guest_state_pointer()));
515 argreg++;
516 }
517
518 /* Compute the function arguments into a temporary register each */
519 for (i = 0; i < n_args; i++) {
520 tmpregs[argreg] = s390_isel_int_expr(env, args[i]);
521 argreg++;
522 }
523
sewardj2019a972011-03-07 16:04:07 +0000524 /* Compute the condition */
525 cc = S390_CC_ALWAYS;
526 if (guard) {
527 if (guard->tag == Iex_Const
528 && guard->Iex.Const.con->tag == Ico_U1
529 && guard->Iex.Const.con->Ico.U1 == True) {
530 /* unconditional -- do nothing */
531 } else {
532 cc = s390_isel_cc(env, guard);
533 }
534 }
535
florian52af7bc2012-05-12 03:44:49 +0000536 /* Move the args to the final register. It is paramount, that the
537 code to move the registers does not clobber the condition code ! */
floriane0654362012-05-09 13:31:09 +0000538 for (i = 0; i < argreg; i++) {
florian52af7bc2012-05-12 03:44:49 +0000539 HReg finalreg;
540
541 finalreg = make_gpr(s390_gprno_from_arg_index(i));
542 size = sizeofIRType(Ity_I64);
543 addInstr(env, s390_insn_move(size, finalreg, tmpregs[i]));
sewardj2019a972011-03-07 16:04:07 +0000544 }
545
546 target = Ptr_to_ULong(callee->addr);
547
548 /* Finally, the call itself. */
549 addInstr(env, s390_insn_helper_call(cc, (Addr64)target, n_args,
florian01ed6e72012-05-27 16:52:43 +0000550 callee->name, dst));
sewardj2019a972011-03-07 16:04:07 +0000551}
552
553
florian2c74d242012-09-12 19:38:42 +0000554/*---------------------------------------------------------*/
555/*--- BFP helper functions ---*/
556/*---------------------------------------------------------*/
557
558/* Set the BFP rounding mode in the FPC. This function is called for
559 all non-conversion BFP instructions as those will always get the
560 rounding mode from the FPC. */
561static void
562set_bfp_rounding_mode_in_fpc(ISelEnv *env, IRExpr *irrm)
sewardj2019a972011-03-07 16:04:07 +0000563{
florian2c74d242012-09-12 19:38:42 +0000564 vassert(typeOfIRExpr(env->type_env, irrm) == Ity_I32);
565
566 /* Do we need to do anything? */
567 if (env->previous_bfp_rounding_mode &&
568 env->previous_bfp_rounding_mode->tag == Iex_RdTmp &&
569 irrm->tag == Iex_RdTmp &&
570 env->previous_bfp_rounding_mode->Iex.RdTmp.tmp == irrm->Iex.RdTmp.tmp) {
571 /* No - new mode is identical to previous mode. */
572 return;
573 }
574
575 /* No luck - we better set it, and remember what we set it to. */
576 env->previous_bfp_rounding_mode = irrm;
577
578 /* The incoming rounding mode is in VEX IR encoding. Need to change
579 to s390.
580
581 rounding mode | s390 | IR
582 -------------------------
583 to nearest | 00 | 00
584 to zero | 01 | 11
585 to +infinity | 10 | 10
586 to -infinity | 11 | 01
587
588 So: s390 = (4 - IR) & 3
589 */
590 HReg ir = s390_isel_int_expr(env, irrm);
591
592 HReg mode = newVRegI(env);
593
594 addInstr(env, s390_insn_load_immediate(4, mode, 4));
595 addInstr(env, s390_insn_alu(4, S390_ALU_SUB, mode, s390_opnd_reg(ir)));
596 addInstr(env, s390_insn_alu(4, S390_ALU_AND, mode, s390_opnd_imm(3)));
597
florian125e20d2012-10-07 15:42:37 +0000598 addInstr(env, s390_insn_set_fpc_bfprm(4, mode));
florian2c74d242012-09-12 19:38:42 +0000599}
600
601
602/* This function is invoked for insns that support a specification of
603 a rounding mode in the insn itself. In that case there is no need to
604 stick the rounding mode into the FPC -- a good thing. However, the
605 rounding mode must be known. */
florian125e20d2012-10-07 15:42:37 +0000606static s390_bfp_round_t
florian2c74d242012-09-12 19:38:42 +0000607get_bfp_rounding_mode(ISelEnv *env, IRExpr *irrm)
608{
609 if (irrm->tag == Iex_Const) { /* rounding mode is known */
610 vassert(irrm->Iex.Const.con->tag == Ico_U32);
611 IRRoundingMode mode = irrm->Iex.Const.con->Ico.U32;
sewardj2019a972011-03-07 16:04:07 +0000612
613 switch (mode) {
florian125e20d2012-10-07 15:42:37 +0000614 case Irrm_NEAREST: return S390_BFP_ROUND_NEAREST_EVEN;
615 case Irrm_ZERO: return S390_BFP_ROUND_ZERO;
616 case Irrm_PosINF: return S390_BFP_ROUND_POSINF;
617 case Irrm_NegINF: return S390_BFP_ROUND_NEGINF;
florian2c74d242012-09-12 19:38:42 +0000618 default:
619 vpanic("get_bfp_rounding_mode");
sewardj2019a972011-03-07 16:04:07 +0000620 }
621 }
622
florian2c74d242012-09-12 19:38:42 +0000623 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +0000624 return S390_BFP_ROUND_PER_FPC;
sewardj2019a972011-03-07 16:04:07 +0000625}
626
627
florianc8e4f562012-10-27 16:19:31 +0000628/*---------------------------------------------------------*/
629/*--- DFP helper functions ---*/
630/*---------------------------------------------------------*/
631
632/* Set the DFP rounding mode in the FPC. This function is called for
633 all non-conversion DFP instructions as those will always get the
634 rounding mode from the FPC. */
florianc8e4f562012-10-27 16:19:31 +0000635static void
636set_dfp_rounding_mode_in_fpc(ISelEnv *env, IRExpr *irrm)
637{
638 vassert(typeOfIRExpr(env->type_env, irrm) == Ity_I32);
639
640 /* Do we need to do anything? */
641 if (env->previous_dfp_rounding_mode &&
642 env->previous_dfp_rounding_mode->tag == Iex_RdTmp &&
643 irrm->tag == Iex_RdTmp &&
644 env->previous_dfp_rounding_mode->Iex.RdTmp.tmp == irrm->Iex.RdTmp.tmp) {
645 /* No - new mode is identical to previous mode. */
646 return;
647 }
648
649 /* No luck - we better set it, and remember what we set it to. */
650 env->previous_dfp_rounding_mode = irrm;
651
652 /* The incoming rounding mode is in VEX IR encoding. Need to change
653 to s390.
654
655 rounding mode | S390 | IR
656 -----------------------------------------------
657 to nearest, ties to even | 000 | 000
658 to zero | 001 | 011
659 to +infinity | 010 | 010
660 to -infinity | 011 | 001
661 to nearest, ties away from 0 | 100 | 100
662 to nearest, ties toward 0 | 101 | 111
663 to away from 0 | 110 | 110
664 to prepare for shorter precision | 111 | 101
665
666 So: s390 = (IR ^ ((IR << 1) & 2))
667 */
668 HReg ir = s390_isel_int_expr(env, irrm);
669
670 HReg mode = newVRegI(env);
671
672 addInstr(env, s390_insn_move(4, mode, ir));
673 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, mode, s390_opnd_imm(1)));
674 addInstr(env, s390_insn_alu(4, S390_ALU_AND, mode, s390_opnd_imm(2)));
675 addInstr(env, s390_insn_alu(4, S390_ALU_XOR, mode, s390_opnd_reg(ir)));
676
677 addInstr(env, s390_insn_set_fpc_dfprm(4, mode));
678}
679
680
681/* This function is invoked for insns that support a specification of
682 a rounding mode in the insn itself. In that case there is no need to
683 stick the rounding mode into the FPC -- a good thing. However, the
684 rounding mode must be known.
florianff9000d2013-02-08 20:22:03 +0000685
686 When mapping an Irrm_DFP_ value to an S390_DFP_ROUND_ value there is
687 often a choice. For instance, Irrm_DFP_ZERO could be mapped to either
688 S390_DFP_ROUND_ZERO_5 or S390_DFP_ROUND_ZERO_9. The difference between
689 those two is that with S390_DFP_ROUND_ZERO_9 the recognition of the
690 quantum exception is suppressed whereas with S390_DFP_ROUND_ZERO_5 it
691 is not. As the quantum exception is not modelled we can choose either
692 value. The choice is to use S390_DFP_ROUND_.. values in the range [8:15],
693 because values in the range [1:7] have unpredictable rounding behaviour
694 when the floating point exception facility is not installed.
florianc8e4f562012-10-27 16:19:31 +0000695
696 Translation table of
697 s390 DFP rounding mode to IRRoundingMode to s390 DFP rounding mode
698
699 s390(S390_DFP_ROUND_) | IR(Irrm_DFP_) | s390(S390_DFP_ROUND_)
700 --------------------------------------------------------------------
florianff9000d2013-02-08 20:22:03 +0000701 NEAREST_TIE_AWAY_0_1 | NEAREST_TIE_AWAY_0 | NEAREST_TIE_AWAY_0_12
florianc8e4f562012-10-27 16:19:31 +0000702 NEAREST_TIE_AWAY_0_12 | " | "
florianff9000d2013-02-08 20:22:03 +0000703 PREPARE_SHORT_3 | PREPARE_SHORTER | PREPARE_SHORT_15
florianc8e4f562012-10-27 16:19:31 +0000704 PREPARE_SHORT_15 | " | "
florianff9000d2013-02-08 20:22:03 +0000705 NEAREST_EVEN_4 | NEAREST | NEAREST_EVEN_8
florianc8e4f562012-10-27 16:19:31 +0000706 NEAREST_EVEN_8 | " | "
florianff9000d2013-02-08 20:22:03 +0000707 ZERO_5 | ZERO | ZERO_9
florianc8e4f562012-10-27 16:19:31 +0000708 ZERO_9 | " | "
florianff9000d2013-02-08 20:22:03 +0000709 POSINF_6 | PosINF | POSINF_10
florianc8e4f562012-10-27 16:19:31 +0000710 POSINF_10 | " | "
florianff9000d2013-02-08 20:22:03 +0000711 NEGINF_7 | NegINF | NEGINF_11
florianc8e4f562012-10-27 16:19:31 +0000712 NEGINF_11 | " | "
713 NEAREST_TIE_TOWARD_0 | NEAREST_TIE_TOWARD_0| NEAREST_TIE_TOWARD_0
714 AWAY_0 | AWAY_FROM_ZERO | AWAY_0
715*/
716static s390_dfp_round_t
717get_dfp_rounding_mode(ISelEnv *env, IRExpr *irrm)
718{
719 if (irrm->tag == Iex_Const) { /* rounding mode is known */
720 vassert(irrm->Iex.Const.con->tag == Ico_U32);
florian3d6a4222012-11-19 16:29:31 +0000721 IRRoundingModeDFP mode = irrm->Iex.Const.con->Ico.U32;
florianc8e4f562012-10-27 16:19:31 +0000722
723 switch (mode) {
724 case Irrm_DFP_NEAREST:
florianff9000d2013-02-08 20:22:03 +0000725 return S390_DFP_ROUND_NEAREST_EVEN_8;
florianc8e4f562012-10-27 16:19:31 +0000726 case Irrm_DFP_NegINF:
florianff9000d2013-02-08 20:22:03 +0000727 return S390_DFP_ROUND_NEGINF_11;
florianc8e4f562012-10-27 16:19:31 +0000728 case Irrm_DFP_PosINF:
florianff9000d2013-02-08 20:22:03 +0000729 return S390_DFP_ROUND_POSINF_10;
florianc8e4f562012-10-27 16:19:31 +0000730 case Irrm_DFP_ZERO:
florianff9000d2013-02-08 20:22:03 +0000731 return S390_DFP_ROUND_ZERO_9;
florianc8e4f562012-10-27 16:19:31 +0000732 case Irrm_DFP_NEAREST_TIE_AWAY_0:
florianff9000d2013-02-08 20:22:03 +0000733 return S390_DFP_ROUND_NEAREST_TIE_AWAY_0_12;
florianc8e4f562012-10-27 16:19:31 +0000734 case Irrm_DFP_PREPARE_SHORTER:
florianff9000d2013-02-08 20:22:03 +0000735 return S390_DFP_ROUND_PREPARE_SHORT_15;
florianc8e4f562012-10-27 16:19:31 +0000736 case Irrm_DFP_AWAY_FROM_ZERO:
737 return S390_DFP_ROUND_AWAY_0;
738 case Irrm_DFP_NEAREST_TIE_TOWARD_0:
739 return S390_DFP_ROUND_NEAREST_TIE_TOWARD_0;
740 default:
741 vpanic("get_dfp_rounding_mode");
742 }
743 }
744
745 set_dfp_rounding_mode_in_fpc(env, irrm);
746 return S390_DFP_ROUND_PER_FPC_0;
747}
florianc8e4f562012-10-27 16:19:31 +0000748
florian2d3d87f2012-12-21 21:05:17 +0000749
750/*---------------------------------------------------------*/
751/*--- Condition code helper functions ---*/
752/*---------------------------------------------------------*/
753
sewardj2019a972011-03-07 16:04:07 +0000754/* CC_S390 holds the condition code in s390 encoding. Convert it to
florian2d3d87f2012-12-21 21:05:17 +0000755 VEX encoding (IRCmpFResult)
sewardj2019a972011-03-07 16:04:07 +0000756
757 s390 VEX b6 b2 b0 cc.1 cc.0
758 0 0x40 EQ 1 0 0 0 0
759 1 0x01 LT 0 0 1 0 1
760 2 0x00 GT 0 0 0 1 0
761 3 0x45 Unordered 1 1 1 1 1
762
763 b0 = cc.0
764 b2 = cc.0 & cc.1
765 b6 = ~(cc.0 ^ cc.1) // ((cc.0 - cc.1) + 0x1 ) & 0x1
766
767 VEX = b0 | (b2 << 2) | (b6 << 6);
768*/
769static HReg
florian2d3d87f2012-12-21 21:05:17 +0000770convert_s390_to_vex_bfpcc(ISelEnv *env, HReg cc_s390)
sewardj2019a972011-03-07 16:04:07 +0000771{
772 HReg cc0, cc1, b2, b6, cc_vex;
773
774 cc0 = newVRegI(env);
775 addInstr(env, s390_insn_move(4, cc0, cc_s390));
776 addInstr(env, s390_insn_alu(4, S390_ALU_AND, cc0, s390_opnd_imm(1)));
777
778 cc1 = newVRegI(env);
779 addInstr(env, s390_insn_move(4, cc1, cc_s390));
780 addInstr(env, s390_insn_alu(4, S390_ALU_RSH, cc1, s390_opnd_imm(1)));
781
782 b2 = newVRegI(env);
783 addInstr(env, s390_insn_move(4, b2, cc0));
784 addInstr(env, s390_insn_alu(4, S390_ALU_AND, b2, s390_opnd_reg(cc1)));
785 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, b2, s390_opnd_imm(2)));
786
787 b6 = newVRegI(env);
788 addInstr(env, s390_insn_move(4, b6, cc0));
789 addInstr(env, s390_insn_alu(4, S390_ALU_SUB, b6, s390_opnd_reg(cc1)));
790 addInstr(env, s390_insn_alu(4, S390_ALU_ADD, b6, s390_opnd_imm(1)));
791 addInstr(env, s390_insn_alu(4, S390_ALU_AND, b6, s390_opnd_imm(1)));
792 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, b6, s390_opnd_imm(6)));
793
794 cc_vex = newVRegI(env);
795 addInstr(env, s390_insn_move(4, cc_vex, cc0));
796 addInstr(env, s390_insn_alu(4, S390_ALU_OR, cc_vex, s390_opnd_reg(b2)));
797 addInstr(env, s390_insn_alu(4, S390_ALU_OR, cc_vex, s390_opnd_reg(b6)));
798
799 return cc_vex;
800}
801
florian2d3d87f2012-12-21 21:05:17 +0000802/* CC_S390 holds the condition code in s390 encoding. Convert it to
803 VEX encoding (IRCmpDResult) */
804static HReg
805convert_s390_to_vex_dfpcc(ISelEnv *env, HReg cc_s390)
806{
807 /* The encodings for IRCmpFResult and IRCmpDResult are the same/ */
808 return convert_s390_to_vex_bfpcc(env, cc_s390);
809}
810
sewardj2019a972011-03-07 16:04:07 +0000811
812/*---------------------------------------------------------*/
813/*--- ISEL: Integer expressions (128 bit) ---*/
814/*---------------------------------------------------------*/
815static void
816s390_isel_int128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
817 IRExpr *expr)
818{
819 IRType ty = typeOfIRExpr(env->type_env, expr);
820
821 vassert(ty == Ity_I128);
822
823 /* No need to consider the following
824 - 128-bit constants (they do not exist in VEX)
825 - 128-bit loads from memory (will not be generated)
826 */
827
828 /* Read 128-bit IRTemp */
829 if (expr->tag == Iex_RdTmp) {
830 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
831 return;
832 }
833
834 if (expr->tag == Iex_Binop) {
835 IRExpr *arg1 = expr->Iex.Binop.arg1;
836 IRExpr *arg2 = expr->Iex.Binop.arg2;
837 Bool is_signed_multiply, is_signed_divide;
838
839 switch (expr->Iex.Binop.op) {
840 case Iop_MullU64:
841 is_signed_multiply = False;
842 goto do_multiply64;
843
844 case Iop_MullS64:
845 is_signed_multiply = True;
846 goto do_multiply64;
847
848 case Iop_DivModU128to64:
849 is_signed_divide = False;
850 goto do_divide64;
851
852 case Iop_DivModS128to64:
853 is_signed_divide = True;
854 goto do_divide64;
855
856 case Iop_64HLto128:
857 *dst_hi = s390_isel_int_expr(env, arg1);
858 *dst_lo = s390_isel_int_expr(env, arg2);
859 return;
860
861 case Iop_DivModS64to64: {
862 HReg r10, r11, h1;
863 s390_opnd_RMI op2;
864
865 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
866 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
867
868 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000869 r10 = make_gpr(10);
870 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000871
872 /* Move 1st operand into r11 and */
873 addInstr(env, s390_insn_move(8, r11, h1));
874
875 /* Divide */
876 addInstr(env, s390_insn_divs(8, r10, r11, op2));
877
878 /* The result is in registers r10 (remainder) and r11 (quotient).
879 Move the result into the reg pair that is being returned such
880 such that the low 64 bits are the quotient and the upper 64 bits
881 are the remainder. (see libvex_ir.h). */
882 *dst_hi = newVRegI(env);
883 *dst_lo = newVRegI(env);
884 addInstr(env, s390_insn_move(8, *dst_hi, r10));
885 addInstr(env, s390_insn_move(8, *dst_lo, r11));
886 return;
887 }
888
889 default:
890 break;
891
892 do_multiply64: {
893 HReg r10, r11, h1;
894 s390_opnd_RMI op2;
895
896 order_commutative_operands(arg1, arg2);
897
898 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
899 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
900
901 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000902 r10 = make_gpr(10);
903 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000904
905 /* Move the first operand to r11 */
906 addInstr(env, s390_insn_move(8, r11, h1));
907
908 /* Multiply */
909 addInstr(env, s390_insn_mul(8, r10, r11, op2, is_signed_multiply));
910
911 /* The result is in registers r10 and r11. Assign to two virtual regs
912 and return. */
913 *dst_hi = newVRegI(env);
914 *dst_lo = newVRegI(env);
915 addInstr(env, s390_insn_move(8, *dst_hi, r10));
916 addInstr(env, s390_insn_move(8, *dst_lo, r11));
917 return;
918 }
919
920 do_divide64: {
921 HReg r10, r11, hi, lo;
922 s390_opnd_RMI op2;
923
924 s390_isel_int128_expr(&hi, &lo, env, arg1);
925 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
926
927 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000928 r10 = make_gpr(10);
929 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000930
931 /* Move high 64 bits of the 1st operand into r10 and
932 the low 64 bits into r11. */
933 addInstr(env, s390_insn_move(8, r10, hi));
934 addInstr(env, s390_insn_move(8, r11, lo));
935
936 /* Divide */
937 addInstr(env, s390_insn_div(8, r10, r11, op2, is_signed_divide));
938
939 /* The result is in registers r10 (remainder) and r11 (quotient).
940 Move the result into the reg pair that is being returned such
941 such that the low 64 bits are the quotient and the upper 64 bits
942 are the remainder. (see libvex_ir.h). */
943 *dst_hi = newVRegI(env);
944 *dst_lo = newVRegI(env);
945 addInstr(env, s390_insn_move(8, *dst_hi, r10));
946 addInstr(env, s390_insn_move(8, *dst_lo, r11));
947 return;
948 }
949 }
950 }
951
952 vpanic("s390_isel_int128_expr");
953}
954
955
956/* Compute a 128-bit value into two 64-bit registers. These may be either
957 real or virtual regs; in any case they must not be changed by subsequent
958 code emitted by the caller. */
959static void
960s390_isel_int128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
961{
962 s390_isel_int128_expr_wrk(dst_hi, dst_lo, env, expr);
963
964 /* Sanity checks ... */
965 vassert(hregIsVirtual(*dst_hi));
966 vassert(hregIsVirtual(*dst_lo));
967 vassert(hregClass(*dst_hi) == HRcInt64);
968 vassert(hregClass(*dst_lo) == HRcInt64);
969}
970
971
972/*---------------------------------------------------------*/
973/*--- ISEL: Integer expressions (64/32/16/8 bit) ---*/
974/*---------------------------------------------------------*/
975
976/* Select insns for an integer-typed expression, and add them to the
977 code list. Return a reg holding the result. This reg will be a
978 virtual register. THE RETURNED REG MUST NOT BE MODIFIED. If you
979 want to modify it, ask for a new vreg, copy it in there, and modify
980 the copy. The register allocator will do its best to map both
981 vregs to the same real register, so the copies will often disappear
982 later in the game.
983
984 This should handle expressions of 64, 32, 16 and 8-bit type.
985 All results are returned in a 64bit register.
986 For 16- and 8-bit expressions, the upper (32/48/56 : 16/24) bits
987 are arbitrary, so you should mask or sign extend partial values
988 if necessary.
989*/
990
991/* DO NOT CALL THIS DIRECTLY ! */
992static HReg
993s390_isel_int_expr_wrk(ISelEnv *env, IRExpr *expr)
994{
995 IRType ty = typeOfIRExpr(env->type_env, expr);
996 UChar size;
florian6dc90242012-12-21 21:43:00 +0000997 s390_bfp_conv_t conv;
florian67a171c2013-01-20 03:08:04 +0000998 s390_dfp_conv_t dconv;
sewardj2019a972011-03-07 16:04:07 +0000999
1000 vassert(ty == Ity_I8 || ty == Ity_I16 || ty == Ity_I32 || ty == Ity_I64);
1001
1002 size = sizeofIRType(ty); /* size of the result after evaluating EXPR */
1003
1004 switch (expr->tag) {
1005
1006 /* --------- TEMP --------- */
1007 case Iex_RdTmp:
1008 /* Return the virtual register that holds the temporary. */
1009 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
1010
1011 /* --------- LOAD --------- */
1012 case Iex_Load: {
1013 HReg dst = newVRegI(env);
1014 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
1015
1016 if (expr->Iex.Load.end != Iend_BE)
1017 goto irreducible;
1018
1019 addInstr(env, s390_insn_load(size, dst, am));
1020
1021 return dst;
1022 }
1023
1024 /* --------- BINARY OP --------- */
1025 case Iex_Binop: {
1026 IRExpr *arg1 = expr->Iex.Binop.arg1;
1027 IRExpr *arg2 = expr->Iex.Binop.arg2;
1028 HReg h1, res;
1029 s390_alu_t opkind;
1030 s390_opnd_RMI op2, value, opnd;
1031 s390_insn *insn;
1032 Bool is_commutative, is_signed_multiply, is_signed_divide;
1033
1034 is_commutative = True;
1035
1036 switch (expr->Iex.Binop.op) {
1037 case Iop_MullU8:
1038 case Iop_MullU16:
1039 case Iop_MullU32:
1040 is_signed_multiply = False;
1041 goto do_multiply;
1042
1043 case Iop_MullS8:
1044 case Iop_MullS16:
1045 case Iop_MullS32:
1046 is_signed_multiply = True;
1047 goto do_multiply;
1048
1049 do_multiply: {
1050 HReg r10, r11;
1051 UInt arg_size = size / 2;
1052
1053 order_commutative_operands(arg1, arg2);
1054
1055 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1056 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1057
1058 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001059 r10 = make_gpr(10);
1060 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001061
1062 /* Move the first operand to r11 */
1063 addInstr(env, s390_insn_move(arg_size, r11, h1));
1064
1065 /* Multiply */
1066 addInstr(env, s390_insn_mul(arg_size, r10, r11, op2, is_signed_multiply));
1067
1068 /* The result is in registers r10 and r11. Combine them into a SIZE-bit
1069 value into the destination register. */
1070 res = newVRegI(env);
1071 addInstr(env, s390_insn_move(arg_size, res, r10));
1072 value = s390_opnd_imm(arg_size * 8);
1073 addInstr(env, s390_insn_alu(size, S390_ALU_LSH, res, value));
1074 value = s390_opnd_imm((((ULong)1) << arg_size * 8) - 1);
1075 addInstr(env, s390_insn_alu(size, S390_ALU_AND, r11, value));
1076 opnd = s390_opnd_reg(r11);
1077 addInstr(env, s390_insn_alu(size, S390_ALU_OR, res, opnd));
1078 return res;
1079 }
1080
1081 case Iop_DivModS64to32:
1082 is_signed_divide = True;
1083 goto do_divide;
1084
1085 case Iop_DivModU64to32:
1086 is_signed_divide = False;
1087 goto do_divide;
1088
1089 do_divide: {
1090 HReg r10, r11;
1091
1092 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1093 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1094
1095 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001096 r10 = make_gpr(10);
1097 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001098
1099 /* Split the first operand and put the high 32 bits into r10 and
1100 the low 32 bits into r11. */
1101 addInstr(env, s390_insn_move(8, r10, h1));
1102 addInstr(env, s390_insn_move(8, r11, h1));
1103 value = s390_opnd_imm(32);
1104 addInstr(env, s390_insn_alu(8, S390_ALU_RSH, r10, value));
1105
1106 /* Divide */
1107 addInstr(env, s390_insn_div(4, r10, r11, op2, is_signed_divide));
1108
1109 /* The result is in registers r10 (remainder) and r11 (quotient).
1110 Combine them into a 64-bit value such that the low 32 bits are
1111 the quotient and the upper 32 bits are the remainder. (see
1112 libvex_ir.h). */
1113 res = newVRegI(env);
1114 addInstr(env, s390_insn_move(8, res, r10));
1115 value = s390_opnd_imm(32);
1116 addInstr(env, s390_insn_alu(8, S390_ALU_LSH, res, value));
1117 value = s390_opnd_imm((((ULong)1) << 32) - 1);
1118 addInstr(env, s390_insn_alu(8, S390_ALU_AND, r11, value));
1119 opnd = s390_opnd_reg(r11);
1120 addInstr(env, s390_insn_alu(8, S390_ALU_OR, res, opnd));
1121 return res;
1122 }
1123
florian9fcff4c2012-09-10 03:09:04 +00001124 case Iop_F32toI32S: conv = S390_BFP_F32_TO_I32; goto do_convert;
1125 case Iop_F32toI64S: conv = S390_BFP_F32_TO_I64; goto do_convert;
1126 case Iop_F32toI32U: conv = S390_BFP_F32_TO_U32; goto do_convert;
1127 case Iop_F32toI64U: conv = S390_BFP_F32_TO_U64; goto do_convert;
1128 case Iop_F64toI32S: conv = S390_BFP_F64_TO_I32; goto do_convert;
1129 case Iop_F64toI64S: conv = S390_BFP_F64_TO_I64; goto do_convert;
1130 case Iop_F64toI32U: conv = S390_BFP_F64_TO_U32; goto do_convert;
1131 case Iop_F64toI64U: conv = S390_BFP_F64_TO_U64; goto do_convert;
1132 case Iop_F128toI32S: conv = S390_BFP_F128_TO_I32; goto do_convert_128;
1133 case Iop_F128toI64S: conv = S390_BFP_F128_TO_I64; goto do_convert_128;
1134 case Iop_F128toI32U: conv = S390_BFP_F128_TO_U32; goto do_convert_128;
1135 case Iop_F128toI64U: conv = S390_BFP_F128_TO_U64; goto do_convert_128;
florian67a171c2013-01-20 03:08:04 +00001136
1137 case Iop_D64toI32S: dconv = S390_DFP_D64_TO_I32; goto do_convert_dfp;
1138 case Iop_D64toI32U: dconv = S390_DFP_D64_TO_U32; goto do_convert_dfp;
1139 case Iop_D64toI64U: dconv = S390_DFP_D64_TO_U64; goto do_convert_dfp;
1140 case Iop_D128toI32S: dconv = S390_DFP_D128_TO_I32; goto do_convert_dfp128;
1141 case Iop_D128toI32U: dconv = S390_DFP_D128_TO_U32; goto do_convert_dfp128;
1142 case Iop_D128toI64U: dconv = S390_DFP_D128_TO_U64; goto do_convert_dfp128;
sewardj2019a972011-03-07 16:04:07 +00001143
1144 do_convert: {
florian125e20d2012-10-07 15:42:37 +00001145 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00001146
1147 res = newVRegI(env);
1148 h1 = s390_isel_float_expr(env, arg2); /* Process operand */
1149
florian2c74d242012-09-12 19:38:42 +00001150 rounding_mode = get_bfp_rounding_mode(env, arg1);
1151 addInstr(env, s390_insn_bfp_convert(size, conv, res, h1,
1152 rounding_mode));
sewardj2019a972011-03-07 16:04:07 +00001153 return res;
1154 }
1155
1156 do_convert_128: {
florian125e20d2012-10-07 15:42:37 +00001157 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00001158 HReg op_hi, op_lo, f13, f15;
1159
1160 res = newVRegI(env);
1161 s390_isel_float128_expr(&op_hi, &op_lo, env, arg2); /* operand */
1162
1163 /* We use non-virtual registers r13 and r15 as pair */
1164 f13 = make_fpr(13);
1165 f15 = make_fpr(15);
1166
1167 /* operand --> (f13, f15) */
1168 addInstr(env, s390_insn_move(8, f13, op_hi));
1169 addInstr(env, s390_insn_move(8, f15, op_lo));
1170
florian2c74d242012-09-12 19:38:42 +00001171 rounding_mode = get_bfp_rounding_mode(env, arg1);
florian9fcff4c2012-09-10 03:09:04 +00001172 addInstr(env, s390_insn_bfp128_convert_from(size, conv, res, f13, f15,
sewardj2019a972011-03-07 16:04:07 +00001173 rounding_mode));
1174 return res;
1175 }
1176
florian5f034622013-01-13 02:29:05 +00001177 do_convert_dfp: {
1178 s390_dfp_round_t rounding_mode;
1179
1180 res = newVRegI(env);
1181 h1 = s390_isel_dfp_expr(env, arg2); /* Process operand */
1182
1183 rounding_mode = get_dfp_rounding_mode(env, arg1);
florian67a171c2013-01-20 03:08:04 +00001184 addInstr(env, s390_insn_dfp_convert(size, dconv, res, h1,
florian5f034622013-01-13 02:29:05 +00001185 rounding_mode));
1186 return res;
1187 }
1188
1189 do_convert_dfp128: {
1190 s390_dfp_round_t rounding_mode;
1191 HReg op_hi, op_lo, f13, f15;
1192
1193 res = newVRegI(env);
1194 s390_isel_dfp128_expr(&op_hi, &op_lo, env, arg2); /* operand */
1195
1196 /* We use non-virtual registers r13 and r15 as pair */
1197 f13 = make_fpr(13);
1198 f15 = make_fpr(15);
1199
1200 /* operand --> (f13, f15) */
1201 addInstr(env, s390_insn_move(8, f13, op_hi));
1202 addInstr(env, s390_insn_move(8, f15, op_lo));
1203
1204 rounding_mode = get_dfp_rounding_mode(env, arg1);
florian67a171c2013-01-20 03:08:04 +00001205 addInstr(env, s390_insn_dfp128_convert_from(size, dconv, res, f13,
florian5f034622013-01-13 02:29:05 +00001206 f15, rounding_mode));
1207 return res;
1208 }
1209
sewardj2019a972011-03-07 16:04:07 +00001210 case Iop_8HLto16:
1211 case Iop_16HLto32:
1212 case Iop_32HLto64: {
1213 HReg h2;
1214 UInt arg_size = size / 2;
1215
1216 res = newVRegI(env);
1217 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1218 h2 = s390_isel_int_expr(env, arg2); /* Process 2nd operand */
1219
1220 addInstr(env, s390_insn_move(arg_size, res, h1));
1221 value = s390_opnd_imm(arg_size * 8);
1222 addInstr(env, s390_insn_alu(size, S390_ALU_LSH, res, value));
1223 value = s390_opnd_imm((((ULong)1) << arg_size * 8) - 1);
1224 addInstr(env, s390_insn_alu(size, S390_ALU_AND, h2, value));
1225 opnd = s390_opnd_reg(h2);
1226 addInstr(env, s390_insn_alu(size, S390_ALU_OR, res, opnd));
1227 return res;
1228 }
1229
1230 case Iop_Max32U: {
1231 /* arg1 > arg2 ? arg1 : arg2 using uint32_t arguments */
1232 res = newVRegI(env);
1233 h1 = s390_isel_int_expr(env, arg1);
1234 op2 = s390_isel_int_expr_RMI(env, arg2);
1235
1236 addInstr(env, s390_insn_move(size, res, h1));
1237 addInstr(env, s390_insn_compare(size, res, op2, False /* signed */));
1238 addInstr(env, s390_insn_cond_move(size, S390_CC_L, res, op2));
1239 return res;
1240 }
1241
1242 case Iop_CmpF32:
1243 case Iop_CmpF64: {
1244 HReg cc_s390, h2;
1245
1246 h1 = s390_isel_float_expr(env, arg1);
1247 h2 = s390_isel_float_expr(env, arg2);
1248 cc_s390 = newVRegI(env);
1249
1250 size = (expr->Iex.Binop.op == Iop_CmpF32) ? 4 : 8;
1251
1252 addInstr(env, s390_insn_bfp_compare(size, cc_s390, h1, h2));
1253
florian2d3d87f2012-12-21 21:05:17 +00001254 return convert_s390_to_vex_bfpcc(env, cc_s390);
sewardj2019a972011-03-07 16:04:07 +00001255 }
1256
1257 case Iop_CmpF128: {
1258 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15, cc_s390;
1259
1260 s390_isel_float128_expr(&op1_hi, &op1_lo, env, arg1); /* 1st operand */
1261 s390_isel_float128_expr(&op2_hi, &op2_lo, env, arg2); /* 2nd operand */
1262 cc_s390 = newVRegI(env);
1263
1264 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1265 f12 = make_fpr(12);
1266 f13 = make_fpr(13);
1267 f14 = make_fpr(14);
1268 f15 = make_fpr(15);
1269
1270 /* 1st operand --> (f12, f14) */
1271 addInstr(env, s390_insn_move(8, f12, op1_hi));
1272 addInstr(env, s390_insn_move(8, f14, op1_lo));
1273
1274 /* 2nd operand --> (f13, f15) */
1275 addInstr(env, s390_insn_move(8, f13, op2_hi));
1276 addInstr(env, s390_insn_move(8, f15, op2_lo));
1277
1278 res = newVRegI(env);
1279 addInstr(env, s390_insn_bfp128_compare(16, cc_s390, f12, f14, f13, f15));
1280
florian2d3d87f2012-12-21 21:05:17 +00001281 return convert_s390_to_vex_bfpcc(env, cc_s390);
sewardj2019a972011-03-07 16:04:07 +00001282 }
1283
florian20c6bca2012-12-26 17:47:19 +00001284 case Iop_CmpD64:
1285 case Iop_CmpExpD64: {
floriane38f6412012-12-21 17:32:12 +00001286 HReg cc_s390, h2;
florian20c6bca2012-12-26 17:47:19 +00001287 s390_dfp_cmp_t cmp;
floriane38f6412012-12-21 17:32:12 +00001288
1289 h1 = s390_isel_dfp_expr(env, arg1);
1290 h2 = s390_isel_dfp_expr(env, arg2);
1291 cc_s390 = newVRegI(env);
floriane38f6412012-12-21 17:32:12 +00001292
florian20c6bca2012-12-26 17:47:19 +00001293 switch(expr->Iex.Binop.op) {
1294 case Iop_CmpD64: cmp = S390_DFP_COMPARE; break;
1295 case Iop_CmpExpD64: cmp = S390_DFP_COMPARE_EXP; break;
1296 default: goto irreducible;
1297 }
1298 addInstr(env, s390_insn_dfp_compare(8, cmp, cc_s390, h1, h2));
floriane38f6412012-12-21 17:32:12 +00001299
florian2d3d87f2012-12-21 21:05:17 +00001300 return convert_s390_to_vex_dfpcc(env, cc_s390);
floriane38f6412012-12-21 17:32:12 +00001301 }
1302
florian20c6bca2012-12-26 17:47:19 +00001303 case Iop_CmpD128:
1304 case Iop_CmpExpD128: {
floriane38f6412012-12-21 17:32:12 +00001305 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15, cc_s390;
florian20c6bca2012-12-26 17:47:19 +00001306 s390_dfp_cmp_t cmp;
floriane38f6412012-12-21 17:32:12 +00001307
1308 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, arg1); /* 1st operand */
1309 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, arg2); /* 2nd operand */
1310 cc_s390 = newVRegI(env);
1311
1312 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1313 f12 = make_fpr(12);
1314 f13 = make_fpr(13);
1315 f14 = make_fpr(14);
1316 f15 = make_fpr(15);
1317
1318 /* 1st operand --> (f12, f14) */
1319 addInstr(env, s390_insn_move(8, f12, op1_hi));
1320 addInstr(env, s390_insn_move(8, f14, op1_lo));
1321
1322 /* 2nd operand --> (f13, f15) */
1323 addInstr(env, s390_insn_move(8, f13, op2_hi));
1324 addInstr(env, s390_insn_move(8, f15, op2_lo));
1325
florian20c6bca2012-12-26 17:47:19 +00001326 switch(expr->Iex.Binop.op) {
1327 case Iop_CmpD128: cmp = S390_DFP_COMPARE; break;
1328 case Iop_CmpExpD128: cmp = S390_DFP_COMPARE_EXP; break;
1329 default: goto irreducible;
1330 }
1331 addInstr(env, s390_insn_dfp128_compare(16, cmp, cc_s390, f12, f14,
1332 f13, f15));
floriane38f6412012-12-21 17:32:12 +00001333
florian2d3d87f2012-12-21 21:05:17 +00001334 return convert_s390_to_vex_dfpcc(env, cc_s390);
floriane38f6412012-12-21 17:32:12 +00001335 }
1336
sewardj2019a972011-03-07 16:04:07 +00001337 case Iop_Add8:
1338 case Iop_Add16:
1339 case Iop_Add32:
1340 case Iop_Add64:
1341 opkind = S390_ALU_ADD;
1342 break;
1343
1344 case Iop_Sub8:
1345 case Iop_Sub16:
1346 case Iop_Sub32:
1347 case Iop_Sub64:
1348 opkind = S390_ALU_SUB;
1349 is_commutative = False;
1350 break;
1351
1352 case Iop_And8:
1353 case Iop_And16:
1354 case Iop_And32:
1355 case Iop_And64:
1356 opkind = S390_ALU_AND;
1357 break;
1358
1359 case Iop_Or8:
1360 case Iop_Or16:
1361 case Iop_Or32:
1362 case Iop_Or64:
1363 opkind = S390_ALU_OR;
1364 break;
1365
1366 case Iop_Xor8:
1367 case Iop_Xor16:
1368 case Iop_Xor32:
1369 case Iop_Xor64:
1370 opkind = S390_ALU_XOR;
1371 break;
1372
1373 case Iop_Shl8:
1374 case Iop_Shl16:
1375 case Iop_Shl32:
1376 case Iop_Shl64:
1377 opkind = S390_ALU_LSH;
1378 is_commutative = False;
1379 break;
1380
1381 case Iop_Shr8:
1382 case Iop_Shr16:
1383 case Iop_Shr32:
1384 case Iop_Shr64:
1385 opkind = S390_ALU_RSH;
1386 is_commutative = False;
1387 break;
1388
1389 case Iop_Sar8:
1390 case Iop_Sar16:
1391 case Iop_Sar32:
1392 case Iop_Sar64:
1393 opkind = S390_ALU_RSHA;
1394 is_commutative = False;
1395 break;
1396
1397 default:
1398 goto irreducible;
1399 }
1400
1401 /* Pattern match: 0 - arg1 --> -arg1 */
1402 if (opkind == S390_ALU_SUB && s390_expr_is_const_zero(arg1)) {
1403 res = newVRegI(env);
1404 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1405 insn = s390_insn_unop(size, S390_NEGATE, res, op2);
1406 addInstr(env, insn);
1407
1408 return res;
1409 }
1410
1411 if (is_commutative) {
1412 order_commutative_operands(arg1, arg2);
1413 }
1414
1415 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1416 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1417 res = newVRegI(env);
florian5e0f2042012-08-20 13:44:29 +00001418
1419 /* As right shifts of one/two byte opreands are implemented using a
1420 4-byte shift op, we first need to zero/sign-extend the shiftee. */
1421 switch (expr->Iex.Binop.op) {
1422 case Iop_Shr8:
1423 insn = s390_insn_unop(4, S390_ZERO_EXTEND_8, res, s390_opnd_reg(h1));
1424 break;
1425 case Iop_Shr16:
1426 insn = s390_insn_unop(4, S390_ZERO_EXTEND_16, res, s390_opnd_reg(h1));
1427 break;
1428 case Iop_Sar8:
1429 insn = s390_insn_unop(4, S390_SIGN_EXTEND_8, res, s390_opnd_reg(h1));
1430 break;
1431 case Iop_Sar16:
1432 insn = s390_insn_unop(4, S390_SIGN_EXTEND_16, res, s390_opnd_reg(h1));
1433 break;
1434 default:
1435 insn = s390_insn_move(size, res, h1);
1436 break;
1437 }
1438 addInstr(env, insn);
1439
sewardj2019a972011-03-07 16:04:07 +00001440 insn = s390_insn_alu(size, opkind, res, op2);
1441
1442 addInstr(env, insn);
1443
1444 return res;
1445 }
1446
1447 /* --------- UNARY OP --------- */
1448 case Iex_Unop: {
1449 static s390_opnd_RMI mask = { S390_OPND_IMMEDIATE };
1450 static s390_opnd_RMI shift = { S390_OPND_IMMEDIATE };
1451 s390_opnd_RMI opnd;
1452 s390_insn *insn;
1453 IRExpr *arg;
1454 HReg dst, h1;
1455 IROp unop, binop;
1456
1457 arg = expr->Iex.Unop.arg;
1458
1459 /* Special cases are handled here */
1460
1461 /* 32-bit multiply with 32-bit result or
1462 64-bit multiply with 64-bit result */
1463 unop = expr->Iex.Unop.op;
1464 binop = arg->Iex.Binop.op;
1465
1466 if ((arg->tag == Iex_Binop &&
1467 ((unop == Iop_64to32 &&
1468 (binop == Iop_MullS32 || binop == Iop_MullU32)) ||
1469 (unop == Iop_128to64 &&
1470 (binop == Iop_MullS64 || binop == Iop_MullU64))))) {
1471 h1 = s390_isel_int_expr(env, arg->Iex.Binop.arg1); /* 1st opnd */
1472 opnd = s390_isel_int_expr_RMI(env, arg->Iex.Binop.arg2); /* 2nd opnd */
1473 dst = newVRegI(env); /* Result goes into a new register */
1474 addInstr(env, s390_insn_move(size, dst, h1));
1475 addInstr(env, s390_insn_alu(size, S390_ALU_MUL, dst, opnd));
1476
1477 return dst;
1478 }
1479
florian4d71a082011-12-18 00:08:17 +00001480 if (unop == Iop_ReinterpF64asI64 || unop == Iop_ReinterpF32asI32) {
sewardj2019a972011-03-07 16:04:07 +00001481 dst = newVRegI(env);
1482 h1 = s390_isel_float_expr(env, arg); /* Process the operand */
1483 addInstr(env, s390_insn_move(size, dst, h1));
1484
1485 return dst;
1486 }
1487
floriane38f6412012-12-21 17:32:12 +00001488 if (unop == Iop_ReinterpD64asI64) {
1489 dst = newVRegI(env);
1490 h1 = s390_isel_dfp_expr(env, arg); /* Process the operand */
1491 addInstr(env, s390_insn_move(size, dst, h1));
1492
1493 return dst;
1494 }
1495
floriance9e3db2012-12-27 20:14:03 +00001496 if (unop == Iop_ExtractSigD64) {
1497 dst = newVRegI(env);
1498 h1 = s390_isel_dfp_expr(env, arg); /* Process the operand */
1499 addInstr(env,
1500 s390_insn_dfp_unop(size, S390_DFP_EXTRACT_SIG_D64, dst, h1));
1501 return dst;
1502 }
1503
1504 if (unop == Iop_ExtractSigD128) {
1505 HReg op_hi, op_lo, f13, f15;
1506 dst = newVRegI(env);
1507 s390_isel_dfp128_expr(&op_hi, &op_lo, env, arg); /* Process operand */
1508
1509 /* We use non-virtual registers r13 and r15 as pair */
1510 f13 = make_fpr(13);
1511 f15 = make_fpr(15);
1512
1513 /* operand --> (f13, f15) */
1514 addInstr(env, s390_insn_move(8, f13, op_hi));
1515 addInstr(env, s390_insn_move(8, f15, op_lo));
1516
1517 addInstr(env, s390_insn_dfp128_unop(size, S390_DFP_EXTRACT_SIG_D128,
1518 dst, f13, f15));
1519 return dst;
1520 }
1521
sewardj2019a972011-03-07 16:04:07 +00001522 /* Expressions whose argument is 1-bit wide */
1523 if (typeOfIRExpr(env->type_env, arg) == Ity_I1) {
1524 s390_cc_t cond = s390_isel_cc(env, arg);
1525 dst = newVRegI(env); /* Result goes into a new register */
1526 addInstr(env, s390_insn_cc2bool(dst, cond));
1527
1528 switch (unop) {
1529 case Iop_1Uto8:
1530 case Iop_1Uto32:
florian5f27dcf2012-08-04 04:25:30 +00001531 /* Zero extend */
1532 mask.variant.imm = 1;
1533 addInstr(env, s390_insn_alu(4, S390_ALU_AND, dst, mask));
1534 break;
1535
sewardj2019a972011-03-07 16:04:07 +00001536 case Iop_1Uto64:
florian5f27dcf2012-08-04 04:25:30 +00001537 /* Zero extend */
1538 mask.variant.imm = 1;
1539 addInstr(env, s390_insn_alu(8, S390_ALU_AND, dst, mask));
sewardj2019a972011-03-07 16:04:07 +00001540 break;
1541
1542 case Iop_1Sto8:
1543 case Iop_1Sto16:
1544 case Iop_1Sto32:
1545 shift.variant.imm = 31;
1546 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, dst, shift));
1547 addInstr(env, s390_insn_alu(4, S390_ALU_RSHA, dst, shift));
1548 break;
1549
1550 case Iop_1Sto64:
1551 shift.variant.imm = 63;
1552 addInstr(env, s390_insn_alu(8, S390_ALU_LSH, dst, shift));
1553 addInstr(env, s390_insn_alu(8, S390_ALU_RSHA, dst, shift));
1554 break;
1555
1556 default:
1557 goto irreducible;
1558 }
1559
1560 return dst;
1561 }
1562
1563 /* Regular processing */
1564
1565 if (unop == Iop_128to64) {
1566 HReg dst_hi, dst_lo;
1567
1568 s390_isel_int128_expr(&dst_hi, &dst_lo, env, arg);
1569 return dst_lo;
1570 }
1571
1572 if (unop == Iop_128HIto64) {
1573 HReg dst_hi, dst_lo;
1574
1575 s390_isel_int128_expr(&dst_hi, &dst_lo, env, arg);
1576 return dst_hi;
1577 }
1578
1579 dst = newVRegI(env); /* Result goes into a new register */
1580 opnd = s390_isel_int_expr_RMI(env, arg); /* Process the operand */
1581
1582 switch (unop) {
1583 case Iop_8Uto16:
1584 case Iop_8Uto32:
1585 case Iop_8Uto64:
1586 insn = s390_insn_unop(size, S390_ZERO_EXTEND_8, dst, opnd);
1587 break;
1588
1589 case Iop_16Uto32:
1590 case Iop_16Uto64:
1591 insn = s390_insn_unop(size, S390_ZERO_EXTEND_16, dst, opnd);
1592 break;
1593
1594 case Iop_32Uto64:
1595 insn = s390_insn_unop(size, S390_ZERO_EXTEND_32, dst, opnd);
1596 break;
1597
1598 case Iop_8Sto16:
1599 case Iop_8Sto32:
1600 case Iop_8Sto64:
1601 insn = s390_insn_unop(size, S390_SIGN_EXTEND_8, dst, opnd);
1602 break;
1603
1604 case Iop_16Sto32:
1605 case Iop_16Sto64:
1606 insn = s390_insn_unop(size, S390_SIGN_EXTEND_16, dst, opnd);
1607 break;
1608
1609 case Iop_32Sto64:
1610 insn = s390_insn_unop(size, S390_SIGN_EXTEND_32, dst, opnd);
1611 break;
1612
1613 case Iop_64to8:
1614 case Iop_64to16:
1615 case Iop_64to32:
1616 case Iop_32to8:
1617 case Iop_32to16:
1618 case Iop_16to8:
1619 /* Down-casts are no-ops. Upstream operations will only look at
1620 the bytes that make up the result of the down-cast. So there
1621 is no point setting the other bytes to 0. */
1622 insn = s390_opnd_copy(8, dst, opnd);
1623 break;
1624
1625 case Iop_64HIto32:
1626 addInstr(env, s390_opnd_copy(8, dst, opnd));
1627 shift.variant.imm = 32;
1628 insn = s390_insn_alu(8, S390_ALU_RSH, dst, shift);
1629 break;
1630
1631 case Iop_32HIto16:
1632 addInstr(env, s390_opnd_copy(4, dst, opnd));
1633 shift.variant.imm = 16;
1634 insn = s390_insn_alu(4, S390_ALU_RSH, dst, shift);
1635 break;
1636
1637 case Iop_16HIto8:
1638 addInstr(env, s390_opnd_copy(2, dst, opnd));
1639 shift.variant.imm = 8;
1640 insn = s390_insn_alu(2, S390_ALU_RSH, dst, shift);
1641 break;
1642
1643 case Iop_Not8:
1644 case Iop_Not16:
1645 case Iop_Not32:
1646 case Iop_Not64:
1647 /* XOR with ffff... */
1648 mask.variant.imm = ~(ULong)0;
1649 addInstr(env, s390_opnd_copy(size, dst, opnd));
1650 insn = s390_insn_alu(size, S390_ALU_XOR, dst, mask);
1651 break;
1652
1653 case Iop_Left8:
1654 case Iop_Left16:
1655 case Iop_Left32:
1656 case Iop_Left64:
1657 addInstr(env, s390_insn_unop(size, S390_NEGATE, dst, opnd));
1658 insn = s390_insn_alu(size, S390_ALU_OR, dst, opnd);
1659 break;
1660
1661 case Iop_CmpwNEZ32:
1662 case Iop_CmpwNEZ64: {
1663 /* Use the fact that x | -x == 0 iff x == 0. Otherwise, either X
1664 or -X will have a 1 in the MSB. */
1665 addInstr(env, s390_insn_unop(size, S390_NEGATE, dst, opnd));
1666 addInstr(env, s390_insn_alu(size, S390_ALU_OR, dst, opnd));
1667 shift.variant.imm = (unop == Iop_CmpwNEZ32) ? 31 : 63;
1668 addInstr(env, s390_insn_alu(size, S390_ALU_RSHA, dst, shift));
1669 return dst;
1670 }
1671
1672 case Iop_Clz64: {
1673 HReg r10, r11;
1674
sewardj611b06e2011-03-24 08:57:29 +00001675 /* This will be implemented using FLOGR, if possible. So we need to
1676 set aside a pair of non-virtual registers. The result (number of
1677 left-most zero bits) will be in r10. The value in r11 is unspecified
1678 and must not be used. */
florian297b6062012-05-08 20:16:17 +00001679 r10 = make_gpr(10);
1680 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001681
sewardj611b06e2011-03-24 08:57:29 +00001682 addInstr(env, s390_insn_clz(8, r10, r11, opnd));
sewardj2019a972011-03-07 16:04:07 +00001683 addInstr(env, s390_insn_move(8, dst, r10));
1684 return dst;
1685 }
1686
1687 default:
1688 goto irreducible;
1689 }
1690
1691 addInstr(env, insn);
1692
1693 return dst;
1694 }
1695
1696 /* --------- GET --------- */
1697 case Iex_Get: {
1698 HReg dst = newVRegI(env);
1699 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
1700
1701 /* We never load more than 8 bytes from the guest state, because the
1702 floating point register pair is not contiguous. */
1703 vassert(size <= 8);
1704
1705 addInstr(env, s390_insn_load(size, dst, am));
1706
1707 return dst;
1708 }
1709
1710 case Iex_GetI:
1711 /* not needed */
1712 break;
1713
1714 /* --------- CCALL --------- */
1715 case Iex_CCall: {
1716 HReg dst = newVRegI(env);
1717
1718 doHelperCall(env, False, NULL, expr->Iex.CCall.cee,
florian01ed6e72012-05-27 16:52:43 +00001719 expr->Iex.CCall.args, dst);
sewardj2019a972011-03-07 16:04:07 +00001720 return dst;
1721 }
1722
1723 /* --------- LITERAL --------- */
1724
1725 /* Load a literal into a register. Create a "load immediate"
1726 v-insn and return the register. */
1727 case Iex_Const: {
1728 ULong value;
1729 HReg dst = newVRegI(env);
1730 const IRConst *con = expr->Iex.Const.con;
1731
1732 /* Bitwise copy of the value. No sign/zero-extension */
1733 switch (con->tag) {
1734 case Ico_U64: value = con->Ico.U64; break;
1735 case Ico_U32: value = con->Ico.U32; break;
1736 case Ico_U16: value = con->Ico.U16; break;
1737 case Ico_U8: value = con->Ico.U8; break;
1738 default: vpanic("s390_isel_int_expr: invalid constant");
1739 }
1740
1741 addInstr(env, s390_insn_load_immediate(size, dst, value));
1742
1743 return dst;
1744 }
1745
1746 /* --------- MULTIPLEX --------- */
florian99dd03e2013-01-29 03:56:06 +00001747 case Iex_ITE: {
sewardj2019a972011-03-07 16:04:07 +00001748 IRExpr *cond_expr;
florian99dd03e2013-01-29 03:56:06 +00001749 HReg dst, r1;
sewardj009230b2013-01-26 11:47:55 +00001750 s390_opnd_RMI r0;
sewardj2019a972011-03-07 16:04:07 +00001751
florian99dd03e2013-01-29 03:56:06 +00001752 cond_expr = expr->Iex.ITE.cond;
sewardj2019a972011-03-07 16:04:07 +00001753
sewardj009230b2013-01-26 11:47:55 +00001754 vassert(typeOfIRExpr(env->type_env, cond_expr) == Ity_I1);
1755
sewardj2019a972011-03-07 16:04:07 +00001756 dst = newVRegI(env);
florian99dd03e2013-01-29 03:56:06 +00001757 r0 = s390_isel_int_expr_RMI(env, expr->Iex.ITE.iffalse);
1758 r1 = s390_isel_int_expr(env, expr->Iex.ITE.iftrue);
1759 size = sizeofIRType(typeOfIRExpr(env->type_env, expr->Iex.ITE.iftrue));
sewardj2019a972011-03-07 16:04:07 +00001760
sewardj009230b2013-01-26 11:47:55 +00001761 s390_cc_t cc = s390_isel_cc(env, cond_expr);
sewardj2019a972011-03-07 16:04:07 +00001762
florian99dd03e2013-01-29 03:56:06 +00001763 addInstr(env, s390_insn_move(size, dst, r1));
sewardj009230b2013-01-26 11:47:55 +00001764 addInstr(env, s390_insn_cond_move(size, s390_cc_invert(cc), dst, r0));
sewardj2019a972011-03-07 16:04:07 +00001765 return dst;
1766 }
1767
1768 default:
1769 break;
1770 }
1771
1772 /* We get here if no pattern matched. */
1773 irreducible:
1774 ppIRExpr(expr);
1775 vpanic("s390_isel_int_expr: cannot reduce tree");
1776}
1777
1778
1779static HReg
1780s390_isel_int_expr(ISelEnv *env, IRExpr *expr)
1781{
1782 HReg dst = s390_isel_int_expr_wrk(env, expr);
1783
1784 /* Sanity checks ... */
1785 vassert(hregClass(dst) == HRcInt64);
1786 vassert(hregIsVirtual(dst));
1787
1788 return dst;
1789}
1790
1791
1792static s390_opnd_RMI
1793s390_isel_int_expr_RMI(ISelEnv *env, IRExpr *expr)
1794{
1795 IRType ty = typeOfIRExpr(env->type_env, expr);
1796 s390_opnd_RMI dst;
1797
1798 vassert(ty == Ity_I8 || ty == Ity_I16 || ty == Ity_I32 ||
1799 ty == Ity_I64);
1800
1801 if (expr->tag == Iex_Load) {
1802 dst.tag = S390_OPND_AMODE;
1803 dst.variant.am = s390_isel_amode(env, expr->Iex.Load.addr);
1804 } else if (expr->tag == Iex_Get) {
1805 dst.tag = S390_OPND_AMODE;
1806 dst.variant.am = s390_amode_for_guest_state(expr->Iex.Get.offset);
1807 } else if (expr->tag == Iex_Const) {
1808 ULong value;
1809
1810 /* The bit pattern for the value will be stored as is in the least
1811 significant bits of VALUE. */
1812 switch (expr->Iex.Const.con->tag) {
1813 case Ico_U1: value = expr->Iex.Const.con->Ico.U1; break;
1814 case Ico_U8: value = expr->Iex.Const.con->Ico.U8; break;
1815 case Ico_U16: value = expr->Iex.Const.con->Ico.U16; break;
1816 case Ico_U32: value = expr->Iex.Const.con->Ico.U32; break;
1817 case Ico_U64: value = expr->Iex.Const.con->Ico.U64; break;
1818 default:
1819 vpanic("s390_isel_int_expr_RMI");
1820 }
1821
1822 dst.tag = S390_OPND_IMMEDIATE;
1823 dst.variant.imm = value;
1824 } else {
1825 dst.tag = S390_OPND_REG;
1826 dst.variant.reg = s390_isel_int_expr(env, expr);
1827 }
1828
1829 return dst;
1830}
1831
1832
1833/*---------------------------------------------------------*/
1834/*--- ISEL: Floating point expressions (128 bit) ---*/
1835/*---------------------------------------------------------*/
1836static void
1837s390_isel_float128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
1838 IRExpr *expr)
1839{
1840 IRType ty = typeOfIRExpr(env->type_env, expr);
1841
1842 vassert(ty == Ity_F128);
1843
sewardj2019a972011-03-07 16:04:07 +00001844 switch (expr->tag) {
1845 case Iex_RdTmp:
1846 /* Return the virtual registers that hold the temporary. */
1847 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
1848 return;
1849
1850 /* --------- LOAD --------- */
1851 case Iex_Load: {
1852 IRExpr *addr_hi, *addr_lo;
1853 s390_amode *am_hi, *am_lo;
1854
1855 if (expr->Iex.Load.end != Iend_BE)
1856 goto irreducible;
1857
1858 addr_hi = expr->Iex.Load.addr;
1859 addr_lo = IRExpr_Binop(Iop_Add64, addr_hi, mkU64(8));
1860
1861 am_hi = s390_isel_amode(env, addr_hi);
1862 am_lo = s390_isel_amode(env, addr_lo);
1863
1864 *dst_hi = newVRegF(env);
1865 *dst_lo = newVRegF(env);
1866 addInstr(env, s390_insn_load(8, *dst_hi, am_hi));
1867 addInstr(env, s390_insn_load(8, *dst_hi, am_lo));
1868 return;
1869 }
1870
1871
1872 /* --------- GET --------- */
1873 case Iex_Get:
1874 /* This is not supported because loading 128-bit from the guest
1875 state is almost certainly wrong. Use get_fpr_pair instead. */
1876 vpanic("Iex_Get with F128 data");
1877
1878 /* --------- 4-ary OP --------- */
1879 case Iex_Qop:
1880 vpanic("Iex_Qop with F128 data");
1881
1882 /* --------- TERNARY OP --------- */
1883 case Iex_Triop: {
florian420bfa92012-06-02 20:29:22 +00001884 IRTriop *triop = expr->Iex.Triop.details;
1885 IROp op = triop->op;
1886 IRExpr *left = triop->arg2;
1887 IRExpr *right = triop->arg3;
sewardj2019a972011-03-07 16:04:07 +00001888 s390_bfp_binop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00001889 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15;
1890
1891 s390_isel_float128_expr(&op1_hi, &op1_lo, env, left); /* 1st operand */
1892 s390_isel_float128_expr(&op2_hi, &op2_lo, env, right); /* 2nd operand */
1893
1894 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1895 f12 = make_fpr(12);
1896 f13 = make_fpr(13);
1897 f14 = make_fpr(14);
1898 f15 = make_fpr(15);
1899
1900 /* 1st operand --> (f12, f14) */
1901 addInstr(env, s390_insn_move(8, f12, op1_hi));
1902 addInstr(env, s390_insn_move(8, f14, op1_lo));
1903
1904 /* 2nd operand --> (f13, f15) */
1905 addInstr(env, s390_insn_move(8, f13, op2_hi));
1906 addInstr(env, s390_insn_move(8, f15, op2_lo));
1907
1908 switch (op) {
1909 case Iop_AddF128: bfpop = S390_BFP_ADD; break;
1910 case Iop_SubF128: bfpop = S390_BFP_SUB; break;
1911 case Iop_MulF128: bfpop = S390_BFP_MUL; break;
1912 case Iop_DivF128: bfpop = S390_BFP_DIV; break;
1913 default:
1914 goto irreducible;
1915 }
1916
florian2c74d242012-09-12 19:38:42 +00001917 set_bfp_rounding_mode_in_fpc(env, triop->arg1);
1918 addInstr(env, s390_insn_bfp128_binop(16, bfpop, f12, f14, f13, f15));
sewardj2019a972011-03-07 16:04:07 +00001919
1920 /* Move result to virtual destination register */
1921 *dst_hi = newVRegF(env);
1922 *dst_lo = newVRegF(env);
1923 addInstr(env, s390_insn_move(8, *dst_hi, f12));
1924 addInstr(env, s390_insn_move(8, *dst_lo, f14));
1925
1926 return;
1927 }
1928
1929 /* --------- BINARY OP --------- */
1930 case Iex_Binop: {
1931 HReg op_hi, op_lo, f12, f13, f14, f15;
sewardj2019a972011-03-07 16:04:07 +00001932
1933 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1934 f12 = make_fpr(12);
1935 f13 = make_fpr(13);
1936 f14 = make_fpr(14);
1937 f15 = make_fpr(15);
1938
1939 switch (expr->Iex.Binop.op) {
1940 case Iop_SqrtF128:
1941 s390_isel_float128_expr(&op_hi, &op_lo, env, expr->Iex.Binop.arg2);
1942
1943 /* operand --> (f13, f15) */
1944 addInstr(env, s390_insn_move(8, f13, op_hi));
1945 addInstr(env, s390_insn_move(8, f15, op_lo));
1946
florian2c74d242012-09-12 19:38:42 +00001947 set_bfp_rounding_mode_in_fpc(env, expr->Iex.Binop.arg1);
1948 addInstr(env, s390_insn_bfp128_unop(16, S390_BFP_SQRT, f12, f14,
1949 f13, f15));
sewardj2019a972011-03-07 16:04:07 +00001950
1951 /* Move result to virtual destination registers */
1952 *dst_hi = newVRegF(env);
1953 *dst_lo = newVRegF(env);
1954 addInstr(env, s390_insn_move(8, *dst_hi, f12));
1955 addInstr(env, s390_insn_move(8, *dst_lo, f14));
1956 return;
1957
1958 case Iop_F64HLtoF128:
1959 *dst_hi = s390_isel_float_expr(env, expr->Iex.Binop.arg1);
1960 *dst_lo = s390_isel_float_expr(env, expr->Iex.Binop.arg2);
1961 return;
1962
1963 default:
1964 goto irreducible;
1965 }
1966 }
1967
1968 /* --------- UNARY OP --------- */
1969 case Iex_Unop: {
florian66e596d2012-09-07 15:00:53 +00001970 IRExpr *left = expr->Iex.Unop.arg;
sewardj2019a972011-03-07 16:04:07 +00001971 s390_bfp_unop_t bfpop;
florian6dc90242012-12-21 21:43:00 +00001972 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00001973 HReg op_hi, op_lo, op, f12, f13, f14, f15;
1974
1975 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1976 f12 = make_fpr(12);
1977 f13 = make_fpr(13);
1978 f14 = make_fpr(14);
1979 f15 = make_fpr(15);
1980
florian66e596d2012-09-07 15:00:53 +00001981 switch (expr->Iex.Unop.op) {
florian3f3e50d2012-09-13 03:13:26 +00001982 case Iop_NegF128:
1983 if (left->tag == Iex_Unop &&
1984 (left->Iex.Unop.op == Iop_AbsF32 ||
1985 left->Iex.Unop.op == Iop_AbsF64))
1986 bfpop = S390_BFP_NABS;
1987 else
1988 bfpop = S390_BFP_NEG;
1989 goto float128_opnd;
florian9fcff4c2012-09-10 03:09:04 +00001990 case Iop_AbsF128: bfpop = S390_BFP_ABS; goto float128_opnd;
1991 case Iop_I32StoF128: conv = S390_BFP_I32_TO_F128; goto convert_int;
1992 case Iop_I64StoF128: conv = S390_BFP_I64_TO_F128; goto convert_int;
1993 case Iop_I32UtoF128: conv = S390_BFP_U32_TO_F128; goto convert_int;
1994 case Iop_I64UtoF128: conv = S390_BFP_U64_TO_F128; goto convert_int;
1995 case Iop_F32toF128: conv = S390_BFP_F32_TO_F128; goto convert_float;
1996 case Iop_F64toF128: conv = S390_BFP_F64_TO_F128; goto convert_float;
sewardj2019a972011-03-07 16:04:07 +00001997 default:
1998 goto irreducible;
1999 }
2000
2001 float128_opnd:
2002 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
2003
2004 /* operand --> (f13, f15) */
2005 addInstr(env, s390_insn_move(8, f13, op_hi));
2006 addInstr(env, s390_insn_move(8, f15, op_lo));
2007
florian2c74d242012-09-12 19:38:42 +00002008 addInstr(env, s390_insn_bfp128_unop(16, bfpop, f12, f14, f13, f15));
sewardj2019a972011-03-07 16:04:07 +00002009 goto move_dst;
2010
2011 convert_float:
2012 op = s390_isel_float_expr(env, left);
florian9fcff4c2012-09-10 03:09:04 +00002013 addInstr(env, s390_insn_bfp128_convert_to(16, conv, f12, f14, op));
sewardj2019a972011-03-07 16:04:07 +00002014 goto move_dst;
2015
2016 convert_int:
2017 op = s390_isel_int_expr(env, left);
florian9fcff4c2012-09-10 03:09:04 +00002018 addInstr(env, s390_insn_bfp128_convert_to(16, conv, f12, f14, op));
sewardj2019a972011-03-07 16:04:07 +00002019 goto move_dst;
2020
2021 move_dst:
2022 /* Move result to virtual destination registers */
2023 *dst_hi = newVRegF(env);
2024 *dst_lo = newVRegF(env);
2025 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2026 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2027 return;
2028 }
2029
2030 default:
2031 goto irreducible;
2032 }
2033
2034 /* We get here if no pattern matched. */
2035 irreducible:
2036 ppIRExpr(expr);
florian4ebaa772012-12-20 19:44:18 +00002037 vpanic("s390_isel_float128_expr: cannot reduce tree");
sewardj2019a972011-03-07 16:04:07 +00002038}
2039
2040/* Compute a 128-bit value into two 64-bit registers. These may be either
2041 real or virtual regs; in any case they must not be changed by subsequent
2042 code emitted by the caller. */
2043static void
2044s390_isel_float128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
2045{
2046 s390_isel_float128_expr_wrk(dst_hi, dst_lo, env, expr);
2047
2048 /* Sanity checks ... */
2049 vassert(hregIsVirtual(*dst_hi));
2050 vassert(hregIsVirtual(*dst_lo));
2051 vassert(hregClass(*dst_hi) == HRcFlt64);
2052 vassert(hregClass(*dst_lo) == HRcFlt64);
2053}
2054
2055
2056/*---------------------------------------------------------*/
2057/*--- ISEL: Floating point expressions (64 bit) ---*/
2058/*---------------------------------------------------------*/
2059
2060static HReg
2061s390_isel_float_expr_wrk(ISelEnv *env, IRExpr *expr)
2062{
2063 IRType ty = typeOfIRExpr(env->type_env, expr);
2064 UChar size;
2065
2066 vassert(ty == Ity_F32 || ty == Ity_F64);
2067
2068 size = sizeofIRType(ty);
2069
2070 switch (expr->tag) {
2071 case Iex_RdTmp:
2072 /* Return the virtual register that holds the temporary. */
2073 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
2074
2075 /* --------- LOAD --------- */
2076 case Iex_Load: {
2077 HReg dst = newVRegF(env);
2078 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
2079
2080 if (expr->Iex.Load.end != Iend_BE)
2081 goto irreducible;
2082
2083 addInstr(env, s390_insn_load(size, dst, am));
2084
2085 return dst;
2086 }
2087
2088 /* --------- GET --------- */
2089 case Iex_Get: {
2090 HReg dst = newVRegF(env);
2091 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
2092
2093 addInstr(env, s390_insn_load(size, dst, am));
2094
2095 return dst;
2096 }
2097
2098 /* --------- LITERAL --------- */
2099
2100 /* Load a literal into a register. Create a "load immediate"
2101 v-insn and return the register. */
2102 case Iex_Const: {
2103 ULong value;
2104 HReg dst = newVRegF(env);
2105 const IRConst *con = expr->Iex.Const.con;
2106
2107 /* Bitwise copy of the value. No sign/zero-extension */
2108 switch (con->tag) {
2109 case Ico_F32i: value = con->Ico.F32i; break;
2110 case Ico_F64i: value = con->Ico.F64i; break;
2111 default: vpanic("s390_isel_float_expr: invalid constant");
2112 }
2113
2114 if (value != 0) vpanic("cannot load immediate floating point constant");
2115
2116 addInstr(env, s390_insn_load_immediate(size, dst, value));
2117
2118 return dst;
2119 }
2120
2121 /* --------- 4-ary OP --------- */
2122 case Iex_Qop: {
2123 HReg op1, op2, op3, dst;
2124 s390_bfp_triop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002125
florian5906a6b2012-10-16 02:53:33 +00002126 op3 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg2);
florian96d7cc32012-06-01 20:41:24 +00002127 op2 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg3);
florian5906a6b2012-10-16 02:53:33 +00002128 op1 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg4);
sewardj2019a972011-03-07 16:04:07 +00002129 dst = newVRegF(env);
2130 addInstr(env, s390_insn_move(size, dst, op1));
2131
florian96d7cc32012-06-01 20:41:24 +00002132 switch (expr->Iex.Qop.details->op) {
sewardj2019a972011-03-07 16:04:07 +00002133 case Iop_MAddF32:
2134 case Iop_MAddF64: bfpop = S390_BFP_MADD; break;
2135 case Iop_MSubF32:
2136 case Iop_MSubF64: bfpop = S390_BFP_MSUB; break;
2137
2138 default:
2139 goto irreducible;
2140 }
2141
florian2c74d242012-09-12 19:38:42 +00002142 set_bfp_rounding_mode_in_fpc(env, expr->Iex.Qop.details->arg1);
2143 addInstr(env, s390_insn_bfp_triop(size, bfpop, dst, op2, op3));
sewardj2019a972011-03-07 16:04:07 +00002144 return dst;
2145 }
2146
2147 /* --------- TERNARY OP --------- */
2148 case Iex_Triop: {
florian420bfa92012-06-02 20:29:22 +00002149 IRTriop *triop = expr->Iex.Triop.details;
2150 IROp op = triop->op;
2151 IRExpr *left = triop->arg2;
2152 IRExpr *right = triop->arg3;
sewardj2019a972011-03-07 16:04:07 +00002153 s390_bfp_binop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002154 HReg h1, op2, dst;
2155
2156 h1 = s390_isel_float_expr(env, left); /* Process 1st operand */
2157 op2 = s390_isel_float_expr(env, right); /* Process 2nd operand */
2158 dst = newVRegF(env);
2159 addInstr(env, s390_insn_move(size, dst, h1));
2160 switch (op) {
2161 case Iop_AddF32:
2162 case Iop_AddF64: bfpop = S390_BFP_ADD; break;
2163 case Iop_SubF32:
2164 case Iop_SubF64: bfpop = S390_BFP_SUB; break;
2165 case Iop_MulF32:
2166 case Iop_MulF64: bfpop = S390_BFP_MUL; break;
2167 case Iop_DivF32:
2168 case Iop_DivF64: bfpop = S390_BFP_DIV; break;
2169
2170 default:
2171 goto irreducible;
2172 }
2173
florian2c74d242012-09-12 19:38:42 +00002174 set_bfp_rounding_mode_in_fpc(env, triop->arg1);
2175 addInstr(env, s390_insn_bfp_binop(size, bfpop, dst, op2));
sewardj2019a972011-03-07 16:04:07 +00002176 return dst;
2177 }
2178
2179 /* --------- BINARY OP --------- */
2180 case Iex_Binop: {
2181 IROp op = expr->Iex.Binop.op;
florian9fcff4c2012-09-10 03:09:04 +00002182 IRExpr *irrm = expr->Iex.Binop.arg1;
sewardj2019a972011-03-07 16:04:07 +00002183 IRExpr *left = expr->Iex.Binop.arg2;
2184 HReg h1, dst;
florian6dc90242012-12-21 21:43:00 +00002185 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00002186
2187 switch (op) {
2188 case Iop_SqrtF32:
2189 case Iop_SqrtF64:
florian9fcff4c2012-09-10 03:09:04 +00002190 h1 = s390_isel_float_expr(env, left);
2191 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002192 set_bfp_rounding_mode_in_fpc(env, irrm);
2193 addInstr(env, s390_insn_bfp_unop(size, S390_BFP_SQRT, dst, h1));
florian9fcff4c2012-09-10 03:09:04 +00002194 return dst;
sewardj2019a972011-03-07 16:04:07 +00002195
florian9fcff4c2012-09-10 03:09:04 +00002196 case Iop_F64toF32: conv = S390_BFP_F64_TO_F32; goto convert_float;
2197 case Iop_I32StoF32: conv = S390_BFP_I32_TO_F32; goto convert_int;
2198 case Iop_I32UtoF32: conv = S390_BFP_U32_TO_F32; goto convert_int;
2199 case Iop_I64StoF32: conv = S390_BFP_I64_TO_F32; goto convert_int;
2200 case Iop_I64StoF64: conv = S390_BFP_I64_TO_F64; goto convert_int;
2201 case Iop_I64UtoF32: conv = S390_BFP_U64_TO_F32; goto convert_int;
2202 case Iop_I64UtoF64: conv = S390_BFP_U64_TO_F64; goto convert_int;
sewardj2019a972011-03-07 16:04:07 +00002203
florian9fcff4c2012-09-10 03:09:04 +00002204 convert_float:
2205 h1 = s390_isel_float_expr(env, left);
2206 goto convert;
florian1c8f7ff2012-09-01 00:12:11 +00002207
florian9fcff4c2012-09-10 03:09:04 +00002208 convert_int:
2209 h1 = s390_isel_int_expr(env, left);
2210 goto convert;
2211
florian2c74d242012-09-12 19:38:42 +00002212 convert: {
florian125e20d2012-10-07 15:42:37 +00002213 s390_bfp_round_t rounding_mode;
florian2c74d242012-09-12 19:38:42 +00002214 /* convert-from-fixed and load-rounded have a rounding mode field
2215 when the floating point extension facility is installed. */
florian9fcff4c2012-09-10 03:09:04 +00002216 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002217 if (s390_host_has_fpext) {
2218 rounding_mode = get_bfp_rounding_mode(env, irrm);
2219 } else {
2220 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +00002221 rounding_mode = S390_BFP_ROUND_PER_FPC;
florian2c74d242012-09-12 19:38:42 +00002222 }
florian9fcff4c2012-09-10 03:09:04 +00002223 addInstr(env, s390_insn_bfp_convert(size, conv, dst, h1,
2224 rounding_mode));
2225 return dst;
florian2c74d242012-09-12 19:38:42 +00002226 }
florian9fcff4c2012-09-10 03:09:04 +00002227
sewardj2019a972011-03-07 16:04:07 +00002228 default:
2229 goto irreducible;
2230
2231 case Iop_F128toF64:
2232 case Iop_F128toF32: {
florian9fcff4c2012-09-10 03:09:04 +00002233 HReg op_hi, op_lo, f13, f15;
florian125e20d2012-10-07 15:42:37 +00002234 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00002235
florian9fcff4c2012-09-10 03:09:04 +00002236 conv = op == Iop_F128toF32 ? S390_BFP_F128_TO_F32
2237 : S390_BFP_F128_TO_F64;
sewardj2019a972011-03-07 16:04:07 +00002238
florian9fcff4c2012-09-10 03:09:04 +00002239 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
sewardj2019a972011-03-07 16:04:07 +00002240
florian9fcff4c2012-09-10 03:09:04 +00002241 /* We use non-virtual registers as pairs (f13, f15) */
sewardj2019a972011-03-07 16:04:07 +00002242 f13 = make_fpr(13);
sewardj2019a972011-03-07 16:04:07 +00002243 f15 = make_fpr(15);
2244
2245 /* operand --> (f13, f15) */
2246 addInstr(env, s390_insn_move(8, f13, op_hi));
2247 addInstr(env, s390_insn_move(8, f15, op_lo));
2248
2249 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002250 /* load-rounded has a rounding mode field when the floating point
2251 extension facility is installed. */
2252 if (s390_host_has_fpext) {
2253 rounding_mode = get_bfp_rounding_mode(env, irrm);
2254 } else {
2255 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +00002256 rounding_mode = S390_BFP_ROUND_PER_FPC;
florian2c74d242012-09-12 19:38:42 +00002257 }
floriancc491a62012-09-10 23:44:37 +00002258 addInstr(env, s390_insn_bfp128_convert_from(size, conv, dst, f13, f15,
florian9fcff4c2012-09-10 03:09:04 +00002259 rounding_mode));
sewardj2019a972011-03-07 16:04:07 +00002260 return dst;
2261 }
2262 }
sewardj2019a972011-03-07 16:04:07 +00002263 }
2264
2265 /* --------- UNARY OP --------- */
2266 case Iex_Unop: {
2267 IROp op = expr->Iex.Unop.op;
2268 IRExpr *left = expr->Iex.Unop.arg;
2269 s390_bfp_unop_t bfpop;
florian6dc90242012-12-21 21:43:00 +00002270 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00002271 HReg h1, dst;
2272
2273 if (op == Iop_F128HItoF64 || op == Iop_F128LOtoF64) {
2274 HReg dst_hi, dst_lo;
2275
2276 s390_isel_float128_expr(&dst_hi, &dst_lo, env, left);
2277 return op == Iop_F128LOtoF64 ? dst_lo : dst_hi;
2278 }
2279
florian4d71a082011-12-18 00:08:17 +00002280 if (op == Iop_ReinterpI64asF64 || op == Iop_ReinterpI32asF32) {
sewardj2019a972011-03-07 16:04:07 +00002281 dst = newVRegF(env);
2282 h1 = s390_isel_int_expr(env, left); /* Process the operand */
2283 addInstr(env, s390_insn_move(size, dst, h1));
2284
2285 return dst;
2286 }
2287
2288 switch (op) {
2289 case Iop_NegF32:
2290 case Iop_NegF64:
2291 if (left->tag == Iex_Unop &&
florian3f3e50d2012-09-13 03:13:26 +00002292 (left->Iex.Unop.op == Iop_AbsF32 ||
2293 left->Iex.Unop.op == Iop_AbsF64))
sewardj2019a972011-03-07 16:04:07 +00002294 bfpop = S390_BFP_NABS;
2295 else
2296 bfpop = S390_BFP_NEG;
2297 break;
2298
2299 case Iop_AbsF32:
florian9fcff4c2012-09-10 03:09:04 +00002300 case Iop_AbsF64:
2301 bfpop = S390_BFP_ABS;
2302 break;
2303
2304 case Iop_I32StoF64: conv = S390_BFP_I32_TO_F64; goto convert_int1;
2305 case Iop_I32UtoF64: conv = S390_BFP_U32_TO_F64; goto convert_int1;
2306 case Iop_F32toF64: conv = S390_BFP_F32_TO_F64; goto convert_float1;
2307
2308 convert_float1:
2309 h1 = s390_isel_float_expr(env, left);
2310 goto convert1;
2311
2312 convert_int1:
2313 h1 = s390_isel_int_expr(env, left);
2314 goto convert1;
2315
2316 convert1:
2317 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002318 /* No rounding mode is needed for these conversions. Just stick
2319 one in. It won't be used later on. */
2320 addInstr(env, s390_insn_bfp_convert(size, conv, dst, h1,
florian125e20d2012-10-07 15:42:37 +00002321 S390_BFP_ROUND_NEAREST_EVEN));
florian9fcff4c2012-09-10 03:09:04 +00002322 return dst;
2323
sewardj2019a972011-03-07 16:04:07 +00002324 default:
2325 goto irreducible;
2326 }
2327
2328 /* Process operand */
florian9fcff4c2012-09-10 03:09:04 +00002329 h1 = s390_isel_float_expr(env, left);
sewardj2019a972011-03-07 16:04:07 +00002330 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002331 addInstr(env, s390_insn_bfp_unop(size, bfpop, dst, h1));
sewardj2019a972011-03-07 16:04:07 +00002332 return dst;
2333 }
2334
2335 default:
2336 goto irreducible;
2337 }
2338
2339 /* We get here if no pattern matched. */
2340 irreducible:
2341 ppIRExpr(expr);
2342 vpanic("s390_isel_float_expr: cannot reduce tree");
2343}
2344
2345
2346static HReg
2347s390_isel_float_expr(ISelEnv *env, IRExpr *expr)
2348{
2349 HReg dst = s390_isel_float_expr_wrk(env, expr);
2350
2351 /* Sanity checks ... */
2352 vassert(hregClass(dst) == HRcFlt64);
2353 vassert(hregIsVirtual(dst));
2354
2355 return dst;
2356}
2357
2358
2359/*---------------------------------------------------------*/
floriane38f6412012-12-21 17:32:12 +00002360/*--- ISEL: Decimal point expressions (128 bit) ---*/
2361/*---------------------------------------------------------*/
2362static void
2363s390_isel_dfp128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
2364 IRExpr *expr)
2365{
2366 IRType ty = typeOfIRExpr(env->type_env, expr);
2367
2368 vassert(ty == Ity_D128);
2369
2370 switch (expr->tag) {
2371 case Iex_RdTmp:
2372 /* Return the virtual registers that hold the temporary. */
2373 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
2374 return;
2375
2376 /* --------- LOAD --------- */
2377 case Iex_Load: {
2378 IRExpr *addr_hi, *addr_lo;
2379 s390_amode *am_hi, *am_lo;
2380
2381 if (expr->Iex.Load.end != Iend_BE)
2382 goto irreducible;
2383
2384 addr_hi = expr->Iex.Load.addr;
2385 addr_lo = IRExpr_Binop(Iop_Add64, addr_hi, mkU64(8));
2386
2387 am_hi = s390_isel_amode(env, addr_hi);
2388 am_lo = s390_isel_amode(env, addr_lo);
2389
2390 *dst_hi = newVRegF(env);
2391 *dst_lo = newVRegF(env);
2392 addInstr(env, s390_insn_load(8, *dst_hi, am_hi));
2393 addInstr(env, s390_insn_load(8, *dst_hi, am_lo));
2394 return;
2395 }
2396
2397 /* --------- GET --------- */
2398 case Iex_Get:
2399 /* This is not supported because loading 128-bit from the guest
2400 state is almost certainly wrong. Use get_dpr_pair instead. */
2401 vpanic("Iex_Get with D128 data");
2402
2403 /* --------- 4-ary OP --------- */
2404 case Iex_Qop:
2405 vpanic("Iex_Qop with D128 data");
2406
2407 /* --------- TERNARY OP --------- */
2408 case Iex_Triop: {
2409 IRTriop *triop = expr->Iex.Triop.details;
2410 IROp op = triop->op;
2411 IRExpr *irrm = triop->arg1;
2412 IRExpr *left = triop->arg2;
2413 IRExpr *right = triop->arg3;
2414 s390_dfp_round_t rounding_mode;
2415 s390_dfp_binop_t dfpop;
2416 HReg op1_hi, op1_lo, op2_hi, op2_lo, f9, f11, f12, f13, f14, f15;
2417
2418 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, left); /* 1st operand */
2419 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, right); /* 2nd operand */
2420
2421 /* We use non-virtual registers as pairs with (f9, f11) as op1,
2422 (f12, f14) as op2 and (f13, f15) as destination) */
2423 f9 = make_fpr(9);
2424 f11 = make_fpr(11);
2425 f12 = make_fpr(12);
2426 f13 = make_fpr(13);
2427 f14 = make_fpr(14);
2428 f15 = make_fpr(15);
2429
2430 /* 1st operand --> (f9, f11) */
2431 addInstr(env, s390_insn_move(8, f9, op1_hi));
2432 addInstr(env, s390_insn_move(8, f11, op1_lo));
2433
2434 /* 2nd operand --> (f12, f14) */
2435 addInstr(env, s390_insn_move(8, f12, op2_hi));
2436 addInstr(env, s390_insn_move(8, f14, op2_lo));
2437
2438 switch (op) {
2439 case Iop_AddD128: dfpop = S390_DFP_ADD; break;
2440 case Iop_SubD128: dfpop = S390_DFP_SUB; break;
2441 case Iop_MulD128: dfpop = S390_DFP_MUL; break;
2442 case Iop_DivD128: dfpop = S390_DFP_DIV; break;
2443 default:
2444 goto irreducible;
2445 }
2446
2447 /* DFP binary ops have insns with rounding mode field
2448 when the floating point extension facility is installed. */
2449 if (s390_host_has_fpext) {
2450 rounding_mode = get_dfp_rounding_mode(env, irrm);
2451 } else {
2452 set_dfp_rounding_mode_in_fpc(env, irrm);
2453 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2454 }
2455
2456 addInstr(env, s390_insn_dfp128_binop(16, dfpop, f13, f15, f9, f11,
2457 f12, f14, rounding_mode));
2458
2459 /* Move result to virtual destination register */
2460 *dst_hi = newVRegF(env);
2461 *dst_lo = newVRegF(env);
2462 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2463 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2464
2465 return;
2466 }
2467
2468 /* --------- BINARY OP --------- */
2469 case Iex_Binop: {
florian1b901d42013-01-01 22:19:24 +00002470
floriane38f6412012-12-21 17:32:12 +00002471 switch (expr->Iex.Binop.op) {
2472 case Iop_D64HLtoD128:
2473 *dst_hi = s390_isel_dfp_expr(env, expr->Iex.Binop.arg1);
2474 *dst_lo = s390_isel_dfp_expr(env, expr->Iex.Binop.arg2);
2475 return;
2476
florian1b901d42013-01-01 22:19:24 +00002477 case Iop_ShlD128:
2478 case Iop_ShrD128: {
2479 HReg op1_hi, op1_lo, op2, f9, f11, f13, f15;
2480 s390_dfp_intop_t intop;
2481 IRExpr *left = expr->Iex.Binop.arg1;
2482 IRExpr *right = expr->Iex.Binop.arg2;
2483
2484 switch (expr->Iex.Binop.op) {
2485 case Iop_ShlD128: intop = S390_DFP_SHIFT_LEFT; break;
2486 case Iop_ShrD128: intop = S390_DFP_SHIFT_RIGHT; break;
2487 default: goto irreducible;
2488 }
2489
2490 /* We use non-virtual registers as pairs (f9, f11) and (f13, f15)) */
2491 f9 = make_fpr(9); /* 128 bit dfp operand */
2492 f11 = make_fpr(11);
2493
2494 f13 = make_fpr(13); /* 128 bit dfp destination */
2495 f15 = make_fpr(15);
2496
2497 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, left); /* dfp operand */
2498 addInstr(env, s390_insn_move(8, f9, op1_hi));
2499 addInstr(env, s390_insn_move(8, f11, op1_lo));
2500
2501 op2 = s390_isel_int_expr(env, right); /* int operand */
2502
2503 addInstr(env,
2504 s390_insn_dfp128_intop(16, intop, f13, f15, op2, f9, f11));
2505
2506 /* Move result to virtual destination register */
2507 *dst_hi = newVRegF(env);
2508 *dst_lo = newVRegF(env);
2509 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2510 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2511 return;
2512 }
2513
floriane38f6412012-12-21 17:32:12 +00002514 default:
2515 goto irreducible;
2516 }
2517 }
2518
2519 /* --------- UNARY OP --------- */
2520 case Iex_Unop: {
2521 IRExpr *left = expr->Iex.Unop.arg;
2522 s390_dfp_conv_t conv;
2523 // HReg op, f12, f13, f14, f15;
2524 HReg op, f12, f14;
2525
2526 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
2527 f12 = make_fpr(12);
2528 // f13 = make_fpr(13);
2529 f14 = make_fpr(14);
2530 // f15 = make_fpr(15);
2531
2532 switch (expr->Iex.Unop.op) {
2533 case Iop_D64toD128: conv = S390_DFP_D64_TO_D128; goto convert_dfp;
florian5f034622013-01-13 02:29:05 +00002534 case Iop_I32StoD128: conv = S390_DFP_I32_TO_D128; goto convert_int;
2535 case Iop_I32UtoD128: conv = S390_DFP_U32_TO_D128; goto convert_int;
2536 case Iop_I64UtoD128: conv = S390_DFP_U64_TO_D128; goto convert_int;
floriane38f6412012-12-21 17:32:12 +00002537 default:
2538 goto irreducible;
2539 }
2540
2541 convert_dfp:
2542 op = s390_isel_dfp_expr(env, left);
2543 addInstr(env, s390_insn_dfp128_convert_to(16, conv, f12, f14, op));
2544 goto move_dst;
2545
florian5f034622013-01-13 02:29:05 +00002546 convert_int:
2547 op = s390_isel_int_expr(env, left);
2548 addInstr(env, s390_insn_dfp128_convert_to(16, conv, f12, f14, op));
2549 goto move_dst;
2550
floriane38f6412012-12-21 17:32:12 +00002551 move_dst:
2552 /* Move result to virtual destination registers */
2553 *dst_hi = newVRegF(env);
2554 *dst_lo = newVRegF(env);
2555 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2556 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2557 return;
2558 }
2559
2560 default:
2561 goto irreducible;
2562 }
2563
2564 /* We get here if no pattern matched. */
2565 irreducible:
2566 ppIRExpr(expr);
2567 vpanic("s390_isel_dfp128_expr_wrk: cannot reduce tree");
2568
2569}
2570
2571
2572/* Compute a 128-bit value into two 64-bit registers. These may be either
2573 real or virtual regs; in any case they must not be changed by subsequent
2574 code emitted by the caller. */
2575static void
2576s390_isel_dfp128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
2577{
2578 s390_isel_dfp128_expr_wrk(dst_hi, dst_lo, env, expr);
2579
2580 /* Sanity checks ... */
2581 vassert(hregIsVirtual(*dst_hi));
2582 vassert(hregIsVirtual(*dst_lo));
2583 vassert(hregClass(*dst_hi) == HRcFlt64);
2584 vassert(hregClass(*dst_lo) == HRcFlt64);
2585}
2586
2587
2588/*---------------------------------------------------------*/
florian12390202012-11-10 22:34:14 +00002589/*--- ISEL: Decimal point expressions (64 bit) ---*/
2590/*---------------------------------------------------------*/
2591
2592static HReg
2593s390_isel_dfp_expr_wrk(ISelEnv *env, IRExpr *expr)
2594{
2595 IRType ty = typeOfIRExpr(env->type_env, expr);
2596 UChar size;
2597
floriane38f6412012-12-21 17:32:12 +00002598 vassert(ty == Ity_D64 || ty == Ity_D32);
florian12390202012-11-10 22:34:14 +00002599
2600 size = sizeofIRType(ty);
2601
2602 switch (expr->tag) {
2603 case Iex_RdTmp:
2604 /* Return the virtual register that holds the temporary. */
2605 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
2606
2607 /* --------- LOAD --------- */
2608 case Iex_Load: {
2609 HReg dst = newVRegF(env);
2610 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
2611
2612 if (expr->Iex.Load.end != Iend_BE)
2613 goto irreducible;
2614
2615 addInstr(env, s390_insn_load(size, dst, am));
2616
2617 return dst;
2618 }
2619
2620 /* --------- GET --------- */
2621 case Iex_Get: {
2622 HReg dst = newVRegF(env);
2623 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
2624
2625 addInstr(env, s390_insn_load(size, dst, am));
2626
2627 return dst;
2628 }
2629
floriane38f6412012-12-21 17:32:12 +00002630 /* --------- BINARY OP --------- */
2631 case Iex_Binop: {
2632 IROp op = expr->Iex.Binop.op;
2633 IRExpr *irrm = expr->Iex.Binop.arg1;
2634 IRExpr *left = expr->Iex.Binop.arg2;
2635 HReg h1, dst;
2636 s390_dfp_conv_t conv;
2637
2638 switch (op) {
2639 case Iop_D64toD32: conv = S390_DFP_D64_TO_D32; goto convert_dfp;
florian5f034622013-01-13 02:29:05 +00002640 case Iop_I64UtoD64: conv = S390_DFP_U64_TO_D64; goto convert_int;
floriane38f6412012-12-21 17:32:12 +00002641
2642 convert_dfp:
2643 h1 = s390_isel_dfp_expr(env, left);
2644 goto convert;
2645
florian5f034622013-01-13 02:29:05 +00002646 convert_int:
2647 h1 = s390_isel_int_expr(env, left);
2648 goto convert;
2649
floriane38f6412012-12-21 17:32:12 +00002650 convert: {
2651 s390_dfp_round_t rounding_mode;
2652 /* convert-from-fixed and load-rounded have a rounding mode field
2653 when the floating point extension facility is installed. */
2654 dst = newVRegF(env);
2655 if (s390_host_has_fpext) {
2656 rounding_mode = get_dfp_rounding_mode(env, irrm);
2657 } else {
2658 set_dfp_rounding_mode_in_fpc(env, irrm);
2659 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2660 }
2661 addInstr(env, s390_insn_dfp_convert(size, conv, dst, h1,
2662 rounding_mode));
2663 return dst;
2664 }
floriane38f6412012-12-21 17:32:12 +00002665
2666 case Iop_D128toD64: {
2667 HReg op_hi, op_lo, f13, f15;
2668 s390_dfp_round_t rounding_mode;
2669
2670 conv = S390_DFP_D128_TO_D64;
2671
2672 s390_isel_dfp128_expr(&op_hi, &op_lo, env, left);
2673
2674 /* We use non-virtual registers as pairs (f13, f15) */
2675 f13 = make_fpr(13);
2676 f15 = make_fpr(15);
2677
2678 /* operand --> (f13, f15) */
2679 addInstr(env, s390_insn_move(8, f13, op_hi));
2680 addInstr(env, s390_insn_move(8, f15, op_lo));
2681
2682 dst = newVRegF(env);
2683 /* load-rounded has a rounding mode field when the floating point
2684 extension facility is installed. */
2685 if (s390_host_has_fpext) {
2686 rounding_mode = get_dfp_rounding_mode(env, irrm);
2687 } else {
2688 set_dfp_rounding_mode_in_fpc(env, irrm);
2689 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2690 }
2691 addInstr(env, s390_insn_dfp128_convert_from(size, conv, dst, f13, f15,
2692 rounding_mode));
2693 return dst;
2694 }
2695
florian1b901d42013-01-01 22:19:24 +00002696 case Iop_ShlD64:
2697 case Iop_ShrD64: {
2698 HReg op2;
2699 HReg op3;
2700 s390_dfp_intop_t intop;
2701 IRExpr *op1 = expr->Iex.Binop.arg1;
2702 IRExpr *shift = expr->Iex.Binop.arg2;
2703
2704 switch (expr->Iex.Binop.op) {
2705 case Iop_ShlD64: intop = S390_DFP_SHIFT_LEFT; break;
2706 case Iop_ShrD64: intop = S390_DFP_SHIFT_RIGHT; break;
2707 default: goto irreducible;
2708 }
2709
2710 op2 = s390_isel_int_expr(env, shift);
2711 op3 = s390_isel_dfp_expr(env, op1);
2712 dst = newVRegF(env);
2713
2714 addInstr(env, s390_insn_dfp_intop(size, intop, dst, op2, op3));
2715 return dst;
2716 }
2717
2718 default:
2719 goto irreducible;
floriane38f6412012-12-21 17:32:12 +00002720 }
2721 }
2722
2723 /* --------- UNARY OP --------- */
2724 case Iex_Unop: {
2725 IROp op = expr->Iex.Unop.op;
2726 IRExpr *left = expr->Iex.Unop.arg;
2727 s390_dfp_conv_t conv;
2728 HReg h1, dst;
2729
2730 if (op == Iop_D128HItoD64 || op == Iop_D128LOtoD64) {
2731 HReg dst_hi, dst_lo;
2732
2733 s390_isel_dfp128_expr(&dst_hi, &dst_lo, env, left);
2734 return op == Iop_D128LOtoD64 ? dst_lo : dst_hi;
2735 }
2736
2737 if (op == Iop_ReinterpI64asD64) {
2738 dst = newVRegF(env);
2739 h1 = s390_isel_int_expr(env, left); /* Process the operand */
2740 addInstr(env, s390_insn_move(size, dst, h1));
2741
2742 return dst;
2743 }
2744
2745 switch (op) {
2746 case Iop_D32toD64: conv = S390_DFP_D32_TO_D64; goto convert_dfp1;
florian5f034622013-01-13 02:29:05 +00002747 case Iop_I32StoD64: conv = S390_DFP_I32_TO_D64; goto convert_int1;
2748 case Iop_I32UtoD64: conv = S390_DFP_U32_TO_D64; goto convert_int1;
floriane38f6412012-12-21 17:32:12 +00002749
2750 convert_dfp1:
2751 h1 = s390_isel_dfp_expr(env, left);
2752 goto convert1;
2753
florian5f034622013-01-13 02:29:05 +00002754 convert_int1:
2755 h1 = s390_isel_int_expr(env, left);
2756 goto convert1;
2757
floriane38f6412012-12-21 17:32:12 +00002758 convert1:
2759 dst = newVRegF(env);
2760 /* No rounding mode is needed for these conversions. Just stick
2761 one in. It won't be used later on. */
2762 addInstr(env, s390_insn_dfp_convert(size, conv, dst, h1,
2763 S390_DFP_ROUND_NEAREST_EVEN_4));
2764 return dst;
2765
2766 default:
2767 goto irreducible;
2768 }
2769 }
2770
florian12390202012-11-10 22:34:14 +00002771 /* --------- TERNARY OP --------- */
2772 case Iex_Triop: {
2773 IRTriop *triop = expr->Iex.Triop.details;
2774 IROp op = triop->op;
2775 IRExpr *irrm = triop->arg1;
2776 IRExpr *left = triop->arg2;
2777 IRExpr *right = triop->arg3;
2778 s390_dfp_round_t rounding_mode;
2779 s390_dfp_binop_t dfpop;
2780 HReg op2, op3, dst;
2781
2782 op2 = s390_isel_dfp_expr(env, left); /* Process 1st operand */
2783 op3 = s390_isel_dfp_expr(env, right); /* Process 2nd operand */
2784 dst = newVRegF(env);
2785 switch (op) {
2786 case Iop_AddD64: dfpop = S390_DFP_ADD; break;
2787 case Iop_SubD64: dfpop = S390_DFP_SUB; break;
2788 case Iop_MulD64: dfpop = S390_DFP_MUL; break;
2789 case Iop_DivD64: dfpop = S390_DFP_DIV; break;
2790 default:
2791 goto irreducible;
2792 }
2793 /* DFP binary ops have insns with rounding mode field
2794 when the floating point extension facility is installed. */
2795 if (s390_host_has_fpext) {
2796 rounding_mode = get_dfp_rounding_mode(env, irrm);
2797 } else {
2798 set_dfp_rounding_mode_in_fpc(env, irrm);
2799 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2800 }
2801
2802 addInstr(env,
2803 s390_insn_dfp_binop(size, dfpop, dst, op2, op3, rounding_mode));
2804 return dst;
2805 }
2806
2807 default:
2808 goto irreducible;
2809 }
2810
2811 /* We get here if no pattern matched. */
2812 irreducible:
2813 ppIRExpr(expr);
2814 vpanic("s390_isel_dfp_expr: cannot reduce tree");
2815}
2816
2817static HReg
2818s390_isel_dfp_expr(ISelEnv *env, IRExpr *expr)
2819{
2820 HReg dst = s390_isel_dfp_expr_wrk(env, expr);
2821
2822 /* Sanity checks ... */
2823 vassert(hregClass(dst) == HRcFlt64);
2824 vassert(hregIsVirtual(dst));
2825
2826 return dst;
2827}
2828
2829
2830/*---------------------------------------------------------*/
sewardj2019a972011-03-07 16:04:07 +00002831/*--- ISEL: Condition Code ---*/
2832/*---------------------------------------------------------*/
2833
2834/* This function handles all operators that produce a 1-bit result */
2835static s390_cc_t
2836s390_isel_cc(ISelEnv *env, IRExpr *cond)
2837{
2838 UChar size;
2839
2840 vassert(typeOfIRExpr(env->type_env, cond) == Ity_I1);
2841
2842 /* Constant: either 1 or 0 */
2843 if (cond->tag == Iex_Const) {
2844 vassert(cond->Iex.Const.con->tag == Ico_U1);
2845 vassert(cond->Iex.Const.con->Ico.U1 == True
2846 || cond->Iex.Const.con->Ico.U1 == False);
2847
2848 return cond->Iex.Const.con->Ico.U1 == True ? S390_CC_ALWAYS : S390_CC_NEVER;
2849 }
2850
2851 /* Variable: values are 1 or 0 */
2852 if (cond->tag == Iex_RdTmp) {
2853 IRTemp tmp = cond->Iex.RdTmp.tmp;
2854 HReg reg = lookupIRTemp(env, tmp);
2855
2856 /* Load-and-test does not modify REG; so this is OK. */
2857 if (typeOfIRTemp(env->type_env, tmp) == Ity_I1)
2858 size = 4;
2859 else
2860 size = sizeofIRType(typeOfIRTemp(env->type_env, tmp));
2861 addInstr(env, s390_insn_test(size, s390_opnd_reg(reg)));
2862 return S390_CC_NE;
2863 }
2864
2865 /* Unary operators */
2866 if (cond->tag == Iex_Unop) {
2867 IRExpr *arg = cond->Iex.Unop.arg;
2868
2869 switch (cond->Iex.Unop.op) {
2870 case Iop_Not1: /* Not1(cond) */
2871 /* Generate code for EXPR, and negate the test condition */
2872 return s390_cc_invert(s390_isel_cc(env, arg));
2873
2874 /* Iop_32/64to1 select the LSB from their operand */
2875 case Iop_32to1:
2876 case Iop_64to1: {
florianf366a802012-08-03 00:42:18 +00002877 HReg dst = newVRegI(env);
2878 HReg h1 = s390_isel_int_expr(env, arg);
sewardj2019a972011-03-07 16:04:07 +00002879
2880 size = sizeofIRType(typeOfIRExpr(env->type_env, arg));
2881
florianf366a802012-08-03 00:42:18 +00002882 addInstr(env, s390_insn_move(size, dst, h1));
sewardj2019a972011-03-07 16:04:07 +00002883 addInstr(env, s390_insn_alu(size, S390_ALU_AND, dst, s390_opnd_imm(1)));
2884 addInstr(env, s390_insn_test(size, s390_opnd_reg(dst)));
2885 return S390_CC_NE;
2886 }
2887
2888 case Iop_CmpNEZ8:
2889 case Iop_CmpNEZ16: {
2890 s390_opnd_RMI src;
2891 s390_unop_t op;
2892 HReg dst;
2893
2894 op = (cond->Iex.Unop.op == Iop_CmpNEZ8) ? S390_ZERO_EXTEND_8
2895 : S390_ZERO_EXTEND_16;
2896 dst = newVRegI(env);
2897 src = s390_isel_int_expr_RMI(env, arg);
2898 addInstr(env, s390_insn_unop(4, op, dst, src));
2899 addInstr(env, s390_insn_test(4, s390_opnd_reg(dst)));
2900 return S390_CC_NE;
2901 }
2902
2903 case Iop_CmpNEZ32:
2904 case Iop_CmpNEZ64: {
2905 s390_opnd_RMI src;
2906
2907 src = s390_isel_int_expr_RMI(env, arg);
2908 size = sizeofIRType(typeOfIRExpr(env->type_env, arg));
2909 addInstr(env, s390_insn_test(size, src));
2910 return S390_CC_NE;
2911 }
2912
2913 default:
2914 goto fail;
2915 }
2916 }
2917
2918 /* Binary operators */
2919 if (cond->tag == Iex_Binop) {
2920 IRExpr *arg1 = cond->Iex.Binop.arg1;
2921 IRExpr *arg2 = cond->Iex.Binop.arg2;
2922 HReg reg1, reg2;
2923
2924 size = sizeofIRType(typeOfIRExpr(env->type_env, arg1));
2925
2926 switch (cond->Iex.Binop.op) {
2927 s390_unop_t op;
2928 s390_cc_t result;
2929
2930 case Iop_CmpEQ8:
2931 case Iop_CasCmpEQ8:
2932 op = S390_ZERO_EXTEND_8;
2933 result = S390_CC_E;
2934 goto do_compare_ze;
2935
2936 case Iop_CmpNE8:
2937 case Iop_CasCmpNE8:
2938 op = S390_ZERO_EXTEND_8;
2939 result = S390_CC_NE;
2940 goto do_compare_ze;
2941
2942 case Iop_CmpEQ16:
2943 case Iop_CasCmpEQ16:
2944 op = S390_ZERO_EXTEND_16;
2945 result = S390_CC_E;
2946 goto do_compare_ze;
2947
2948 case Iop_CmpNE16:
2949 case Iop_CasCmpNE16:
2950 op = S390_ZERO_EXTEND_16;
2951 result = S390_CC_NE;
2952 goto do_compare_ze;
2953
2954 do_compare_ze: {
2955 s390_opnd_RMI op1, op2;
2956
2957 op1 = s390_isel_int_expr_RMI(env, arg1);
2958 reg1 = newVRegI(env);
2959 addInstr(env, s390_insn_unop(4, op, reg1, op1));
2960
2961 op2 = s390_isel_int_expr_RMI(env, arg2);
2962 reg2 = newVRegI(env);
2963 addInstr(env, s390_insn_unop(4, op, reg2, op2)); /* zero extend */
2964
2965 op2 = s390_opnd_reg(reg2);
2966 addInstr(env, s390_insn_compare(4, reg1, op2, False));
2967
2968 return result;
2969 }
2970
2971 case Iop_CmpEQ32:
2972 case Iop_CmpEQ64:
2973 case Iop_CasCmpEQ32:
2974 case Iop_CasCmpEQ64:
2975 result = S390_CC_E;
2976 goto do_compare;
2977
2978 case Iop_CmpNE32:
2979 case Iop_CmpNE64:
2980 case Iop_CasCmpNE32:
2981 case Iop_CasCmpNE64:
2982 result = S390_CC_NE;
2983 goto do_compare;
2984
2985 do_compare: {
2986 HReg op1;
2987 s390_opnd_RMI op2;
2988
2989 order_commutative_operands(arg1, arg2);
2990
2991 op1 = s390_isel_int_expr(env, arg1);
2992 op2 = s390_isel_int_expr_RMI(env, arg2);
2993
2994 addInstr(env, s390_insn_compare(size, op1, op2, False));
2995
2996 return result;
2997 }
2998
2999 case Iop_CmpLT32S:
3000 case Iop_CmpLE32S:
3001 case Iop_CmpLT64S:
3002 case Iop_CmpLE64S: {
3003 HReg op1;
3004 s390_opnd_RMI op2;
3005
3006 op1 = s390_isel_int_expr(env, arg1);
3007 op2 = s390_isel_int_expr_RMI(env, arg2);
3008
3009 addInstr(env, s390_insn_compare(size, op1, op2, True));
3010
3011 return (cond->Iex.Binop.op == Iop_CmpLT32S ||
3012 cond->Iex.Binop.op == Iop_CmpLT64S) ? S390_CC_L : S390_CC_LE;
3013 }
3014
3015 case Iop_CmpLT32U:
3016 case Iop_CmpLE32U:
3017 case Iop_CmpLT64U:
3018 case Iop_CmpLE64U: {
3019 HReg op1;
3020 s390_opnd_RMI op2;
3021
3022 op1 = s390_isel_int_expr(env, arg1);
3023 op2 = s390_isel_int_expr_RMI(env, arg2);
3024
3025 addInstr(env, s390_insn_compare(size, op1, op2, False));
3026
3027 return (cond->Iex.Binop.op == Iop_CmpLT32U ||
3028 cond->Iex.Binop.op == Iop_CmpLT64U) ? S390_CC_L : S390_CC_LE;
3029 }
3030
3031 default:
3032 goto fail;
3033 }
3034 }
3035
3036 fail:
3037 ppIRExpr(cond);
3038 vpanic("s390_isel_cc: unexpected operator");
3039}
3040
3041
3042/*---------------------------------------------------------*/
3043/*--- ISEL: Statements ---*/
3044/*---------------------------------------------------------*/
3045
3046static void
3047s390_isel_stmt(ISelEnv *env, IRStmt *stmt)
3048{
3049 if (vex_traceflags & VEX_TRACE_VCODE) {
3050 vex_printf("\n -- ");
3051 ppIRStmt(stmt);
3052 vex_printf("\n");
3053 }
3054
3055 switch (stmt->tag) {
3056
3057 /* --------- STORE --------- */
3058 case Ist_Store: {
3059 IRType tyd = typeOfIRExpr(env->type_env, stmt->Ist.Store.data);
3060 s390_amode *am;
3061 HReg src;
3062
3063 if (stmt->Ist.Store.end != Iend_BE) goto stmt_fail;
3064
3065 am = s390_isel_amode(env, stmt->Ist.Store.addr);
3066
3067 switch (tyd) {
3068 case Ity_I8:
3069 case Ity_I16:
3070 case Ity_I32:
3071 case Ity_I64:
florianf85fe3e2012-12-22 02:28:25 +00003072 /* fixs390: We could check for INSN_MADD here. */
florian09bbba82012-12-11 04:09:43 +00003073 if (am->tag == S390_AMODE_B12 &&
florianb93348d2012-12-27 00:59:43 +00003074 stmt->Ist.Store.data->tag == Iex_Const) {
3075 ULong value =
3076 get_const_value_as_ulong(stmt->Ist.Store.data->Iex.Const.con);
3077 addInstr(env, s390_insn_mimm(sizeofIRType(tyd), am, value));
florian09bbba82012-12-11 04:09:43 +00003078 return;
3079 }
floriancec3a8a2013-02-02 00:16:58 +00003080 /* Check whether we can use a memcpy here. Currently, the restriction
3081 is that both amodes need to be B12, so MVC can be emitted.
3082 We do not consider a store whose data expression is a load because
3083 we don't want to deal with overlapping locations. */
3084 /* store(get) never overlaps*/
3085 if (am->tag == S390_AMODE_B12 &&
3086 stmt->Ist.Store.data->tag == Iex_Get) {
3087 UInt offset = stmt->Ist.Store.data->Iex.Get.offset;
3088 s390_amode *from = s390_amode_for_guest_state(offset);
3089 addInstr(env, s390_insn_memcpy(sizeofIRType(tyd), am, from));
3090 return;
3091 }
3092 /* General case: compile data into a register */
sewardj2019a972011-03-07 16:04:07 +00003093 src = s390_isel_int_expr(env, stmt->Ist.Store.data);
3094 break;
3095
3096 case Ity_F32:
3097 case Ity_F64:
3098 src = s390_isel_float_expr(env, stmt->Ist.Store.data);
3099 break;
3100
florianeb981ae2012-12-21 18:55:03 +00003101 case Ity_D32:
3102 case Ity_D64:
3103 src = s390_isel_dfp_expr(env, stmt->Ist.Store.data);
3104 break;
3105
sewardj2019a972011-03-07 16:04:07 +00003106 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003107 case Ity_D128:
sewardj2019a972011-03-07 16:04:07 +00003108 /* Cannot occur. No such instruction */
floriane38f6412012-12-21 17:32:12 +00003109 vpanic("Ist_Store with 128-bit floating point data");
sewardj2019a972011-03-07 16:04:07 +00003110
3111 default:
3112 goto stmt_fail;
3113 }
3114
3115 addInstr(env, s390_insn_store(sizeofIRType(tyd), am, src));
3116 return;
3117 }
3118
3119 /* --------- PUT --------- */
3120 case Ist_Put: {
3121 IRType tyd = typeOfIRExpr(env->type_env, stmt->Ist.Put.data);
3122 HReg src;
3123 s390_amode *am;
florianad43b3a2012-02-20 15:01:14 +00003124 ULong new_value, old_value, difference;
sewardj2019a972011-03-07 16:04:07 +00003125
florianad43b3a2012-02-20 15:01:14 +00003126 /* Detect updates to certain guest registers. We track the contents
3127 of those registers as long as they contain constants. If the new
3128 constant is either zero or in the 8-bit neighbourhood of the
3129 current value we can use a memory-to-memory insn to do the update. */
3130
3131 Int offset = stmt->Ist.Put.offset;
3132
3133 /* Check necessary conditions:
3134 (1) must be one of the registers we care about
3135 (2) assigned value must be a constant */
3136 Int guest_reg = get_guest_reg(offset);
3137
3138 if (guest_reg == GUEST_UNKNOWN) goto not_special;
3139
florianad43b3a2012-02-20 15:01:14 +00003140 if (stmt->Ist.Put.data->tag != Iex_Const) {
3141 /* Invalidate guest register contents */
3142 env->old_value_valid[guest_reg] = False;
3143 goto not_special;
3144 }
3145
cborntraaf7ad282012-08-08 14:11:33 +00003146 /* We can only handle Ity_I64, but the CC_DEPS field can have floats */
3147 if (tyd != Ity_I64)
3148 goto not_special;
florianad43b3a2012-02-20 15:01:14 +00003149
cborntraaf7ad282012-08-08 14:11:33 +00003150 /* OK. Necessary conditions are satisfied. */
florianad43b3a2012-02-20 15:01:14 +00003151
3152 old_value = env->old_value[guest_reg];
3153 new_value = stmt->Ist.Put.data->Iex.Const.con->Ico.U64;
3154 env->old_value[guest_reg] = new_value;
3155
3156 Bool old_value_is_valid = env->old_value_valid[guest_reg];
3157 env->old_value_valid[guest_reg] = True;
3158
3159 /* If the register already contains the new value, there is nothing
florian9f42ab42012-12-23 01:09:16 +00003160 to do here. */
florianad43b3a2012-02-20 15:01:14 +00003161 if (old_value_is_valid && new_value == old_value) {
florian9f42ab42012-12-23 01:09:16 +00003162 return;
florianad43b3a2012-02-20 15:01:14 +00003163 }
3164
florianad43b3a2012-02-20 15:01:14 +00003165 if (old_value_is_valid == False) goto not_special;
3166
3167 /* If the new value is in the neighbourhood of the old value
3168 we can use a memory-to-memory insn */
3169 difference = new_value - old_value;
3170
3171 if (s390_host_has_gie && ulong_fits_signed_8bit(difference)) {
florianf85fe3e2012-12-22 02:28:25 +00003172 am = s390_amode_for_guest_state(offset);
3173 addInstr(env, s390_insn_madd(sizeofIRType(tyd), am,
florianad43b3a2012-02-20 15:01:14 +00003174 (difference & 0xFF), new_value));
3175 return;
3176 }
3177
florianb93348d2012-12-27 00:59:43 +00003178 /* If the high word is the same it is sufficient to load the low word. */
florianad43b3a2012-02-20 15:01:14 +00003179 if ((old_value >> 32) == (new_value >> 32)) {
florianf85fe3e2012-12-22 02:28:25 +00003180 am = s390_amode_for_guest_state(offset + 4);
florianb93348d2012-12-27 00:59:43 +00003181 addInstr(env, s390_insn_mimm(4, am, new_value & 0xFFFFFFFF));
florianad43b3a2012-02-20 15:01:14 +00003182 return;
3183 }
3184
3185 /* No special case applies... fall through */
3186
3187 not_special:
florianb93348d2012-12-27 00:59:43 +00003188 am = s390_amode_for_guest_state(offset);
sewardj2019a972011-03-07 16:04:07 +00003189
3190 switch (tyd) {
3191 case Ity_I8:
3192 case Ity_I16:
3193 case Ity_I32:
3194 case Ity_I64:
florian09bbba82012-12-11 04:09:43 +00003195 if (am->tag == S390_AMODE_B12 &&
florianb93348d2012-12-27 00:59:43 +00003196 stmt->Ist.Put.data->tag == Iex_Const) {
3197 ULong value =
3198 get_const_value_as_ulong(stmt->Ist.Put.data->Iex.Const.con);
3199 addInstr(env, s390_insn_mimm(sizeofIRType(tyd), am, value));
florian09bbba82012-12-11 04:09:43 +00003200 return;
3201 }
floriancec3a8a2013-02-02 00:16:58 +00003202 /* Check whether we can use a memcpy here. Currently, the restriction
3203 is that both amodes need to be B12, so MVC can be emitted. */
3204 /* put(load) never overlaps */
3205 if (am->tag == S390_AMODE_B12 &&
3206 stmt->Ist.Put.data->tag == Iex_Load) {
3207 if (stmt->Ist.Put.data->Iex.Load.end != Iend_BE) goto stmt_fail;
3208 IRExpr *data = stmt->Ist.Put.data->Iex.Load.addr;
3209 s390_amode *from = s390_isel_amode(env, data);
3210 UInt size = sizeofIRType(tyd);
3211
3212 if (from->tag == S390_AMODE_B12) {
3213 /* Source can be compiled into a B12 amode. */
3214 addInstr(env, s390_insn_memcpy(size, am, from));
3215 return;
3216 }
3217
3218 src = newVRegI(env);
3219 addInstr(env, s390_insn_load(size, src, from));
3220 break;
3221 }
3222 /* put(get) */
3223 if (am->tag == S390_AMODE_B12 &&
3224 stmt->Ist.Put.data->tag == Iex_Get) {
3225 UInt put_offset = am->d;
3226 UInt get_offset = stmt->Ist.Put.data->Iex.Get.offset;
3227 UInt size = sizeofIRType(tyd);
3228 /* don't memcpy in case of overlap */
3229 if (put_offset + size <= get_offset ||
3230 get_offset + size <= put_offset) {
3231 s390_amode *from = s390_amode_for_guest_state(get_offset);
3232 addInstr(env, s390_insn_memcpy(size, am, from));
3233 return;
3234 }
3235 goto no_memcpy_put;
3236 }
3237 /* General case: compile data into a register */
3238no_memcpy_put:
sewardj2019a972011-03-07 16:04:07 +00003239 src = s390_isel_int_expr(env, stmt->Ist.Put.data);
3240 break;
3241
3242 case Ity_F32:
3243 case Ity_F64:
3244 src = s390_isel_float_expr(env, stmt->Ist.Put.data);
3245 break;
3246
3247 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003248 case Ity_D128:
3249 /* Does not occur. See function put_(f|d)pr_pair. */
3250 vpanic("Ist_Put with 128-bit floating point data");
sewardj2019a972011-03-07 16:04:07 +00003251
floriane38f6412012-12-21 17:32:12 +00003252 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003253 case Ity_D64:
3254 src = s390_isel_dfp_expr(env, stmt->Ist.Put.data);
3255 break;
3256
sewardj2019a972011-03-07 16:04:07 +00003257 default:
3258 goto stmt_fail;
3259 }
3260
3261 addInstr(env, s390_insn_store(sizeofIRType(tyd), am, src));
3262 return;
3263 }
3264
3265 /* --------- TMP --------- */
3266 case Ist_WrTmp: {
3267 IRTemp tmp = stmt->Ist.WrTmp.tmp;
3268 IRType tyd = typeOfIRTemp(env->type_env, tmp);
3269 HReg src, dst;
3270
3271 switch (tyd) {
3272 case Ity_I128: {
3273 HReg dst_hi, dst_lo, res_hi, res_lo;
3274
3275 s390_isel_int128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3276 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3277
3278 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3279 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3280 return;
3281 }
3282
3283 case Ity_I8:
3284 case Ity_I16:
3285 case Ity_I32:
3286 case Ity_I64:
3287 src = s390_isel_int_expr(env, stmt->Ist.WrTmp.data);
3288 dst = lookupIRTemp(env, tmp);
3289 break;
3290
3291 case Ity_I1: {
3292 s390_cc_t cond = s390_isel_cc(env, stmt->Ist.WrTmp.data);
3293 dst = lookupIRTemp(env, tmp);
3294 addInstr(env, s390_insn_cc2bool(dst, cond));
3295 return;
3296 }
3297
3298 case Ity_F32:
3299 case Ity_F64:
3300 src = s390_isel_float_expr(env, stmt->Ist.WrTmp.data);
3301 dst = lookupIRTemp(env, tmp);
3302 break;
3303
3304 case Ity_F128: {
3305 HReg dst_hi, dst_lo, res_hi, res_lo;
3306
3307 s390_isel_float128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3308 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3309
3310 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3311 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3312 return;
3313 }
3314
floriane38f6412012-12-21 17:32:12 +00003315 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003316 case Ity_D64:
3317 src = s390_isel_dfp_expr(env, stmt->Ist.WrTmp.data);
3318 dst = lookupIRTemp(env, tmp);
3319 break;
3320
floriane38f6412012-12-21 17:32:12 +00003321 case Ity_D128: {
3322 HReg dst_hi, dst_lo, res_hi, res_lo;
3323
3324 s390_isel_dfp128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3325 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3326
3327 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3328 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3329 return;
3330 }
3331
sewardj2019a972011-03-07 16:04:07 +00003332 default:
3333 goto stmt_fail;
3334 }
3335
3336 addInstr(env, s390_insn_move(sizeofIRType(tyd), dst, src));
3337 return;
3338 }
3339
3340 /* --------- Call to DIRTY helper --------- */
3341 case Ist_Dirty: {
3342 IRType retty;
3343 IRDirty* d = stmt->Ist.Dirty.details;
3344 Bool passBBP;
florian01ed6e72012-05-27 16:52:43 +00003345 HReg dst;
florianad43b3a2012-02-20 15:01:14 +00003346 Int i;
3347
3348 /* Invalidate tracked values of those guest state registers that are
3349 modified by this helper. */
3350 for (i = 0; i < d->nFxState; ++i) {
sewardjc9069f22012-06-01 16:09:50 +00003351 /* JRS 1 June 2012: AFAICS, s390 guest doesn't use 'repeat'
3352 descriptors in guest state effect descriptions. Hence: */
3353 vassert(d->fxState[i].nRepeats == 0 && d->fxState[i].repeatLen == 0);
florianad43b3a2012-02-20 15:01:14 +00003354 if ((d->fxState[i].fx == Ifx_Write || d->fxState[i].fx == Ifx_Modify)) {
3355 Int guest_reg = get_guest_reg(d->fxState[i].offset);
3356 if (guest_reg != GUEST_UNKNOWN)
3357 env->old_value_valid[guest_reg] = False;
3358 }
3359 }
sewardj2019a972011-03-07 16:04:07 +00003360
3361 if (d->nFxState == 0)
3362 vassert(!d->needsBBP);
3363
3364 passBBP = toBool(d->nFxState > 0 && d->needsBBP);
3365
florian01ed6e72012-05-27 16:52:43 +00003366 if (d->tmp == IRTemp_INVALID) {
3367 /* No return value. */
3368 dst = INVALID_HREG;
3369 doHelperCall(env, passBBP, d->guard, d->cee, d->args, dst);
sewardj2019a972011-03-07 16:04:07 +00003370 return;
florian01ed6e72012-05-27 16:52:43 +00003371 }
sewardj2019a972011-03-07 16:04:07 +00003372
3373 retty = typeOfIRTemp(env->type_env, d->tmp);
3374 if (retty == Ity_I64 || retty == Ity_I32
3375 || retty == Ity_I16 || retty == Ity_I8) {
florian297b6062012-05-08 20:16:17 +00003376 /* Move the returned value to the destination register */
florian01ed6e72012-05-27 16:52:43 +00003377 dst = lookupIRTemp(env, d->tmp);
3378 doHelperCall(env, passBBP, d->guard, d->cee, d->args, dst);
sewardj2019a972011-03-07 16:04:07 +00003379 return;
3380 }
3381 break;
3382 }
3383
3384 case Ist_CAS:
3385 if (stmt->Ist.CAS.details->oldHi == IRTemp_INVALID) {
3386 IRCAS *cas = stmt->Ist.CAS.details;
3387 s390_amode *op2 = s390_isel_amode(env, cas->addr);
3388 HReg op3 = s390_isel_int_expr(env, cas->dataLo); /* new value */
3389 HReg op1 = s390_isel_int_expr(env, cas->expdLo); /* expected value */
3390 HReg old = lookupIRTemp(env, cas->oldLo);
3391
3392 if (typeOfIRTemp(env->type_env, cas->oldLo) == Ity_I32) {
3393 addInstr(env, s390_insn_cas(4, op1, op2, op3, old));
3394 } else {
3395 addInstr(env, s390_insn_cas(8, op1, op2, op3, old));
3396 }
3397 return;
3398 } else {
florian448cbba2012-06-06 02:26:01 +00003399 IRCAS *cas = stmt->Ist.CAS.details;
3400 s390_amode *op2 = s390_isel_amode(env, cas->addr);
3401 HReg r8, r9, r10, r11, r1;
3402 HReg op3_high = s390_isel_int_expr(env, cas->dataHi); /* new value */
3403 HReg op3_low = s390_isel_int_expr(env, cas->dataLo); /* new value */
3404 HReg op1_high = s390_isel_int_expr(env, cas->expdHi); /* expected value */
3405 HReg op1_low = s390_isel_int_expr(env, cas->expdLo); /* expected value */
3406 HReg old_low = lookupIRTemp(env, cas->oldLo);
3407 HReg old_high = lookupIRTemp(env, cas->oldHi);
3408
3409 /* Use non-virtual registers r8 and r9 as pair for op1
3410 and move op1 there */
3411 r8 = make_gpr(8);
3412 r9 = make_gpr(9);
3413 addInstr(env, s390_insn_move(8, r8, op1_high));
3414 addInstr(env, s390_insn_move(8, r9, op1_low));
3415
3416 /* Use non-virtual registers r10 and r11 as pair for op3
3417 and move op3 there */
3418 r10 = make_gpr(10);
3419 r11 = make_gpr(11);
3420 addInstr(env, s390_insn_move(8, r10, op3_high));
3421 addInstr(env, s390_insn_move(8, r11, op3_low));
3422
3423 /* Register r1 is used as a scratch register */
3424 r1 = make_gpr(1);
3425
3426 if (typeOfIRTemp(env->type_env, cas->oldLo) == Ity_I32) {
3427 addInstr(env, s390_insn_cdas(4, r8, r9, op2, r10, r11,
3428 old_high, old_low, r1));
3429 } else {
3430 addInstr(env, s390_insn_cdas(8, r8, r9, op2, r10, r11,
3431 old_high, old_low, r1));
3432 }
3433 addInstr(env, s390_insn_move(8, op1_high, r8));
3434 addInstr(env, s390_insn_move(8, op1_low, r9));
3435 addInstr(env, s390_insn_move(8, op3_high, r10));
3436 addInstr(env, s390_insn_move(8, op3_low, r11));
3437 return;
sewardj2019a972011-03-07 16:04:07 +00003438 }
3439 break;
3440
3441 /* --------- EXIT --------- */
3442 case Ist_Exit: {
sewardj2019a972011-03-07 16:04:07 +00003443 s390_cc_t cond;
3444 IRConstTag tag = stmt->Ist.Exit.dst->tag;
3445
3446 if (tag != Ico_U64)
3447 vpanic("s390_isel_stmt: Ist_Exit: dst is not a 64-bit value");
3448
florian8844a632012-04-13 04:04:06 +00003449 s390_amode *guest_IA = s390_amode_for_guest_state(stmt->Ist.Exit.offsIP);
sewardj2019a972011-03-07 16:04:07 +00003450 cond = s390_isel_cc(env, stmt->Ist.Exit.guard);
florian8844a632012-04-13 04:04:06 +00003451
3452 /* Case: boring transfer to known address */
3453 if (stmt->Ist.Exit.jk == Ijk_Boring) {
3454 if (env->chaining_allowed) {
3455 /* .. almost always true .. */
3456 /* Skip the event check at the dst if this is a forwards
3457 edge. */
3458 Bool to_fast_entry
3459 = ((Addr64)stmt->Ist.Exit.dst->Ico.U64) > env->max_ga;
3460 if (0) vex_printf("%s", to_fast_entry ? "Y" : ",");
3461 addInstr(env, s390_insn_xdirect(cond, stmt->Ist.Exit.dst->Ico.U64,
3462 guest_IA, to_fast_entry));
3463 } else {
3464 /* .. very occasionally .. */
3465 /* We can't use chaining, so ask for an assisted transfer,
3466 as that's the only alternative that is allowable. */
3467 HReg dst = s390_isel_int_expr(env,
3468 IRExpr_Const(stmt->Ist.Exit.dst));
3469 addInstr(env, s390_insn_xassisted(cond, dst, guest_IA, Ijk_Boring));
3470 }
3471 return;
3472 }
3473
3474 /* Case: assisted transfer to arbitrary address */
3475 switch (stmt->Ist.Exit.jk) {
florian4e0083e2012-08-26 03:41:56 +00003476 case Ijk_EmFail:
florian4b8efad2012-09-02 18:07:08 +00003477 case Ijk_EmWarn:
florian65b5b3f2012-04-22 02:51:27 +00003478 case Ijk_NoDecode:
florian8844a632012-04-13 04:04:06 +00003479 case Ijk_TInval:
florian2d98d892012-04-14 20:35:17 +00003480 case Ijk_Sys_syscall:
3481 case Ijk_ClientReq:
3482 case Ijk_NoRedir:
3483 case Ijk_Yield:
3484 case Ijk_SigTRAP: {
florian8844a632012-04-13 04:04:06 +00003485 HReg dst = s390_isel_int_expr(env, IRExpr_Const(stmt->Ist.Exit.dst));
3486 addInstr(env, s390_insn_xassisted(cond, dst, guest_IA,
3487 stmt->Ist.Exit.jk));
3488 return;
3489 }
3490 default:
3491 break;
3492 }
3493
3494 /* Do we ever expect to see any other kind? */
3495 goto stmt_fail;
sewardj2019a972011-03-07 16:04:07 +00003496 }
3497
3498 /* --------- MEM FENCE --------- */
sewardja52e37e2011-04-28 18:48:06 +00003499 case Ist_MBE:
3500 switch (stmt->Ist.MBE.event) {
3501 case Imbe_Fence:
3502 addInstr(env, s390_insn_mfence());
3503 return;
3504 default:
3505 break;
3506 }
sewardj2019a972011-03-07 16:04:07 +00003507 break;
3508
3509 /* --------- Miscellaneous --------- */
3510
3511 case Ist_PutI: /* Not needed */
3512 case Ist_IMark: /* Doesn't generate any executable code */
3513 case Ist_NoOp: /* Doesn't generate any executable code */
3514 case Ist_AbiHint: /* Meaningless in IR */
3515 return;
3516
3517 default:
3518 break;
3519 }
3520
3521 stmt_fail:
3522 ppIRStmt(stmt);
3523 vpanic("s390_isel_stmt");
3524}
3525
3526
3527/*---------------------------------------------------------*/
3528/*--- ISEL: Basic block terminators (Nexts) ---*/
3529/*---------------------------------------------------------*/
3530
3531static void
florianffbd84d2012-12-09 02:06:29 +00003532iselNext(ISelEnv *env, IRExpr *next, IRJumpKind jk, Int offsIP)
sewardj2019a972011-03-07 16:04:07 +00003533{
sewardj2019a972011-03-07 16:04:07 +00003534 if (vex_traceflags & VEX_TRACE_VCODE) {
florian8844a632012-04-13 04:04:06 +00003535 vex_printf("\n-- PUT(%d) = ", offsIP);
sewardj2019a972011-03-07 16:04:07 +00003536 ppIRExpr(next);
florian8844a632012-04-13 04:04:06 +00003537 vex_printf("; exit-");
3538 ppIRJumpKind(jk);
sewardj2019a972011-03-07 16:04:07 +00003539 vex_printf("\n");
3540 }
3541
florian8844a632012-04-13 04:04:06 +00003542 s390_amode *guest_IA = s390_amode_for_guest_state(offsIP);
3543
3544 /* Case: boring transfer to known address */
3545 if (next->tag == Iex_Const) {
3546 IRConst *cdst = next->Iex.Const.con;
3547 vassert(cdst->tag == Ico_U64);
3548 if (jk == Ijk_Boring || jk == Ijk_Call) {
3549 /* Boring transfer to known address */
3550 if (env->chaining_allowed) {
3551 /* .. almost always true .. */
3552 /* Skip the event check at the dst if this is a forwards
3553 edge. */
3554 Bool to_fast_entry
3555 = ((Addr64)cdst->Ico.U64) > env->max_ga;
3556 if (0) vex_printf("%s", to_fast_entry ? "X" : ".");
3557 addInstr(env, s390_insn_xdirect(S390_CC_ALWAYS, cdst->Ico.U64,
3558 guest_IA, to_fast_entry));
3559 } else {
3560 /* .. very occasionally .. */
3561 /* We can't use chaining, so ask for an indirect transfer,
3562 as that's the cheapest alternative that is allowable. */
3563 HReg dst = s390_isel_int_expr(env, next);
3564 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA,
3565 Ijk_Boring));
3566 }
3567 return;
3568 }
3569 }
3570
3571 /* Case: call/return (==boring) transfer to any address */
3572 switch (jk) {
3573 case Ijk_Boring:
3574 case Ijk_Ret:
3575 case Ijk_Call: {
3576 HReg dst = s390_isel_int_expr(env, next);
3577 if (env->chaining_allowed) {
3578 addInstr(env, s390_insn_xindir(S390_CC_ALWAYS, dst, guest_IA));
3579 } else {
3580 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA,
3581 Ijk_Boring));
3582 }
3583 return;
3584 }
3585 default:
3586 break;
3587 }
3588
3589 /* Case: some other kind of transfer to any address */
3590 switch (jk) {
florian4e0083e2012-08-26 03:41:56 +00003591 case Ijk_EmFail:
florian4b8efad2012-09-02 18:07:08 +00003592 case Ijk_EmWarn:
florian65b5b3f2012-04-22 02:51:27 +00003593 case Ijk_NoDecode:
florian2d98d892012-04-14 20:35:17 +00003594 case Ijk_TInval:
florian8844a632012-04-13 04:04:06 +00003595 case Ijk_Sys_syscall:
3596 case Ijk_ClientReq:
3597 case Ijk_NoRedir:
3598 case Ijk_Yield:
3599 case Ijk_SigTRAP: {
3600 HReg dst = s390_isel_int_expr(env, next);
3601 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA, jk));
3602 return;
3603 }
3604 default:
3605 break;
3606 }
3607
3608 vpanic("iselNext");
sewardj2019a972011-03-07 16:04:07 +00003609}
3610
3611
3612/*---------------------------------------------------------*/
3613/*--- Insn selector top-level ---*/
3614/*---------------------------------------------------------*/
3615
florianf26994a2012-04-21 03:34:54 +00003616/* Translate an entire SB to s390 code.
3617 Note: archinfo_host is a pointer to a stack-allocated variable.
3618 Do not assign it to a global variable! */
sewardj2019a972011-03-07 16:04:07 +00003619
3620HInstrArray *
3621iselSB_S390(IRSB *bb, VexArch arch_host, VexArchInfo *archinfo_host,
florian8844a632012-04-13 04:04:06 +00003622 VexAbiInfo *vbi, Int offset_host_evcheck_counter,
3623 Int offset_host_evcheck_fail_addr, Bool chaining_allowed,
3624 Bool add_profinc, Addr64 max_ga)
sewardj2019a972011-03-07 16:04:07 +00003625{
3626 UInt i, j;
3627 HReg hreg, hregHI;
3628 ISelEnv *env;
3629 UInt hwcaps_host = archinfo_host->hwcaps;
3630
florianf26994a2012-04-21 03:34:54 +00003631 /* KLUDGE: export hwcaps. */
3632 s390_host_hwcaps = hwcaps_host;
sewardj2019a972011-03-07 16:04:07 +00003633
sewardj2019a972011-03-07 16:04:07 +00003634 /* Do some sanity checks */
sewardj652b56a2011-04-13 15:38:17 +00003635 vassert((VEX_HWCAPS_S390X(hwcaps_host) & ~(VEX_HWCAPS_S390X_ALL)) == 0);
sewardj2019a972011-03-07 16:04:07 +00003636
3637 /* Make up an initial environment to use. */
3638 env = LibVEX_Alloc(sizeof(ISelEnv));
3639 env->vreg_ctr = 0;
3640
3641 /* Set up output code array. */
3642 env->code = newHInstrArray();
3643
3644 /* Copy BB's type env. */
3645 env->type_env = bb->tyenv;
3646
florianad43b3a2012-02-20 15:01:14 +00003647 /* Set up data structures for tracking guest register values. */
florianad43b3a2012-02-20 15:01:14 +00003648 for (i = 0; i < NUM_TRACKED_REGS; ++i) {
3649 env->old_value[i] = 0; /* just something to have a defined value */
3650 env->old_value_valid[i] = False;
3651 }
3652
sewardj2019a972011-03-07 16:04:07 +00003653 /* Make up an IRTemp -> virtual HReg mapping. This doesn't
3654 change as we go along. For some reason types_used has Int type -- but
3655 it should be unsigned. Internally we use an unsigned type; so we
3656 assert it here. */
3657 vassert(bb->tyenv->types_used >= 0);
3658
3659 env->n_vregmap = bb->tyenv->types_used;
3660 env->vregmap = LibVEX_Alloc(env->n_vregmap * sizeof(HReg));
3661 env->vregmapHI = LibVEX_Alloc(env->n_vregmap * sizeof(HReg));
3662
florian2c74d242012-09-12 19:38:42 +00003663 env->previous_bfp_rounding_mode = NULL;
florianc8e4f562012-10-27 16:19:31 +00003664 env->previous_dfp_rounding_mode = NULL;
florian2c74d242012-09-12 19:38:42 +00003665
sewardj2019a972011-03-07 16:04:07 +00003666 /* and finally ... */
3667 env->hwcaps = hwcaps_host;
3668
florian8844a632012-04-13 04:04:06 +00003669 env->max_ga = max_ga;
3670 env->chaining_allowed = chaining_allowed;
3671
sewardj2019a972011-03-07 16:04:07 +00003672 /* For each IR temporary, allocate a suitably-kinded virtual
3673 register. */
3674 j = 0;
3675 for (i = 0; i < env->n_vregmap; i++) {
3676 hregHI = hreg = INVALID_HREG;
3677 switch (bb->tyenv->types[i]) {
3678 case Ity_I1:
3679 case Ity_I8:
3680 case Ity_I16:
3681 case Ity_I32:
3682 hreg = mkHReg(j++, HRcInt64, True);
3683 break;
3684
3685 case Ity_I64:
3686 hreg = mkHReg(j++, HRcInt64, True);
3687 break;
3688
3689 case Ity_I128:
3690 hreg = mkHReg(j++, HRcInt64, True);
3691 hregHI = mkHReg(j++, HRcInt64, True);
3692 break;
3693
3694 case Ity_F32:
3695 case Ity_F64:
floriane38f6412012-12-21 17:32:12 +00003696 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003697 case Ity_D64:
sewardj2019a972011-03-07 16:04:07 +00003698 hreg = mkHReg(j++, HRcFlt64, True);
3699 break;
3700
3701 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003702 case Ity_D128:
sewardj2019a972011-03-07 16:04:07 +00003703 hreg = mkHReg(j++, HRcFlt64, True);
3704 hregHI = mkHReg(j++, HRcFlt64, True);
3705 break;
3706
3707 case Ity_V128: /* fall through */
3708 default:
3709 ppIRType(bb->tyenv->types[i]);
florian4ebaa772012-12-20 19:44:18 +00003710 vpanic("iselSB_S390: IRTemp type");
sewardj2019a972011-03-07 16:04:07 +00003711 }
3712
3713 env->vregmap[i] = hreg;
3714 env->vregmapHI[i] = hregHI;
3715 }
3716 env->vreg_ctr = j;
3717
florian8844a632012-04-13 04:04:06 +00003718 /* The very first instruction must be an event check. */
3719 s390_amode *counter, *fail_addr;
3720 counter = s390_amode_for_guest_state(offset_host_evcheck_counter);
3721 fail_addr = s390_amode_for_guest_state(offset_host_evcheck_fail_addr);
3722 addInstr(env, s390_insn_evcheck(counter, fail_addr));
3723
3724 /* Possibly a block counter increment (for profiling). At this
3725 point we don't know the address of the counter, so just pretend
3726 it is zero. It will have to be patched later, but before this
3727 translation is used, by a call to LibVEX_patchProfInc. */
3728 if (add_profinc) {
3729 addInstr(env, s390_insn_profinc());
3730 }
3731
sewardj2019a972011-03-07 16:04:07 +00003732 /* Ok, finally we can iterate over the statements. */
3733 for (i = 0; i < bb->stmts_used; i++)
3734 if (bb->stmts[i])
3735 s390_isel_stmt(env, bb->stmts[i]);
3736
florian8844a632012-04-13 04:04:06 +00003737 iselNext(env, bb->next, bb->jumpkind, bb->offsIP);
sewardj2019a972011-03-07 16:04:07 +00003738
3739 /* Record the number of vregs we used. */
3740 env->code->n_vregs = env->vreg_ctr;
3741
3742 return env->code;
3743}
3744
3745/*---------------------------------------------------------------*/
3746/*--- end host_s390_isel.c ---*/
3747/*---------------------------------------------------------------*/