blob: d8cbd279e7a0f5f806727840b5a27710770b61ac [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.
685 The IR to s390 encoding is chosen in the range 0:7 except
686 S390_DFP_ROUND_NEAREST_TIE_TOWARD_0 and
687 S390_DFP_ROUND_AWAY_0 which have no choice within the range.
688 Since the s390 dfp rounding mode encoding in 8:15 is not used, the
689 quantum excpetion is not suppressed and this is fine as valgrind does
690 not model this exception.
691
692 Translation table of
693 s390 DFP rounding mode to IRRoundingMode to s390 DFP rounding mode
694
695 s390(S390_DFP_ROUND_) | IR(Irrm_DFP_) | s390(S390_DFP_ROUND_)
696 --------------------------------------------------------------------
697 NEAREST_TIE_AWAY_0_1 | NEAREST_TIE_AWAY_0 | NEAREST_TIE_AWAY_0_1
698 NEAREST_TIE_AWAY_0_12 | " | "
699 PREPARE_SHORT_3 | PREPARE_SHORTER | PREPARE_SHORT_3
700 PREPARE_SHORT_15 | " | "
701 NEAREST_EVEN_4 | NEAREST | NEAREST_EVEN_4
702 NEAREST_EVEN_8 | " | "
703 ZERO_5 | ZERO | ZERO_5
704 ZERO_9 | " | "
705 POSINF_6 | PosINF | POSINF_6
706 POSINF_10 | " | "
707 NEGINF_7 | NegINF | NEGINF_7
708 NEGINF_11 | " | "
709 NEAREST_TIE_TOWARD_0 | NEAREST_TIE_TOWARD_0| NEAREST_TIE_TOWARD_0
710 AWAY_0 | AWAY_FROM_ZERO | AWAY_0
711*/
712static s390_dfp_round_t
713get_dfp_rounding_mode(ISelEnv *env, IRExpr *irrm)
714{
715 if (irrm->tag == Iex_Const) { /* rounding mode is known */
716 vassert(irrm->Iex.Const.con->tag == Ico_U32);
florian3d6a4222012-11-19 16:29:31 +0000717 IRRoundingModeDFP mode = irrm->Iex.Const.con->Ico.U32;
florianc8e4f562012-10-27 16:19:31 +0000718
719 switch (mode) {
720 case Irrm_DFP_NEAREST:
721 return S390_DFP_ROUND_NEAREST_EVEN_4;
722 case Irrm_DFP_NegINF:
723 return S390_DFP_ROUND_NEGINF_7;
724 case Irrm_DFP_PosINF:
725 return S390_DFP_ROUND_POSINF_6;
726 case Irrm_DFP_ZERO:
727 return S390_DFP_ROUND_ZERO_5;
728 case Irrm_DFP_NEAREST_TIE_AWAY_0:
729 return S390_DFP_ROUND_NEAREST_TIE_AWAY_0_1;
730 case Irrm_DFP_PREPARE_SHORTER:
731 return S390_DFP_ROUND_PREPARE_SHORT_3;
732 case Irrm_DFP_AWAY_FROM_ZERO:
733 return S390_DFP_ROUND_AWAY_0;
734 case Irrm_DFP_NEAREST_TIE_TOWARD_0:
735 return S390_DFP_ROUND_NEAREST_TIE_TOWARD_0;
736 default:
737 vpanic("get_dfp_rounding_mode");
738 }
739 }
740
741 set_dfp_rounding_mode_in_fpc(env, irrm);
742 return S390_DFP_ROUND_PER_FPC_0;
743}
florianc8e4f562012-10-27 16:19:31 +0000744
florian2d3d87f2012-12-21 21:05:17 +0000745
746/*---------------------------------------------------------*/
747/*--- Condition code helper functions ---*/
748/*---------------------------------------------------------*/
749
sewardj2019a972011-03-07 16:04:07 +0000750/* CC_S390 holds the condition code in s390 encoding. Convert it to
florian2d3d87f2012-12-21 21:05:17 +0000751 VEX encoding (IRCmpFResult)
sewardj2019a972011-03-07 16:04:07 +0000752
753 s390 VEX b6 b2 b0 cc.1 cc.0
754 0 0x40 EQ 1 0 0 0 0
755 1 0x01 LT 0 0 1 0 1
756 2 0x00 GT 0 0 0 1 0
757 3 0x45 Unordered 1 1 1 1 1
758
759 b0 = cc.0
760 b2 = cc.0 & cc.1
761 b6 = ~(cc.0 ^ cc.1) // ((cc.0 - cc.1) + 0x1 ) & 0x1
762
763 VEX = b0 | (b2 << 2) | (b6 << 6);
764*/
765static HReg
florian2d3d87f2012-12-21 21:05:17 +0000766convert_s390_to_vex_bfpcc(ISelEnv *env, HReg cc_s390)
sewardj2019a972011-03-07 16:04:07 +0000767{
768 HReg cc0, cc1, b2, b6, cc_vex;
769
770 cc0 = newVRegI(env);
771 addInstr(env, s390_insn_move(4, cc0, cc_s390));
772 addInstr(env, s390_insn_alu(4, S390_ALU_AND, cc0, s390_opnd_imm(1)));
773
774 cc1 = newVRegI(env);
775 addInstr(env, s390_insn_move(4, cc1, cc_s390));
776 addInstr(env, s390_insn_alu(4, S390_ALU_RSH, cc1, s390_opnd_imm(1)));
777
778 b2 = newVRegI(env);
779 addInstr(env, s390_insn_move(4, b2, cc0));
780 addInstr(env, s390_insn_alu(4, S390_ALU_AND, b2, s390_opnd_reg(cc1)));
781 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, b2, s390_opnd_imm(2)));
782
783 b6 = newVRegI(env);
784 addInstr(env, s390_insn_move(4, b6, cc0));
785 addInstr(env, s390_insn_alu(4, S390_ALU_SUB, b6, s390_opnd_reg(cc1)));
786 addInstr(env, s390_insn_alu(4, S390_ALU_ADD, b6, s390_opnd_imm(1)));
787 addInstr(env, s390_insn_alu(4, S390_ALU_AND, b6, s390_opnd_imm(1)));
788 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, b6, s390_opnd_imm(6)));
789
790 cc_vex = newVRegI(env);
791 addInstr(env, s390_insn_move(4, cc_vex, cc0));
792 addInstr(env, s390_insn_alu(4, S390_ALU_OR, cc_vex, s390_opnd_reg(b2)));
793 addInstr(env, s390_insn_alu(4, S390_ALU_OR, cc_vex, s390_opnd_reg(b6)));
794
795 return cc_vex;
796}
797
florian2d3d87f2012-12-21 21:05:17 +0000798/* CC_S390 holds the condition code in s390 encoding. Convert it to
799 VEX encoding (IRCmpDResult) */
800static HReg
801convert_s390_to_vex_dfpcc(ISelEnv *env, HReg cc_s390)
802{
803 /* The encodings for IRCmpFResult and IRCmpDResult are the same/ */
804 return convert_s390_to_vex_bfpcc(env, cc_s390);
805}
806
sewardj2019a972011-03-07 16:04:07 +0000807
808/*---------------------------------------------------------*/
809/*--- ISEL: Integer expressions (128 bit) ---*/
810/*---------------------------------------------------------*/
811static void
812s390_isel_int128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
813 IRExpr *expr)
814{
815 IRType ty = typeOfIRExpr(env->type_env, expr);
816
817 vassert(ty == Ity_I128);
818
819 /* No need to consider the following
820 - 128-bit constants (they do not exist in VEX)
821 - 128-bit loads from memory (will not be generated)
822 */
823
824 /* Read 128-bit IRTemp */
825 if (expr->tag == Iex_RdTmp) {
826 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
827 return;
828 }
829
830 if (expr->tag == Iex_Binop) {
831 IRExpr *arg1 = expr->Iex.Binop.arg1;
832 IRExpr *arg2 = expr->Iex.Binop.arg2;
833 Bool is_signed_multiply, is_signed_divide;
834
835 switch (expr->Iex.Binop.op) {
836 case Iop_MullU64:
837 is_signed_multiply = False;
838 goto do_multiply64;
839
840 case Iop_MullS64:
841 is_signed_multiply = True;
842 goto do_multiply64;
843
844 case Iop_DivModU128to64:
845 is_signed_divide = False;
846 goto do_divide64;
847
848 case Iop_DivModS128to64:
849 is_signed_divide = True;
850 goto do_divide64;
851
852 case Iop_64HLto128:
853 *dst_hi = s390_isel_int_expr(env, arg1);
854 *dst_lo = s390_isel_int_expr(env, arg2);
855 return;
856
857 case Iop_DivModS64to64: {
858 HReg r10, r11, h1;
859 s390_opnd_RMI op2;
860
861 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
862 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
863
864 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000865 r10 = make_gpr(10);
866 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000867
868 /* Move 1st operand into r11 and */
869 addInstr(env, s390_insn_move(8, r11, h1));
870
871 /* Divide */
872 addInstr(env, s390_insn_divs(8, r10, r11, op2));
873
874 /* The result is in registers r10 (remainder) and r11 (quotient).
875 Move the result into the reg pair that is being returned such
876 such that the low 64 bits are the quotient and the upper 64 bits
877 are the remainder. (see libvex_ir.h). */
878 *dst_hi = newVRegI(env);
879 *dst_lo = newVRegI(env);
880 addInstr(env, s390_insn_move(8, *dst_hi, r10));
881 addInstr(env, s390_insn_move(8, *dst_lo, r11));
882 return;
883 }
884
885 default:
886 break;
887
888 do_multiply64: {
889 HReg r10, r11, h1;
890 s390_opnd_RMI op2;
891
892 order_commutative_operands(arg1, arg2);
893
894 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
895 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
896
897 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000898 r10 = make_gpr(10);
899 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000900
901 /* Move the first operand to r11 */
902 addInstr(env, s390_insn_move(8, r11, h1));
903
904 /* Multiply */
905 addInstr(env, s390_insn_mul(8, r10, r11, op2, is_signed_multiply));
906
907 /* The result is in registers r10 and r11. Assign to two virtual regs
908 and return. */
909 *dst_hi = newVRegI(env);
910 *dst_lo = newVRegI(env);
911 addInstr(env, s390_insn_move(8, *dst_hi, r10));
912 addInstr(env, s390_insn_move(8, *dst_lo, r11));
913 return;
914 }
915
916 do_divide64: {
917 HReg r10, r11, hi, lo;
918 s390_opnd_RMI op2;
919
920 s390_isel_int128_expr(&hi, &lo, env, arg1);
921 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
922
923 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000924 r10 = make_gpr(10);
925 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000926
927 /* Move high 64 bits of the 1st operand into r10 and
928 the low 64 bits into r11. */
929 addInstr(env, s390_insn_move(8, r10, hi));
930 addInstr(env, s390_insn_move(8, r11, lo));
931
932 /* Divide */
933 addInstr(env, s390_insn_div(8, r10, r11, op2, is_signed_divide));
934
935 /* The result is in registers r10 (remainder) and r11 (quotient).
936 Move the result into the reg pair that is being returned such
937 such that the low 64 bits are the quotient and the upper 64 bits
938 are the remainder. (see libvex_ir.h). */
939 *dst_hi = newVRegI(env);
940 *dst_lo = newVRegI(env);
941 addInstr(env, s390_insn_move(8, *dst_hi, r10));
942 addInstr(env, s390_insn_move(8, *dst_lo, r11));
943 return;
944 }
945 }
946 }
947
948 vpanic("s390_isel_int128_expr");
949}
950
951
952/* Compute a 128-bit value into two 64-bit registers. These may be either
953 real or virtual regs; in any case they must not be changed by subsequent
954 code emitted by the caller. */
955static void
956s390_isel_int128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
957{
958 s390_isel_int128_expr_wrk(dst_hi, dst_lo, env, expr);
959
960 /* Sanity checks ... */
961 vassert(hregIsVirtual(*dst_hi));
962 vassert(hregIsVirtual(*dst_lo));
963 vassert(hregClass(*dst_hi) == HRcInt64);
964 vassert(hregClass(*dst_lo) == HRcInt64);
965}
966
967
968/*---------------------------------------------------------*/
969/*--- ISEL: Integer expressions (64/32/16/8 bit) ---*/
970/*---------------------------------------------------------*/
971
972/* Select insns for an integer-typed expression, and add them to the
973 code list. Return a reg holding the result. This reg will be a
974 virtual register. THE RETURNED REG MUST NOT BE MODIFIED. If you
975 want to modify it, ask for a new vreg, copy it in there, and modify
976 the copy. The register allocator will do its best to map both
977 vregs to the same real register, so the copies will often disappear
978 later in the game.
979
980 This should handle expressions of 64, 32, 16 and 8-bit type.
981 All results are returned in a 64bit register.
982 For 16- and 8-bit expressions, the upper (32/48/56 : 16/24) bits
983 are arbitrary, so you should mask or sign extend partial values
984 if necessary.
985*/
986
987/* DO NOT CALL THIS DIRECTLY ! */
988static HReg
989s390_isel_int_expr_wrk(ISelEnv *env, IRExpr *expr)
990{
991 IRType ty = typeOfIRExpr(env->type_env, expr);
992 UChar size;
florian6dc90242012-12-21 21:43:00 +0000993 s390_bfp_conv_t conv;
florian67a171c2013-01-20 03:08:04 +0000994 s390_dfp_conv_t dconv;
sewardj2019a972011-03-07 16:04:07 +0000995
996 vassert(ty == Ity_I8 || ty == Ity_I16 || ty == Ity_I32 || ty == Ity_I64);
997
998 size = sizeofIRType(ty); /* size of the result after evaluating EXPR */
999
1000 switch (expr->tag) {
1001
1002 /* --------- TEMP --------- */
1003 case Iex_RdTmp:
1004 /* Return the virtual register that holds the temporary. */
1005 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
1006
1007 /* --------- LOAD --------- */
1008 case Iex_Load: {
1009 HReg dst = newVRegI(env);
1010 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
1011
1012 if (expr->Iex.Load.end != Iend_BE)
1013 goto irreducible;
1014
1015 addInstr(env, s390_insn_load(size, dst, am));
1016
1017 return dst;
1018 }
1019
1020 /* --------- BINARY OP --------- */
1021 case Iex_Binop: {
1022 IRExpr *arg1 = expr->Iex.Binop.arg1;
1023 IRExpr *arg2 = expr->Iex.Binop.arg2;
1024 HReg h1, res;
1025 s390_alu_t opkind;
1026 s390_opnd_RMI op2, value, opnd;
1027 s390_insn *insn;
1028 Bool is_commutative, is_signed_multiply, is_signed_divide;
1029
1030 is_commutative = True;
1031
1032 switch (expr->Iex.Binop.op) {
1033 case Iop_MullU8:
1034 case Iop_MullU16:
1035 case Iop_MullU32:
1036 is_signed_multiply = False;
1037 goto do_multiply;
1038
1039 case Iop_MullS8:
1040 case Iop_MullS16:
1041 case Iop_MullS32:
1042 is_signed_multiply = True;
1043 goto do_multiply;
1044
1045 do_multiply: {
1046 HReg r10, r11;
1047 UInt arg_size = size / 2;
1048
1049 order_commutative_operands(arg1, arg2);
1050
1051 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1052 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1053
1054 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001055 r10 = make_gpr(10);
1056 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001057
1058 /* Move the first operand to r11 */
1059 addInstr(env, s390_insn_move(arg_size, r11, h1));
1060
1061 /* Multiply */
1062 addInstr(env, s390_insn_mul(arg_size, r10, r11, op2, is_signed_multiply));
1063
1064 /* The result is in registers r10 and r11. Combine them into a SIZE-bit
1065 value into the destination register. */
1066 res = newVRegI(env);
1067 addInstr(env, s390_insn_move(arg_size, res, r10));
1068 value = s390_opnd_imm(arg_size * 8);
1069 addInstr(env, s390_insn_alu(size, S390_ALU_LSH, res, value));
1070 value = s390_opnd_imm((((ULong)1) << arg_size * 8) - 1);
1071 addInstr(env, s390_insn_alu(size, S390_ALU_AND, r11, value));
1072 opnd = s390_opnd_reg(r11);
1073 addInstr(env, s390_insn_alu(size, S390_ALU_OR, res, opnd));
1074 return res;
1075 }
1076
1077 case Iop_DivModS64to32:
1078 is_signed_divide = True;
1079 goto do_divide;
1080
1081 case Iop_DivModU64to32:
1082 is_signed_divide = False;
1083 goto do_divide;
1084
1085 do_divide: {
1086 HReg r10, r11;
1087
1088 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1089 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1090
1091 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001092 r10 = make_gpr(10);
1093 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001094
1095 /* Split the first operand and put the high 32 bits into r10 and
1096 the low 32 bits into r11. */
1097 addInstr(env, s390_insn_move(8, r10, h1));
1098 addInstr(env, s390_insn_move(8, r11, h1));
1099 value = s390_opnd_imm(32);
1100 addInstr(env, s390_insn_alu(8, S390_ALU_RSH, r10, value));
1101
1102 /* Divide */
1103 addInstr(env, s390_insn_div(4, r10, r11, op2, is_signed_divide));
1104
1105 /* The result is in registers r10 (remainder) and r11 (quotient).
1106 Combine them into a 64-bit value such that the low 32 bits are
1107 the quotient and the upper 32 bits are the remainder. (see
1108 libvex_ir.h). */
1109 res = newVRegI(env);
1110 addInstr(env, s390_insn_move(8, res, r10));
1111 value = s390_opnd_imm(32);
1112 addInstr(env, s390_insn_alu(8, S390_ALU_LSH, res, value));
1113 value = s390_opnd_imm((((ULong)1) << 32) - 1);
1114 addInstr(env, s390_insn_alu(8, S390_ALU_AND, r11, value));
1115 opnd = s390_opnd_reg(r11);
1116 addInstr(env, s390_insn_alu(8, S390_ALU_OR, res, opnd));
1117 return res;
1118 }
1119
florian9fcff4c2012-09-10 03:09:04 +00001120 case Iop_F32toI32S: conv = S390_BFP_F32_TO_I32; goto do_convert;
1121 case Iop_F32toI64S: conv = S390_BFP_F32_TO_I64; goto do_convert;
1122 case Iop_F32toI32U: conv = S390_BFP_F32_TO_U32; goto do_convert;
1123 case Iop_F32toI64U: conv = S390_BFP_F32_TO_U64; goto do_convert;
1124 case Iop_F64toI32S: conv = S390_BFP_F64_TO_I32; goto do_convert;
1125 case Iop_F64toI64S: conv = S390_BFP_F64_TO_I64; goto do_convert;
1126 case Iop_F64toI32U: conv = S390_BFP_F64_TO_U32; goto do_convert;
1127 case Iop_F64toI64U: conv = S390_BFP_F64_TO_U64; goto do_convert;
1128 case Iop_F128toI32S: conv = S390_BFP_F128_TO_I32; goto do_convert_128;
1129 case Iop_F128toI64S: conv = S390_BFP_F128_TO_I64; goto do_convert_128;
1130 case Iop_F128toI32U: conv = S390_BFP_F128_TO_U32; goto do_convert_128;
1131 case Iop_F128toI64U: conv = S390_BFP_F128_TO_U64; goto do_convert_128;
florian67a171c2013-01-20 03:08:04 +00001132
1133 case Iop_D64toI32S: dconv = S390_DFP_D64_TO_I32; goto do_convert_dfp;
1134 case Iop_D64toI32U: dconv = S390_DFP_D64_TO_U32; goto do_convert_dfp;
1135 case Iop_D64toI64U: dconv = S390_DFP_D64_TO_U64; goto do_convert_dfp;
1136 case Iop_D128toI32S: dconv = S390_DFP_D128_TO_I32; goto do_convert_dfp128;
1137 case Iop_D128toI32U: dconv = S390_DFP_D128_TO_U32; goto do_convert_dfp128;
1138 case Iop_D128toI64U: dconv = S390_DFP_D128_TO_U64; goto do_convert_dfp128;
sewardj2019a972011-03-07 16:04:07 +00001139
1140 do_convert: {
florian125e20d2012-10-07 15:42:37 +00001141 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00001142
1143 res = newVRegI(env);
1144 h1 = s390_isel_float_expr(env, arg2); /* Process operand */
1145
florian2c74d242012-09-12 19:38:42 +00001146 rounding_mode = get_bfp_rounding_mode(env, arg1);
1147 addInstr(env, s390_insn_bfp_convert(size, conv, res, h1,
1148 rounding_mode));
sewardj2019a972011-03-07 16:04:07 +00001149 return res;
1150 }
1151
1152 do_convert_128: {
florian125e20d2012-10-07 15:42:37 +00001153 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00001154 HReg op_hi, op_lo, f13, f15;
1155
1156 res = newVRegI(env);
1157 s390_isel_float128_expr(&op_hi, &op_lo, env, arg2); /* operand */
1158
1159 /* We use non-virtual registers r13 and r15 as pair */
1160 f13 = make_fpr(13);
1161 f15 = make_fpr(15);
1162
1163 /* operand --> (f13, f15) */
1164 addInstr(env, s390_insn_move(8, f13, op_hi));
1165 addInstr(env, s390_insn_move(8, f15, op_lo));
1166
florian2c74d242012-09-12 19:38:42 +00001167 rounding_mode = get_bfp_rounding_mode(env, arg1);
florian9fcff4c2012-09-10 03:09:04 +00001168 addInstr(env, s390_insn_bfp128_convert_from(size, conv, res, f13, f15,
sewardj2019a972011-03-07 16:04:07 +00001169 rounding_mode));
1170 return res;
1171 }
1172
florian5f034622013-01-13 02:29:05 +00001173 do_convert_dfp: {
1174 s390_dfp_round_t rounding_mode;
1175
1176 res = newVRegI(env);
1177 h1 = s390_isel_dfp_expr(env, arg2); /* Process operand */
1178
1179 rounding_mode = get_dfp_rounding_mode(env, arg1);
florian67a171c2013-01-20 03:08:04 +00001180 addInstr(env, s390_insn_dfp_convert(size, dconv, res, h1,
florian5f034622013-01-13 02:29:05 +00001181 rounding_mode));
1182 return res;
1183 }
1184
1185 do_convert_dfp128: {
1186 s390_dfp_round_t rounding_mode;
1187 HReg op_hi, op_lo, f13, f15;
1188
1189 res = newVRegI(env);
1190 s390_isel_dfp128_expr(&op_hi, &op_lo, env, arg2); /* operand */
1191
1192 /* We use non-virtual registers r13 and r15 as pair */
1193 f13 = make_fpr(13);
1194 f15 = make_fpr(15);
1195
1196 /* operand --> (f13, f15) */
1197 addInstr(env, s390_insn_move(8, f13, op_hi));
1198 addInstr(env, s390_insn_move(8, f15, op_lo));
1199
1200 rounding_mode = get_dfp_rounding_mode(env, arg1);
florian67a171c2013-01-20 03:08:04 +00001201 addInstr(env, s390_insn_dfp128_convert_from(size, dconv, res, f13,
florian5f034622013-01-13 02:29:05 +00001202 f15, rounding_mode));
1203 return res;
1204 }
1205
sewardj2019a972011-03-07 16:04:07 +00001206 case Iop_8HLto16:
1207 case Iop_16HLto32:
1208 case Iop_32HLto64: {
1209 HReg h2;
1210 UInt arg_size = size / 2;
1211
1212 res = newVRegI(env);
1213 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1214 h2 = s390_isel_int_expr(env, arg2); /* Process 2nd operand */
1215
1216 addInstr(env, s390_insn_move(arg_size, res, h1));
1217 value = s390_opnd_imm(arg_size * 8);
1218 addInstr(env, s390_insn_alu(size, S390_ALU_LSH, res, value));
1219 value = s390_opnd_imm((((ULong)1) << arg_size * 8) - 1);
1220 addInstr(env, s390_insn_alu(size, S390_ALU_AND, h2, value));
1221 opnd = s390_opnd_reg(h2);
1222 addInstr(env, s390_insn_alu(size, S390_ALU_OR, res, opnd));
1223 return res;
1224 }
1225
1226 case Iop_Max32U: {
1227 /* arg1 > arg2 ? arg1 : arg2 using uint32_t arguments */
1228 res = newVRegI(env);
1229 h1 = s390_isel_int_expr(env, arg1);
1230 op2 = s390_isel_int_expr_RMI(env, arg2);
1231
1232 addInstr(env, s390_insn_move(size, res, h1));
1233 addInstr(env, s390_insn_compare(size, res, op2, False /* signed */));
1234 addInstr(env, s390_insn_cond_move(size, S390_CC_L, res, op2));
1235 return res;
1236 }
1237
1238 case Iop_CmpF32:
1239 case Iop_CmpF64: {
1240 HReg cc_s390, h2;
1241
1242 h1 = s390_isel_float_expr(env, arg1);
1243 h2 = s390_isel_float_expr(env, arg2);
1244 cc_s390 = newVRegI(env);
1245
1246 size = (expr->Iex.Binop.op == Iop_CmpF32) ? 4 : 8;
1247
1248 addInstr(env, s390_insn_bfp_compare(size, cc_s390, h1, h2));
1249
florian2d3d87f2012-12-21 21:05:17 +00001250 return convert_s390_to_vex_bfpcc(env, cc_s390);
sewardj2019a972011-03-07 16:04:07 +00001251 }
1252
1253 case Iop_CmpF128: {
1254 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15, cc_s390;
1255
1256 s390_isel_float128_expr(&op1_hi, &op1_lo, env, arg1); /* 1st operand */
1257 s390_isel_float128_expr(&op2_hi, &op2_lo, env, arg2); /* 2nd operand */
1258 cc_s390 = newVRegI(env);
1259
1260 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1261 f12 = make_fpr(12);
1262 f13 = make_fpr(13);
1263 f14 = make_fpr(14);
1264 f15 = make_fpr(15);
1265
1266 /* 1st operand --> (f12, f14) */
1267 addInstr(env, s390_insn_move(8, f12, op1_hi));
1268 addInstr(env, s390_insn_move(8, f14, op1_lo));
1269
1270 /* 2nd operand --> (f13, f15) */
1271 addInstr(env, s390_insn_move(8, f13, op2_hi));
1272 addInstr(env, s390_insn_move(8, f15, op2_lo));
1273
1274 res = newVRegI(env);
1275 addInstr(env, s390_insn_bfp128_compare(16, cc_s390, f12, f14, f13, f15));
1276
florian2d3d87f2012-12-21 21:05:17 +00001277 return convert_s390_to_vex_bfpcc(env, cc_s390);
sewardj2019a972011-03-07 16:04:07 +00001278 }
1279
florian20c6bca2012-12-26 17:47:19 +00001280 case Iop_CmpD64:
1281 case Iop_CmpExpD64: {
floriane38f6412012-12-21 17:32:12 +00001282 HReg cc_s390, h2;
florian20c6bca2012-12-26 17:47:19 +00001283 s390_dfp_cmp_t cmp;
floriane38f6412012-12-21 17:32:12 +00001284
1285 h1 = s390_isel_dfp_expr(env, arg1);
1286 h2 = s390_isel_dfp_expr(env, arg2);
1287 cc_s390 = newVRegI(env);
floriane38f6412012-12-21 17:32:12 +00001288
florian20c6bca2012-12-26 17:47:19 +00001289 switch(expr->Iex.Binop.op) {
1290 case Iop_CmpD64: cmp = S390_DFP_COMPARE; break;
1291 case Iop_CmpExpD64: cmp = S390_DFP_COMPARE_EXP; break;
1292 default: goto irreducible;
1293 }
1294 addInstr(env, s390_insn_dfp_compare(8, cmp, cc_s390, h1, h2));
floriane38f6412012-12-21 17:32:12 +00001295
florian2d3d87f2012-12-21 21:05:17 +00001296 return convert_s390_to_vex_dfpcc(env, cc_s390);
floriane38f6412012-12-21 17:32:12 +00001297 }
1298
florian20c6bca2012-12-26 17:47:19 +00001299 case Iop_CmpD128:
1300 case Iop_CmpExpD128: {
floriane38f6412012-12-21 17:32:12 +00001301 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15, cc_s390;
florian20c6bca2012-12-26 17:47:19 +00001302 s390_dfp_cmp_t cmp;
floriane38f6412012-12-21 17:32:12 +00001303
1304 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, arg1); /* 1st operand */
1305 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, arg2); /* 2nd operand */
1306 cc_s390 = newVRegI(env);
1307
1308 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1309 f12 = make_fpr(12);
1310 f13 = make_fpr(13);
1311 f14 = make_fpr(14);
1312 f15 = make_fpr(15);
1313
1314 /* 1st operand --> (f12, f14) */
1315 addInstr(env, s390_insn_move(8, f12, op1_hi));
1316 addInstr(env, s390_insn_move(8, f14, op1_lo));
1317
1318 /* 2nd operand --> (f13, f15) */
1319 addInstr(env, s390_insn_move(8, f13, op2_hi));
1320 addInstr(env, s390_insn_move(8, f15, op2_lo));
1321
florian20c6bca2012-12-26 17:47:19 +00001322 switch(expr->Iex.Binop.op) {
1323 case Iop_CmpD128: cmp = S390_DFP_COMPARE; break;
1324 case Iop_CmpExpD128: cmp = S390_DFP_COMPARE_EXP; break;
1325 default: goto irreducible;
1326 }
1327 addInstr(env, s390_insn_dfp128_compare(16, cmp, cc_s390, f12, f14,
1328 f13, f15));
floriane38f6412012-12-21 17:32:12 +00001329
florian2d3d87f2012-12-21 21:05:17 +00001330 return convert_s390_to_vex_dfpcc(env, cc_s390);
floriane38f6412012-12-21 17:32:12 +00001331 }
1332
sewardj2019a972011-03-07 16:04:07 +00001333 case Iop_Add8:
1334 case Iop_Add16:
1335 case Iop_Add32:
1336 case Iop_Add64:
1337 opkind = S390_ALU_ADD;
1338 break;
1339
1340 case Iop_Sub8:
1341 case Iop_Sub16:
1342 case Iop_Sub32:
1343 case Iop_Sub64:
1344 opkind = S390_ALU_SUB;
1345 is_commutative = False;
1346 break;
1347
1348 case Iop_And8:
1349 case Iop_And16:
1350 case Iop_And32:
1351 case Iop_And64:
1352 opkind = S390_ALU_AND;
1353 break;
1354
1355 case Iop_Or8:
1356 case Iop_Or16:
1357 case Iop_Or32:
1358 case Iop_Or64:
1359 opkind = S390_ALU_OR;
1360 break;
1361
1362 case Iop_Xor8:
1363 case Iop_Xor16:
1364 case Iop_Xor32:
1365 case Iop_Xor64:
1366 opkind = S390_ALU_XOR;
1367 break;
1368
1369 case Iop_Shl8:
1370 case Iop_Shl16:
1371 case Iop_Shl32:
1372 case Iop_Shl64:
1373 opkind = S390_ALU_LSH;
1374 is_commutative = False;
1375 break;
1376
1377 case Iop_Shr8:
1378 case Iop_Shr16:
1379 case Iop_Shr32:
1380 case Iop_Shr64:
1381 opkind = S390_ALU_RSH;
1382 is_commutative = False;
1383 break;
1384
1385 case Iop_Sar8:
1386 case Iop_Sar16:
1387 case Iop_Sar32:
1388 case Iop_Sar64:
1389 opkind = S390_ALU_RSHA;
1390 is_commutative = False;
1391 break;
1392
1393 default:
1394 goto irreducible;
1395 }
1396
1397 /* Pattern match: 0 - arg1 --> -arg1 */
1398 if (opkind == S390_ALU_SUB && s390_expr_is_const_zero(arg1)) {
1399 res = newVRegI(env);
1400 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1401 insn = s390_insn_unop(size, S390_NEGATE, res, op2);
1402 addInstr(env, insn);
1403
1404 return res;
1405 }
1406
1407 if (is_commutative) {
1408 order_commutative_operands(arg1, arg2);
1409 }
1410
1411 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1412 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1413 res = newVRegI(env);
florian5e0f2042012-08-20 13:44:29 +00001414
1415 /* As right shifts of one/two byte opreands are implemented using a
1416 4-byte shift op, we first need to zero/sign-extend the shiftee. */
1417 switch (expr->Iex.Binop.op) {
1418 case Iop_Shr8:
1419 insn = s390_insn_unop(4, S390_ZERO_EXTEND_8, res, s390_opnd_reg(h1));
1420 break;
1421 case Iop_Shr16:
1422 insn = s390_insn_unop(4, S390_ZERO_EXTEND_16, res, s390_opnd_reg(h1));
1423 break;
1424 case Iop_Sar8:
1425 insn = s390_insn_unop(4, S390_SIGN_EXTEND_8, res, s390_opnd_reg(h1));
1426 break;
1427 case Iop_Sar16:
1428 insn = s390_insn_unop(4, S390_SIGN_EXTEND_16, res, s390_opnd_reg(h1));
1429 break;
1430 default:
1431 insn = s390_insn_move(size, res, h1);
1432 break;
1433 }
1434 addInstr(env, insn);
1435
sewardj2019a972011-03-07 16:04:07 +00001436 insn = s390_insn_alu(size, opkind, res, op2);
1437
1438 addInstr(env, insn);
1439
1440 return res;
1441 }
1442
1443 /* --------- UNARY OP --------- */
1444 case Iex_Unop: {
1445 static s390_opnd_RMI mask = { S390_OPND_IMMEDIATE };
1446 static s390_opnd_RMI shift = { S390_OPND_IMMEDIATE };
1447 s390_opnd_RMI opnd;
1448 s390_insn *insn;
1449 IRExpr *arg;
1450 HReg dst, h1;
1451 IROp unop, binop;
1452
1453 arg = expr->Iex.Unop.arg;
1454
1455 /* Special cases are handled here */
1456
1457 /* 32-bit multiply with 32-bit result or
1458 64-bit multiply with 64-bit result */
1459 unop = expr->Iex.Unop.op;
1460 binop = arg->Iex.Binop.op;
1461
1462 if ((arg->tag == Iex_Binop &&
1463 ((unop == Iop_64to32 &&
1464 (binop == Iop_MullS32 || binop == Iop_MullU32)) ||
1465 (unop == Iop_128to64 &&
1466 (binop == Iop_MullS64 || binop == Iop_MullU64))))) {
1467 h1 = s390_isel_int_expr(env, arg->Iex.Binop.arg1); /* 1st opnd */
1468 opnd = s390_isel_int_expr_RMI(env, arg->Iex.Binop.arg2); /* 2nd opnd */
1469 dst = newVRegI(env); /* Result goes into a new register */
1470 addInstr(env, s390_insn_move(size, dst, h1));
1471 addInstr(env, s390_insn_alu(size, S390_ALU_MUL, dst, opnd));
1472
1473 return dst;
1474 }
1475
florian4d71a082011-12-18 00:08:17 +00001476 if (unop == Iop_ReinterpF64asI64 || unop == Iop_ReinterpF32asI32) {
sewardj2019a972011-03-07 16:04:07 +00001477 dst = newVRegI(env);
1478 h1 = s390_isel_float_expr(env, arg); /* Process the operand */
1479 addInstr(env, s390_insn_move(size, dst, h1));
1480
1481 return dst;
1482 }
1483
floriane38f6412012-12-21 17:32:12 +00001484 if (unop == Iop_ReinterpD64asI64) {
1485 dst = newVRegI(env);
1486 h1 = s390_isel_dfp_expr(env, arg); /* Process the operand */
1487 addInstr(env, s390_insn_move(size, dst, h1));
1488
1489 return dst;
1490 }
1491
floriance9e3db2012-12-27 20:14:03 +00001492 if (unop == Iop_ExtractSigD64) {
1493 dst = newVRegI(env);
1494 h1 = s390_isel_dfp_expr(env, arg); /* Process the operand */
1495 addInstr(env,
1496 s390_insn_dfp_unop(size, S390_DFP_EXTRACT_SIG_D64, dst, h1));
1497 return dst;
1498 }
1499
1500 if (unop == Iop_ExtractSigD128) {
1501 HReg op_hi, op_lo, f13, f15;
1502 dst = newVRegI(env);
1503 s390_isel_dfp128_expr(&op_hi, &op_lo, env, arg); /* Process operand */
1504
1505 /* We use non-virtual registers r13 and r15 as pair */
1506 f13 = make_fpr(13);
1507 f15 = make_fpr(15);
1508
1509 /* operand --> (f13, f15) */
1510 addInstr(env, s390_insn_move(8, f13, op_hi));
1511 addInstr(env, s390_insn_move(8, f15, op_lo));
1512
1513 addInstr(env, s390_insn_dfp128_unop(size, S390_DFP_EXTRACT_SIG_D128,
1514 dst, f13, f15));
1515 return dst;
1516 }
1517
sewardj2019a972011-03-07 16:04:07 +00001518 /* Expressions whose argument is 1-bit wide */
1519 if (typeOfIRExpr(env->type_env, arg) == Ity_I1) {
1520 s390_cc_t cond = s390_isel_cc(env, arg);
1521 dst = newVRegI(env); /* Result goes into a new register */
1522 addInstr(env, s390_insn_cc2bool(dst, cond));
1523
1524 switch (unop) {
1525 case Iop_1Uto8:
1526 case Iop_1Uto32:
florian5f27dcf2012-08-04 04:25:30 +00001527 /* Zero extend */
1528 mask.variant.imm = 1;
1529 addInstr(env, s390_insn_alu(4, S390_ALU_AND, dst, mask));
1530 break;
1531
sewardj2019a972011-03-07 16:04:07 +00001532 case Iop_1Uto64:
florian5f27dcf2012-08-04 04:25:30 +00001533 /* Zero extend */
1534 mask.variant.imm = 1;
1535 addInstr(env, s390_insn_alu(8, S390_ALU_AND, dst, mask));
sewardj2019a972011-03-07 16:04:07 +00001536 break;
1537
1538 case Iop_1Sto8:
1539 case Iop_1Sto16:
1540 case Iop_1Sto32:
1541 shift.variant.imm = 31;
1542 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, dst, shift));
1543 addInstr(env, s390_insn_alu(4, S390_ALU_RSHA, dst, shift));
1544 break;
1545
1546 case Iop_1Sto64:
1547 shift.variant.imm = 63;
1548 addInstr(env, s390_insn_alu(8, S390_ALU_LSH, dst, shift));
1549 addInstr(env, s390_insn_alu(8, S390_ALU_RSHA, dst, shift));
1550 break;
1551
1552 default:
1553 goto irreducible;
1554 }
1555
1556 return dst;
1557 }
1558
1559 /* Regular processing */
1560
1561 if (unop == Iop_128to64) {
1562 HReg dst_hi, dst_lo;
1563
1564 s390_isel_int128_expr(&dst_hi, &dst_lo, env, arg);
1565 return dst_lo;
1566 }
1567
1568 if (unop == Iop_128HIto64) {
1569 HReg dst_hi, dst_lo;
1570
1571 s390_isel_int128_expr(&dst_hi, &dst_lo, env, arg);
1572 return dst_hi;
1573 }
1574
1575 dst = newVRegI(env); /* Result goes into a new register */
1576 opnd = s390_isel_int_expr_RMI(env, arg); /* Process the operand */
1577
1578 switch (unop) {
1579 case Iop_8Uto16:
1580 case Iop_8Uto32:
1581 case Iop_8Uto64:
1582 insn = s390_insn_unop(size, S390_ZERO_EXTEND_8, dst, opnd);
1583 break;
1584
1585 case Iop_16Uto32:
1586 case Iop_16Uto64:
1587 insn = s390_insn_unop(size, S390_ZERO_EXTEND_16, dst, opnd);
1588 break;
1589
1590 case Iop_32Uto64:
1591 insn = s390_insn_unop(size, S390_ZERO_EXTEND_32, dst, opnd);
1592 break;
1593
1594 case Iop_8Sto16:
1595 case Iop_8Sto32:
1596 case Iop_8Sto64:
1597 insn = s390_insn_unop(size, S390_SIGN_EXTEND_8, dst, opnd);
1598 break;
1599
1600 case Iop_16Sto32:
1601 case Iop_16Sto64:
1602 insn = s390_insn_unop(size, S390_SIGN_EXTEND_16, dst, opnd);
1603 break;
1604
1605 case Iop_32Sto64:
1606 insn = s390_insn_unop(size, S390_SIGN_EXTEND_32, dst, opnd);
1607 break;
1608
1609 case Iop_64to8:
1610 case Iop_64to16:
1611 case Iop_64to32:
1612 case Iop_32to8:
1613 case Iop_32to16:
1614 case Iop_16to8:
1615 /* Down-casts are no-ops. Upstream operations will only look at
1616 the bytes that make up the result of the down-cast. So there
1617 is no point setting the other bytes to 0. */
1618 insn = s390_opnd_copy(8, dst, opnd);
1619 break;
1620
1621 case Iop_64HIto32:
1622 addInstr(env, s390_opnd_copy(8, dst, opnd));
1623 shift.variant.imm = 32;
1624 insn = s390_insn_alu(8, S390_ALU_RSH, dst, shift);
1625 break;
1626
1627 case Iop_32HIto16:
1628 addInstr(env, s390_opnd_copy(4, dst, opnd));
1629 shift.variant.imm = 16;
1630 insn = s390_insn_alu(4, S390_ALU_RSH, dst, shift);
1631 break;
1632
1633 case Iop_16HIto8:
1634 addInstr(env, s390_opnd_copy(2, dst, opnd));
1635 shift.variant.imm = 8;
1636 insn = s390_insn_alu(2, S390_ALU_RSH, dst, shift);
1637 break;
1638
1639 case Iop_Not8:
1640 case Iop_Not16:
1641 case Iop_Not32:
1642 case Iop_Not64:
1643 /* XOR with ffff... */
1644 mask.variant.imm = ~(ULong)0;
1645 addInstr(env, s390_opnd_copy(size, dst, opnd));
1646 insn = s390_insn_alu(size, S390_ALU_XOR, dst, mask);
1647 break;
1648
1649 case Iop_Left8:
1650 case Iop_Left16:
1651 case Iop_Left32:
1652 case Iop_Left64:
1653 addInstr(env, s390_insn_unop(size, S390_NEGATE, dst, opnd));
1654 insn = s390_insn_alu(size, S390_ALU_OR, dst, opnd);
1655 break;
1656
1657 case Iop_CmpwNEZ32:
1658 case Iop_CmpwNEZ64: {
1659 /* Use the fact that x | -x == 0 iff x == 0. Otherwise, either X
1660 or -X will have a 1 in the MSB. */
1661 addInstr(env, s390_insn_unop(size, S390_NEGATE, dst, opnd));
1662 addInstr(env, s390_insn_alu(size, S390_ALU_OR, dst, opnd));
1663 shift.variant.imm = (unop == Iop_CmpwNEZ32) ? 31 : 63;
1664 addInstr(env, s390_insn_alu(size, S390_ALU_RSHA, dst, shift));
1665 return dst;
1666 }
1667
1668 case Iop_Clz64: {
1669 HReg r10, r11;
1670
sewardj611b06e2011-03-24 08:57:29 +00001671 /* This will be implemented using FLOGR, if possible. So we need to
1672 set aside a pair of non-virtual registers. The result (number of
1673 left-most zero bits) will be in r10. The value in r11 is unspecified
1674 and must not be used. */
florian297b6062012-05-08 20:16:17 +00001675 r10 = make_gpr(10);
1676 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001677
sewardj611b06e2011-03-24 08:57:29 +00001678 addInstr(env, s390_insn_clz(8, r10, r11, opnd));
sewardj2019a972011-03-07 16:04:07 +00001679 addInstr(env, s390_insn_move(8, dst, r10));
1680 return dst;
1681 }
1682
1683 default:
1684 goto irreducible;
1685 }
1686
1687 addInstr(env, insn);
1688
1689 return dst;
1690 }
1691
1692 /* --------- GET --------- */
1693 case Iex_Get: {
1694 HReg dst = newVRegI(env);
1695 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
1696
1697 /* We never load more than 8 bytes from the guest state, because the
1698 floating point register pair is not contiguous. */
1699 vassert(size <= 8);
1700
1701 addInstr(env, s390_insn_load(size, dst, am));
1702
1703 return dst;
1704 }
1705
1706 case Iex_GetI:
1707 /* not needed */
1708 break;
1709
1710 /* --------- CCALL --------- */
1711 case Iex_CCall: {
1712 HReg dst = newVRegI(env);
1713
1714 doHelperCall(env, False, NULL, expr->Iex.CCall.cee,
florian01ed6e72012-05-27 16:52:43 +00001715 expr->Iex.CCall.args, dst);
sewardj2019a972011-03-07 16:04:07 +00001716 return dst;
1717 }
1718
1719 /* --------- LITERAL --------- */
1720
1721 /* Load a literal into a register. Create a "load immediate"
1722 v-insn and return the register. */
1723 case Iex_Const: {
1724 ULong value;
1725 HReg dst = newVRegI(env);
1726 const IRConst *con = expr->Iex.Const.con;
1727
1728 /* Bitwise copy of the value. No sign/zero-extension */
1729 switch (con->tag) {
1730 case Ico_U64: value = con->Ico.U64; break;
1731 case Ico_U32: value = con->Ico.U32; break;
1732 case Ico_U16: value = con->Ico.U16; break;
1733 case Ico_U8: value = con->Ico.U8; break;
1734 default: vpanic("s390_isel_int_expr: invalid constant");
1735 }
1736
1737 addInstr(env, s390_insn_load_immediate(size, dst, value));
1738
1739 return dst;
1740 }
1741
1742 /* --------- MULTIPLEX --------- */
1743 case Iex_Mux0X: {
1744 IRExpr *cond_expr;
sewardj009230b2013-01-26 11:47:55 +00001745 HReg dst, rX;
1746 s390_opnd_RMI r0;
sewardj2019a972011-03-07 16:04:07 +00001747
1748 cond_expr = expr->Iex.Mux0X.cond;
1749
sewardj009230b2013-01-26 11:47:55 +00001750 vassert(typeOfIRExpr(env->type_env, cond_expr) == Ity_I1);
1751
sewardj2019a972011-03-07 16:04:07 +00001752 dst = newVRegI(env);
1753 r0 = s390_isel_int_expr_RMI(env, expr->Iex.Mux0X.expr0);
1754 rX = s390_isel_int_expr(env, expr->Iex.Mux0X.exprX);
1755 size = sizeofIRType(typeOfIRExpr(env->type_env, expr->Iex.Mux0X.exprX));
1756
sewardj009230b2013-01-26 11:47:55 +00001757 s390_cc_t cc = s390_isel_cc(env, cond_expr);
sewardj2019a972011-03-07 16:04:07 +00001758
sewardj2019a972011-03-07 16:04:07 +00001759 addInstr(env, s390_insn_move(size, dst, rX));
sewardj009230b2013-01-26 11:47:55 +00001760 addInstr(env, s390_insn_cond_move(size, s390_cc_invert(cc), dst, r0));
sewardj2019a972011-03-07 16:04:07 +00001761 return dst;
1762 }
1763
1764 default:
1765 break;
1766 }
1767
1768 /* We get here if no pattern matched. */
1769 irreducible:
1770 ppIRExpr(expr);
1771 vpanic("s390_isel_int_expr: cannot reduce tree");
1772}
1773
1774
1775static HReg
1776s390_isel_int_expr(ISelEnv *env, IRExpr *expr)
1777{
1778 HReg dst = s390_isel_int_expr_wrk(env, expr);
1779
1780 /* Sanity checks ... */
1781 vassert(hregClass(dst) == HRcInt64);
1782 vassert(hregIsVirtual(dst));
1783
1784 return dst;
1785}
1786
1787
1788static s390_opnd_RMI
1789s390_isel_int_expr_RMI(ISelEnv *env, IRExpr *expr)
1790{
1791 IRType ty = typeOfIRExpr(env->type_env, expr);
1792 s390_opnd_RMI dst;
1793
1794 vassert(ty == Ity_I8 || ty == Ity_I16 || ty == Ity_I32 ||
1795 ty == Ity_I64);
1796
1797 if (expr->tag == Iex_Load) {
1798 dst.tag = S390_OPND_AMODE;
1799 dst.variant.am = s390_isel_amode(env, expr->Iex.Load.addr);
1800 } else if (expr->tag == Iex_Get) {
1801 dst.tag = S390_OPND_AMODE;
1802 dst.variant.am = s390_amode_for_guest_state(expr->Iex.Get.offset);
1803 } else if (expr->tag == Iex_Const) {
1804 ULong value;
1805
1806 /* The bit pattern for the value will be stored as is in the least
1807 significant bits of VALUE. */
1808 switch (expr->Iex.Const.con->tag) {
1809 case Ico_U1: value = expr->Iex.Const.con->Ico.U1; break;
1810 case Ico_U8: value = expr->Iex.Const.con->Ico.U8; break;
1811 case Ico_U16: value = expr->Iex.Const.con->Ico.U16; break;
1812 case Ico_U32: value = expr->Iex.Const.con->Ico.U32; break;
1813 case Ico_U64: value = expr->Iex.Const.con->Ico.U64; break;
1814 default:
1815 vpanic("s390_isel_int_expr_RMI");
1816 }
1817
1818 dst.tag = S390_OPND_IMMEDIATE;
1819 dst.variant.imm = value;
1820 } else {
1821 dst.tag = S390_OPND_REG;
1822 dst.variant.reg = s390_isel_int_expr(env, expr);
1823 }
1824
1825 return dst;
1826}
1827
1828
1829/*---------------------------------------------------------*/
1830/*--- ISEL: Floating point expressions (128 bit) ---*/
1831/*---------------------------------------------------------*/
1832static void
1833s390_isel_float128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
1834 IRExpr *expr)
1835{
1836 IRType ty = typeOfIRExpr(env->type_env, expr);
1837
1838 vassert(ty == Ity_F128);
1839
sewardj2019a972011-03-07 16:04:07 +00001840 switch (expr->tag) {
1841 case Iex_RdTmp:
1842 /* Return the virtual registers that hold the temporary. */
1843 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
1844 return;
1845
1846 /* --------- LOAD --------- */
1847 case Iex_Load: {
1848 IRExpr *addr_hi, *addr_lo;
1849 s390_amode *am_hi, *am_lo;
1850
1851 if (expr->Iex.Load.end != Iend_BE)
1852 goto irreducible;
1853
1854 addr_hi = expr->Iex.Load.addr;
1855 addr_lo = IRExpr_Binop(Iop_Add64, addr_hi, mkU64(8));
1856
1857 am_hi = s390_isel_amode(env, addr_hi);
1858 am_lo = s390_isel_amode(env, addr_lo);
1859
1860 *dst_hi = newVRegF(env);
1861 *dst_lo = newVRegF(env);
1862 addInstr(env, s390_insn_load(8, *dst_hi, am_hi));
1863 addInstr(env, s390_insn_load(8, *dst_hi, am_lo));
1864 return;
1865 }
1866
1867
1868 /* --------- GET --------- */
1869 case Iex_Get:
1870 /* This is not supported because loading 128-bit from the guest
1871 state is almost certainly wrong. Use get_fpr_pair instead. */
1872 vpanic("Iex_Get with F128 data");
1873
1874 /* --------- 4-ary OP --------- */
1875 case Iex_Qop:
1876 vpanic("Iex_Qop with F128 data");
1877
1878 /* --------- TERNARY OP --------- */
1879 case Iex_Triop: {
florian420bfa92012-06-02 20:29:22 +00001880 IRTriop *triop = expr->Iex.Triop.details;
1881 IROp op = triop->op;
1882 IRExpr *left = triop->arg2;
1883 IRExpr *right = triop->arg3;
sewardj2019a972011-03-07 16:04:07 +00001884 s390_bfp_binop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00001885 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15;
1886
1887 s390_isel_float128_expr(&op1_hi, &op1_lo, env, left); /* 1st operand */
1888 s390_isel_float128_expr(&op2_hi, &op2_lo, env, right); /* 2nd operand */
1889
1890 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1891 f12 = make_fpr(12);
1892 f13 = make_fpr(13);
1893 f14 = make_fpr(14);
1894 f15 = make_fpr(15);
1895
1896 /* 1st operand --> (f12, f14) */
1897 addInstr(env, s390_insn_move(8, f12, op1_hi));
1898 addInstr(env, s390_insn_move(8, f14, op1_lo));
1899
1900 /* 2nd operand --> (f13, f15) */
1901 addInstr(env, s390_insn_move(8, f13, op2_hi));
1902 addInstr(env, s390_insn_move(8, f15, op2_lo));
1903
1904 switch (op) {
1905 case Iop_AddF128: bfpop = S390_BFP_ADD; break;
1906 case Iop_SubF128: bfpop = S390_BFP_SUB; break;
1907 case Iop_MulF128: bfpop = S390_BFP_MUL; break;
1908 case Iop_DivF128: bfpop = S390_BFP_DIV; break;
1909 default:
1910 goto irreducible;
1911 }
1912
florian2c74d242012-09-12 19:38:42 +00001913 set_bfp_rounding_mode_in_fpc(env, triop->arg1);
1914 addInstr(env, s390_insn_bfp128_binop(16, bfpop, f12, f14, f13, f15));
sewardj2019a972011-03-07 16:04:07 +00001915
1916 /* Move result to virtual destination register */
1917 *dst_hi = newVRegF(env);
1918 *dst_lo = newVRegF(env);
1919 addInstr(env, s390_insn_move(8, *dst_hi, f12));
1920 addInstr(env, s390_insn_move(8, *dst_lo, f14));
1921
1922 return;
1923 }
1924
1925 /* --------- BINARY OP --------- */
1926 case Iex_Binop: {
1927 HReg op_hi, op_lo, f12, f13, f14, f15;
sewardj2019a972011-03-07 16:04:07 +00001928
1929 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1930 f12 = make_fpr(12);
1931 f13 = make_fpr(13);
1932 f14 = make_fpr(14);
1933 f15 = make_fpr(15);
1934
1935 switch (expr->Iex.Binop.op) {
1936 case Iop_SqrtF128:
1937 s390_isel_float128_expr(&op_hi, &op_lo, env, expr->Iex.Binop.arg2);
1938
1939 /* operand --> (f13, f15) */
1940 addInstr(env, s390_insn_move(8, f13, op_hi));
1941 addInstr(env, s390_insn_move(8, f15, op_lo));
1942
florian2c74d242012-09-12 19:38:42 +00001943 set_bfp_rounding_mode_in_fpc(env, expr->Iex.Binop.arg1);
1944 addInstr(env, s390_insn_bfp128_unop(16, S390_BFP_SQRT, f12, f14,
1945 f13, f15));
sewardj2019a972011-03-07 16:04:07 +00001946
1947 /* Move result to virtual destination registers */
1948 *dst_hi = newVRegF(env);
1949 *dst_lo = newVRegF(env);
1950 addInstr(env, s390_insn_move(8, *dst_hi, f12));
1951 addInstr(env, s390_insn_move(8, *dst_lo, f14));
1952 return;
1953
1954 case Iop_F64HLtoF128:
1955 *dst_hi = s390_isel_float_expr(env, expr->Iex.Binop.arg1);
1956 *dst_lo = s390_isel_float_expr(env, expr->Iex.Binop.arg2);
1957 return;
1958
1959 default:
1960 goto irreducible;
1961 }
1962 }
1963
1964 /* --------- UNARY OP --------- */
1965 case Iex_Unop: {
florian66e596d2012-09-07 15:00:53 +00001966 IRExpr *left = expr->Iex.Unop.arg;
sewardj2019a972011-03-07 16:04:07 +00001967 s390_bfp_unop_t bfpop;
florian6dc90242012-12-21 21:43:00 +00001968 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00001969 HReg op_hi, op_lo, op, f12, f13, f14, f15;
1970
1971 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1972 f12 = make_fpr(12);
1973 f13 = make_fpr(13);
1974 f14 = make_fpr(14);
1975 f15 = make_fpr(15);
1976
florian66e596d2012-09-07 15:00:53 +00001977 switch (expr->Iex.Unop.op) {
florian3f3e50d2012-09-13 03:13:26 +00001978 case Iop_NegF128:
1979 if (left->tag == Iex_Unop &&
1980 (left->Iex.Unop.op == Iop_AbsF32 ||
1981 left->Iex.Unop.op == Iop_AbsF64))
1982 bfpop = S390_BFP_NABS;
1983 else
1984 bfpop = S390_BFP_NEG;
1985 goto float128_opnd;
florian9fcff4c2012-09-10 03:09:04 +00001986 case Iop_AbsF128: bfpop = S390_BFP_ABS; goto float128_opnd;
1987 case Iop_I32StoF128: conv = S390_BFP_I32_TO_F128; goto convert_int;
1988 case Iop_I64StoF128: conv = S390_BFP_I64_TO_F128; goto convert_int;
1989 case Iop_I32UtoF128: conv = S390_BFP_U32_TO_F128; goto convert_int;
1990 case Iop_I64UtoF128: conv = S390_BFP_U64_TO_F128; goto convert_int;
1991 case Iop_F32toF128: conv = S390_BFP_F32_TO_F128; goto convert_float;
1992 case Iop_F64toF128: conv = S390_BFP_F64_TO_F128; goto convert_float;
sewardj2019a972011-03-07 16:04:07 +00001993 default:
1994 goto irreducible;
1995 }
1996
1997 float128_opnd:
1998 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
1999
2000 /* operand --> (f13, f15) */
2001 addInstr(env, s390_insn_move(8, f13, op_hi));
2002 addInstr(env, s390_insn_move(8, f15, op_lo));
2003
florian2c74d242012-09-12 19:38:42 +00002004 addInstr(env, s390_insn_bfp128_unop(16, bfpop, f12, f14, f13, f15));
sewardj2019a972011-03-07 16:04:07 +00002005 goto move_dst;
2006
2007 convert_float:
2008 op = s390_isel_float_expr(env, left);
florian9fcff4c2012-09-10 03:09:04 +00002009 addInstr(env, s390_insn_bfp128_convert_to(16, conv, f12, f14, op));
sewardj2019a972011-03-07 16:04:07 +00002010 goto move_dst;
2011
2012 convert_int:
2013 op = s390_isel_int_expr(env, left);
florian9fcff4c2012-09-10 03:09:04 +00002014 addInstr(env, s390_insn_bfp128_convert_to(16, conv, f12, f14, op));
sewardj2019a972011-03-07 16:04:07 +00002015 goto move_dst;
2016
2017 move_dst:
2018 /* Move result to virtual destination registers */
2019 *dst_hi = newVRegF(env);
2020 *dst_lo = newVRegF(env);
2021 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2022 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2023 return;
2024 }
2025
2026 default:
2027 goto irreducible;
2028 }
2029
2030 /* We get here if no pattern matched. */
2031 irreducible:
2032 ppIRExpr(expr);
florian4ebaa772012-12-20 19:44:18 +00002033 vpanic("s390_isel_float128_expr: cannot reduce tree");
sewardj2019a972011-03-07 16:04:07 +00002034}
2035
2036/* Compute a 128-bit value into two 64-bit registers. These may be either
2037 real or virtual regs; in any case they must not be changed by subsequent
2038 code emitted by the caller. */
2039static void
2040s390_isel_float128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
2041{
2042 s390_isel_float128_expr_wrk(dst_hi, dst_lo, env, expr);
2043
2044 /* Sanity checks ... */
2045 vassert(hregIsVirtual(*dst_hi));
2046 vassert(hregIsVirtual(*dst_lo));
2047 vassert(hregClass(*dst_hi) == HRcFlt64);
2048 vassert(hregClass(*dst_lo) == HRcFlt64);
2049}
2050
2051
2052/*---------------------------------------------------------*/
2053/*--- ISEL: Floating point expressions (64 bit) ---*/
2054/*---------------------------------------------------------*/
2055
2056static HReg
2057s390_isel_float_expr_wrk(ISelEnv *env, IRExpr *expr)
2058{
2059 IRType ty = typeOfIRExpr(env->type_env, expr);
2060 UChar size;
2061
2062 vassert(ty == Ity_F32 || ty == Ity_F64);
2063
2064 size = sizeofIRType(ty);
2065
2066 switch (expr->tag) {
2067 case Iex_RdTmp:
2068 /* Return the virtual register that holds the temporary. */
2069 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
2070
2071 /* --------- LOAD --------- */
2072 case Iex_Load: {
2073 HReg dst = newVRegF(env);
2074 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
2075
2076 if (expr->Iex.Load.end != Iend_BE)
2077 goto irreducible;
2078
2079 addInstr(env, s390_insn_load(size, dst, am));
2080
2081 return dst;
2082 }
2083
2084 /* --------- GET --------- */
2085 case Iex_Get: {
2086 HReg dst = newVRegF(env);
2087 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
2088
2089 addInstr(env, s390_insn_load(size, dst, am));
2090
2091 return dst;
2092 }
2093
2094 /* --------- LITERAL --------- */
2095
2096 /* Load a literal into a register. Create a "load immediate"
2097 v-insn and return the register. */
2098 case Iex_Const: {
2099 ULong value;
2100 HReg dst = newVRegF(env);
2101 const IRConst *con = expr->Iex.Const.con;
2102
2103 /* Bitwise copy of the value. No sign/zero-extension */
2104 switch (con->tag) {
2105 case Ico_F32i: value = con->Ico.F32i; break;
2106 case Ico_F64i: value = con->Ico.F64i; break;
2107 default: vpanic("s390_isel_float_expr: invalid constant");
2108 }
2109
2110 if (value != 0) vpanic("cannot load immediate floating point constant");
2111
2112 addInstr(env, s390_insn_load_immediate(size, dst, value));
2113
2114 return dst;
2115 }
2116
2117 /* --------- 4-ary OP --------- */
2118 case Iex_Qop: {
2119 HReg op1, op2, op3, dst;
2120 s390_bfp_triop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002121
florian5906a6b2012-10-16 02:53:33 +00002122 op3 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg2);
florian96d7cc32012-06-01 20:41:24 +00002123 op2 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg3);
florian5906a6b2012-10-16 02:53:33 +00002124 op1 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg4);
sewardj2019a972011-03-07 16:04:07 +00002125 dst = newVRegF(env);
2126 addInstr(env, s390_insn_move(size, dst, op1));
2127
florian96d7cc32012-06-01 20:41:24 +00002128 switch (expr->Iex.Qop.details->op) {
sewardj2019a972011-03-07 16:04:07 +00002129 case Iop_MAddF32:
2130 case Iop_MAddF64: bfpop = S390_BFP_MADD; break;
2131 case Iop_MSubF32:
2132 case Iop_MSubF64: bfpop = S390_BFP_MSUB; break;
2133
2134 default:
2135 goto irreducible;
2136 }
2137
florian2c74d242012-09-12 19:38:42 +00002138 set_bfp_rounding_mode_in_fpc(env, expr->Iex.Qop.details->arg1);
2139 addInstr(env, s390_insn_bfp_triop(size, bfpop, dst, op2, op3));
sewardj2019a972011-03-07 16:04:07 +00002140 return dst;
2141 }
2142
2143 /* --------- TERNARY OP --------- */
2144 case Iex_Triop: {
florian420bfa92012-06-02 20:29:22 +00002145 IRTriop *triop = expr->Iex.Triop.details;
2146 IROp op = triop->op;
2147 IRExpr *left = triop->arg2;
2148 IRExpr *right = triop->arg3;
sewardj2019a972011-03-07 16:04:07 +00002149 s390_bfp_binop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002150 HReg h1, op2, dst;
2151
2152 h1 = s390_isel_float_expr(env, left); /* Process 1st operand */
2153 op2 = s390_isel_float_expr(env, right); /* Process 2nd operand */
2154 dst = newVRegF(env);
2155 addInstr(env, s390_insn_move(size, dst, h1));
2156 switch (op) {
2157 case Iop_AddF32:
2158 case Iop_AddF64: bfpop = S390_BFP_ADD; break;
2159 case Iop_SubF32:
2160 case Iop_SubF64: bfpop = S390_BFP_SUB; break;
2161 case Iop_MulF32:
2162 case Iop_MulF64: bfpop = S390_BFP_MUL; break;
2163 case Iop_DivF32:
2164 case Iop_DivF64: bfpop = S390_BFP_DIV; break;
2165
2166 default:
2167 goto irreducible;
2168 }
2169
florian2c74d242012-09-12 19:38:42 +00002170 set_bfp_rounding_mode_in_fpc(env, triop->arg1);
2171 addInstr(env, s390_insn_bfp_binop(size, bfpop, dst, op2));
sewardj2019a972011-03-07 16:04:07 +00002172 return dst;
2173 }
2174
2175 /* --------- BINARY OP --------- */
2176 case Iex_Binop: {
2177 IROp op = expr->Iex.Binop.op;
florian9fcff4c2012-09-10 03:09:04 +00002178 IRExpr *irrm = expr->Iex.Binop.arg1;
sewardj2019a972011-03-07 16:04:07 +00002179 IRExpr *left = expr->Iex.Binop.arg2;
2180 HReg h1, dst;
florian6dc90242012-12-21 21:43:00 +00002181 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00002182
2183 switch (op) {
2184 case Iop_SqrtF32:
2185 case Iop_SqrtF64:
florian9fcff4c2012-09-10 03:09:04 +00002186 h1 = s390_isel_float_expr(env, left);
2187 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002188 set_bfp_rounding_mode_in_fpc(env, irrm);
2189 addInstr(env, s390_insn_bfp_unop(size, S390_BFP_SQRT, dst, h1));
florian9fcff4c2012-09-10 03:09:04 +00002190 return dst;
sewardj2019a972011-03-07 16:04:07 +00002191
florian9fcff4c2012-09-10 03:09:04 +00002192 case Iop_F64toF32: conv = S390_BFP_F64_TO_F32; goto convert_float;
2193 case Iop_I32StoF32: conv = S390_BFP_I32_TO_F32; goto convert_int;
2194 case Iop_I32UtoF32: conv = S390_BFP_U32_TO_F32; goto convert_int;
2195 case Iop_I64StoF32: conv = S390_BFP_I64_TO_F32; goto convert_int;
2196 case Iop_I64StoF64: conv = S390_BFP_I64_TO_F64; goto convert_int;
2197 case Iop_I64UtoF32: conv = S390_BFP_U64_TO_F32; goto convert_int;
2198 case Iop_I64UtoF64: conv = S390_BFP_U64_TO_F64; goto convert_int;
sewardj2019a972011-03-07 16:04:07 +00002199
florian9fcff4c2012-09-10 03:09:04 +00002200 convert_float:
2201 h1 = s390_isel_float_expr(env, left);
2202 goto convert;
florian1c8f7ff2012-09-01 00:12:11 +00002203
florian9fcff4c2012-09-10 03:09:04 +00002204 convert_int:
2205 h1 = s390_isel_int_expr(env, left);
2206 goto convert;
2207
florian2c74d242012-09-12 19:38:42 +00002208 convert: {
florian125e20d2012-10-07 15:42:37 +00002209 s390_bfp_round_t rounding_mode;
florian2c74d242012-09-12 19:38:42 +00002210 /* convert-from-fixed and load-rounded have a rounding mode field
2211 when the floating point extension facility is installed. */
florian9fcff4c2012-09-10 03:09:04 +00002212 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002213 if (s390_host_has_fpext) {
2214 rounding_mode = get_bfp_rounding_mode(env, irrm);
2215 } else {
2216 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +00002217 rounding_mode = S390_BFP_ROUND_PER_FPC;
florian2c74d242012-09-12 19:38:42 +00002218 }
florian9fcff4c2012-09-10 03:09:04 +00002219 addInstr(env, s390_insn_bfp_convert(size, conv, dst, h1,
2220 rounding_mode));
2221 return dst;
florian2c74d242012-09-12 19:38:42 +00002222 }
florian9fcff4c2012-09-10 03:09:04 +00002223
sewardj2019a972011-03-07 16:04:07 +00002224 default:
2225 goto irreducible;
2226
2227 case Iop_F128toF64:
2228 case Iop_F128toF32: {
florian9fcff4c2012-09-10 03:09:04 +00002229 HReg op_hi, op_lo, f13, f15;
florian125e20d2012-10-07 15:42:37 +00002230 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00002231
florian9fcff4c2012-09-10 03:09:04 +00002232 conv = op == Iop_F128toF32 ? S390_BFP_F128_TO_F32
2233 : S390_BFP_F128_TO_F64;
sewardj2019a972011-03-07 16:04:07 +00002234
florian9fcff4c2012-09-10 03:09:04 +00002235 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
sewardj2019a972011-03-07 16:04:07 +00002236
florian9fcff4c2012-09-10 03:09:04 +00002237 /* We use non-virtual registers as pairs (f13, f15) */
sewardj2019a972011-03-07 16:04:07 +00002238 f13 = make_fpr(13);
sewardj2019a972011-03-07 16:04:07 +00002239 f15 = make_fpr(15);
2240
2241 /* operand --> (f13, f15) */
2242 addInstr(env, s390_insn_move(8, f13, op_hi));
2243 addInstr(env, s390_insn_move(8, f15, op_lo));
2244
2245 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002246 /* load-rounded has a rounding mode field when the floating point
2247 extension facility is installed. */
2248 if (s390_host_has_fpext) {
2249 rounding_mode = get_bfp_rounding_mode(env, irrm);
2250 } else {
2251 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +00002252 rounding_mode = S390_BFP_ROUND_PER_FPC;
florian2c74d242012-09-12 19:38:42 +00002253 }
floriancc491a62012-09-10 23:44:37 +00002254 addInstr(env, s390_insn_bfp128_convert_from(size, conv, dst, f13, f15,
florian9fcff4c2012-09-10 03:09:04 +00002255 rounding_mode));
sewardj2019a972011-03-07 16:04:07 +00002256 return dst;
2257 }
2258 }
sewardj2019a972011-03-07 16:04:07 +00002259 }
2260
2261 /* --------- UNARY OP --------- */
2262 case Iex_Unop: {
2263 IROp op = expr->Iex.Unop.op;
2264 IRExpr *left = expr->Iex.Unop.arg;
2265 s390_bfp_unop_t bfpop;
florian6dc90242012-12-21 21:43:00 +00002266 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00002267 HReg h1, dst;
2268
2269 if (op == Iop_F128HItoF64 || op == Iop_F128LOtoF64) {
2270 HReg dst_hi, dst_lo;
2271
2272 s390_isel_float128_expr(&dst_hi, &dst_lo, env, left);
2273 return op == Iop_F128LOtoF64 ? dst_lo : dst_hi;
2274 }
2275
florian4d71a082011-12-18 00:08:17 +00002276 if (op == Iop_ReinterpI64asF64 || op == Iop_ReinterpI32asF32) {
sewardj2019a972011-03-07 16:04:07 +00002277 dst = newVRegF(env);
2278 h1 = s390_isel_int_expr(env, left); /* Process the operand */
2279 addInstr(env, s390_insn_move(size, dst, h1));
2280
2281 return dst;
2282 }
2283
2284 switch (op) {
2285 case Iop_NegF32:
2286 case Iop_NegF64:
2287 if (left->tag == Iex_Unop &&
florian3f3e50d2012-09-13 03:13:26 +00002288 (left->Iex.Unop.op == Iop_AbsF32 ||
2289 left->Iex.Unop.op == Iop_AbsF64))
sewardj2019a972011-03-07 16:04:07 +00002290 bfpop = S390_BFP_NABS;
2291 else
2292 bfpop = S390_BFP_NEG;
2293 break;
2294
2295 case Iop_AbsF32:
florian9fcff4c2012-09-10 03:09:04 +00002296 case Iop_AbsF64:
2297 bfpop = S390_BFP_ABS;
2298 break;
2299
2300 case Iop_I32StoF64: conv = S390_BFP_I32_TO_F64; goto convert_int1;
2301 case Iop_I32UtoF64: conv = S390_BFP_U32_TO_F64; goto convert_int1;
2302 case Iop_F32toF64: conv = S390_BFP_F32_TO_F64; goto convert_float1;
2303
2304 convert_float1:
2305 h1 = s390_isel_float_expr(env, left);
2306 goto convert1;
2307
2308 convert_int1:
2309 h1 = s390_isel_int_expr(env, left);
2310 goto convert1;
2311
2312 convert1:
2313 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002314 /* No rounding mode is needed for these conversions. Just stick
2315 one in. It won't be used later on. */
2316 addInstr(env, s390_insn_bfp_convert(size, conv, dst, h1,
florian125e20d2012-10-07 15:42:37 +00002317 S390_BFP_ROUND_NEAREST_EVEN));
florian9fcff4c2012-09-10 03:09:04 +00002318 return dst;
2319
sewardj2019a972011-03-07 16:04:07 +00002320 default:
2321 goto irreducible;
2322 }
2323
2324 /* Process operand */
florian9fcff4c2012-09-10 03:09:04 +00002325 h1 = s390_isel_float_expr(env, left);
sewardj2019a972011-03-07 16:04:07 +00002326 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002327 addInstr(env, s390_insn_bfp_unop(size, bfpop, dst, h1));
sewardj2019a972011-03-07 16:04:07 +00002328 return dst;
2329 }
2330
2331 default:
2332 goto irreducible;
2333 }
2334
2335 /* We get here if no pattern matched. */
2336 irreducible:
2337 ppIRExpr(expr);
2338 vpanic("s390_isel_float_expr: cannot reduce tree");
2339}
2340
2341
2342static HReg
2343s390_isel_float_expr(ISelEnv *env, IRExpr *expr)
2344{
2345 HReg dst = s390_isel_float_expr_wrk(env, expr);
2346
2347 /* Sanity checks ... */
2348 vassert(hregClass(dst) == HRcFlt64);
2349 vassert(hregIsVirtual(dst));
2350
2351 return dst;
2352}
2353
2354
2355/*---------------------------------------------------------*/
floriane38f6412012-12-21 17:32:12 +00002356/*--- ISEL: Decimal point expressions (128 bit) ---*/
2357/*---------------------------------------------------------*/
2358static void
2359s390_isel_dfp128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
2360 IRExpr *expr)
2361{
2362 IRType ty = typeOfIRExpr(env->type_env, expr);
2363
2364 vassert(ty == Ity_D128);
2365
2366 switch (expr->tag) {
2367 case Iex_RdTmp:
2368 /* Return the virtual registers that hold the temporary. */
2369 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
2370 return;
2371
2372 /* --------- LOAD --------- */
2373 case Iex_Load: {
2374 IRExpr *addr_hi, *addr_lo;
2375 s390_amode *am_hi, *am_lo;
2376
2377 if (expr->Iex.Load.end != Iend_BE)
2378 goto irreducible;
2379
2380 addr_hi = expr->Iex.Load.addr;
2381 addr_lo = IRExpr_Binop(Iop_Add64, addr_hi, mkU64(8));
2382
2383 am_hi = s390_isel_amode(env, addr_hi);
2384 am_lo = s390_isel_amode(env, addr_lo);
2385
2386 *dst_hi = newVRegF(env);
2387 *dst_lo = newVRegF(env);
2388 addInstr(env, s390_insn_load(8, *dst_hi, am_hi));
2389 addInstr(env, s390_insn_load(8, *dst_hi, am_lo));
2390 return;
2391 }
2392
2393 /* --------- GET --------- */
2394 case Iex_Get:
2395 /* This is not supported because loading 128-bit from the guest
2396 state is almost certainly wrong. Use get_dpr_pair instead. */
2397 vpanic("Iex_Get with D128 data");
2398
2399 /* --------- 4-ary OP --------- */
2400 case Iex_Qop:
2401 vpanic("Iex_Qop with D128 data");
2402
2403 /* --------- TERNARY OP --------- */
2404 case Iex_Triop: {
2405 IRTriop *triop = expr->Iex.Triop.details;
2406 IROp op = triop->op;
2407 IRExpr *irrm = triop->arg1;
2408 IRExpr *left = triop->arg2;
2409 IRExpr *right = triop->arg3;
2410 s390_dfp_round_t rounding_mode;
2411 s390_dfp_binop_t dfpop;
2412 HReg op1_hi, op1_lo, op2_hi, op2_lo, f9, f11, f12, f13, f14, f15;
2413
2414 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, left); /* 1st operand */
2415 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, right); /* 2nd operand */
2416
2417 /* We use non-virtual registers as pairs with (f9, f11) as op1,
2418 (f12, f14) as op2 and (f13, f15) as destination) */
2419 f9 = make_fpr(9);
2420 f11 = make_fpr(11);
2421 f12 = make_fpr(12);
2422 f13 = make_fpr(13);
2423 f14 = make_fpr(14);
2424 f15 = make_fpr(15);
2425
2426 /* 1st operand --> (f9, f11) */
2427 addInstr(env, s390_insn_move(8, f9, op1_hi));
2428 addInstr(env, s390_insn_move(8, f11, op1_lo));
2429
2430 /* 2nd operand --> (f12, f14) */
2431 addInstr(env, s390_insn_move(8, f12, op2_hi));
2432 addInstr(env, s390_insn_move(8, f14, op2_lo));
2433
2434 switch (op) {
2435 case Iop_AddD128: dfpop = S390_DFP_ADD; break;
2436 case Iop_SubD128: dfpop = S390_DFP_SUB; break;
2437 case Iop_MulD128: dfpop = S390_DFP_MUL; break;
2438 case Iop_DivD128: dfpop = S390_DFP_DIV; break;
2439 default:
2440 goto irreducible;
2441 }
2442
2443 /* DFP binary ops have insns with rounding mode field
2444 when the floating point extension facility is installed. */
2445 if (s390_host_has_fpext) {
2446 rounding_mode = get_dfp_rounding_mode(env, irrm);
2447 } else {
2448 set_dfp_rounding_mode_in_fpc(env, irrm);
2449 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2450 }
2451
2452 addInstr(env, s390_insn_dfp128_binop(16, dfpop, f13, f15, f9, f11,
2453 f12, f14, rounding_mode));
2454
2455 /* Move result to virtual destination register */
2456 *dst_hi = newVRegF(env);
2457 *dst_lo = newVRegF(env);
2458 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2459 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2460
2461 return;
2462 }
2463
2464 /* --------- BINARY OP --------- */
2465 case Iex_Binop: {
florian1b901d42013-01-01 22:19:24 +00002466
floriane38f6412012-12-21 17:32:12 +00002467 switch (expr->Iex.Binop.op) {
2468 case Iop_D64HLtoD128:
2469 *dst_hi = s390_isel_dfp_expr(env, expr->Iex.Binop.arg1);
2470 *dst_lo = s390_isel_dfp_expr(env, expr->Iex.Binop.arg2);
2471 return;
2472
florian1b901d42013-01-01 22:19:24 +00002473 case Iop_ShlD128:
2474 case Iop_ShrD128: {
2475 HReg op1_hi, op1_lo, op2, f9, f11, f13, f15;
2476 s390_dfp_intop_t intop;
2477 IRExpr *left = expr->Iex.Binop.arg1;
2478 IRExpr *right = expr->Iex.Binop.arg2;
2479
2480 switch (expr->Iex.Binop.op) {
2481 case Iop_ShlD128: intop = S390_DFP_SHIFT_LEFT; break;
2482 case Iop_ShrD128: intop = S390_DFP_SHIFT_RIGHT; break;
2483 default: goto irreducible;
2484 }
2485
2486 /* We use non-virtual registers as pairs (f9, f11) and (f13, f15)) */
2487 f9 = make_fpr(9); /* 128 bit dfp operand */
2488 f11 = make_fpr(11);
2489
2490 f13 = make_fpr(13); /* 128 bit dfp destination */
2491 f15 = make_fpr(15);
2492
2493 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, left); /* dfp operand */
2494 addInstr(env, s390_insn_move(8, f9, op1_hi));
2495 addInstr(env, s390_insn_move(8, f11, op1_lo));
2496
2497 op2 = s390_isel_int_expr(env, right); /* int operand */
2498
2499 addInstr(env,
2500 s390_insn_dfp128_intop(16, intop, f13, f15, op2, f9, f11));
2501
2502 /* Move result to virtual destination register */
2503 *dst_hi = newVRegF(env);
2504 *dst_lo = newVRegF(env);
2505 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2506 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2507 return;
2508 }
2509
floriane38f6412012-12-21 17:32:12 +00002510 default:
2511 goto irreducible;
2512 }
2513 }
2514
2515 /* --------- UNARY OP --------- */
2516 case Iex_Unop: {
2517 IRExpr *left = expr->Iex.Unop.arg;
2518 s390_dfp_conv_t conv;
2519 // HReg op, f12, f13, f14, f15;
2520 HReg op, f12, f14;
2521
2522 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
2523 f12 = make_fpr(12);
2524 // f13 = make_fpr(13);
2525 f14 = make_fpr(14);
2526 // f15 = make_fpr(15);
2527
2528 switch (expr->Iex.Unop.op) {
2529 case Iop_D64toD128: conv = S390_DFP_D64_TO_D128; goto convert_dfp;
florian5f034622013-01-13 02:29:05 +00002530 case Iop_I32StoD128: conv = S390_DFP_I32_TO_D128; goto convert_int;
2531 case Iop_I32UtoD128: conv = S390_DFP_U32_TO_D128; goto convert_int;
2532 case Iop_I64UtoD128: conv = S390_DFP_U64_TO_D128; goto convert_int;
floriane38f6412012-12-21 17:32:12 +00002533 default:
2534 goto irreducible;
2535 }
2536
2537 convert_dfp:
2538 op = s390_isel_dfp_expr(env, left);
2539 addInstr(env, s390_insn_dfp128_convert_to(16, conv, f12, f14, op));
2540 goto move_dst;
2541
florian5f034622013-01-13 02:29:05 +00002542 convert_int:
2543 op = s390_isel_int_expr(env, left);
2544 addInstr(env, s390_insn_dfp128_convert_to(16, conv, f12, f14, op));
2545 goto move_dst;
2546
floriane38f6412012-12-21 17:32:12 +00002547 move_dst:
2548 /* Move result to virtual destination registers */
2549 *dst_hi = newVRegF(env);
2550 *dst_lo = newVRegF(env);
2551 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2552 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2553 return;
2554 }
2555
2556 default:
2557 goto irreducible;
2558 }
2559
2560 /* We get here if no pattern matched. */
2561 irreducible:
2562 ppIRExpr(expr);
2563 vpanic("s390_isel_dfp128_expr_wrk: cannot reduce tree");
2564
2565}
2566
2567
2568/* Compute a 128-bit value into two 64-bit registers. These may be either
2569 real or virtual regs; in any case they must not be changed by subsequent
2570 code emitted by the caller. */
2571static void
2572s390_isel_dfp128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
2573{
2574 s390_isel_dfp128_expr_wrk(dst_hi, dst_lo, env, expr);
2575
2576 /* Sanity checks ... */
2577 vassert(hregIsVirtual(*dst_hi));
2578 vassert(hregIsVirtual(*dst_lo));
2579 vassert(hregClass(*dst_hi) == HRcFlt64);
2580 vassert(hregClass(*dst_lo) == HRcFlt64);
2581}
2582
2583
2584/*---------------------------------------------------------*/
florian12390202012-11-10 22:34:14 +00002585/*--- ISEL: Decimal point expressions (64 bit) ---*/
2586/*---------------------------------------------------------*/
2587
2588static HReg
2589s390_isel_dfp_expr_wrk(ISelEnv *env, IRExpr *expr)
2590{
2591 IRType ty = typeOfIRExpr(env->type_env, expr);
2592 UChar size;
2593
floriane38f6412012-12-21 17:32:12 +00002594 vassert(ty == Ity_D64 || ty == Ity_D32);
florian12390202012-11-10 22:34:14 +00002595
2596 size = sizeofIRType(ty);
2597
2598 switch (expr->tag) {
2599 case Iex_RdTmp:
2600 /* Return the virtual register that holds the temporary. */
2601 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
2602
2603 /* --------- LOAD --------- */
2604 case Iex_Load: {
2605 HReg dst = newVRegF(env);
2606 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
2607
2608 if (expr->Iex.Load.end != Iend_BE)
2609 goto irreducible;
2610
2611 addInstr(env, s390_insn_load(size, dst, am));
2612
2613 return dst;
2614 }
2615
2616 /* --------- GET --------- */
2617 case Iex_Get: {
2618 HReg dst = newVRegF(env);
2619 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
2620
2621 addInstr(env, s390_insn_load(size, dst, am));
2622
2623 return dst;
2624 }
2625
floriane38f6412012-12-21 17:32:12 +00002626 /* --------- BINARY OP --------- */
2627 case Iex_Binop: {
2628 IROp op = expr->Iex.Binop.op;
2629 IRExpr *irrm = expr->Iex.Binop.arg1;
2630 IRExpr *left = expr->Iex.Binop.arg2;
2631 HReg h1, dst;
2632 s390_dfp_conv_t conv;
2633
2634 switch (op) {
2635 case Iop_D64toD32: conv = S390_DFP_D64_TO_D32; goto convert_dfp;
florian5f034622013-01-13 02:29:05 +00002636 case Iop_I64UtoD64: conv = S390_DFP_U64_TO_D64; goto convert_int;
floriane38f6412012-12-21 17:32:12 +00002637
2638 convert_dfp:
2639 h1 = s390_isel_dfp_expr(env, left);
2640 goto convert;
2641
florian5f034622013-01-13 02:29:05 +00002642 convert_int:
2643 h1 = s390_isel_int_expr(env, left);
2644 goto convert;
2645
floriane38f6412012-12-21 17:32:12 +00002646 convert: {
2647 s390_dfp_round_t rounding_mode;
2648 /* convert-from-fixed and load-rounded have a rounding mode field
2649 when the floating point extension facility is installed. */
2650 dst = newVRegF(env);
2651 if (s390_host_has_fpext) {
2652 rounding_mode = get_dfp_rounding_mode(env, irrm);
2653 } else {
2654 set_dfp_rounding_mode_in_fpc(env, irrm);
2655 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2656 }
2657 addInstr(env, s390_insn_dfp_convert(size, conv, dst, h1,
2658 rounding_mode));
2659 return dst;
2660 }
floriane38f6412012-12-21 17:32:12 +00002661
2662 case Iop_D128toD64: {
2663 HReg op_hi, op_lo, f13, f15;
2664 s390_dfp_round_t rounding_mode;
2665
2666 conv = S390_DFP_D128_TO_D64;
2667
2668 s390_isel_dfp128_expr(&op_hi, &op_lo, env, left);
2669
2670 /* We use non-virtual registers as pairs (f13, f15) */
2671 f13 = make_fpr(13);
2672 f15 = make_fpr(15);
2673
2674 /* operand --> (f13, f15) */
2675 addInstr(env, s390_insn_move(8, f13, op_hi));
2676 addInstr(env, s390_insn_move(8, f15, op_lo));
2677
2678 dst = newVRegF(env);
2679 /* load-rounded has a rounding mode field when the floating point
2680 extension facility is installed. */
2681 if (s390_host_has_fpext) {
2682 rounding_mode = get_dfp_rounding_mode(env, irrm);
2683 } else {
2684 set_dfp_rounding_mode_in_fpc(env, irrm);
2685 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2686 }
2687 addInstr(env, s390_insn_dfp128_convert_from(size, conv, dst, f13, f15,
2688 rounding_mode));
2689 return dst;
2690 }
2691
florian1b901d42013-01-01 22:19:24 +00002692 case Iop_ShlD64:
2693 case Iop_ShrD64: {
2694 HReg op2;
2695 HReg op3;
2696 s390_dfp_intop_t intop;
2697 IRExpr *op1 = expr->Iex.Binop.arg1;
2698 IRExpr *shift = expr->Iex.Binop.arg2;
2699
2700 switch (expr->Iex.Binop.op) {
2701 case Iop_ShlD64: intop = S390_DFP_SHIFT_LEFT; break;
2702 case Iop_ShrD64: intop = S390_DFP_SHIFT_RIGHT; break;
2703 default: goto irreducible;
2704 }
2705
2706 op2 = s390_isel_int_expr(env, shift);
2707 op3 = s390_isel_dfp_expr(env, op1);
2708 dst = newVRegF(env);
2709
2710 addInstr(env, s390_insn_dfp_intop(size, intop, dst, op2, op3));
2711 return dst;
2712 }
2713
2714 default:
2715 goto irreducible;
floriane38f6412012-12-21 17:32:12 +00002716 }
2717 }
2718
2719 /* --------- UNARY OP --------- */
2720 case Iex_Unop: {
2721 IROp op = expr->Iex.Unop.op;
2722 IRExpr *left = expr->Iex.Unop.arg;
2723 s390_dfp_conv_t conv;
2724 HReg h1, dst;
2725
2726 if (op == Iop_D128HItoD64 || op == Iop_D128LOtoD64) {
2727 HReg dst_hi, dst_lo;
2728
2729 s390_isel_dfp128_expr(&dst_hi, &dst_lo, env, left);
2730 return op == Iop_D128LOtoD64 ? dst_lo : dst_hi;
2731 }
2732
2733 if (op == Iop_ReinterpI64asD64) {
2734 dst = newVRegF(env);
2735 h1 = s390_isel_int_expr(env, left); /* Process the operand */
2736 addInstr(env, s390_insn_move(size, dst, h1));
2737
2738 return dst;
2739 }
2740
2741 switch (op) {
2742 case Iop_D32toD64: conv = S390_DFP_D32_TO_D64; goto convert_dfp1;
florian5f034622013-01-13 02:29:05 +00002743 case Iop_I32StoD64: conv = S390_DFP_I32_TO_D64; goto convert_int1;
2744 case Iop_I32UtoD64: conv = S390_DFP_U32_TO_D64; goto convert_int1;
floriane38f6412012-12-21 17:32:12 +00002745
2746 convert_dfp1:
2747 h1 = s390_isel_dfp_expr(env, left);
2748 goto convert1;
2749
florian5f034622013-01-13 02:29:05 +00002750 convert_int1:
2751 h1 = s390_isel_int_expr(env, left);
2752 goto convert1;
2753
floriane38f6412012-12-21 17:32:12 +00002754 convert1:
2755 dst = newVRegF(env);
2756 /* No rounding mode is needed for these conversions. Just stick
2757 one in. It won't be used later on. */
2758 addInstr(env, s390_insn_dfp_convert(size, conv, dst, h1,
2759 S390_DFP_ROUND_NEAREST_EVEN_4));
2760 return dst;
2761
2762 default:
2763 goto irreducible;
2764 }
2765 }
2766
florian12390202012-11-10 22:34:14 +00002767 /* --------- TERNARY OP --------- */
2768 case Iex_Triop: {
2769 IRTriop *triop = expr->Iex.Triop.details;
2770 IROp op = triop->op;
2771 IRExpr *irrm = triop->arg1;
2772 IRExpr *left = triop->arg2;
2773 IRExpr *right = triop->arg3;
2774 s390_dfp_round_t rounding_mode;
2775 s390_dfp_binop_t dfpop;
2776 HReg op2, op3, dst;
2777
2778 op2 = s390_isel_dfp_expr(env, left); /* Process 1st operand */
2779 op3 = s390_isel_dfp_expr(env, right); /* Process 2nd operand */
2780 dst = newVRegF(env);
2781 switch (op) {
2782 case Iop_AddD64: dfpop = S390_DFP_ADD; break;
2783 case Iop_SubD64: dfpop = S390_DFP_SUB; break;
2784 case Iop_MulD64: dfpop = S390_DFP_MUL; break;
2785 case Iop_DivD64: dfpop = S390_DFP_DIV; break;
2786 default:
2787 goto irreducible;
2788 }
2789 /* DFP binary ops have insns with rounding mode field
2790 when the floating point extension facility is installed. */
2791 if (s390_host_has_fpext) {
2792 rounding_mode = get_dfp_rounding_mode(env, irrm);
2793 } else {
2794 set_dfp_rounding_mode_in_fpc(env, irrm);
2795 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2796 }
2797
2798 addInstr(env,
2799 s390_insn_dfp_binop(size, dfpop, dst, op2, op3, rounding_mode));
2800 return dst;
2801 }
2802
2803 default:
2804 goto irreducible;
2805 }
2806
2807 /* We get here if no pattern matched. */
2808 irreducible:
2809 ppIRExpr(expr);
2810 vpanic("s390_isel_dfp_expr: cannot reduce tree");
2811}
2812
2813static HReg
2814s390_isel_dfp_expr(ISelEnv *env, IRExpr *expr)
2815{
2816 HReg dst = s390_isel_dfp_expr_wrk(env, expr);
2817
2818 /* Sanity checks ... */
2819 vassert(hregClass(dst) == HRcFlt64);
2820 vassert(hregIsVirtual(dst));
2821
2822 return dst;
2823}
2824
2825
2826/*---------------------------------------------------------*/
sewardj2019a972011-03-07 16:04:07 +00002827/*--- ISEL: Condition Code ---*/
2828/*---------------------------------------------------------*/
2829
2830/* This function handles all operators that produce a 1-bit result */
2831static s390_cc_t
2832s390_isel_cc(ISelEnv *env, IRExpr *cond)
2833{
2834 UChar size;
2835
2836 vassert(typeOfIRExpr(env->type_env, cond) == Ity_I1);
2837
2838 /* Constant: either 1 or 0 */
2839 if (cond->tag == Iex_Const) {
2840 vassert(cond->Iex.Const.con->tag == Ico_U1);
2841 vassert(cond->Iex.Const.con->Ico.U1 == True
2842 || cond->Iex.Const.con->Ico.U1 == False);
2843
2844 return cond->Iex.Const.con->Ico.U1 == True ? S390_CC_ALWAYS : S390_CC_NEVER;
2845 }
2846
2847 /* Variable: values are 1 or 0 */
2848 if (cond->tag == Iex_RdTmp) {
2849 IRTemp tmp = cond->Iex.RdTmp.tmp;
2850 HReg reg = lookupIRTemp(env, tmp);
2851
2852 /* Load-and-test does not modify REG; so this is OK. */
2853 if (typeOfIRTemp(env->type_env, tmp) == Ity_I1)
2854 size = 4;
2855 else
2856 size = sizeofIRType(typeOfIRTemp(env->type_env, tmp));
2857 addInstr(env, s390_insn_test(size, s390_opnd_reg(reg)));
2858 return S390_CC_NE;
2859 }
2860
2861 /* Unary operators */
2862 if (cond->tag == Iex_Unop) {
2863 IRExpr *arg = cond->Iex.Unop.arg;
2864
2865 switch (cond->Iex.Unop.op) {
2866 case Iop_Not1: /* Not1(cond) */
2867 /* Generate code for EXPR, and negate the test condition */
2868 return s390_cc_invert(s390_isel_cc(env, arg));
2869
2870 /* Iop_32/64to1 select the LSB from their operand */
2871 case Iop_32to1:
2872 case Iop_64to1: {
florianf366a802012-08-03 00:42:18 +00002873 HReg dst = newVRegI(env);
2874 HReg h1 = s390_isel_int_expr(env, arg);
sewardj2019a972011-03-07 16:04:07 +00002875
2876 size = sizeofIRType(typeOfIRExpr(env->type_env, arg));
2877
florianf366a802012-08-03 00:42:18 +00002878 addInstr(env, s390_insn_move(size, dst, h1));
sewardj2019a972011-03-07 16:04:07 +00002879 addInstr(env, s390_insn_alu(size, S390_ALU_AND, dst, s390_opnd_imm(1)));
2880 addInstr(env, s390_insn_test(size, s390_opnd_reg(dst)));
2881 return S390_CC_NE;
2882 }
2883
2884 case Iop_CmpNEZ8:
2885 case Iop_CmpNEZ16: {
2886 s390_opnd_RMI src;
2887 s390_unop_t op;
2888 HReg dst;
2889
2890 op = (cond->Iex.Unop.op == Iop_CmpNEZ8) ? S390_ZERO_EXTEND_8
2891 : S390_ZERO_EXTEND_16;
2892 dst = newVRegI(env);
2893 src = s390_isel_int_expr_RMI(env, arg);
2894 addInstr(env, s390_insn_unop(4, op, dst, src));
2895 addInstr(env, s390_insn_test(4, s390_opnd_reg(dst)));
2896 return S390_CC_NE;
2897 }
2898
2899 case Iop_CmpNEZ32:
2900 case Iop_CmpNEZ64: {
2901 s390_opnd_RMI src;
2902
2903 src = s390_isel_int_expr_RMI(env, arg);
2904 size = sizeofIRType(typeOfIRExpr(env->type_env, arg));
2905 addInstr(env, s390_insn_test(size, src));
2906 return S390_CC_NE;
2907 }
2908
2909 default:
2910 goto fail;
2911 }
2912 }
2913
2914 /* Binary operators */
2915 if (cond->tag == Iex_Binop) {
2916 IRExpr *arg1 = cond->Iex.Binop.arg1;
2917 IRExpr *arg2 = cond->Iex.Binop.arg2;
2918 HReg reg1, reg2;
2919
2920 size = sizeofIRType(typeOfIRExpr(env->type_env, arg1));
2921
2922 switch (cond->Iex.Binop.op) {
2923 s390_unop_t op;
2924 s390_cc_t result;
2925
2926 case Iop_CmpEQ8:
2927 case Iop_CasCmpEQ8:
2928 op = S390_ZERO_EXTEND_8;
2929 result = S390_CC_E;
2930 goto do_compare_ze;
2931
2932 case Iop_CmpNE8:
2933 case Iop_CasCmpNE8:
2934 op = S390_ZERO_EXTEND_8;
2935 result = S390_CC_NE;
2936 goto do_compare_ze;
2937
2938 case Iop_CmpEQ16:
2939 case Iop_CasCmpEQ16:
2940 op = S390_ZERO_EXTEND_16;
2941 result = S390_CC_E;
2942 goto do_compare_ze;
2943
2944 case Iop_CmpNE16:
2945 case Iop_CasCmpNE16:
2946 op = S390_ZERO_EXTEND_16;
2947 result = S390_CC_NE;
2948 goto do_compare_ze;
2949
2950 do_compare_ze: {
2951 s390_opnd_RMI op1, op2;
2952
2953 op1 = s390_isel_int_expr_RMI(env, arg1);
2954 reg1 = newVRegI(env);
2955 addInstr(env, s390_insn_unop(4, op, reg1, op1));
2956
2957 op2 = s390_isel_int_expr_RMI(env, arg2);
2958 reg2 = newVRegI(env);
2959 addInstr(env, s390_insn_unop(4, op, reg2, op2)); /* zero extend */
2960
2961 op2 = s390_opnd_reg(reg2);
2962 addInstr(env, s390_insn_compare(4, reg1, op2, False));
2963
2964 return result;
2965 }
2966
2967 case Iop_CmpEQ32:
2968 case Iop_CmpEQ64:
2969 case Iop_CasCmpEQ32:
2970 case Iop_CasCmpEQ64:
2971 result = S390_CC_E;
2972 goto do_compare;
2973
2974 case Iop_CmpNE32:
2975 case Iop_CmpNE64:
2976 case Iop_CasCmpNE32:
2977 case Iop_CasCmpNE64:
2978 result = S390_CC_NE;
2979 goto do_compare;
2980
2981 do_compare: {
2982 HReg op1;
2983 s390_opnd_RMI op2;
2984
2985 order_commutative_operands(arg1, arg2);
2986
2987 op1 = s390_isel_int_expr(env, arg1);
2988 op2 = s390_isel_int_expr_RMI(env, arg2);
2989
2990 addInstr(env, s390_insn_compare(size, op1, op2, False));
2991
2992 return result;
2993 }
2994
2995 case Iop_CmpLT32S:
2996 case Iop_CmpLE32S:
2997 case Iop_CmpLT64S:
2998 case Iop_CmpLE64S: {
2999 HReg op1;
3000 s390_opnd_RMI op2;
3001
3002 op1 = s390_isel_int_expr(env, arg1);
3003 op2 = s390_isel_int_expr_RMI(env, arg2);
3004
3005 addInstr(env, s390_insn_compare(size, op1, op2, True));
3006
3007 return (cond->Iex.Binop.op == Iop_CmpLT32S ||
3008 cond->Iex.Binop.op == Iop_CmpLT64S) ? S390_CC_L : S390_CC_LE;
3009 }
3010
3011 case Iop_CmpLT32U:
3012 case Iop_CmpLE32U:
3013 case Iop_CmpLT64U:
3014 case Iop_CmpLE64U: {
3015 HReg op1;
3016 s390_opnd_RMI op2;
3017
3018 op1 = s390_isel_int_expr(env, arg1);
3019 op2 = s390_isel_int_expr_RMI(env, arg2);
3020
3021 addInstr(env, s390_insn_compare(size, op1, op2, False));
3022
3023 return (cond->Iex.Binop.op == Iop_CmpLT32U ||
3024 cond->Iex.Binop.op == Iop_CmpLT64U) ? S390_CC_L : S390_CC_LE;
3025 }
3026
3027 default:
3028 goto fail;
3029 }
3030 }
3031
3032 fail:
3033 ppIRExpr(cond);
3034 vpanic("s390_isel_cc: unexpected operator");
3035}
3036
3037
3038/*---------------------------------------------------------*/
3039/*--- ISEL: Statements ---*/
3040/*---------------------------------------------------------*/
3041
3042static void
3043s390_isel_stmt(ISelEnv *env, IRStmt *stmt)
3044{
3045 if (vex_traceflags & VEX_TRACE_VCODE) {
3046 vex_printf("\n -- ");
3047 ppIRStmt(stmt);
3048 vex_printf("\n");
3049 }
3050
3051 switch (stmt->tag) {
3052
3053 /* --------- STORE --------- */
3054 case Ist_Store: {
3055 IRType tyd = typeOfIRExpr(env->type_env, stmt->Ist.Store.data);
3056 s390_amode *am;
3057 HReg src;
3058
3059 if (stmt->Ist.Store.end != Iend_BE) goto stmt_fail;
3060
3061 am = s390_isel_amode(env, stmt->Ist.Store.addr);
3062
3063 switch (tyd) {
3064 case Ity_I8:
3065 case Ity_I16:
3066 case Ity_I32:
3067 case Ity_I64:
florianf85fe3e2012-12-22 02:28:25 +00003068 /* fixs390: We could check for INSN_MADD here. */
florian09bbba82012-12-11 04:09:43 +00003069 if (am->tag == S390_AMODE_B12 &&
florianb93348d2012-12-27 00:59:43 +00003070 stmt->Ist.Store.data->tag == Iex_Const) {
3071 ULong value =
3072 get_const_value_as_ulong(stmt->Ist.Store.data->Iex.Const.con);
3073 addInstr(env, s390_insn_mimm(sizeofIRType(tyd), am, value));
florian09bbba82012-12-11 04:09:43 +00003074 return;
3075 }
sewardj2019a972011-03-07 16:04:07 +00003076 src = s390_isel_int_expr(env, stmt->Ist.Store.data);
3077 break;
3078
3079 case Ity_F32:
3080 case Ity_F64:
3081 src = s390_isel_float_expr(env, stmt->Ist.Store.data);
3082 break;
3083
florianeb981ae2012-12-21 18:55:03 +00003084 case Ity_D32:
3085 case Ity_D64:
3086 src = s390_isel_dfp_expr(env, stmt->Ist.Store.data);
3087 break;
3088
sewardj2019a972011-03-07 16:04:07 +00003089 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003090 case Ity_D128:
sewardj2019a972011-03-07 16:04:07 +00003091 /* Cannot occur. No such instruction */
floriane38f6412012-12-21 17:32:12 +00003092 vpanic("Ist_Store with 128-bit floating point data");
sewardj2019a972011-03-07 16:04:07 +00003093
3094 default:
3095 goto stmt_fail;
3096 }
3097
3098 addInstr(env, s390_insn_store(sizeofIRType(tyd), am, src));
3099 return;
3100 }
3101
3102 /* --------- PUT --------- */
3103 case Ist_Put: {
3104 IRType tyd = typeOfIRExpr(env->type_env, stmt->Ist.Put.data);
3105 HReg src;
3106 s390_amode *am;
florianad43b3a2012-02-20 15:01:14 +00003107 ULong new_value, old_value, difference;
sewardj2019a972011-03-07 16:04:07 +00003108
florianad43b3a2012-02-20 15:01:14 +00003109 /* Detect updates to certain guest registers. We track the contents
3110 of those registers as long as they contain constants. If the new
3111 constant is either zero or in the 8-bit neighbourhood of the
3112 current value we can use a memory-to-memory insn to do the update. */
3113
3114 Int offset = stmt->Ist.Put.offset;
3115
3116 /* Check necessary conditions:
3117 (1) must be one of the registers we care about
3118 (2) assigned value must be a constant */
3119 Int guest_reg = get_guest_reg(offset);
3120
3121 if (guest_reg == GUEST_UNKNOWN) goto not_special;
3122
florianad43b3a2012-02-20 15:01:14 +00003123 if (stmt->Ist.Put.data->tag != Iex_Const) {
3124 /* Invalidate guest register contents */
3125 env->old_value_valid[guest_reg] = False;
3126 goto not_special;
3127 }
3128
cborntraaf7ad282012-08-08 14:11:33 +00003129 /* We can only handle Ity_I64, but the CC_DEPS field can have floats */
3130 if (tyd != Ity_I64)
3131 goto not_special;
florianad43b3a2012-02-20 15:01:14 +00003132
cborntraaf7ad282012-08-08 14:11:33 +00003133 /* OK. Necessary conditions are satisfied. */
florianad43b3a2012-02-20 15:01:14 +00003134
3135 old_value = env->old_value[guest_reg];
3136 new_value = stmt->Ist.Put.data->Iex.Const.con->Ico.U64;
3137 env->old_value[guest_reg] = new_value;
3138
3139 Bool old_value_is_valid = env->old_value_valid[guest_reg];
3140 env->old_value_valid[guest_reg] = True;
3141
3142 /* If the register already contains the new value, there is nothing
florian9f42ab42012-12-23 01:09:16 +00003143 to do here. */
florianad43b3a2012-02-20 15:01:14 +00003144 if (old_value_is_valid && new_value == old_value) {
florian9f42ab42012-12-23 01:09:16 +00003145 return;
florianad43b3a2012-02-20 15:01:14 +00003146 }
3147
florianad43b3a2012-02-20 15:01:14 +00003148 if (old_value_is_valid == False) goto not_special;
3149
3150 /* If the new value is in the neighbourhood of the old value
3151 we can use a memory-to-memory insn */
3152 difference = new_value - old_value;
3153
3154 if (s390_host_has_gie && ulong_fits_signed_8bit(difference)) {
florianf85fe3e2012-12-22 02:28:25 +00003155 am = s390_amode_for_guest_state(offset);
3156 addInstr(env, s390_insn_madd(sizeofIRType(tyd), am,
florianad43b3a2012-02-20 15:01:14 +00003157 (difference & 0xFF), new_value));
3158 return;
3159 }
3160
florianb93348d2012-12-27 00:59:43 +00003161 /* If the high word is the same it is sufficient to load the low word. */
florianad43b3a2012-02-20 15:01:14 +00003162 if ((old_value >> 32) == (new_value >> 32)) {
florianf85fe3e2012-12-22 02:28:25 +00003163 am = s390_amode_for_guest_state(offset + 4);
florianb93348d2012-12-27 00:59:43 +00003164 addInstr(env, s390_insn_mimm(4, am, new_value & 0xFFFFFFFF));
florianad43b3a2012-02-20 15:01:14 +00003165 return;
3166 }
3167
3168 /* No special case applies... fall through */
3169
3170 not_special:
florianb93348d2012-12-27 00:59:43 +00003171 am = s390_amode_for_guest_state(offset);
sewardj2019a972011-03-07 16:04:07 +00003172
3173 switch (tyd) {
3174 case Ity_I8:
3175 case Ity_I16:
3176 case Ity_I32:
3177 case Ity_I64:
florian09bbba82012-12-11 04:09:43 +00003178 if (am->tag == S390_AMODE_B12 &&
florianb93348d2012-12-27 00:59:43 +00003179 stmt->Ist.Put.data->tag == Iex_Const) {
3180 ULong value =
3181 get_const_value_as_ulong(stmt->Ist.Put.data->Iex.Const.con);
3182 addInstr(env, s390_insn_mimm(sizeofIRType(tyd), am, value));
florian09bbba82012-12-11 04:09:43 +00003183 return;
3184 }
sewardj2019a972011-03-07 16:04:07 +00003185 src = s390_isel_int_expr(env, stmt->Ist.Put.data);
3186 break;
3187
3188 case Ity_F32:
3189 case Ity_F64:
3190 src = s390_isel_float_expr(env, stmt->Ist.Put.data);
3191 break;
3192
3193 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003194 case Ity_D128:
3195 /* Does not occur. See function put_(f|d)pr_pair. */
3196 vpanic("Ist_Put with 128-bit floating point data");
sewardj2019a972011-03-07 16:04:07 +00003197
floriane38f6412012-12-21 17:32:12 +00003198 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003199 case Ity_D64:
3200 src = s390_isel_dfp_expr(env, stmt->Ist.Put.data);
3201 break;
3202
sewardj2019a972011-03-07 16:04:07 +00003203 default:
3204 goto stmt_fail;
3205 }
3206
3207 addInstr(env, s390_insn_store(sizeofIRType(tyd), am, src));
3208 return;
3209 }
3210
3211 /* --------- TMP --------- */
3212 case Ist_WrTmp: {
3213 IRTemp tmp = stmt->Ist.WrTmp.tmp;
3214 IRType tyd = typeOfIRTemp(env->type_env, tmp);
3215 HReg src, dst;
3216
3217 switch (tyd) {
3218 case Ity_I128: {
3219 HReg dst_hi, dst_lo, res_hi, res_lo;
3220
3221 s390_isel_int128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3222 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3223
3224 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3225 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3226 return;
3227 }
3228
3229 case Ity_I8:
3230 case Ity_I16:
3231 case Ity_I32:
3232 case Ity_I64:
3233 src = s390_isel_int_expr(env, stmt->Ist.WrTmp.data);
3234 dst = lookupIRTemp(env, tmp);
3235 break;
3236
3237 case Ity_I1: {
3238 s390_cc_t cond = s390_isel_cc(env, stmt->Ist.WrTmp.data);
3239 dst = lookupIRTemp(env, tmp);
3240 addInstr(env, s390_insn_cc2bool(dst, cond));
3241 return;
3242 }
3243
3244 case Ity_F32:
3245 case Ity_F64:
3246 src = s390_isel_float_expr(env, stmt->Ist.WrTmp.data);
3247 dst = lookupIRTemp(env, tmp);
3248 break;
3249
3250 case Ity_F128: {
3251 HReg dst_hi, dst_lo, res_hi, res_lo;
3252
3253 s390_isel_float128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3254 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3255
3256 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3257 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3258 return;
3259 }
3260
floriane38f6412012-12-21 17:32:12 +00003261 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003262 case Ity_D64:
3263 src = s390_isel_dfp_expr(env, stmt->Ist.WrTmp.data);
3264 dst = lookupIRTemp(env, tmp);
3265 break;
3266
floriane38f6412012-12-21 17:32:12 +00003267 case Ity_D128: {
3268 HReg dst_hi, dst_lo, res_hi, res_lo;
3269
3270 s390_isel_dfp128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3271 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3272
3273 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3274 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3275 return;
3276 }
3277
sewardj2019a972011-03-07 16:04:07 +00003278 default:
3279 goto stmt_fail;
3280 }
3281
3282 addInstr(env, s390_insn_move(sizeofIRType(tyd), dst, src));
3283 return;
3284 }
3285
3286 /* --------- Call to DIRTY helper --------- */
3287 case Ist_Dirty: {
3288 IRType retty;
3289 IRDirty* d = stmt->Ist.Dirty.details;
3290 Bool passBBP;
florian01ed6e72012-05-27 16:52:43 +00003291 HReg dst;
florianad43b3a2012-02-20 15:01:14 +00003292 Int i;
3293
3294 /* Invalidate tracked values of those guest state registers that are
3295 modified by this helper. */
3296 for (i = 0; i < d->nFxState; ++i) {
sewardjc9069f22012-06-01 16:09:50 +00003297 /* JRS 1 June 2012: AFAICS, s390 guest doesn't use 'repeat'
3298 descriptors in guest state effect descriptions. Hence: */
3299 vassert(d->fxState[i].nRepeats == 0 && d->fxState[i].repeatLen == 0);
florianad43b3a2012-02-20 15:01:14 +00003300 if ((d->fxState[i].fx == Ifx_Write || d->fxState[i].fx == Ifx_Modify)) {
3301 Int guest_reg = get_guest_reg(d->fxState[i].offset);
3302 if (guest_reg != GUEST_UNKNOWN)
3303 env->old_value_valid[guest_reg] = False;
3304 }
3305 }
sewardj2019a972011-03-07 16:04:07 +00003306
3307 if (d->nFxState == 0)
3308 vassert(!d->needsBBP);
3309
3310 passBBP = toBool(d->nFxState > 0 && d->needsBBP);
3311
florian01ed6e72012-05-27 16:52:43 +00003312 if (d->tmp == IRTemp_INVALID) {
3313 /* No return value. */
3314 dst = INVALID_HREG;
3315 doHelperCall(env, passBBP, d->guard, d->cee, d->args, dst);
sewardj2019a972011-03-07 16:04:07 +00003316 return;
florian01ed6e72012-05-27 16:52:43 +00003317 }
sewardj2019a972011-03-07 16:04:07 +00003318
3319 retty = typeOfIRTemp(env->type_env, d->tmp);
3320 if (retty == Ity_I64 || retty == Ity_I32
3321 || retty == Ity_I16 || retty == Ity_I8) {
florian297b6062012-05-08 20:16:17 +00003322 /* Move the returned value to the destination register */
florian01ed6e72012-05-27 16:52:43 +00003323 dst = lookupIRTemp(env, d->tmp);
3324 doHelperCall(env, passBBP, d->guard, d->cee, d->args, dst);
sewardj2019a972011-03-07 16:04:07 +00003325 return;
3326 }
3327 break;
3328 }
3329
3330 case Ist_CAS:
3331 if (stmt->Ist.CAS.details->oldHi == IRTemp_INVALID) {
3332 IRCAS *cas = stmt->Ist.CAS.details;
3333 s390_amode *op2 = s390_isel_amode(env, cas->addr);
3334 HReg op3 = s390_isel_int_expr(env, cas->dataLo); /* new value */
3335 HReg op1 = s390_isel_int_expr(env, cas->expdLo); /* expected value */
3336 HReg old = lookupIRTemp(env, cas->oldLo);
3337
3338 if (typeOfIRTemp(env->type_env, cas->oldLo) == Ity_I32) {
3339 addInstr(env, s390_insn_cas(4, op1, op2, op3, old));
3340 } else {
3341 addInstr(env, s390_insn_cas(8, op1, op2, op3, old));
3342 }
3343 return;
3344 } else {
florian448cbba2012-06-06 02:26:01 +00003345 IRCAS *cas = stmt->Ist.CAS.details;
3346 s390_amode *op2 = s390_isel_amode(env, cas->addr);
3347 HReg r8, r9, r10, r11, r1;
3348 HReg op3_high = s390_isel_int_expr(env, cas->dataHi); /* new value */
3349 HReg op3_low = s390_isel_int_expr(env, cas->dataLo); /* new value */
3350 HReg op1_high = s390_isel_int_expr(env, cas->expdHi); /* expected value */
3351 HReg op1_low = s390_isel_int_expr(env, cas->expdLo); /* expected value */
3352 HReg old_low = lookupIRTemp(env, cas->oldLo);
3353 HReg old_high = lookupIRTemp(env, cas->oldHi);
3354
3355 /* Use non-virtual registers r8 and r9 as pair for op1
3356 and move op1 there */
3357 r8 = make_gpr(8);
3358 r9 = make_gpr(9);
3359 addInstr(env, s390_insn_move(8, r8, op1_high));
3360 addInstr(env, s390_insn_move(8, r9, op1_low));
3361
3362 /* Use non-virtual registers r10 and r11 as pair for op3
3363 and move op3 there */
3364 r10 = make_gpr(10);
3365 r11 = make_gpr(11);
3366 addInstr(env, s390_insn_move(8, r10, op3_high));
3367 addInstr(env, s390_insn_move(8, r11, op3_low));
3368
3369 /* Register r1 is used as a scratch register */
3370 r1 = make_gpr(1);
3371
3372 if (typeOfIRTemp(env->type_env, cas->oldLo) == Ity_I32) {
3373 addInstr(env, s390_insn_cdas(4, r8, r9, op2, r10, r11,
3374 old_high, old_low, r1));
3375 } else {
3376 addInstr(env, s390_insn_cdas(8, r8, r9, op2, r10, r11,
3377 old_high, old_low, r1));
3378 }
3379 addInstr(env, s390_insn_move(8, op1_high, r8));
3380 addInstr(env, s390_insn_move(8, op1_low, r9));
3381 addInstr(env, s390_insn_move(8, op3_high, r10));
3382 addInstr(env, s390_insn_move(8, op3_low, r11));
3383 return;
sewardj2019a972011-03-07 16:04:07 +00003384 }
3385 break;
3386
3387 /* --------- EXIT --------- */
3388 case Ist_Exit: {
sewardj2019a972011-03-07 16:04:07 +00003389 s390_cc_t cond;
3390 IRConstTag tag = stmt->Ist.Exit.dst->tag;
3391
3392 if (tag != Ico_U64)
3393 vpanic("s390_isel_stmt: Ist_Exit: dst is not a 64-bit value");
3394
florian8844a632012-04-13 04:04:06 +00003395 s390_amode *guest_IA = s390_amode_for_guest_state(stmt->Ist.Exit.offsIP);
sewardj2019a972011-03-07 16:04:07 +00003396 cond = s390_isel_cc(env, stmt->Ist.Exit.guard);
florian8844a632012-04-13 04:04:06 +00003397
3398 /* Case: boring transfer to known address */
3399 if (stmt->Ist.Exit.jk == Ijk_Boring) {
3400 if (env->chaining_allowed) {
3401 /* .. almost always true .. */
3402 /* Skip the event check at the dst if this is a forwards
3403 edge. */
3404 Bool to_fast_entry
3405 = ((Addr64)stmt->Ist.Exit.dst->Ico.U64) > env->max_ga;
3406 if (0) vex_printf("%s", to_fast_entry ? "Y" : ",");
3407 addInstr(env, s390_insn_xdirect(cond, stmt->Ist.Exit.dst->Ico.U64,
3408 guest_IA, to_fast_entry));
3409 } else {
3410 /* .. very occasionally .. */
3411 /* We can't use chaining, so ask for an assisted transfer,
3412 as that's the only alternative that is allowable. */
3413 HReg dst = s390_isel_int_expr(env,
3414 IRExpr_Const(stmt->Ist.Exit.dst));
3415 addInstr(env, s390_insn_xassisted(cond, dst, guest_IA, Ijk_Boring));
3416 }
3417 return;
3418 }
3419
3420 /* Case: assisted transfer to arbitrary address */
3421 switch (stmt->Ist.Exit.jk) {
florian4e0083e2012-08-26 03:41:56 +00003422 case Ijk_EmFail:
florian4b8efad2012-09-02 18:07:08 +00003423 case Ijk_EmWarn:
florian65b5b3f2012-04-22 02:51:27 +00003424 case Ijk_NoDecode:
florian8844a632012-04-13 04:04:06 +00003425 case Ijk_TInval:
florian2d98d892012-04-14 20:35:17 +00003426 case Ijk_Sys_syscall:
3427 case Ijk_ClientReq:
3428 case Ijk_NoRedir:
3429 case Ijk_Yield:
3430 case Ijk_SigTRAP: {
florian8844a632012-04-13 04:04:06 +00003431 HReg dst = s390_isel_int_expr(env, IRExpr_Const(stmt->Ist.Exit.dst));
3432 addInstr(env, s390_insn_xassisted(cond, dst, guest_IA,
3433 stmt->Ist.Exit.jk));
3434 return;
3435 }
3436 default:
3437 break;
3438 }
3439
3440 /* Do we ever expect to see any other kind? */
3441 goto stmt_fail;
sewardj2019a972011-03-07 16:04:07 +00003442 }
3443
3444 /* --------- MEM FENCE --------- */
sewardja52e37e2011-04-28 18:48:06 +00003445 case Ist_MBE:
3446 switch (stmt->Ist.MBE.event) {
3447 case Imbe_Fence:
3448 addInstr(env, s390_insn_mfence());
3449 return;
3450 default:
3451 break;
3452 }
sewardj2019a972011-03-07 16:04:07 +00003453 break;
3454
3455 /* --------- Miscellaneous --------- */
3456
3457 case Ist_PutI: /* Not needed */
3458 case Ist_IMark: /* Doesn't generate any executable code */
3459 case Ist_NoOp: /* Doesn't generate any executable code */
3460 case Ist_AbiHint: /* Meaningless in IR */
3461 return;
3462
3463 default:
3464 break;
3465 }
3466
3467 stmt_fail:
3468 ppIRStmt(stmt);
3469 vpanic("s390_isel_stmt");
3470}
3471
3472
3473/*---------------------------------------------------------*/
3474/*--- ISEL: Basic block terminators (Nexts) ---*/
3475/*---------------------------------------------------------*/
3476
3477static void
florianffbd84d2012-12-09 02:06:29 +00003478iselNext(ISelEnv *env, IRExpr *next, IRJumpKind jk, Int offsIP)
sewardj2019a972011-03-07 16:04:07 +00003479{
sewardj2019a972011-03-07 16:04:07 +00003480 if (vex_traceflags & VEX_TRACE_VCODE) {
florian8844a632012-04-13 04:04:06 +00003481 vex_printf("\n-- PUT(%d) = ", offsIP);
sewardj2019a972011-03-07 16:04:07 +00003482 ppIRExpr(next);
florian8844a632012-04-13 04:04:06 +00003483 vex_printf("; exit-");
3484 ppIRJumpKind(jk);
sewardj2019a972011-03-07 16:04:07 +00003485 vex_printf("\n");
3486 }
3487
florian8844a632012-04-13 04:04:06 +00003488 s390_amode *guest_IA = s390_amode_for_guest_state(offsIP);
3489
3490 /* Case: boring transfer to known address */
3491 if (next->tag == Iex_Const) {
3492 IRConst *cdst = next->Iex.Const.con;
3493 vassert(cdst->tag == Ico_U64);
3494 if (jk == Ijk_Boring || jk == Ijk_Call) {
3495 /* Boring transfer to known address */
3496 if (env->chaining_allowed) {
3497 /* .. almost always true .. */
3498 /* Skip the event check at the dst if this is a forwards
3499 edge. */
3500 Bool to_fast_entry
3501 = ((Addr64)cdst->Ico.U64) > env->max_ga;
3502 if (0) vex_printf("%s", to_fast_entry ? "X" : ".");
3503 addInstr(env, s390_insn_xdirect(S390_CC_ALWAYS, cdst->Ico.U64,
3504 guest_IA, to_fast_entry));
3505 } else {
3506 /* .. very occasionally .. */
3507 /* We can't use chaining, so ask for an indirect transfer,
3508 as that's the cheapest alternative that is allowable. */
3509 HReg dst = s390_isel_int_expr(env, next);
3510 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA,
3511 Ijk_Boring));
3512 }
3513 return;
3514 }
3515 }
3516
3517 /* Case: call/return (==boring) transfer to any address */
3518 switch (jk) {
3519 case Ijk_Boring:
3520 case Ijk_Ret:
3521 case Ijk_Call: {
3522 HReg dst = s390_isel_int_expr(env, next);
3523 if (env->chaining_allowed) {
3524 addInstr(env, s390_insn_xindir(S390_CC_ALWAYS, dst, guest_IA));
3525 } else {
3526 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA,
3527 Ijk_Boring));
3528 }
3529 return;
3530 }
3531 default:
3532 break;
3533 }
3534
3535 /* Case: some other kind of transfer to any address */
3536 switch (jk) {
florian4e0083e2012-08-26 03:41:56 +00003537 case Ijk_EmFail:
florian4b8efad2012-09-02 18:07:08 +00003538 case Ijk_EmWarn:
florian65b5b3f2012-04-22 02:51:27 +00003539 case Ijk_NoDecode:
florian2d98d892012-04-14 20:35:17 +00003540 case Ijk_TInval:
florian8844a632012-04-13 04:04:06 +00003541 case Ijk_Sys_syscall:
3542 case Ijk_ClientReq:
3543 case Ijk_NoRedir:
3544 case Ijk_Yield:
3545 case Ijk_SigTRAP: {
3546 HReg dst = s390_isel_int_expr(env, next);
3547 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA, jk));
3548 return;
3549 }
3550 default:
3551 break;
3552 }
3553
3554 vpanic("iselNext");
sewardj2019a972011-03-07 16:04:07 +00003555}
3556
3557
3558/*---------------------------------------------------------*/
3559/*--- Insn selector top-level ---*/
3560/*---------------------------------------------------------*/
3561
florianf26994a2012-04-21 03:34:54 +00003562/* Translate an entire SB to s390 code.
3563 Note: archinfo_host is a pointer to a stack-allocated variable.
3564 Do not assign it to a global variable! */
sewardj2019a972011-03-07 16:04:07 +00003565
3566HInstrArray *
3567iselSB_S390(IRSB *bb, VexArch arch_host, VexArchInfo *archinfo_host,
florian8844a632012-04-13 04:04:06 +00003568 VexAbiInfo *vbi, Int offset_host_evcheck_counter,
3569 Int offset_host_evcheck_fail_addr, Bool chaining_allowed,
3570 Bool add_profinc, Addr64 max_ga)
sewardj2019a972011-03-07 16:04:07 +00003571{
3572 UInt i, j;
3573 HReg hreg, hregHI;
3574 ISelEnv *env;
3575 UInt hwcaps_host = archinfo_host->hwcaps;
3576
florianf26994a2012-04-21 03:34:54 +00003577 /* KLUDGE: export hwcaps. */
3578 s390_host_hwcaps = hwcaps_host;
sewardj2019a972011-03-07 16:04:07 +00003579
sewardj2019a972011-03-07 16:04:07 +00003580 /* Do some sanity checks */
sewardj652b56a2011-04-13 15:38:17 +00003581 vassert((VEX_HWCAPS_S390X(hwcaps_host) & ~(VEX_HWCAPS_S390X_ALL)) == 0);
sewardj2019a972011-03-07 16:04:07 +00003582
3583 /* Make up an initial environment to use. */
3584 env = LibVEX_Alloc(sizeof(ISelEnv));
3585 env->vreg_ctr = 0;
3586
3587 /* Set up output code array. */
3588 env->code = newHInstrArray();
3589
3590 /* Copy BB's type env. */
3591 env->type_env = bb->tyenv;
3592
florianad43b3a2012-02-20 15:01:14 +00003593 /* Set up data structures for tracking guest register values. */
florianad43b3a2012-02-20 15:01:14 +00003594 for (i = 0; i < NUM_TRACKED_REGS; ++i) {
3595 env->old_value[i] = 0; /* just something to have a defined value */
3596 env->old_value_valid[i] = False;
3597 }
3598
sewardj2019a972011-03-07 16:04:07 +00003599 /* Make up an IRTemp -> virtual HReg mapping. This doesn't
3600 change as we go along. For some reason types_used has Int type -- but
3601 it should be unsigned. Internally we use an unsigned type; so we
3602 assert it here. */
3603 vassert(bb->tyenv->types_used >= 0);
3604
3605 env->n_vregmap = bb->tyenv->types_used;
3606 env->vregmap = LibVEX_Alloc(env->n_vregmap * sizeof(HReg));
3607 env->vregmapHI = LibVEX_Alloc(env->n_vregmap * sizeof(HReg));
3608
florian2c74d242012-09-12 19:38:42 +00003609 env->previous_bfp_rounding_mode = NULL;
florianc8e4f562012-10-27 16:19:31 +00003610 env->previous_dfp_rounding_mode = NULL;
florian2c74d242012-09-12 19:38:42 +00003611
sewardj2019a972011-03-07 16:04:07 +00003612 /* and finally ... */
3613 env->hwcaps = hwcaps_host;
3614
florian8844a632012-04-13 04:04:06 +00003615 env->max_ga = max_ga;
3616 env->chaining_allowed = chaining_allowed;
3617
sewardj2019a972011-03-07 16:04:07 +00003618 /* For each IR temporary, allocate a suitably-kinded virtual
3619 register. */
3620 j = 0;
3621 for (i = 0; i < env->n_vregmap; i++) {
3622 hregHI = hreg = INVALID_HREG;
3623 switch (bb->tyenv->types[i]) {
3624 case Ity_I1:
3625 case Ity_I8:
3626 case Ity_I16:
3627 case Ity_I32:
3628 hreg = mkHReg(j++, HRcInt64, True);
3629 break;
3630
3631 case Ity_I64:
3632 hreg = mkHReg(j++, HRcInt64, True);
3633 break;
3634
3635 case Ity_I128:
3636 hreg = mkHReg(j++, HRcInt64, True);
3637 hregHI = mkHReg(j++, HRcInt64, True);
3638 break;
3639
3640 case Ity_F32:
3641 case Ity_F64:
floriane38f6412012-12-21 17:32:12 +00003642 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003643 case Ity_D64:
sewardj2019a972011-03-07 16:04:07 +00003644 hreg = mkHReg(j++, HRcFlt64, True);
3645 break;
3646
3647 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003648 case Ity_D128:
sewardj2019a972011-03-07 16:04:07 +00003649 hreg = mkHReg(j++, HRcFlt64, True);
3650 hregHI = mkHReg(j++, HRcFlt64, True);
3651 break;
3652
3653 case Ity_V128: /* fall through */
3654 default:
3655 ppIRType(bb->tyenv->types[i]);
florian4ebaa772012-12-20 19:44:18 +00003656 vpanic("iselSB_S390: IRTemp type");
sewardj2019a972011-03-07 16:04:07 +00003657 }
3658
3659 env->vregmap[i] = hreg;
3660 env->vregmapHI[i] = hregHI;
3661 }
3662 env->vreg_ctr = j;
3663
florian8844a632012-04-13 04:04:06 +00003664 /* The very first instruction must be an event check. */
3665 s390_amode *counter, *fail_addr;
3666 counter = s390_amode_for_guest_state(offset_host_evcheck_counter);
3667 fail_addr = s390_amode_for_guest_state(offset_host_evcheck_fail_addr);
3668 addInstr(env, s390_insn_evcheck(counter, fail_addr));
3669
3670 /* Possibly a block counter increment (for profiling). At this
3671 point we don't know the address of the counter, so just pretend
3672 it is zero. It will have to be patched later, but before this
3673 translation is used, by a call to LibVEX_patchProfInc. */
3674 if (add_profinc) {
3675 addInstr(env, s390_insn_profinc());
3676 }
3677
sewardj2019a972011-03-07 16:04:07 +00003678 /* Ok, finally we can iterate over the statements. */
3679 for (i = 0; i < bb->stmts_used; i++)
3680 if (bb->stmts[i])
3681 s390_isel_stmt(env, bb->stmts[i]);
3682
florian8844a632012-04-13 04:04:06 +00003683 iselNext(env, bb->next, bb->jumpkind, bb->offsIP);
sewardj2019a972011-03-07 16:04:07 +00003684
3685 /* Record the number of vregs we used. */
3686 env->code->n_vregs = env->vreg_ctr;
3687
3688 return env->code;
3689}
3690
3691/*---------------------------------------------------------------*/
3692/*--- end host_s390_isel.c ---*/
3693/*---------------------------------------------------------------*/