blob: d84125d8ab17d4476bfc3658085d59373140ab77 [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);
florian79efdc62013-02-11 00:47:35 +0000199 vassert(! hregIsInvalid(env->vregmap[tmp]));
sewardj2019a972011-03-07 16:04:07 +0000200
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);
florian79efdc62013-02-11 00:47:35 +0000210 vassert(! hregIsInvalid(env->vregmapHI[tmp]));
sewardj2019a972011-03-07 16:04:07 +0000211
212 *lo = env->vregmap[tmp];
213 *hi = env->vregmapHI[tmp];
214}
215
216
217/* Allocate a new integer register */
218static HReg
219newVRegI(ISelEnv *env)
220{
221 HReg reg = mkHReg(env->vreg_ctr, HRcInt64, True /* virtual */ );
222 env->vreg_ctr++;
223
224 return reg;
225}
226
227
228/* Allocate a new floating point register */
229static HReg
230newVRegF(ISelEnv *env)
231{
232 HReg reg = mkHReg(env->vreg_ctr, HRcFlt64, True /* virtual */ );
233
234 env->vreg_ctr++;
235
236 return reg;
237}
238
239
240/* Construct a non-virtual general purpose register */
241static __inline__ HReg
florian297b6062012-05-08 20:16:17 +0000242make_gpr(UInt regno)
sewardj2019a972011-03-07 16:04:07 +0000243{
244 return mkHReg(regno, HRcInt64, False /* virtual */ );
245}
246
247
248/* Construct a non-virtual floating point register */
249static __inline__ HReg
250make_fpr(UInt regno)
251{
252 return mkHReg(regno, HRcFlt64, False /* virtual */ );
253}
254
255
256/*---------------------------------------------------------*/
257/*--- Amode ---*/
258/*---------------------------------------------------------*/
259
260static __inline__ Bool
261ulong_fits_unsigned_12bit(ULong val)
262{
263 return (val & 0xFFFu) == val;
264}
265
266
267static __inline__ Bool
268ulong_fits_signed_20bit(ULong val)
269{
270 Long v = val & 0xFFFFFu;
271
272 v = (v << 44) >> 44; /* sign extend */
273
274 return val == (ULong)v;
275}
276
277
florianad43b3a2012-02-20 15:01:14 +0000278static __inline__ Bool
279ulong_fits_signed_8bit(ULong val)
280{
281 Long v = val & 0xFFu;
282
283 v = (v << 56) >> 56; /* sign extend */
284
285 return val == (ULong)v;
286}
287
sewardj2019a972011-03-07 16:04:07 +0000288/* EXPR is an expression that is used as an address. Return an s390_amode
289 for it. */
290static s390_amode *
291s390_isel_amode_wrk(ISelEnv *env, IRExpr *expr)
292{
293 if (expr->tag == Iex_Binop && expr->Iex.Binop.op == Iop_Add64) {
294 IRExpr *arg1 = expr->Iex.Binop.arg1;
295 IRExpr *arg2 = expr->Iex.Binop.arg2;
296
297 /* Move constant into right subtree */
298 if (arg1->tag == Iex_Const) {
299 IRExpr *tmp;
300 tmp = arg1;
301 arg1 = arg2;
302 arg2 = tmp;
303 }
304
305 /* r + constant: Check for b12 first, then b20 */
306 if (arg2->tag == Iex_Const && arg2->Iex.Const.con->tag == Ico_U64) {
307 ULong value = arg2->Iex.Const.con->Ico.U64;
308
309 if (ulong_fits_unsigned_12bit(value)) {
310 return s390_amode_b12((Int)value, s390_isel_int_expr(env, arg1));
311 }
sewardj652b56a2011-04-13 15:38:17 +0000312 /* If long-displacement is not available, do not construct B20 or
313 BX20 amodes because code generation cannot handle them. */
314 if (s390_host_has_ldisp && ulong_fits_signed_20bit(value)) {
sewardj2019a972011-03-07 16:04:07 +0000315 return s390_amode_b20((Int)value, s390_isel_int_expr(env, arg1));
316 }
317 }
318 }
319
320 /* Doesn't match anything in particular. Generate it into
321 a register and use that. */
322 return s390_amode_b12(0, s390_isel_int_expr(env, expr));
323}
324
325
326static s390_amode *
327s390_isel_amode(ISelEnv *env, IRExpr *expr)
328{
florian35da8612011-06-25 02:25:41 +0000329 s390_amode *am;
sewardj2019a972011-03-07 16:04:07 +0000330
331 /* Address computation should yield a 64-bit value */
332 vassert(typeOfIRExpr(env->type_env, expr) == Ity_I64);
333
334 am = s390_isel_amode_wrk(env, expr);
335
336 /* Check post-condition */
337 vassert(s390_amode_is_sane(am));
338
339 return am;
340}
341
342
343/*---------------------------------------------------------*/
344/*--- Helper functions ---*/
345/*---------------------------------------------------------*/
346
347/* Constants and memory accesses should be right operands */
348#define order_commutative_operands(left, right) \
349 do { \
350 if (left->tag == Iex_Const || left->tag == Iex_Load || \
351 left->tag == Iex_Get) { \
352 IRExpr *tmp; \
353 tmp = left; \
354 left = right; \
355 right = tmp; \
356 } \
357 } while (0)
358
359
360/* Copy an RMI operand to the DST register */
361static s390_insn *
362s390_opnd_copy(UChar size, HReg dst, s390_opnd_RMI opnd)
363{
364 switch (opnd.tag) {
365 case S390_OPND_AMODE:
366 return s390_insn_load(size, dst, opnd.variant.am);
367
368 case S390_OPND_REG:
369 return s390_insn_move(size, dst, opnd.variant.reg);
370
371 case S390_OPND_IMMEDIATE:
372 return s390_insn_load_immediate(size, dst, opnd.variant.imm);
373
374 default:
375 vpanic("s390_opnd_copy");
376 }
377}
378
379
380/* Construct a RMI operand for a register */
381static __inline__ s390_opnd_RMI
382s390_opnd_reg(HReg reg)
383{
384 s390_opnd_RMI opnd;
385
386 opnd.tag = S390_OPND_REG;
387 opnd.variant.reg = reg;
388
389 return opnd;
390}
391
392
393/* Construct a RMI operand for an immediate constant */
394static __inline__ s390_opnd_RMI
395s390_opnd_imm(ULong value)
396{
397 s390_opnd_RMI opnd;
398
399 opnd.tag = S390_OPND_IMMEDIATE;
400 opnd.variant.imm = value;
401
402 return opnd;
403}
404
405
florianffbd84d2012-12-09 02:06:29 +0000406/* Return 1, if EXPR represents the constant 0 */
407static Bool
sewardj2019a972011-03-07 16:04:07 +0000408s390_expr_is_const_zero(IRExpr *expr)
409{
410 ULong value;
411
412 if (expr->tag == Iex_Const) {
413 switch (expr->Iex.Const.con->tag) {
414 case Ico_U1: value = expr->Iex.Const.con->Ico.U1; break;
415 case Ico_U8: value = expr->Iex.Const.con->Ico.U8; break;
416 case Ico_U16: value = expr->Iex.Const.con->Ico.U16; break;
417 case Ico_U32: value = expr->Iex.Const.con->Ico.U32; break;
418 case Ico_U64: value = expr->Iex.Const.con->Ico.U64; break;
419 default:
420 vpanic("s390_expr_is_const_zero");
421 }
422 return value == 0;
423 }
424
425 return 0;
426}
427
428
florianb93348d2012-12-27 00:59:43 +0000429/* Return the value of CON as a sign-exteded ULong value */
430static ULong
431get_const_value_as_ulong(const IRConst *con)
432{
433 Long value;
434
435 switch (con->tag) {
436 case Ico_U1: value = con->Ico.U1; return (ULong) ((value << 63) >> 63);
437 case Ico_U8: value = con->Ico.U8; return (ULong) ((value << 56) >> 56);
438 case Ico_U16: value = con->Ico.U16; return (ULong) ((value << 48) >> 48);
439 case Ico_U32: value = con->Ico.U32; return (ULong) ((value << 32) >> 32);
440 case Ico_U64: return con->Ico.U64;
441 default:
442 vpanic("get_const_value_as_ulong");
443 }
444}
445
446
sewardj2019a972011-03-07 16:04:07 +0000447/* Call a helper (clean or dirty)
448 Arguments must satisfy the following conditions:
floriane0654362012-05-09 13:31:09 +0000449
sewardj2019a972011-03-07 16:04:07 +0000450 (a) they are expressions yielding an integer result
451 (b) there can be no more than S390_NUM_GPRPARMS arguments
floriane0654362012-05-09 13:31:09 +0000452
453 guard is a Ity_Bit expression indicating whether or not the
454 call happens. If guard == NULL, the call is unconditional.
florian52af7bc2012-05-12 03:44:49 +0000455
456 Calling the helper function proceeds as follows:
457
458 (1) The helper arguments are evaluated and their value stored in
459 virtual registers.
460 (2) The condition code is evaluated
461 (3) The argument values are copied from the virtual registers to the
462 registers mandated by the ABI.
463 (4) Call the helper function.
464
465 This is not the most efficient way as step 3 generates register-to-register
466 moves. But it is the least fragile way as the only hidden dependency here
467 is that register-to-register moves (step 3) must not clobber the condition
468 code. Other schemes (e.g. VEX r2326) that attempt to avoid the register-
469 to-register add more such dependencies. Not good. Besides, it's the job
470 of the register allocator to throw out those reg-to-reg moves.
sewardj2019a972011-03-07 16:04:07 +0000471*/
472static void
473doHelperCall(ISelEnv *env, Bool passBBP, IRExpr *guard,
florian01ed6e72012-05-27 16:52:43 +0000474 IRCallee *callee, IRExpr **args, HReg dst)
sewardj2019a972011-03-07 16:04:07 +0000475{
florian52af7bc2012-05-12 03:44:49 +0000476 UInt n_args, i, argreg, size;
sewardj2019a972011-03-07 16:04:07 +0000477 ULong target;
478 HReg tmpregs[S390_NUM_GPRPARMS];
479 s390_cc_t cc;
480
481 n_args = 0;
482 for (i = 0; args[i]; i++)
483 ++n_args;
484
485 if (n_args > (S390_NUM_GPRPARMS - (passBBP ? 1 : 0))) {
486 vpanic("doHelperCall: too many arguments");
487 }
488
florian11b8ee82012-08-06 13:35:33 +0000489 /* All arguments must have Ity_I64. For two reasons:
490 (1) We do not handle floating point arguments.
491 (2) The ABI requires that integer values are sign- or zero-extended
492 to 64 bit.
493 */
494 Int arg_errors = 0;
495 for (i = 0; i < n_args; ++i) {
496 IRType type = typeOfIRExpr(env->type_env, args[i]);
497 if (type != Ity_I64) {
498 ++arg_errors;
499 vex_printf("calling %s: argument #%d has type ", callee->name, i);
500 ppIRType(type);
501 vex_printf("; Ity_I64 is required\n");
502 }
503 }
504
505 if (arg_errors)
506 vpanic("cannot continue due to errors in argument passing");
507
florian52af7bc2012-05-12 03:44:49 +0000508 argreg = 0;
509
510 /* If we need the guest state pointer put it in a temporary arg reg */
511 if (passBBP) {
512 tmpregs[argreg] = newVRegI(env);
513 addInstr(env, s390_insn_move(sizeof(ULong), tmpregs[argreg],
514 s390_hreg_guest_state_pointer()));
515 argreg++;
516 }
517
518 /* Compute the function arguments into a temporary register each */
519 for (i = 0; i < n_args; i++) {
520 tmpregs[argreg] = s390_isel_int_expr(env, args[i]);
521 argreg++;
522 }
523
sewardj2019a972011-03-07 16:04:07 +0000524 /* Compute the condition */
525 cc = S390_CC_ALWAYS;
526 if (guard) {
527 if (guard->tag == Iex_Const
528 && guard->Iex.Const.con->tag == Ico_U1
529 && guard->Iex.Const.con->Ico.U1 == True) {
530 /* unconditional -- do nothing */
531 } else {
532 cc = s390_isel_cc(env, guard);
533 }
534 }
535
florian52af7bc2012-05-12 03:44:49 +0000536 /* Move the args to the final register. It is paramount, that the
537 code to move the registers does not clobber the condition code ! */
floriane0654362012-05-09 13:31:09 +0000538 for (i = 0; i < argreg; i++) {
florian52af7bc2012-05-12 03:44:49 +0000539 HReg finalreg;
540
541 finalreg = make_gpr(s390_gprno_from_arg_index(i));
542 size = sizeofIRType(Ity_I64);
543 addInstr(env, s390_insn_move(size, finalreg, tmpregs[i]));
sewardj2019a972011-03-07 16:04:07 +0000544 }
545
546 target = Ptr_to_ULong(callee->addr);
547
548 /* Finally, the call itself. */
549 addInstr(env, s390_insn_helper_call(cc, (Addr64)target, n_args,
florian01ed6e72012-05-27 16:52:43 +0000550 callee->name, dst));
sewardj2019a972011-03-07 16:04:07 +0000551}
552
553
florian2c74d242012-09-12 19:38:42 +0000554/*---------------------------------------------------------*/
555/*--- BFP helper functions ---*/
556/*---------------------------------------------------------*/
557
558/* Set the BFP rounding mode in the FPC. This function is called for
559 all non-conversion BFP instructions as those will always get the
560 rounding mode from the FPC. */
561static void
562set_bfp_rounding_mode_in_fpc(ISelEnv *env, IRExpr *irrm)
sewardj2019a972011-03-07 16:04:07 +0000563{
florian2c74d242012-09-12 19:38:42 +0000564 vassert(typeOfIRExpr(env->type_env, irrm) == Ity_I32);
565
566 /* Do we need to do anything? */
567 if (env->previous_bfp_rounding_mode &&
568 env->previous_bfp_rounding_mode->tag == Iex_RdTmp &&
569 irrm->tag == Iex_RdTmp &&
570 env->previous_bfp_rounding_mode->Iex.RdTmp.tmp == irrm->Iex.RdTmp.tmp) {
571 /* No - new mode is identical to previous mode. */
572 return;
573 }
574
575 /* No luck - we better set it, and remember what we set it to. */
576 env->previous_bfp_rounding_mode = irrm;
577
578 /* The incoming rounding mode is in VEX IR encoding. Need to change
579 to s390.
580
581 rounding mode | s390 | IR
582 -------------------------
583 to nearest | 00 | 00
584 to zero | 01 | 11
585 to +infinity | 10 | 10
586 to -infinity | 11 | 01
587
588 So: s390 = (4 - IR) & 3
589 */
590 HReg ir = s390_isel_int_expr(env, irrm);
591
592 HReg mode = newVRegI(env);
593
594 addInstr(env, s390_insn_load_immediate(4, mode, 4));
595 addInstr(env, s390_insn_alu(4, S390_ALU_SUB, mode, s390_opnd_reg(ir)));
596 addInstr(env, s390_insn_alu(4, S390_ALU_AND, mode, s390_opnd_imm(3)));
597
florian125e20d2012-10-07 15:42:37 +0000598 addInstr(env, s390_insn_set_fpc_bfprm(4, mode));
florian2c74d242012-09-12 19:38:42 +0000599}
600
601
602/* This function is invoked for insns that support a specification of
603 a rounding mode in the insn itself. In that case there is no need to
604 stick the rounding mode into the FPC -- a good thing. However, the
605 rounding mode must be known. */
florian125e20d2012-10-07 15:42:37 +0000606static s390_bfp_round_t
florian2c74d242012-09-12 19:38:42 +0000607get_bfp_rounding_mode(ISelEnv *env, IRExpr *irrm)
608{
609 if (irrm->tag == Iex_Const) { /* rounding mode is known */
610 vassert(irrm->Iex.Const.con->tag == Ico_U32);
611 IRRoundingMode mode = irrm->Iex.Const.con->Ico.U32;
sewardj2019a972011-03-07 16:04:07 +0000612
613 switch (mode) {
florian125e20d2012-10-07 15:42:37 +0000614 case Irrm_NEAREST: return S390_BFP_ROUND_NEAREST_EVEN;
615 case Irrm_ZERO: return S390_BFP_ROUND_ZERO;
616 case Irrm_PosINF: return S390_BFP_ROUND_POSINF;
617 case Irrm_NegINF: return S390_BFP_ROUND_NEGINF;
florian2c74d242012-09-12 19:38:42 +0000618 default:
619 vpanic("get_bfp_rounding_mode");
sewardj2019a972011-03-07 16:04:07 +0000620 }
621 }
622
florian2c74d242012-09-12 19:38:42 +0000623 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +0000624 return S390_BFP_ROUND_PER_FPC;
sewardj2019a972011-03-07 16:04:07 +0000625}
626
627
florianc8e4f562012-10-27 16:19:31 +0000628/*---------------------------------------------------------*/
629/*--- DFP helper functions ---*/
630/*---------------------------------------------------------*/
631
632/* Set the DFP rounding mode in the FPC. This function is called for
633 all non-conversion DFP instructions as those will always get the
634 rounding mode from the FPC. */
florianc8e4f562012-10-27 16:19:31 +0000635static void
636set_dfp_rounding_mode_in_fpc(ISelEnv *env, IRExpr *irrm)
637{
638 vassert(typeOfIRExpr(env->type_env, irrm) == Ity_I32);
639
640 /* Do we need to do anything? */
641 if (env->previous_dfp_rounding_mode &&
642 env->previous_dfp_rounding_mode->tag == Iex_RdTmp &&
643 irrm->tag == Iex_RdTmp &&
644 env->previous_dfp_rounding_mode->Iex.RdTmp.tmp == irrm->Iex.RdTmp.tmp) {
645 /* No - new mode is identical to previous mode. */
646 return;
647 }
648
649 /* No luck - we better set it, and remember what we set it to. */
650 env->previous_dfp_rounding_mode = irrm;
651
652 /* The incoming rounding mode is in VEX IR encoding. Need to change
653 to s390.
654
655 rounding mode | S390 | IR
656 -----------------------------------------------
657 to nearest, ties to even | 000 | 000
658 to zero | 001 | 011
659 to +infinity | 010 | 010
660 to -infinity | 011 | 001
661 to nearest, ties away from 0 | 100 | 100
662 to nearest, ties toward 0 | 101 | 111
663 to away from 0 | 110 | 110
664 to prepare for shorter precision | 111 | 101
665
666 So: s390 = (IR ^ ((IR << 1) & 2))
667 */
668 HReg ir = s390_isel_int_expr(env, irrm);
669
670 HReg mode = newVRegI(env);
671
672 addInstr(env, s390_insn_move(4, mode, ir));
673 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, mode, s390_opnd_imm(1)));
674 addInstr(env, s390_insn_alu(4, S390_ALU_AND, mode, s390_opnd_imm(2)));
675 addInstr(env, s390_insn_alu(4, S390_ALU_XOR, mode, s390_opnd_reg(ir)));
676
677 addInstr(env, s390_insn_set_fpc_dfprm(4, mode));
678}
679
680
681/* This function is invoked for insns that support a specification of
682 a rounding mode in the insn itself. In that case there is no need to
683 stick the rounding mode into the FPC -- a good thing. However, the
684 rounding mode must be known.
florianff9000d2013-02-08 20:22:03 +0000685
florian79e5a482013-06-06 19:12:46 +0000686 When mapping an Irrm_XYZ value to an S390_DFP_ROUND_ value there is
687 often a choice. For instance, Irrm_ZERO could be mapped to either
florianff9000d2013-02-08 20:22:03 +0000688 S390_DFP_ROUND_ZERO_5 or S390_DFP_ROUND_ZERO_9. The difference between
689 those two is that with S390_DFP_ROUND_ZERO_9 the recognition of the
690 quantum exception is suppressed whereas with S390_DFP_ROUND_ZERO_5 it
691 is not. As the quantum exception is not modelled we can choose either
692 value. The choice is to use S390_DFP_ROUND_.. values in the range [8:15],
693 because values in the range [1:7] have unpredictable rounding behaviour
694 when the floating point exception facility is not installed.
florianc8e4f562012-10-27 16:19:31 +0000695
696 Translation table of
697 s390 DFP rounding mode to IRRoundingMode to s390 DFP rounding mode
698
florian79e5a482013-06-06 19:12:46 +0000699 s390(S390_DFP_ROUND_) | IR(Irrm_) | s390(S390_DFP_ROUND_)
florianc8e4f562012-10-27 16:19:31 +0000700 --------------------------------------------------------------------
florianff9000d2013-02-08 20:22:03 +0000701 NEAREST_TIE_AWAY_0_1 | NEAREST_TIE_AWAY_0 | NEAREST_TIE_AWAY_0_12
florianc8e4f562012-10-27 16:19:31 +0000702 NEAREST_TIE_AWAY_0_12 | " | "
florianff9000d2013-02-08 20:22:03 +0000703 PREPARE_SHORT_3 | PREPARE_SHORTER | PREPARE_SHORT_15
florianc8e4f562012-10-27 16:19:31 +0000704 PREPARE_SHORT_15 | " | "
florianff9000d2013-02-08 20:22:03 +0000705 NEAREST_EVEN_4 | NEAREST | NEAREST_EVEN_8
florianc8e4f562012-10-27 16:19:31 +0000706 NEAREST_EVEN_8 | " | "
florianff9000d2013-02-08 20:22:03 +0000707 ZERO_5 | ZERO | ZERO_9
florianc8e4f562012-10-27 16:19:31 +0000708 ZERO_9 | " | "
florianff9000d2013-02-08 20:22:03 +0000709 POSINF_6 | PosINF | POSINF_10
florianc8e4f562012-10-27 16:19:31 +0000710 POSINF_10 | " | "
florianff9000d2013-02-08 20:22:03 +0000711 NEGINF_7 | NegINF | NEGINF_11
florianc8e4f562012-10-27 16:19:31 +0000712 NEGINF_11 | " | "
713 NEAREST_TIE_TOWARD_0 | NEAREST_TIE_TOWARD_0| NEAREST_TIE_TOWARD_0
714 AWAY_0 | AWAY_FROM_ZERO | AWAY_0
715*/
716static s390_dfp_round_t
717get_dfp_rounding_mode(ISelEnv *env, IRExpr *irrm)
718{
719 if (irrm->tag == Iex_Const) { /* rounding mode is known */
720 vassert(irrm->Iex.Const.con->tag == Ico_U32);
florian79e5a482013-06-06 19:12:46 +0000721 IRRoundingMode mode = irrm->Iex.Const.con->Ico.U32;
florianc8e4f562012-10-27 16:19:31 +0000722
723 switch (mode) {
florian79e5a482013-06-06 19:12:46 +0000724 case Irrm_NEAREST:
florianff9000d2013-02-08 20:22:03 +0000725 return S390_DFP_ROUND_NEAREST_EVEN_8;
florian79e5a482013-06-06 19:12:46 +0000726 case Irrm_NegINF:
florianff9000d2013-02-08 20:22:03 +0000727 return S390_DFP_ROUND_NEGINF_11;
florian79e5a482013-06-06 19:12:46 +0000728 case Irrm_PosINF:
florianff9000d2013-02-08 20:22:03 +0000729 return S390_DFP_ROUND_POSINF_10;
florian79e5a482013-06-06 19:12:46 +0000730 case Irrm_ZERO:
florianff9000d2013-02-08 20:22:03 +0000731 return S390_DFP_ROUND_ZERO_9;
florian79e5a482013-06-06 19:12:46 +0000732 case Irrm_NEAREST_TIE_AWAY_0:
florianff9000d2013-02-08 20:22:03 +0000733 return S390_DFP_ROUND_NEAREST_TIE_AWAY_0_12;
florian79e5a482013-06-06 19:12:46 +0000734 case Irrm_PREPARE_SHORTER:
florianff9000d2013-02-08 20:22:03 +0000735 return S390_DFP_ROUND_PREPARE_SHORT_15;
florian79e5a482013-06-06 19:12:46 +0000736 case Irrm_AWAY_FROM_ZERO:
florianc8e4f562012-10-27 16:19:31 +0000737 return S390_DFP_ROUND_AWAY_0;
florian79e5a482013-06-06 19:12:46 +0000738 case Irrm_NEAREST_TIE_TOWARD_0:
florianc8e4f562012-10-27 16:19:31 +0000739 return S390_DFP_ROUND_NEAREST_TIE_TOWARD_0;
740 default:
741 vpanic("get_dfp_rounding_mode");
742 }
743 }
744
745 set_dfp_rounding_mode_in_fpc(env, irrm);
746 return S390_DFP_ROUND_PER_FPC_0;
747}
florianc8e4f562012-10-27 16:19:31 +0000748
florian2d3d87f2012-12-21 21:05:17 +0000749
750/*---------------------------------------------------------*/
751/*--- Condition code helper functions ---*/
752/*---------------------------------------------------------*/
753
sewardj2019a972011-03-07 16:04:07 +0000754/* CC_S390 holds the condition code in s390 encoding. Convert it to
florian2d3d87f2012-12-21 21:05:17 +0000755 VEX encoding (IRCmpFResult)
sewardj2019a972011-03-07 16:04:07 +0000756
757 s390 VEX b6 b2 b0 cc.1 cc.0
758 0 0x40 EQ 1 0 0 0 0
759 1 0x01 LT 0 0 1 0 1
760 2 0x00 GT 0 0 0 1 0
761 3 0x45 Unordered 1 1 1 1 1
762
763 b0 = cc.0
764 b2 = cc.0 & cc.1
765 b6 = ~(cc.0 ^ cc.1) // ((cc.0 - cc.1) + 0x1 ) & 0x1
766
767 VEX = b0 | (b2 << 2) | (b6 << 6);
768*/
769static HReg
florian2d3d87f2012-12-21 21:05:17 +0000770convert_s390_to_vex_bfpcc(ISelEnv *env, HReg cc_s390)
sewardj2019a972011-03-07 16:04:07 +0000771{
772 HReg cc0, cc1, b2, b6, cc_vex;
773
774 cc0 = newVRegI(env);
775 addInstr(env, s390_insn_move(4, cc0, cc_s390));
776 addInstr(env, s390_insn_alu(4, S390_ALU_AND, cc0, s390_opnd_imm(1)));
777
778 cc1 = newVRegI(env);
779 addInstr(env, s390_insn_move(4, cc1, cc_s390));
780 addInstr(env, s390_insn_alu(4, S390_ALU_RSH, cc1, s390_opnd_imm(1)));
781
782 b2 = newVRegI(env);
783 addInstr(env, s390_insn_move(4, b2, cc0));
784 addInstr(env, s390_insn_alu(4, S390_ALU_AND, b2, s390_opnd_reg(cc1)));
785 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, b2, s390_opnd_imm(2)));
786
787 b6 = newVRegI(env);
788 addInstr(env, s390_insn_move(4, b6, cc0));
789 addInstr(env, s390_insn_alu(4, S390_ALU_SUB, b6, s390_opnd_reg(cc1)));
790 addInstr(env, s390_insn_alu(4, S390_ALU_ADD, b6, s390_opnd_imm(1)));
791 addInstr(env, s390_insn_alu(4, S390_ALU_AND, b6, s390_opnd_imm(1)));
792 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, b6, s390_opnd_imm(6)));
793
794 cc_vex = newVRegI(env);
795 addInstr(env, s390_insn_move(4, cc_vex, cc0));
796 addInstr(env, s390_insn_alu(4, S390_ALU_OR, cc_vex, s390_opnd_reg(b2)));
797 addInstr(env, s390_insn_alu(4, S390_ALU_OR, cc_vex, s390_opnd_reg(b6)));
798
799 return cc_vex;
800}
801
florian2d3d87f2012-12-21 21:05:17 +0000802/* CC_S390 holds the condition code in s390 encoding. Convert it to
803 VEX encoding (IRCmpDResult) */
804static HReg
805convert_s390_to_vex_dfpcc(ISelEnv *env, HReg cc_s390)
806{
807 /* The encodings for IRCmpFResult and IRCmpDResult are the same/ */
808 return convert_s390_to_vex_bfpcc(env, cc_s390);
809}
810
sewardj2019a972011-03-07 16:04:07 +0000811
812/*---------------------------------------------------------*/
813/*--- ISEL: Integer expressions (128 bit) ---*/
814/*---------------------------------------------------------*/
815static void
816s390_isel_int128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
817 IRExpr *expr)
818{
819 IRType ty = typeOfIRExpr(env->type_env, expr);
820
821 vassert(ty == Ity_I128);
822
823 /* No need to consider the following
824 - 128-bit constants (they do not exist in VEX)
825 - 128-bit loads from memory (will not be generated)
826 */
827
828 /* Read 128-bit IRTemp */
829 if (expr->tag == Iex_RdTmp) {
830 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
831 return;
832 }
833
834 if (expr->tag == Iex_Binop) {
835 IRExpr *arg1 = expr->Iex.Binop.arg1;
836 IRExpr *arg2 = expr->Iex.Binop.arg2;
837 Bool is_signed_multiply, is_signed_divide;
838
839 switch (expr->Iex.Binop.op) {
840 case Iop_MullU64:
841 is_signed_multiply = False;
842 goto do_multiply64;
843
844 case Iop_MullS64:
845 is_signed_multiply = True;
846 goto do_multiply64;
847
848 case Iop_DivModU128to64:
849 is_signed_divide = False;
850 goto do_divide64;
851
852 case Iop_DivModS128to64:
853 is_signed_divide = True;
854 goto do_divide64;
855
856 case Iop_64HLto128:
857 *dst_hi = s390_isel_int_expr(env, arg1);
858 *dst_lo = s390_isel_int_expr(env, arg2);
859 return;
860
861 case Iop_DivModS64to64: {
862 HReg r10, r11, h1;
863 s390_opnd_RMI op2;
864
865 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
866 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
867
868 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000869 r10 = make_gpr(10);
870 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000871
872 /* Move 1st operand into r11 and */
873 addInstr(env, s390_insn_move(8, r11, h1));
874
875 /* Divide */
876 addInstr(env, s390_insn_divs(8, r10, r11, op2));
877
878 /* The result is in registers r10 (remainder) and r11 (quotient).
879 Move the result into the reg pair that is being returned such
880 such that the low 64 bits are the quotient and the upper 64 bits
881 are the remainder. (see libvex_ir.h). */
882 *dst_hi = newVRegI(env);
883 *dst_lo = newVRegI(env);
884 addInstr(env, s390_insn_move(8, *dst_hi, r10));
885 addInstr(env, s390_insn_move(8, *dst_lo, r11));
886 return;
887 }
888
889 default:
890 break;
891
892 do_multiply64: {
893 HReg r10, r11, h1;
894 s390_opnd_RMI op2;
895
896 order_commutative_operands(arg1, arg2);
897
898 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
899 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
900
901 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000902 r10 = make_gpr(10);
903 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000904
905 /* Move the first operand to r11 */
906 addInstr(env, s390_insn_move(8, r11, h1));
907
908 /* Multiply */
909 addInstr(env, s390_insn_mul(8, r10, r11, op2, is_signed_multiply));
910
911 /* The result is in registers r10 and r11. Assign to two virtual regs
912 and return. */
913 *dst_hi = newVRegI(env);
914 *dst_lo = newVRegI(env);
915 addInstr(env, s390_insn_move(8, *dst_hi, r10));
916 addInstr(env, s390_insn_move(8, *dst_lo, r11));
917 return;
918 }
919
920 do_divide64: {
921 HReg r10, r11, hi, lo;
922 s390_opnd_RMI op2;
923
924 s390_isel_int128_expr(&hi, &lo, env, arg1);
925 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
926
927 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000928 r10 = make_gpr(10);
929 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000930
931 /* Move high 64 bits of the 1st operand into r10 and
932 the low 64 bits into r11. */
933 addInstr(env, s390_insn_move(8, r10, hi));
934 addInstr(env, s390_insn_move(8, r11, lo));
935
936 /* Divide */
937 addInstr(env, s390_insn_div(8, r10, r11, op2, is_signed_divide));
938
939 /* The result is in registers r10 (remainder) and r11 (quotient).
940 Move the result into the reg pair that is being returned such
941 such that the low 64 bits are the quotient and the upper 64 bits
942 are the remainder. (see libvex_ir.h). */
943 *dst_hi = newVRegI(env);
944 *dst_lo = newVRegI(env);
945 addInstr(env, s390_insn_move(8, *dst_hi, r10));
946 addInstr(env, s390_insn_move(8, *dst_lo, r11));
947 return;
948 }
949 }
950 }
951
952 vpanic("s390_isel_int128_expr");
953}
954
955
956/* Compute a 128-bit value into two 64-bit registers. These may be either
957 real or virtual regs; in any case they must not be changed by subsequent
958 code emitted by the caller. */
959static void
960s390_isel_int128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
961{
962 s390_isel_int128_expr_wrk(dst_hi, dst_lo, env, expr);
963
964 /* Sanity checks ... */
965 vassert(hregIsVirtual(*dst_hi));
966 vassert(hregIsVirtual(*dst_lo));
967 vassert(hregClass(*dst_hi) == HRcInt64);
968 vassert(hregClass(*dst_lo) == HRcInt64);
969}
970
971
972/*---------------------------------------------------------*/
973/*--- ISEL: Integer expressions (64/32/16/8 bit) ---*/
974/*---------------------------------------------------------*/
975
976/* Select insns for an integer-typed expression, and add them to the
977 code list. Return a reg holding the result. This reg will be a
978 virtual register. THE RETURNED REG MUST NOT BE MODIFIED. If you
979 want to modify it, ask for a new vreg, copy it in there, and modify
980 the copy. The register allocator will do its best to map both
981 vregs to the same real register, so the copies will often disappear
982 later in the game.
983
984 This should handle expressions of 64, 32, 16 and 8-bit type.
985 All results are returned in a 64bit register.
986 For 16- and 8-bit expressions, the upper (32/48/56 : 16/24) bits
987 are arbitrary, so you should mask or sign extend partial values
988 if necessary.
989*/
990
991/* DO NOT CALL THIS DIRECTLY ! */
992static HReg
993s390_isel_int_expr_wrk(ISelEnv *env, IRExpr *expr)
994{
995 IRType ty = typeOfIRExpr(env->type_env, expr);
996 UChar size;
florian6dc90242012-12-21 21:43:00 +0000997 s390_bfp_conv_t conv;
florian67a171c2013-01-20 03:08:04 +0000998 s390_dfp_conv_t dconv;
sewardj2019a972011-03-07 16:04:07 +0000999
1000 vassert(ty == Ity_I8 || ty == Ity_I16 || ty == Ity_I32 || ty == Ity_I64);
1001
1002 size = sizeofIRType(ty); /* size of the result after evaluating EXPR */
1003
1004 switch (expr->tag) {
1005
1006 /* --------- TEMP --------- */
1007 case Iex_RdTmp:
1008 /* Return the virtual register that holds the temporary. */
1009 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
1010
1011 /* --------- LOAD --------- */
1012 case Iex_Load: {
1013 HReg dst = newVRegI(env);
1014 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
1015
1016 if (expr->Iex.Load.end != Iend_BE)
1017 goto irreducible;
1018
1019 addInstr(env, s390_insn_load(size, dst, am));
1020
1021 return dst;
1022 }
1023
1024 /* --------- BINARY OP --------- */
1025 case Iex_Binop: {
1026 IRExpr *arg1 = expr->Iex.Binop.arg1;
1027 IRExpr *arg2 = expr->Iex.Binop.arg2;
1028 HReg h1, res;
1029 s390_alu_t opkind;
1030 s390_opnd_RMI op2, value, opnd;
1031 s390_insn *insn;
1032 Bool is_commutative, is_signed_multiply, is_signed_divide;
1033
1034 is_commutative = True;
1035
1036 switch (expr->Iex.Binop.op) {
1037 case Iop_MullU8:
1038 case Iop_MullU16:
1039 case Iop_MullU32:
1040 is_signed_multiply = False;
1041 goto do_multiply;
1042
1043 case Iop_MullS8:
1044 case Iop_MullS16:
1045 case Iop_MullS32:
1046 is_signed_multiply = True;
1047 goto do_multiply;
1048
1049 do_multiply: {
1050 HReg r10, r11;
1051 UInt arg_size = size / 2;
1052
1053 order_commutative_operands(arg1, arg2);
1054
1055 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1056 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1057
1058 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001059 r10 = make_gpr(10);
1060 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001061
1062 /* Move the first operand to r11 */
1063 addInstr(env, s390_insn_move(arg_size, r11, h1));
1064
1065 /* Multiply */
1066 addInstr(env, s390_insn_mul(arg_size, r10, r11, op2, is_signed_multiply));
1067
1068 /* The result is in registers r10 and r11. Combine them into a SIZE-bit
1069 value into the destination register. */
1070 res = newVRegI(env);
1071 addInstr(env, s390_insn_move(arg_size, res, r10));
1072 value = s390_opnd_imm(arg_size * 8);
1073 addInstr(env, s390_insn_alu(size, S390_ALU_LSH, res, value));
1074 value = s390_opnd_imm((((ULong)1) << arg_size * 8) - 1);
1075 addInstr(env, s390_insn_alu(size, S390_ALU_AND, r11, value));
1076 opnd = s390_opnd_reg(r11);
1077 addInstr(env, s390_insn_alu(size, S390_ALU_OR, res, opnd));
1078 return res;
1079 }
1080
1081 case Iop_DivModS64to32:
1082 is_signed_divide = True;
1083 goto do_divide;
1084
1085 case Iop_DivModU64to32:
1086 is_signed_divide = False;
1087 goto do_divide;
1088
1089 do_divide: {
1090 HReg r10, r11;
1091
1092 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1093 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1094
1095 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001096 r10 = make_gpr(10);
1097 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001098
1099 /* Split the first operand and put the high 32 bits into r10 and
1100 the low 32 bits into r11. */
1101 addInstr(env, s390_insn_move(8, r10, h1));
1102 addInstr(env, s390_insn_move(8, r11, h1));
1103 value = s390_opnd_imm(32);
1104 addInstr(env, s390_insn_alu(8, S390_ALU_RSH, r10, value));
1105
1106 /* Divide */
1107 addInstr(env, s390_insn_div(4, r10, r11, op2, is_signed_divide));
1108
1109 /* The result is in registers r10 (remainder) and r11 (quotient).
1110 Combine them into a 64-bit value such that the low 32 bits are
1111 the quotient and the upper 32 bits are the remainder. (see
1112 libvex_ir.h). */
1113 res = newVRegI(env);
1114 addInstr(env, s390_insn_move(8, res, r10));
1115 value = s390_opnd_imm(32);
1116 addInstr(env, s390_insn_alu(8, S390_ALU_LSH, res, value));
1117 value = s390_opnd_imm((((ULong)1) << 32) - 1);
1118 addInstr(env, s390_insn_alu(8, S390_ALU_AND, r11, value));
1119 opnd = s390_opnd_reg(r11);
1120 addInstr(env, s390_insn_alu(8, S390_ALU_OR, res, opnd));
1121 return res;
1122 }
1123
florian9fcff4c2012-09-10 03:09:04 +00001124 case Iop_F32toI32S: conv = S390_BFP_F32_TO_I32; goto do_convert;
1125 case Iop_F32toI64S: conv = S390_BFP_F32_TO_I64; goto do_convert;
1126 case Iop_F32toI32U: conv = S390_BFP_F32_TO_U32; goto do_convert;
1127 case Iop_F32toI64U: conv = S390_BFP_F32_TO_U64; goto do_convert;
1128 case Iop_F64toI32S: conv = S390_BFP_F64_TO_I32; goto do_convert;
1129 case Iop_F64toI64S: conv = S390_BFP_F64_TO_I64; goto do_convert;
1130 case Iop_F64toI32U: conv = S390_BFP_F64_TO_U32; goto do_convert;
1131 case Iop_F64toI64U: conv = S390_BFP_F64_TO_U64; goto do_convert;
1132 case Iop_F128toI32S: conv = S390_BFP_F128_TO_I32; goto do_convert_128;
1133 case Iop_F128toI64S: conv = S390_BFP_F128_TO_I64; goto do_convert_128;
1134 case Iop_F128toI32U: conv = S390_BFP_F128_TO_U32; goto do_convert_128;
1135 case Iop_F128toI64U: conv = S390_BFP_F128_TO_U64; goto do_convert_128;
florian67a171c2013-01-20 03:08:04 +00001136
1137 case Iop_D64toI32S: dconv = S390_DFP_D64_TO_I32; goto do_convert_dfp;
floriana887acd2013-02-08 23:32:54 +00001138 case Iop_D64toI64S: dconv = S390_DFP_D64_TO_I64; goto do_convert_dfp;
florian67a171c2013-01-20 03:08:04 +00001139 case Iop_D64toI32U: dconv = S390_DFP_D64_TO_U32; goto do_convert_dfp;
1140 case Iop_D64toI64U: dconv = S390_DFP_D64_TO_U64; goto do_convert_dfp;
1141 case Iop_D128toI32S: dconv = S390_DFP_D128_TO_I32; goto do_convert_dfp128;
floriana887acd2013-02-08 23:32:54 +00001142 case Iop_D128toI64S: dconv = S390_DFP_D128_TO_I64; goto do_convert_dfp128;
florian67a171c2013-01-20 03:08:04 +00001143 case Iop_D128toI32U: dconv = S390_DFP_D128_TO_U32; goto do_convert_dfp128;
1144 case Iop_D128toI64U: dconv = S390_DFP_D128_TO_U64; goto do_convert_dfp128;
sewardj2019a972011-03-07 16:04:07 +00001145
1146 do_convert: {
florian125e20d2012-10-07 15:42:37 +00001147 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00001148
1149 res = newVRegI(env);
1150 h1 = s390_isel_float_expr(env, arg2); /* Process operand */
1151
florian2c74d242012-09-12 19:38:42 +00001152 rounding_mode = get_bfp_rounding_mode(env, arg1);
1153 addInstr(env, s390_insn_bfp_convert(size, conv, res, h1,
1154 rounding_mode));
sewardj2019a972011-03-07 16:04:07 +00001155 return res;
1156 }
1157
1158 do_convert_128: {
florian125e20d2012-10-07 15:42:37 +00001159 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00001160 HReg op_hi, op_lo, f13, f15;
1161
1162 res = newVRegI(env);
1163 s390_isel_float128_expr(&op_hi, &op_lo, env, arg2); /* operand */
1164
1165 /* We use non-virtual registers r13 and r15 as pair */
1166 f13 = make_fpr(13);
1167 f15 = make_fpr(15);
1168
1169 /* operand --> (f13, f15) */
1170 addInstr(env, s390_insn_move(8, f13, op_hi));
1171 addInstr(env, s390_insn_move(8, f15, op_lo));
1172
florian2c74d242012-09-12 19:38:42 +00001173 rounding_mode = get_bfp_rounding_mode(env, arg1);
florian9fcff4c2012-09-10 03:09:04 +00001174 addInstr(env, s390_insn_bfp128_convert_from(size, conv, res, f13, f15,
sewardj2019a972011-03-07 16:04:07 +00001175 rounding_mode));
1176 return res;
1177 }
1178
florian5f034622013-01-13 02:29:05 +00001179 do_convert_dfp: {
1180 s390_dfp_round_t rounding_mode;
1181
1182 res = newVRegI(env);
1183 h1 = s390_isel_dfp_expr(env, arg2); /* Process operand */
1184
1185 rounding_mode = get_dfp_rounding_mode(env, arg1);
florian67a171c2013-01-20 03:08:04 +00001186 addInstr(env, s390_insn_dfp_convert(size, dconv, res, h1,
florian5f034622013-01-13 02:29:05 +00001187 rounding_mode));
1188 return res;
1189 }
1190
1191 do_convert_dfp128: {
1192 s390_dfp_round_t rounding_mode;
1193 HReg op_hi, op_lo, f13, f15;
1194
1195 res = newVRegI(env);
1196 s390_isel_dfp128_expr(&op_hi, &op_lo, env, arg2); /* operand */
1197
1198 /* We use non-virtual registers r13 and r15 as pair */
1199 f13 = make_fpr(13);
1200 f15 = make_fpr(15);
1201
1202 /* operand --> (f13, f15) */
1203 addInstr(env, s390_insn_move(8, f13, op_hi));
1204 addInstr(env, s390_insn_move(8, f15, op_lo));
1205
1206 rounding_mode = get_dfp_rounding_mode(env, arg1);
florian67a171c2013-01-20 03:08:04 +00001207 addInstr(env, s390_insn_dfp128_convert_from(size, dconv, res, f13,
florian5f034622013-01-13 02:29:05 +00001208 f15, rounding_mode));
1209 return res;
1210 }
1211
sewardj2019a972011-03-07 16:04:07 +00001212 case Iop_8HLto16:
1213 case Iop_16HLto32:
1214 case Iop_32HLto64: {
1215 HReg h2;
1216 UInt arg_size = size / 2;
1217
1218 res = newVRegI(env);
1219 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1220 h2 = s390_isel_int_expr(env, arg2); /* Process 2nd operand */
1221
1222 addInstr(env, s390_insn_move(arg_size, res, h1));
1223 value = s390_opnd_imm(arg_size * 8);
1224 addInstr(env, s390_insn_alu(size, S390_ALU_LSH, res, value));
1225 value = s390_opnd_imm((((ULong)1) << arg_size * 8) - 1);
1226 addInstr(env, s390_insn_alu(size, S390_ALU_AND, h2, value));
1227 opnd = s390_opnd_reg(h2);
1228 addInstr(env, s390_insn_alu(size, S390_ALU_OR, res, opnd));
1229 return res;
1230 }
1231
1232 case Iop_Max32U: {
1233 /* arg1 > arg2 ? arg1 : arg2 using uint32_t arguments */
1234 res = newVRegI(env);
1235 h1 = s390_isel_int_expr(env, arg1);
1236 op2 = s390_isel_int_expr_RMI(env, arg2);
1237
1238 addInstr(env, s390_insn_move(size, res, h1));
1239 addInstr(env, s390_insn_compare(size, res, op2, False /* signed */));
1240 addInstr(env, s390_insn_cond_move(size, S390_CC_L, res, op2));
1241 return res;
1242 }
1243
1244 case Iop_CmpF32:
1245 case Iop_CmpF64: {
1246 HReg cc_s390, h2;
1247
1248 h1 = s390_isel_float_expr(env, arg1);
1249 h2 = s390_isel_float_expr(env, arg2);
1250 cc_s390 = newVRegI(env);
1251
1252 size = (expr->Iex.Binop.op == Iop_CmpF32) ? 4 : 8;
1253
1254 addInstr(env, s390_insn_bfp_compare(size, cc_s390, h1, h2));
1255
florian2d3d87f2012-12-21 21:05:17 +00001256 return convert_s390_to_vex_bfpcc(env, cc_s390);
sewardj2019a972011-03-07 16:04:07 +00001257 }
1258
1259 case Iop_CmpF128: {
1260 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15, cc_s390;
1261
1262 s390_isel_float128_expr(&op1_hi, &op1_lo, env, arg1); /* 1st operand */
1263 s390_isel_float128_expr(&op2_hi, &op2_lo, env, arg2); /* 2nd operand */
1264 cc_s390 = newVRegI(env);
1265
1266 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1267 f12 = make_fpr(12);
1268 f13 = make_fpr(13);
1269 f14 = make_fpr(14);
1270 f15 = make_fpr(15);
1271
1272 /* 1st operand --> (f12, f14) */
1273 addInstr(env, s390_insn_move(8, f12, op1_hi));
1274 addInstr(env, s390_insn_move(8, f14, op1_lo));
1275
1276 /* 2nd operand --> (f13, f15) */
1277 addInstr(env, s390_insn_move(8, f13, op2_hi));
1278 addInstr(env, s390_insn_move(8, f15, op2_lo));
1279
1280 res = newVRegI(env);
1281 addInstr(env, s390_insn_bfp128_compare(16, cc_s390, f12, f14, f13, f15));
1282
florian2d3d87f2012-12-21 21:05:17 +00001283 return convert_s390_to_vex_bfpcc(env, cc_s390);
sewardj2019a972011-03-07 16:04:07 +00001284 }
1285
florian20c6bca2012-12-26 17:47:19 +00001286 case Iop_CmpD64:
1287 case Iop_CmpExpD64: {
floriane38f6412012-12-21 17:32:12 +00001288 HReg cc_s390, h2;
florian20c6bca2012-12-26 17:47:19 +00001289 s390_dfp_cmp_t cmp;
floriane38f6412012-12-21 17:32:12 +00001290
1291 h1 = s390_isel_dfp_expr(env, arg1);
1292 h2 = s390_isel_dfp_expr(env, arg2);
1293 cc_s390 = newVRegI(env);
floriane38f6412012-12-21 17:32:12 +00001294
florian20c6bca2012-12-26 17:47:19 +00001295 switch(expr->Iex.Binop.op) {
1296 case Iop_CmpD64: cmp = S390_DFP_COMPARE; break;
1297 case Iop_CmpExpD64: cmp = S390_DFP_COMPARE_EXP; break;
1298 default: goto irreducible;
1299 }
1300 addInstr(env, s390_insn_dfp_compare(8, cmp, cc_s390, h1, h2));
floriane38f6412012-12-21 17:32:12 +00001301
florian2d3d87f2012-12-21 21:05:17 +00001302 return convert_s390_to_vex_dfpcc(env, cc_s390);
floriane38f6412012-12-21 17:32:12 +00001303 }
1304
florian20c6bca2012-12-26 17:47:19 +00001305 case Iop_CmpD128:
1306 case Iop_CmpExpD128: {
floriane38f6412012-12-21 17:32:12 +00001307 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15, cc_s390;
florian20c6bca2012-12-26 17:47:19 +00001308 s390_dfp_cmp_t cmp;
floriane38f6412012-12-21 17:32:12 +00001309
1310 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, arg1); /* 1st operand */
1311 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, arg2); /* 2nd operand */
1312 cc_s390 = newVRegI(env);
1313
1314 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1315 f12 = make_fpr(12);
1316 f13 = make_fpr(13);
1317 f14 = make_fpr(14);
1318 f15 = make_fpr(15);
1319
1320 /* 1st operand --> (f12, f14) */
1321 addInstr(env, s390_insn_move(8, f12, op1_hi));
1322 addInstr(env, s390_insn_move(8, f14, op1_lo));
1323
1324 /* 2nd operand --> (f13, f15) */
1325 addInstr(env, s390_insn_move(8, f13, op2_hi));
1326 addInstr(env, s390_insn_move(8, f15, op2_lo));
1327
florian20c6bca2012-12-26 17:47:19 +00001328 switch(expr->Iex.Binop.op) {
1329 case Iop_CmpD128: cmp = S390_DFP_COMPARE; break;
1330 case Iop_CmpExpD128: cmp = S390_DFP_COMPARE_EXP; break;
1331 default: goto irreducible;
1332 }
1333 addInstr(env, s390_insn_dfp128_compare(16, cmp, cc_s390, f12, f14,
1334 f13, f15));
floriane38f6412012-12-21 17:32:12 +00001335
florian2d3d87f2012-12-21 21:05:17 +00001336 return convert_s390_to_vex_dfpcc(env, cc_s390);
floriane38f6412012-12-21 17:32:12 +00001337 }
1338
sewardj2019a972011-03-07 16:04:07 +00001339 case Iop_Add8:
1340 case Iop_Add16:
1341 case Iop_Add32:
1342 case Iop_Add64:
1343 opkind = S390_ALU_ADD;
1344 break;
1345
1346 case Iop_Sub8:
1347 case Iop_Sub16:
1348 case Iop_Sub32:
1349 case Iop_Sub64:
1350 opkind = S390_ALU_SUB;
1351 is_commutative = False;
1352 break;
1353
1354 case Iop_And8:
1355 case Iop_And16:
1356 case Iop_And32:
1357 case Iop_And64:
1358 opkind = S390_ALU_AND;
1359 break;
1360
1361 case Iop_Or8:
1362 case Iop_Or16:
1363 case Iop_Or32:
1364 case Iop_Or64:
1365 opkind = S390_ALU_OR;
1366 break;
1367
1368 case Iop_Xor8:
1369 case Iop_Xor16:
1370 case Iop_Xor32:
1371 case Iop_Xor64:
1372 opkind = S390_ALU_XOR;
1373 break;
1374
1375 case Iop_Shl8:
1376 case Iop_Shl16:
1377 case Iop_Shl32:
1378 case Iop_Shl64:
1379 opkind = S390_ALU_LSH;
1380 is_commutative = False;
1381 break;
1382
1383 case Iop_Shr8:
1384 case Iop_Shr16:
1385 case Iop_Shr32:
1386 case Iop_Shr64:
1387 opkind = S390_ALU_RSH;
1388 is_commutative = False;
1389 break;
1390
1391 case Iop_Sar8:
1392 case Iop_Sar16:
1393 case Iop_Sar32:
1394 case Iop_Sar64:
1395 opkind = S390_ALU_RSHA;
1396 is_commutative = False;
1397 break;
1398
1399 default:
1400 goto irreducible;
1401 }
1402
1403 /* Pattern match: 0 - arg1 --> -arg1 */
1404 if (opkind == S390_ALU_SUB && s390_expr_is_const_zero(arg1)) {
1405 res = newVRegI(env);
1406 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1407 insn = s390_insn_unop(size, S390_NEGATE, res, op2);
1408 addInstr(env, insn);
1409
1410 return res;
1411 }
1412
1413 if (is_commutative) {
1414 order_commutative_operands(arg1, arg2);
1415 }
1416
1417 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1418 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1419 res = newVRegI(env);
florian5e0f2042012-08-20 13:44:29 +00001420
1421 /* As right shifts of one/two byte opreands are implemented using a
1422 4-byte shift op, we first need to zero/sign-extend the shiftee. */
1423 switch (expr->Iex.Binop.op) {
1424 case Iop_Shr8:
1425 insn = s390_insn_unop(4, S390_ZERO_EXTEND_8, res, s390_opnd_reg(h1));
1426 break;
1427 case Iop_Shr16:
1428 insn = s390_insn_unop(4, S390_ZERO_EXTEND_16, res, s390_opnd_reg(h1));
1429 break;
1430 case Iop_Sar8:
1431 insn = s390_insn_unop(4, S390_SIGN_EXTEND_8, res, s390_opnd_reg(h1));
1432 break;
1433 case Iop_Sar16:
1434 insn = s390_insn_unop(4, S390_SIGN_EXTEND_16, res, s390_opnd_reg(h1));
1435 break;
1436 default:
1437 insn = s390_insn_move(size, res, h1);
1438 break;
1439 }
1440 addInstr(env, insn);
1441
sewardj2019a972011-03-07 16:04:07 +00001442 insn = s390_insn_alu(size, opkind, res, op2);
1443
1444 addInstr(env, insn);
1445
1446 return res;
1447 }
1448
1449 /* --------- UNARY OP --------- */
1450 case Iex_Unop: {
1451 static s390_opnd_RMI mask = { S390_OPND_IMMEDIATE };
1452 static s390_opnd_RMI shift = { S390_OPND_IMMEDIATE };
1453 s390_opnd_RMI opnd;
1454 s390_insn *insn;
1455 IRExpr *arg;
1456 HReg dst, h1;
1457 IROp unop, binop;
1458
1459 arg = expr->Iex.Unop.arg;
1460
1461 /* Special cases are handled here */
1462
1463 /* 32-bit multiply with 32-bit result or
1464 64-bit multiply with 64-bit result */
1465 unop = expr->Iex.Unop.op;
1466 binop = arg->Iex.Binop.op;
1467
1468 if ((arg->tag == Iex_Binop &&
1469 ((unop == Iop_64to32 &&
1470 (binop == Iop_MullS32 || binop == Iop_MullU32)) ||
1471 (unop == Iop_128to64 &&
1472 (binop == Iop_MullS64 || binop == Iop_MullU64))))) {
1473 h1 = s390_isel_int_expr(env, arg->Iex.Binop.arg1); /* 1st opnd */
1474 opnd = s390_isel_int_expr_RMI(env, arg->Iex.Binop.arg2); /* 2nd opnd */
1475 dst = newVRegI(env); /* Result goes into a new register */
1476 addInstr(env, s390_insn_move(size, dst, h1));
1477 addInstr(env, s390_insn_alu(size, S390_ALU_MUL, dst, opnd));
1478
1479 return dst;
1480 }
1481
florian4d71a082011-12-18 00:08:17 +00001482 if (unop == Iop_ReinterpF64asI64 || unop == Iop_ReinterpF32asI32) {
sewardj2019a972011-03-07 16:04:07 +00001483 dst = newVRegI(env);
1484 h1 = s390_isel_float_expr(env, arg); /* Process the operand */
1485 addInstr(env, s390_insn_move(size, dst, h1));
1486
1487 return dst;
1488 }
1489
floriane38f6412012-12-21 17:32:12 +00001490 if (unop == Iop_ReinterpD64asI64) {
1491 dst = newVRegI(env);
1492 h1 = s390_isel_dfp_expr(env, arg); /* Process the operand */
1493 addInstr(env, s390_insn_move(size, dst, h1));
1494
1495 return dst;
1496 }
1497
florian5c539732013-02-14 14:27:12 +00001498 if (unop == Iop_ExtractExpD64 || unop == Iop_ExtractSigD64) {
1499 s390_dfp_unop_t dfpop;
1500 switch(unop) {
1501 case Iop_ExtractExpD64: dfpop = S390_DFP_EXTRACT_EXP_D64; break;
1502 case Iop_ExtractSigD64: dfpop = S390_DFP_EXTRACT_SIG_D64; break;
1503 default: goto irreducible;
1504 }
floriance9e3db2012-12-27 20:14:03 +00001505 dst = newVRegI(env);
1506 h1 = s390_isel_dfp_expr(env, arg); /* Process the operand */
florian5c539732013-02-14 14:27:12 +00001507 addInstr(env, s390_insn_dfp_unop(size, dfpop, dst, h1));
floriance9e3db2012-12-27 20:14:03 +00001508 return dst;
1509 }
1510
florian5c539732013-02-14 14:27:12 +00001511 if (unop == Iop_ExtractExpD128 || unop == Iop_ExtractSigD128) {
1512 s390_dfp_unop_t dfpop;
floriance9e3db2012-12-27 20:14:03 +00001513 HReg op_hi, op_lo, f13, f15;
florian5c539732013-02-14 14:27:12 +00001514
1515 switch(unop) {
1516 case Iop_ExtractExpD128: dfpop = S390_DFP_EXTRACT_EXP_D128; break;
1517 case Iop_ExtractSigD128: dfpop = S390_DFP_EXTRACT_SIG_D128; break;
1518 default: goto irreducible;
1519 }
floriance9e3db2012-12-27 20:14:03 +00001520 dst = newVRegI(env);
1521 s390_isel_dfp128_expr(&op_hi, &op_lo, env, arg); /* Process operand */
1522
1523 /* We use non-virtual registers r13 and r15 as pair */
1524 f13 = make_fpr(13);
1525 f15 = make_fpr(15);
1526
1527 /* operand --> (f13, f15) */
1528 addInstr(env, s390_insn_move(8, f13, op_hi));
1529 addInstr(env, s390_insn_move(8, f15, op_lo));
1530
florian5c539732013-02-14 14:27:12 +00001531 addInstr(env, s390_insn_dfp128_unop(size, dfpop, dst, f13, f15));
floriance9e3db2012-12-27 20:14:03 +00001532 return dst;
1533 }
1534
sewardj2019a972011-03-07 16:04:07 +00001535 /* Expressions whose argument is 1-bit wide */
1536 if (typeOfIRExpr(env->type_env, arg) == Ity_I1) {
1537 s390_cc_t cond = s390_isel_cc(env, arg);
1538 dst = newVRegI(env); /* Result goes into a new register */
1539 addInstr(env, s390_insn_cc2bool(dst, cond));
1540
1541 switch (unop) {
1542 case Iop_1Uto8:
1543 case Iop_1Uto32:
florian5f27dcf2012-08-04 04:25:30 +00001544 /* Zero extend */
1545 mask.variant.imm = 1;
1546 addInstr(env, s390_insn_alu(4, S390_ALU_AND, dst, mask));
1547 break;
1548
sewardj2019a972011-03-07 16:04:07 +00001549 case Iop_1Uto64:
florian5f27dcf2012-08-04 04:25:30 +00001550 /* Zero extend */
1551 mask.variant.imm = 1;
1552 addInstr(env, s390_insn_alu(8, S390_ALU_AND, dst, mask));
sewardj2019a972011-03-07 16:04:07 +00001553 break;
1554
1555 case Iop_1Sto8:
1556 case Iop_1Sto16:
1557 case Iop_1Sto32:
1558 shift.variant.imm = 31;
1559 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, dst, shift));
1560 addInstr(env, s390_insn_alu(4, S390_ALU_RSHA, dst, shift));
1561 break;
1562
1563 case Iop_1Sto64:
1564 shift.variant.imm = 63;
1565 addInstr(env, s390_insn_alu(8, S390_ALU_LSH, dst, shift));
1566 addInstr(env, s390_insn_alu(8, S390_ALU_RSHA, dst, shift));
1567 break;
1568
1569 default:
1570 goto irreducible;
1571 }
1572
1573 return dst;
1574 }
1575
1576 /* Regular processing */
1577
1578 if (unop == Iop_128to64) {
1579 HReg dst_hi, dst_lo;
1580
1581 s390_isel_int128_expr(&dst_hi, &dst_lo, env, arg);
1582 return dst_lo;
1583 }
1584
1585 if (unop == Iop_128HIto64) {
1586 HReg dst_hi, dst_lo;
1587
1588 s390_isel_int128_expr(&dst_hi, &dst_lo, env, arg);
1589 return dst_hi;
1590 }
1591
1592 dst = newVRegI(env); /* Result goes into a new register */
1593 opnd = s390_isel_int_expr_RMI(env, arg); /* Process the operand */
1594
1595 switch (unop) {
1596 case Iop_8Uto16:
1597 case Iop_8Uto32:
1598 case Iop_8Uto64:
1599 insn = s390_insn_unop(size, S390_ZERO_EXTEND_8, dst, opnd);
1600 break;
1601
1602 case Iop_16Uto32:
1603 case Iop_16Uto64:
1604 insn = s390_insn_unop(size, S390_ZERO_EXTEND_16, dst, opnd);
1605 break;
1606
1607 case Iop_32Uto64:
1608 insn = s390_insn_unop(size, S390_ZERO_EXTEND_32, dst, opnd);
1609 break;
1610
1611 case Iop_8Sto16:
1612 case Iop_8Sto32:
1613 case Iop_8Sto64:
1614 insn = s390_insn_unop(size, S390_SIGN_EXTEND_8, dst, opnd);
1615 break;
1616
1617 case Iop_16Sto32:
1618 case Iop_16Sto64:
1619 insn = s390_insn_unop(size, S390_SIGN_EXTEND_16, dst, opnd);
1620 break;
1621
1622 case Iop_32Sto64:
1623 insn = s390_insn_unop(size, S390_SIGN_EXTEND_32, dst, opnd);
1624 break;
1625
1626 case Iop_64to8:
1627 case Iop_64to16:
1628 case Iop_64to32:
1629 case Iop_32to8:
1630 case Iop_32to16:
1631 case Iop_16to8:
1632 /* Down-casts are no-ops. Upstream operations will only look at
1633 the bytes that make up the result of the down-cast. So there
1634 is no point setting the other bytes to 0. */
1635 insn = s390_opnd_copy(8, dst, opnd);
1636 break;
1637
1638 case Iop_64HIto32:
1639 addInstr(env, s390_opnd_copy(8, dst, opnd));
1640 shift.variant.imm = 32;
1641 insn = s390_insn_alu(8, S390_ALU_RSH, dst, shift);
1642 break;
1643
1644 case Iop_32HIto16:
1645 addInstr(env, s390_opnd_copy(4, dst, opnd));
1646 shift.variant.imm = 16;
1647 insn = s390_insn_alu(4, S390_ALU_RSH, dst, shift);
1648 break;
1649
1650 case Iop_16HIto8:
1651 addInstr(env, s390_opnd_copy(2, dst, opnd));
1652 shift.variant.imm = 8;
1653 insn = s390_insn_alu(2, S390_ALU_RSH, dst, shift);
1654 break;
1655
1656 case Iop_Not8:
1657 case Iop_Not16:
1658 case Iop_Not32:
1659 case Iop_Not64:
1660 /* XOR with ffff... */
1661 mask.variant.imm = ~(ULong)0;
1662 addInstr(env, s390_opnd_copy(size, dst, opnd));
1663 insn = s390_insn_alu(size, S390_ALU_XOR, dst, mask);
1664 break;
1665
1666 case Iop_Left8:
1667 case Iop_Left16:
1668 case Iop_Left32:
1669 case Iop_Left64:
1670 addInstr(env, s390_insn_unop(size, S390_NEGATE, dst, opnd));
1671 insn = s390_insn_alu(size, S390_ALU_OR, dst, opnd);
1672 break;
1673
1674 case Iop_CmpwNEZ32:
1675 case Iop_CmpwNEZ64: {
1676 /* Use the fact that x | -x == 0 iff x == 0. Otherwise, either X
1677 or -X will have a 1 in the MSB. */
1678 addInstr(env, s390_insn_unop(size, S390_NEGATE, dst, opnd));
1679 addInstr(env, s390_insn_alu(size, S390_ALU_OR, dst, opnd));
1680 shift.variant.imm = (unop == Iop_CmpwNEZ32) ? 31 : 63;
1681 addInstr(env, s390_insn_alu(size, S390_ALU_RSHA, dst, shift));
1682 return dst;
1683 }
1684
1685 case Iop_Clz64: {
1686 HReg r10, r11;
1687
sewardj611b06e2011-03-24 08:57:29 +00001688 /* This will be implemented using FLOGR, if possible. So we need to
1689 set aside a pair of non-virtual registers. The result (number of
1690 left-most zero bits) will be in r10. The value in r11 is unspecified
1691 and must not be used. */
florian297b6062012-05-08 20:16:17 +00001692 r10 = make_gpr(10);
1693 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001694
sewardj611b06e2011-03-24 08:57:29 +00001695 addInstr(env, s390_insn_clz(8, r10, r11, opnd));
sewardj2019a972011-03-07 16:04:07 +00001696 addInstr(env, s390_insn_move(8, dst, r10));
1697 return dst;
1698 }
1699
1700 default:
1701 goto irreducible;
1702 }
1703
1704 addInstr(env, insn);
1705
1706 return dst;
1707 }
1708
1709 /* --------- GET --------- */
1710 case Iex_Get: {
1711 HReg dst = newVRegI(env);
1712 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
1713
1714 /* We never load more than 8 bytes from the guest state, because the
1715 floating point register pair is not contiguous. */
1716 vassert(size <= 8);
1717
1718 addInstr(env, s390_insn_load(size, dst, am));
1719
1720 return dst;
1721 }
1722
1723 case Iex_GetI:
1724 /* not needed */
1725 break;
1726
1727 /* --------- CCALL --------- */
1728 case Iex_CCall: {
1729 HReg dst = newVRegI(env);
1730
1731 doHelperCall(env, False, NULL, expr->Iex.CCall.cee,
florian01ed6e72012-05-27 16:52:43 +00001732 expr->Iex.CCall.args, dst);
sewardj2019a972011-03-07 16:04:07 +00001733 return dst;
1734 }
1735
1736 /* --------- LITERAL --------- */
1737
1738 /* Load a literal into a register. Create a "load immediate"
1739 v-insn and return the register. */
1740 case Iex_Const: {
1741 ULong value;
1742 HReg dst = newVRegI(env);
1743 const IRConst *con = expr->Iex.Const.con;
1744
1745 /* Bitwise copy of the value. No sign/zero-extension */
1746 switch (con->tag) {
1747 case Ico_U64: value = con->Ico.U64; break;
1748 case Ico_U32: value = con->Ico.U32; break;
1749 case Ico_U16: value = con->Ico.U16; break;
1750 case Ico_U8: value = con->Ico.U8; break;
1751 default: vpanic("s390_isel_int_expr: invalid constant");
1752 }
1753
1754 addInstr(env, s390_insn_load_immediate(size, dst, value));
1755
1756 return dst;
1757 }
1758
1759 /* --------- MULTIPLEX --------- */
florian99dd03e2013-01-29 03:56:06 +00001760 case Iex_ITE: {
sewardj2019a972011-03-07 16:04:07 +00001761 IRExpr *cond_expr;
florian99dd03e2013-01-29 03:56:06 +00001762 HReg dst, r1;
sewardj009230b2013-01-26 11:47:55 +00001763 s390_opnd_RMI r0;
sewardj2019a972011-03-07 16:04:07 +00001764
florian99dd03e2013-01-29 03:56:06 +00001765 cond_expr = expr->Iex.ITE.cond;
sewardj2019a972011-03-07 16:04:07 +00001766
sewardj009230b2013-01-26 11:47:55 +00001767 vassert(typeOfIRExpr(env->type_env, cond_expr) == Ity_I1);
1768
sewardj2019a972011-03-07 16:04:07 +00001769 dst = newVRegI(env);
florian99dd03e2013-01-29 03:56:06 +00001770 r0 = s390_isel_int_expr_RMI(env, expr->Iex.ITE.iffalse);
1771 r1 = s390_isel_int_expr(env, expr->Iex.ITE.iftrue);
1772 size = sizeofIRType(typeOfIRExpr(env->type_env, expr->Iex.ITE.iftrue));
sewardj2019a972011-03-07 16:04:07 +00001773
sewardj009230b2013-01-26 11:47:55 +00001774 s390_cc_t cc = s390_isel_cc(env, cond_expr);
sewardj2019a972011-03-07 16:04:07 +00001775
florian99dd03e2013-01-29 03:56:06 +00001776 addInstr(env, s390_insn_move(size, dst, r1));
sewardj009230b2013-01-26 11:47:55 +00001777 addInstr(env, s390_insn_cond_move(size, s390_cc_invert(cc), dst, r0));
sewardj2019a972011-03-07 16:04:07 +00001778 return dst;
1779 }
1780
1781 default:
1782 break;
1783 }
1784
1785 /* We get here if no pattern matched. */
1786 irreducible:
1787 ppIRExpr(expr);
1788 vpanic("s390_isel_int_expr: cannot reduce tree");
1789}
1790
1791
1792static HReg
1793s390_isel_int_expr(ISelEnv *env, IRExpr *expr)
1794{
1795 HReg dst = s390_isel_int_expr_wrk(env, expr);
1796
1797 /* Sanity checks ... */
1798 vassert(hregClass(dst) == HRcInt64);
1799 vassert(hregIsVirtual(dst));
1800
1801 return dst;
1802}
1803
1804
1805static s390_opnd_RMI
1806s390_isel_int_expr_RMI(ISelEnv *env, IRExpr *expr)
1807{
1808 IRType ty = typeOfIRExpr(env->type_env, expr);
1809 s390_opnd_RMI dst;
1810
1811 vassert(ty == Ity_I8 || ty == Ity_I16 || ty == Ity_I32 ||
1812 ty == Ity_I64);
1813
1814 if (expr->tag == Iex_Load) {
1815 dst.tag = S390_OPND_AMODE;
1816 dst.variant.am = s390_isel_amode(env, expr->Iex.Load.addr);
1817 } else if (expr->tag == Iex_Get) {
1818 dst.tag = S390_OPND_AMODE;
1819 dst.variant.am = s390_amode_for_guest_state(expr->Iex.Get.offset);
1820 } else if (expr->tag == Iex_Const) {
1821 ULong value;
1822
1823 /* The bit pattern for the value will be stored as is in the least
1824 significant bits of VALUE. */
1825 switch (expr->Iex.Const.con->tag) {
1826 case Ico_U1: value = expr->Iex.Const.con->Ico.U1; break;
1827 case Ico_U8: value = expr->Iex.Const.con->Ico.U8; break;
1828 case Ico_U16: value = expr->Iex.Const.con->Ico.U16; break;
1829 case Ico_U32: value = expr->Iex.Const.con->Ico.U32; break;
1830 case Ico_U64: value = expr->Iex.Const.con->Ico.U64; break;
1831 default:
1832 vpanic("s390_isel_int_expr_RMI");
1833 }
1834
1835 dst.tag = S390_OPND_IMMEDIATE;
1836 dst.variant.imm = value;
1837 } else {
1838 dst.tag = S390_OPND_REG;
1839 dst.variant.reg = s390_isel_int_expr(env, expr);
1840 }
1841
1842 return dst;
1843}
1844
1845
1846/*---------------------------------------------------------*/
1847/*--- ISEL: Floating point expressions (128 bit) ---*/
1848/*---------------------------------------------------------*/
1849static void
1850s390_isel_float128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
1851 IRExpr *expr)
1852{
1853 IRType ty = typeOfIRExpr(env->type_env, expr);
1854
1855 vassert(ty == Ity_F128);
1856
sewardj2019a972011-03-07 16:04:07 +00001857 switch (expr->tag) {
1858 case Iex_RdTmp:
1859 /* Return the virtual registers that hold the temporary. */
1860 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
1861 return;
1862
1863 /* --------- LOAD --------- */
1864 case Iex_Load: {
1865 IRExpr *addr_hi, *addr_lo;
1866 s390_amode *am_hi, *am_lo;
1867
1868 if (expr->Iex.Load.end != Iend_BE)
1869 goto irreducible;
1870
1871 addr_hi = expr->Iex.Load.addr;
1872 addr_lo = IRExpr_Binop(Iop_Add64, addr_hi, mkU64(8));
1873
1874 am_hi = s390_isel_amode(env, addr_hi);
1875 am_lo = s390_isel_amode(env, addr_lo);
1876
1877 *dst_hi = newVRegF(env);
1878 *dst_lo = newVRegF(env);
1879 addInstr(env, s390_insn_load(8, *dst_hi, am_hi));
1880 addInstr(env, s390_insn_load(8, *dst_hi, am_lo));
1881 return;
1882 }
1883
1884
1885 /* --------- GET --------- */
1886 case Iex_Get:
1887 /* This is not supported because loading 128-bit from the guest
1888 state is almost certainly wrong. Use get_fpr_pair instead. */
1889 vpanic("Iex_Get with F128 data");
1890
1891 /* --------- 4-ary OP --------- */
1892 case Iex_Qop:
1893 vpanic("Iex_Qop with F128 data");
1894
1895 /* --------- TERNARY OP --------- */
1896 case Iex_Triop: {
florian420bfa92012-06-02 20:29:22 +00001897 IRTriop *triop = expr->Iex.Triop.details;
1898 IROp op = triop->op;
1899 IRExpr *left = triop->arg2;
1900 IRExpr *right = triop->arg3;
sewardj2019a972011-03-07 16:04:07 +00001901 s390_bfp_binop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00001902 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15;
1903
1904 s390_isel_float128_expr(&op1_hi, &op1_lo, env, left); /* 1st operand */
1905 s390_isel_float128_expr(&op2_hi, &op2_lo, env, right); /* 2nd operand */
1906
1907 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1908 f12 = make_fpr(12);
1909 f13 = make_fpr(13);
1910 f14 = make_fpr(14);
1911 f15 = make_fpr(15);
1912
1913 /* 1st operand --> (f12, f14) */
1914 addInstr(env, s390_insn_move(8, f12, op1_hi));
1915 addInstr(env, s390_insn_move(8, f14, op1_lo));
1916
1917 /* 2nd operand --> (f13, f15) */
1918 addInstr(env, s390_insn_move(8, f13, op2_hi));
1919 addInstr(env, s390_insn_move(8, f15, op2_lo));
1920
1921 switch (op) {
1922 case Iop_AddF128: bfpop = S390_BFP_ADD; break;
1923 case Iop_SubF128: bfpop = S390_BFP_SUB; break;
1924 case Iop_MulF128: bfpop = S390_BFP_MUL; break;
1925 case Iop_DivF128: bfpop = S390_BFP_DIV; break;
1926 default:
1927 goto irreducible;
1928 }
1929
florian2c74d242012-09-12 19:38:42 +00001930 set_bfp_rounding_mode_in_fpc(env, triop->arg1);
1931 addInstr(env, s390_insn_bfp128_binop(16, bfpop, f12, f14, f13, f15));
sewardj2019a972011-03-07 16:04:07 +00001932
1933 /* Move result to virtual destination register */
1934 *dst_hi = newVRegF(env);
1935 *dst_lo = newVRegF(env);
1936 addInstr(env, s390_insn_move(8, *dst_hi, f12));
1937 addInstr(env, s390_insn_move(8, *dst_lo, f14));
1938
1939 return;
1940 }
1941
1942 /* --------- BINARY OP --------- */
1943 case Iex_Binop: {
sewardj2019a972011-03-07 16:04:07 +00001944 switch (expr->Iex.Binop.op) {
florian78d5ef72013-05-11 15:02:58 +00001945 case Iop_SqrtF128: {
1946 HReg op_hi, op_lo, f12, f13, f14, f15;
1947
1948 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1949 f12 = make_fpr(12);
1950 f13 = make_fpr(13);
1951 f14 = make_fpr(14);
1952 f15 = make_fpr(15);
1953
sewardj2019a972011-03-07 16:04:07 +00001954 s390_isel_float128_expr(&op_hi, &op_lo, env, expr->Iex.Binop.arg2);
1955
1956 /* operand --> (f13, f15) */
1957 addInstr(env, s390_insn_move(8, f13, op_hi));
1958 addInstr(env, s390_insn_move(8, f15, op_lo));
1959
florian2c74d242012-09-12 19:38:42 +00001960 set_bfp_rounding_mode_in_fpc(env, expr->Iex.Binop.arg1);
1961 addInstr(env, s390_insn_bfp128_unop(16, S390_BFP_SQRT, f12, f14,
1962 f13, f15));
sewardj2019a972011-03-07 16:04:07 +00001963
1964 /* Move result to virtual destination registers */
1965 *dst_hi = newVRegF(env);
1966 *dst_lo = newVRegF(env);
1967 addInstr(env, s390_insn_move(8, *dst_hi, f12));
1968 addInstr(env, s390_insn_move(8, *dst_lo, f14));
1969 return;
florian78d5ef72013-05-11 15:02:58 +00001970 }
sewardj2019a972011-03-07 16:04:07 +00001971
1972 case Iop_F64HLtoF128:
1973 *dst_hi = s390_isel_float_expr(env, expr->Iex.Binop.arg1);
1974 *dst_lo = s390_isel_float_expr(env, expr->Iex.Binop.arg2);
1975 return;
1976
florian7ab421d2013-06-17 21:03:56 +00001977 case Iop_D32toF128:
1978 case Iop_D64toF128: {
1979 IRExpr *irrm;
1980 IRExpr *left;
1981 s390_dfp_round_t rm;
1982 HReg h1; /* virtual reg. to hold source */
1983 HReg f0, f2, f4, r1; /* real registers used by PFPO */
1984 s390_fp_conv_t fpconv;
1985
1986 switch (expr->Iex.Binop.op) {
1987 case Iop_D32toF128:
1988 fpconv = S390_FP_D32_TO_F128;
1989 break;
1990 case Iop_D64toF128:
1991 fpconv = S390_FP_D64_TO_F128;
1992 break;
1993 default: goto irreducible;
1994 }
1995
1996 f4 = make_fpr(4); /* source */
1997 f0 = make_fpr(0); /* destination */
1998 f2 = make_fpr(2); /* destination */
1999 r1 = make_gpr(1); /* GPR #1 clobbered */
2000 irrm = expr->Iex.Binop.arg1;
2001 left = expr->Iex.Binop.arg2;
2002 rm = get_dfp_rounding_mode(env, irrm);
2003 h1 = s390_isel_dfp_expr(env, left);
2004 addInstr(env, s390_insn_move(8, f4, h1));
2005 addInstr(env, s390_insn_fp128_convert(16, fpconv, f0, f2,
2006 f4, INVALID_HREG, r1, rm));
2007 /* (f0, f2) --> destination */
2008 *dst_hi = newVRegF(env);
2009 *dst_lo = newVRegF(env);
2010 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2011 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2012
2013 return;
2014 }
2015
florian78d5ef72013-05-11 15:02:58 +00002016 case Iop_D128toF128: {
2017 IRExpr *irrm;
2018 IRExpr *left;
2019 s390_dfp_round_t rm;
2020 HReg op_hi, op_lo;
2021 HReg f0, f2, f4, f6, r1; /* real registers used by PFPO */
2022
2023 f4 = make_fpr(4); /* source */
2024 f6 = make_fpr(6); /* source */
2025 f0 = make_fpr(0); /* destination */
2026 f2 = make_fpr(2); /* destination */
2027 r1 = make_gpr(1); /* GPR #1 clobbered */
2028
2029 irrm = expr->Iex.Binop.arg1;
2030 left = expr->Iex.Binop.arg2;
2031 rm = get_dfp_rounding_mode(env, irrm);
2032 s390_isel_dfp128_expr(&op_hi, &op_lo, env, left);
2033 /* operand --> (f4, f6) */
2034 addInstr(env, s390_insn_move(8, f4, op_hi));
2035 addInstr(env, s390_insn_move(8, f6, op_lo));
2036 addInstr(env, s390_insn_fp128_convert(16, S390_FP_D128_TO_F128, f0, f2,
2037 f4, f6, r1, rm));
2038 /* (f0, f2) --> destination */
2039 *dst_hi = newVRegF(env);
2040 *dst_lo = newVRegF(env);
2041 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2042 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2043
2044 return;
2045 }
2046
sewardj2019a972011-03-07 16:04:07 +00002047 default:
2048 goto irreducible;
2049 }
2050 }
2051
2052 /* --------- UNARY OP --------- */
2053 case Iex_Unop: {
florian66e596d2012-09-07 15:00:53 +00002054 IRExpr *left = expr->Iex.Unop.arg;
sewardj2019a972011-03-07 16:04:07 +00002055 s390_bfp_unop_t bfpop;
florian6dc90242012-12-21 21:43:00 +00002056 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00002057 HReg op_hi, op_lo, op, f12, f13, f14, f15;
2058
2059 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
2060 f12 = make_fpr(12);
2061 f13 = make_fpr(13);
2062 f14 = make_fpr(14);
2063 f15 = make_fpr(15);
2064
florian66e596d2012-09-07 15:00:53 +00002065 switch (expr->Iex.Unop.op) {
florian3f3e50d2012-09-13 03:13:26 +00002066 case Iop_NegF128:
2067 if (left->tag == Iex_Unop &&
2068 (left->Iex.Unop.op == Iop_AbsF32 ||
2069 left->Iex.Unop.op == Iop_AbsF64))
2070 bfpop = S390_BFP_NABS;
2071 else
2072 bfpop = S390_BFP_NEG;
2073 goto float128_opnd;
florian9fcff4c2012-09-10 03:09:04 +00002074 case Iop_AbsF128: bfpop = S390_BFP_ABS; goto float128_opnd;
2075 case Iop_I32StoF128: conv = S390_BFP_I32_TO_F128; goto convert_int;
2076 case Iop_I64StoF128: conv = S390_BFP_I64_TO_F128; goto convert_int;
2077 case Iop_I32UtoF128: conv = S390_BFP_U32_TO_F128; goto convert_int;
2078 case Iop_I64UtoF128: conv = S390_BFP_U64_TO_F128; goto convert_int;
2079 case Iop_F32toF128: conv = S390_BFP_F32_TO_F128; goto convert_float;
2080 case Iop_F64toF128: conv = S390_BFP_F64_TO_F128; goto convert_float;
sewardj2019a972011-03-07 16:04:07 +00002081 default:
2082 goto irreducible;
2083 }
2084
2085 float128_opnd:
2086 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
2087
2088 /* operand --> (f13, f15) */
2089 addInstr(env, s390_insn_move(8, f13, op_hi));
2090 addInstr(env, s390_insn_move(8, f15, op_lo));
2091
florian2c74d242012-09-12 19:38:42 +00002092 addInstr(env, s390_insn_bfp128_unop(16, bfpop, f12, f14, f13, f15));
sewardj2019a972011-03-07 16:04:07 +00002093 goto move_dst;
2094
2095 convert_float:
2096 op = s390_isel_float_expr(env, left);
florian9fcff4c2012-09-10 03:09:04 +00002097 addInstr(env, s390_insn_bfp128_convert_to(16, conv, f12, f14, op));
sewardj2019a972011-03-07 16:04:07 +00002098 goto move_dst;
2099
2100 convert_int:
2101 op = s390_isel_int_expr(env, left);
florian9fcff4c2012-09-10 03:09:04 +00002102 addInstr(env, s390_insn_bfp128_convert_to(16, conv, f12, f14, op));
sewardj2019a972011-03-07 16:04:07 +00002103 goto move_dst;
2104
2105 move_dst:
2106 /* Move result to virtual destination registers */
2107 *dst_hi = newVRegF(env);
2108 *dst_lo = newVRegF(env);
2109 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2110 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2111 return;
2112 }
2113
2114 default:
2115 goto irreducible;
2116 }
2117
2118 /* We get here if no pattern matched. */
2119 irreducible:
2120 ppIRExpr(expr);
florian4ebaa772012-12-20 19:44:18 +00002121 vpanic("s390_isel_float128_expr: cannot reduce tree");
sewardj2019a972011-03-07 16:04:07 +00002122}
2123
2124/* Compute a 128-bit value into two 64-bit registers. These may be either
2125 real or virtual regs; in any case they must not be changed by subsequent
2126 code emitted by the caller. */
2127static void
2128s390_isel_float128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
2129{
2130 s390_isel_float128_expr_wrk(dst_hi, dst_lo, env, expr);
2131
2132 /* Sanity checks ... */
2133 vassert(hregIsVirtual(*dst_hi));
2134 vassert(hregIsVirtual(*dst_lo));
2135 vassert(hregClass(*dst_hi) == HRcFlt64);
2136 vassert(hregClass(*dst_lo) == HRcFlt64);
2137}
2138
2139
2140/*---------------------------------------------------------*/
2141/*--- ISEL: Floating point expressions (64 bit) ---*/
2142/*---------------------------------------------------------*/
2143
2144static HReg
2145s390_isel_float_expr_wrk(ISelEnv *env, IRExpr *expr)
2146{
2147 IRType ty = typeOfIRExpr(env->type_env, expr);
2148 UChar size;
2149
2150 vassert(ty == Ity_F32 || ty == Ity_F64);
2151
2152 size = sizeofIRType(ty);
2153
2154 switch (expr->tag) {
2155 case Iex_RdTmp:
2156 /* Return the virtual register that holds the temporary. */
2157 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
2158
2159 /* --------- LOAD --------- */
2160 case Iex_Load: {
2161 HReg dst = newVRegF(env);
2162 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
2163
2164 if (expr->Iex.Load.end != Iend_BE)
2165 goto irreducible;
2166
2167 addInstr(env, s390_insn_load(size, dst, am));
2168
2169 return dst;
2170 }
2171
2172 /* --------- GET --------- */
2173 case Iex_Get: {
2174 HReg dst = newVRegF(env);
2175 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
2176
2177 addInstr(env, s390_insn_load(size, dst, am));
2178
2179 return dst;
2180 }
2181
2182 /* --------- LITERAL --------- */
2183
2184 /* Load a literal into a register. Create a "load immediate"
2185 v-insn and return the register. */
2186 case Iex_Const: {
2187 ULong value;
2188 HReg dst = newVRegF(env);
2189 const IRConst *con = expr->Iex.Const.con;
2190
2191 /* Bitwise copy of the value. No sign/zero-extension */
2192 switch (con->tag) {
2193 case Ico_F32i: value = con->Ico.F32i; break;
2194 case Ico_F64i: value = con->Ico.F64i; break;
2195 default: vpanic("s390_isel_float_expr: invalid constant");
2196 }
2197
2198 if (value != 0) vpanic("cannot load immediate floating point constant");
2199
2200 addInstr(env, s390_insn_load_immediate(size, dst, value));
2201
2202 return dst;
2203 }
2204
2205 /* --------- 4-ary OP --------- */
2206 case Iex_Qop: {
2207 HReg op1, op2, op3, dst;
2208 s390_bfp_triop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002209
florian5906a6b2012-10-16 02:53:33 +00002210 op3 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg2);
florian96d7cc32012-06-01 20:41:24 +00002211 op2 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg3);
florian5906a6b2012-10-16 02:53:33 +00002212 op1 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg4);
sewardj2019a972011-03-07 16:04:07 +00002213 dst = newVRegF(env);
2214 addInstr(env, s390_insn_move(size, dst, op1));
2215
florian96d7cc32012-06-01 20:41:24 +00002216 switch (expr->Iex.Qop.details->op) {
sewardj2019a972011-03-07 16:04:07 +00002217 case Iop_MAddF32:
2218 case Iop_MAddF64: bfpop = S390_BFP_MADD; break;
2219 case Iop_MSubF32:
2220 case Iop_MSubF64: bfpop = S390_BFP_MSUB; break;
2221
2222 default:
2223 goto irreducible;
2224 }
2225
florian2c74d242012-09-12 19:38:42 +00002226 set_bfp_rounding_mode_in_fpc(env, expr->Iex.Qop.details->arg1);
2227 addInstr(env, s390_insn_bfp_triop(size, bfpop, dst, op2, op3));
sewardj2019a972011-03-07 16:04:07 +00002228 return dst;
2229 }
2230
2231 /* --------- TERNARY OP --------- */
2232 case Iex_Triop: {
florian420bfa92012-06-02 20:29:22 +00002233 IRTriop *triop = expr->Iex.Triop.details;
2234 IROp op = triop->op;
2235 IRExpr *left = triop->arg2;
2236 IRExpr *right = triop->arg3;
sewardj2019a972011-03-07 16:04:07 +00002237 s390_bfp_binop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002238 HReg h1, op2, dst;
2239
2240 h1 = s390_isel_float_expr(env, left); /* Process 1st operand */
2241 op2 = s390_isel_float_expr(env, right); /* Process 2nd operand */
2242 dst = newVRegF(env);
2243 addInstr(env, s390_insn_move(size, dst, h1));
2244 switch (op) {
2245 case Iop_AddF32:
2246 case Iop_AddF64: bfpop = S390_BFP_ADD; break;
2247 case Iop_SubF32:
2248 case Iop_SubF64: bfpop = S390_BFP_SUB; break;
2249 case Iop_MulF32:
2250 case Iop_MulF64: bfpop = S390_BFP_MUL; break;
2251 case Iop_DivF32:
2252 case Iop_DivF64: bfpop = S390_BFP_DIV; break;
2253
2254 default:
2255 goto irreducible;
2256 }
2257
florian2c74d242012-09-12 19:38:42 +00002258 set_bfp_rounding_mode_in_fpc(env, triop->arg1);
2259 addInstr(env, s390_insn_bfp_binop(size, bfpop, dst, op2));
sewardj2019a972011-03-07 16:04:07 +00002260 return dst;
2261 }
2262
2263 /* --------- BINARY OP --------- */
2264 case Iex_Binop: {
2265 IROp op = expr->Iex.Binop.op;
florian9fcff4c2012-09-10 03:09:04 +00002266 IRExpr *irrm = expr->Iex.Binop.arg1;
sewardj2019a972011-03-07 16:04:07 +00002267 IRExpr *left = expr->Iex.Binop.arg2;
2268 HReg h1, dst;
florian6dc90242012-12-21 21:43:00 +00002269 s390_bfp_conv_t conv;
florian78d5ef72013-05-11 15:02:58 +00002270 s390_fp_conv_t fpconv;
sewardj2019a972011-03-07 16:04:07 +00002271
2272 switch (op) {
2273 case Iop_SqrtF32:
2274 case Iop_SqrtF64:
florian9fcff4c2012-09-10 03:09:04 +00002275 h1 = s390_isel_float_expr(env, left);
2276 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002277 set_bfp_rounding_mode_in_fpc(env, irrm);
2278 addInstr(env, s390_insn_bfp_unop(size, S390_BFP_SQRT, dst, h1));
florian9fcff4c2012-09-10 03:09:04 +00002279 return dst;
sewardj2019a972011-03-07 16:04:07 +00002280
florian9fcff4c2012-09-10 03:09:04 +00002281 case Iop_F64toF32: conv = S390_BFP_F64_TO_F32; goto convert_float;
2282 case Iop_I32StoF32: conv = S390_BFP_I32_TO_F32; goto convert_int;
2283 case Iop_I32UtoF32: conv = S390_BFP_U32_TO_F32; goto convert_int;
2284 case Iop_I64StoF32: conv = S390_BFP_I64_TO_F32; goto convert_int;
2285 case Iop_I64StoF64: conv = S390_BFP_I64_TO_F64; goto convert_int;
2286 case Iop_I64UtoF32: conv = S390_BFP_U64_TO_F32; goto convert_int;
2287 case Iop_I64UtoF64: conv = S390_BFP_U64_TO_F64; goto convert_int;
florian7ab421d2013-06-17 21:03:56 +00002288 case Iop_D32toF32: fpconv = S390_FP_D32_TO_F32; goto convert_dfp;
2289 case Iop_D32toF64: fpconv = S390_FP_D32_TO_F64; goto convert_dfp;
2290 case Iop_D64toF32: fpconv = S390_FP_D64_TO_F32; goto convert_dfp;
florian78d5ef72013-05-11 15:02:58 +00002291 case Iop_D64toF64: fpconv = S390_FP_D64_TO_F64; goto convert_dfp;
florian7ab421d2013-06-17 21:03:56 +00002292 case Iop_D128toF32: fpconv = S390_FP_D128_TO_F32; goto convert_dfp128;
florian78d5ef72013-05-11 15:02:58 +00002293 case Iop_D128toF64: fpconv = S390_FP_D128_TO_F64; goto convert_dfp128;
sewardj2019a972011-03-07 16:04:07 +00002294
florian9fcff4c2012-09-10 03:09:04 +00002295 convert_float:
2296 h1 = s390_isel_float_expr(env, left);
2297 goto convert;
florian1c8f7ff2012-09-01 00:12:11 +00002298
florian9fcff4c2012-09-10 03:09:04 +00002299 convert_int:
2300 h1 = s390_isel_int_expr(env, left);
2301 goto convert;
2302
florian2c74d242012-09-12 19:38:42 +00002303 convert: {
florian125e20d2012-10-07 15:42:37 +00002304 s390_bfp_round_t rounding_mode;
florian2c74d242012-09-12 19:38:42 +00002305 /* convert-from-fixed and load-rounded have a rounding mode field
2306 when the floating point extension facility is installed. */
florian9fcff4c2012-09-10 03:09:04 +00002307 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002308 if (s390_host_has_fpext) {
2309 rounding_mode = get_bfp_rounding_mode(env, irrm);
2310 } else {
2311 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +00002312 rounding_mode = S390_BFP_ROUND_PER_FPC;
florian2c74d242012-09-12 19:38:42 +00002313 }
florian9fcff4c2012-09-10 03:09:04 +00002314 addInstr(env, s390_insn_bfp_convert(size, conv, dst, h1,
2315 rounding_mode));
2316 return dst;
florian2c74d242012-09-12 19:38:42 +00002317 }
florian78d5ef72013-05-11 15:02:58 +00002318
2319 convert_dfp: {
2320 s390_dfp_round_t rm;
2321 HReg f0, f4, r1; /* real registers used by PFPO */
2322
2323 f4 = make_fpr(4); /* source */
2324 f0 = make_fpr(0); /* destination */
2325 r1 = make_gpr(1); /* GPR #1 clobbered */
2326 h1 = s390_isel_dfp_expr(env, left);
2327 dst = newVRegF(env);
2328 rm = get_dfp_rounding_mode(env, irrm);
2329 /* operand --> f4 */
2330 addInstr(env, s390_insn_move(8, f4, h1));
2331 addInstr(env, s390_insn_fp_convert(size, fpconv, f0, f4, r1, rm));
2332 /* f0 --> destination */
2333 addInstr(env, s390_insn_move(8, dst, f0));
2334 return dst;
2335 }
2336
2337 convert_dfp128: {
2338 s390_dfp_round_t rm;
2339 HReg op_hi, op_lo;
2340 HReg f0, f4, f6, r1; /* real registers used by PFPO */
2341
2342 f4 = make_fpr(4); /* source */
2343 f6 = make_fpr(6); /* source */
2344 f0 = make_fpr(0); /* destination */
2345 r1 = make_gpr(1); /* GPR #1 clobbered */
2346 s390_isel_dfp128_expr(&op_hi, &op_lo, env, left);
2347 dst = newVRegF(env);
2348 rm = get_dfp_rounding_mode(env, irrm);
2349 /* operand --> (f4, f6) */
2350 addInstr(env, s390_insn_move(8, f4, op_hi));
2351 addInstr(env, s390_insn_move(8, f6, op_lo));
2352 addInstr(env, s390_insn_fp128_convert(16, fpconv, f0, INVALID_HREG,
2353 f4, f6, r1, rm));
2354 /* f0 --> destination */
2355 addInstr(env, s390_insn_move(8, dst, f0));
2356 return dst;
2357 }
2358
sewardj2019a972011-03-07 16:04:07 +00002359 default:
2360 goto irreducible;
2361
2362 case Iop_F128toF64:
2363 case Iop_F128toF32: {
florian9fcff4c2012-09-10 03:09:04 +00002364 HReg op_hi, op_lo, f13, f15;
florian125e20d2012-10-07 15:42:37 +00002365 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00002366
florian9fcff4c2012-09-10 03:09:04 +00002367 conv = op == Iop_F128toF32 ? S390_BFP_F128_TO_F32
2368 : S390_BFP_F128_TO_F64;
sewardj2019a972011-03-07 16:04:07 +00002369
florian9fcff4c2012-09-10 03:09:04 +00002370 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
sewardj2019a972011-03-07 16:04:07 +00002371
florian9fcff4c2012-09-10 03:09:04 +00002372 /* We use non-virtual registers as pairs (f13, f15) */
sewardj2019a972011-03-07 16:04:07 +00002373 f13 = make_fpr(13);
sewardj2019a972011-03-07 16:04:07 +00002374 f15 = make_fpr(15);
2375
2376 /* operand --> (f13, f15) */
2377 addInstr(env, s390_insn_move(8, f13, op_hi));
2378 addInstr(env, s390_insn_move(8, f15, op_lo));
2379
2380 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002381 /* load-rounded has a rounding mode field when the floating point
2382 extension facility is installed. */
2383 if (s390_host_has_fpext) {
2384 rounding_mode = get_bfp_rounding_mode(env, irrm);
2385 } else {
2386 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +00002387 rounding_mode = S390_BFP_ROUND_PER_FPC;
florian2c74d242012-09-12 19:38:42 +00002388 }
floriancc491a62012-09-10 23:44:37 +00002389 addInstr(env, s390_insn_bfp128_convert_from(size, conv, dst, f13, f15,
florian9fcff4c2012-09-10 03:09:04 +00002390 rounding_mode));
sewardj2019a972011-03-07 16:04:07 +00002391 return dst;
2392 }
2393 }
sewardj2019a972011-03-07 16:04:07 +00002394 }
2395
2396 /* --------- UNARY OP --------- */
2397 case Iex_Unop: {
2398 IROp op = expr->Iex.Unop.op;
2399 IRExpr *left = expr->Iex.Unop.arg;
2400 s390_bfp_unop_t bfpop;
florian6dc90242012-12-21 21:43:00 +00002401 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00002402 HReg h1, dst;
2403
2404 if (op == Iop_F128HItoF64 || op == Iop_F128LOtoF64) {
2405 HReg dst_hi, dst_lo;
2406
2407 s390_isel_float128_expr(&dst_hi, &dst_lo, env, left);
2408 return op == Iop_F128LOtoF64 ? dst_lo : dst_hi;
2409 }
2410
florian4d71a082011-12-18 00:08:17 +00002411 if (op == Iop_ReinterpI64asF64 || op == Iop_ReinterpI32asF32) {
sewardj2019a972011-03-07 16:04:07 +00002412 dst = newVRegF(env);
2413 h1 = s390_isel_int_expr(env, left); /* Process the operand */
2414 addInstr(env, s390_insn_move(size, dst, h1));
2415
2416 return dst;
2417 }
2418
2419 switch (op) {
2420 case Iop_NegF32:
2421 case Iop_NegF64:
2422 if (left->tag == Iex_Unop &&
florian3f3e50d2012-09-13 03:13:26 +00002423 (left->Iex.Unop.op == Iop_AbsF32 ||
2424 left->Iex.Unop.op == Iop_AbsF64))
sewardj2019a972011-03-07 16:04:07 +00002425 bfpop = S390_BFP_NABS;
2426 else
2427 bfpop = S390_BFP_NEG;
2428 break;
2429
2430 case Iop_AbsF32:
florian9fcff4c2012-09-10 03:09:04 +00002431 case Iop_AbsF64:
2432 bfpop = S390_BFP_ABS;
2433 break;
2434
2435 case Iop_I32StoF64: conv = S390_BFP_I32_TO_F64; goto convert_int1;
2436 case Iop_I32UtoF64: conv = S390_BFP_U32_TO_F64; goto convert_int1;
2437 case Iop_F32toF64: conv = S390_BFP_F32_TO_F64; goto convert_float1;
2438
2439 convert_float1:
2440 h1 = s390_isel_float_expr(env, left);
2441 goto convert1;
2442
2443 convert_int1:
2444 h1 = s390_isel_int_expr(env, left);
2445 goto convert1;
2446
2447 convert1:
2448 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002449 /* No rounding mode is needed for these conversions. Just stick
2450 one in. It won't be used later on. */
2451 addInstr(env, s390_insn_bfp_convert(size, conv, dst, h1,
florian125e20d2012-10-07 15:42:37 +00002452 S390_BFP_ROUND_NEAREST_EVEN));
florian9fcff4c2012-09-10 03:09:04 +00002453 return dst;
2454
sewardj2019a972011-03-07 16:04:07 +00002455 default:
2456 goto irreducible;
2457 }
2458
2459 /* Process operand */
florian9fcff4c2012-09-10 03:09:04 +00002460 h1 = s390_isel_float_expr(env, left);
sewardj2019a972011-03-07 16:04:07 +00002461 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002462 addInstr(env, s390_insn_bfp_unop(size, bfpop, dst, h1));
sewardj2019a972011-03-07 16:04:07 +00002463 return dst;
2464 }
2465
2466 default:
2467 goto irreducible;
2468 }
2469
2470 /* We get here if no pattern matched. */
2471 irreducible:
2472 ppIRExpr(expr);
2473 vpanic("s390_isel_float_expr: cannot reduce tree");
2474}
2475
2476
2477static HReg
2478s390_isel_float_expr(ISelEnv *env, IRExpr *expr)
2479{
2480 HReg dst = s390_isel_float_expr_wrk(env, expr);
2481
2482 /* Sanity checks ... */
2483 vassert(hregClass(dst) == HRcFlt64);
2484 vassert(hregIsVirtual(dst));
2485
2486 return dst;
2487}
2488
2489
2490/*---------------------------------------------------------*/
floriane38f6412012-12-21 17:32:12 +00002491/*--- ISEL: Decimal point expressions (128 bit) ---*/
2492/*---------------------------------------------------------*/
2493static void
2494s390_isel_dfp128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
2495 IRExpr *expr)
2496{
2497 IRType ty = typeOfIRExpr(env->type_env, expr);
2498
2499 vassert(ty == Ity_D128);
2500
2501 switch (expr->tag) {
2502 case Iex_RdTmp:
2503 /* Return the virtual registers that hold the temporary. */
2504 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
2505 return;
2506
2507 /* --------- LOAD --------- */
2508 case Iex_Load: {
2509 IRExpr *addr_hi, *addr_lo;
2510 s390_amode *am_hi, *am_lo;
2511
2512 if (expr->Iex.Load.end != Iend_BE)
2513 goto irreducible;
2514
2515 addr_hi = expr->Iex.Load.addr;
2516 addr_lo = IRExpr_Binop(Iop_Add64, addr_hi, mkU64(8));
2517
2518 am_hi = s390_isel_amode(env, addr_hi);
2519 am_lo = s390_isel_amode(env, addr_lo);
2520
2521 *dst_hi = newVRegF(env);
2522 *dst_lo = newVRegF(env);
2523 addInstr(env, s390_insn_load(8, *dst_hi, am_hi));
2524 addInstr(env, s390_insn_load(8, *dst_hi, am_lo));
2525 return;
2526 }
2527
2528 /* --------- GET --------- */
2529 case Iex_Get:
2530 /* This is not supported because loading 128-bit from the guest
2531 state is almost certainly wrong. Use get_dpr_pair instead. */
2532 vpanic("Iex_Get with D128 data");
2533
2534 /* --------- 4-ary OP --------- */
2535 case Iex_Qop:
2536 vpanic("Iex_Qop with D128 data");
2537
2538 /* --------- TERNARY OP --------- */
2539 case Iex_Triop: {
2540 IRTriop *triop = expr->Iex.Triop.details;
2541 IROp op = triop->op;
2542 IRExpr *irrm = triop->arg1;
2543 IRExpr *left = triop->arg2;
2544 IRExpr *right = triop->arg3;
2545 s390_dfp_round_t rounding_mode;
2546 s390_dfp_binop_t dfpop;
2547 HReg op1_hi, op1_lo, op2_hi, op2_lo, f9, f11, f12, f13, f14, f15;
2548
floriane38f6412012-12-21 17:32:12 +00002549 /* We use non-virtual registers as pairs with (f9, f11) as op1,
2550 (f12, f14) as op2 and (f13, f15) as destination) */
2551 f9 = make_fpr(9);
2552 f11 = make_fpr(11);
2553 f12 = make_fpr(12);
2554 f13 = make_fpr(13);
2555 f14 = make_fpr(14);
2556 f15 = make_fpr(15);
2557
floriane38f6412012-12-21 17:32:12 +00002558 switch (op) {
florian5c539732013-02-14 14:27:12 +00002559 case Iop_AddD128: dfpop = S390_DFP_ADD; goto evaluate_dfp128;
2560 case Iop_SubD128: dfpop = S390_DFP_SUB; goto evaluate_dfp128;
2561 case Iop_MulD128: dfpop = S390_DFP_MUL; goto evaluate_dfp128;
2562 case Iop_DivD128: dfpop = S390_DFP_DIV; goto evaluate_dfp128;
2563 case Iop_QuantizeD128: dfpop = S390_DFP_QUANTIZE; goto evaluate_dfp128;
2564
2565 evaluate_dfp128: {
2566 /* Process 1st operand */
2567 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, left);
2568 /* 1st operand --> (f9, f11) */
2569 addInstr(env, s390_insn_move(8, f9, op1_hi));
2570 addInstr(env, s390_insn_move(8, f11, op1_lo));
2571
2572 /* Process 2nd operand */
2573 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, right);
2574 /* 2nd operand --> (f12, f14) */
2575 addInstr(env, s390_insn_move(8, f12, op2_hi));
2576 addInstr(env, s390_insn_move(8, f14, op2_lo));
2577
2578 /* DFP arithmetic ops take rounding mode only when fpext is
2579 installed. But, DFP quantize operation takes rm irrespective
2580 of fpext facility . */
floriand18287d2013-02-21 03:03:05 +00002581 if (s390_host_has_fpext || op == Iop_QuantizeD128) {
florian5c539732013-02-14 14:27:12 +00002582 rounding_mode = get_dfp_rounding_mode(env, irrm);
2583 } else {
2584 set_dfp_rounding_mode_in_fpc(env, irrm);
2585 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2586 }
2587 addInstr(env, s390_insn_dfp128_binop(16, dfpop, f13, f15, f9, f11,
2588 f12, f14, rounding_mode));
2589 /* Move result to virtual destination register */
2590 *dst_hi = newVRegF(env);
2591 *dst_lo = newVRegF(env);
2592 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2593 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2594 return;
2595 }
2596
2597 case Iop_SignificanceRoundD128: {
2598 /* Process 1st operand */
2599 HReg op1 = s390_isel_int_expr(env, left);
2600 /* Process 2nd operand */
2601 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, right);
2602 /* 2nd operand --> (f12, f14) */
2603 addInstr(env, s390_insn_move(8, f12, op2_hi));
2604 addInstr(env, s390_insn_move(8, f14, op2_lo));
2605
2606 rounding_mode = get_dfp_rounding_mode(env, irrm);
2607 addInstr(env, s390_insn_dfp128_reround(16, f13, f15, op1, f12, f14,
2608 rounding_mode));
2609 /* Move result to virtual destination register */
2610 *dst_hi = newVRegF(env);
2611 *dst_lo = newVRegF(env);
2612 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2613 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2614 return;
2615 }
2616
floriane38f6412012-12-21 17:32:12 +00002617 default:
2618 goto irreducible;
2619 }
floriane38f6412012-12-21 17:32:12 +00002620 }
2621
2622 /* --------- BINARY OP --------- */
2623 case Iex_Binop: {
florian1b901d42013-01-01 22:19:24 +00002624
floriane38f6412012-12-21 17:32:12 +00002625 switch (expr->Iex.Binop.op) {
2626 case Iop_D64HLtoD128:
2627 *dst_hi = s390_isel_dfp_expr(env, expr->Iex.Binop.arg1);
2628 *dst_lo = s390_isel_dfp_expr(env, expr->Iex.Binop.arg2);
2629 return;
2630
florian1b901d42013-01-01 22:19:24 +00002631 case Iop_ShlD128:
florian5c539732013-02-14 14:27:12 +00002632 case Iop_ShrD128:
2633 case Iop_InsertExpD128: {
florian1b901d42013-01-01 22:19:24 +00002634 HReg op1_hi, op1_lo, op2, f9, f11, f13, f15;
2635 s390_dfp_intop_t intop;
florian5c539732013-02-14 14:27:12 +00002636 IRExpr *dfp_op;
2637 IRExpr *int_op;
florian1b901d42013-01-01 22:19:24 +00002638
2639 switch (expr->Iex.Binop.op) {
florian5c539732013-02-14 14:27:12 +00002640 case Iop_ShlD128: /* (D128, I64) -> D128 */
2641 intop = S390_DFP_SHIFT_LEFT;
2642 dfp_op = expr->Iex.Binop.arg1;
2643 int_op = expr->Iex.Binop.arg2;
2644 break;
2645 case Iop_ShrD128: /* (D128, I64) -> D128 */
2646 intop = S390_DFP_SHIFT_RIGHT;
2647 dfp_op = expr->Iex.Binop.arg1;
2648 int_op = expr->Iex.Binop.arg2;
2649 break;
2650 case Iop_InsertExpD128: /* (I64, D128) -> D128 */
2651 intop = S390_DFP_INSERT_EXP;
2652 int_op = expr->Iex.Binop.arg1;
2653 dfp_op = expr->Iex.Binop.arg2;
2654 break;
florian1b901d42013-01-01 22:19:24 +00002655 default: goto irreducible;
2656 }
2657
2658 /* We use non-virtual registers as pairs (f9, f11) and (f13, f15)) */
2659 f9 = make_fpr(9); /* 128 bit dfp operand */
2660 f11 = make_fpr(11);
2661
2662 f13 = make_fpr(13); /* 128 bit dfp destination */
2663 f15 = make_fpr(15);
2664
florian5c539732013-02-14 14:27:12 +00002665 /* Process dfp operand */
2666 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, dfp_op);
2667 /* op1 -> (f9,f11) */
florian1b901d42013-01-01 22:19:24 +00002668 addInstr(env, s390_insn_move(8, f9, op1_hi));
2669 addInstr(env, s390_insn_move(8, f11, op1_lo));
2670
florian5c539732013-02-14 14:27:12 +00002671 op2 = s390_isel_int_expr(env, int_op); /* int operand */
florian1b901d42013-01-01 22:19:24 +00002672
2673 addInstr(env,
2674 s390_insn_dfp128_intop(16, intop, f13, f15, op2, f9, f11));
2675
2676 /* Move result to virtual destination register */
2677 *dst_hi = newVRegF(env);
2678 *dst_lo = newVRegF(env);
2679 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2680 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2681 return;
2682 }
2683
florian7ab421d2013-06-17 21:03:56 +00002684 case Iop_F32toD128:
florian78d5ef72013-05-11 15:02:58 +00002685 case Iop_F64toD128: {
2686 IRExpr *irrm;
2687 IRExpr *left;
2688 s390_dfp_round_t rm;
2689 HReg h1; /* virtual reg. to hold source */
2690 HReg f0, f2, f4, r1; /* real registers used by PFPO */
florian7ab421d2013-06-17 21:03:56 +00002691 s390_fp_conv_t fpconv;
2692
2693 switch (expr->Iex.Binop.op) {
2694 case Iop_F32toD128: /* (D128, I64) -> D128 */
2695 fpconv = S390_FP_F32_TO_D128;
2696 break;
2697 case Iop_F64toD128: /* (D128, I64) -> D128 */
2698 fpconv = S390_FP_F64_TO_D128;
2699 break;
2700 default: goto irreducible;
2701 }
florian78d5ef72013-05-11 15:02:58 +00002702
2703 f4 = make_fpr(4); /* source */
2704 f0 = make_fpr(0); /* destination */
2705 f2 = make_fpr(2); /* destination */
2706 r1 = make_gpr(1); /* GPR #1 clobbered */
2707 irrm = expr->Iex.Binop.arg1;
2708 left = expr->Iex.Binop.arg2;
2709 rm = get_dfp_rounding_mode(env, irrm);
2710 h1 = s390_isel_float_expr(env, left);
2711 addInstr(env, s390_insn_move(8, f4, h1));
florian7ab421d2013-06-17 21:03:56 +00002712 addInstr(env, s390_insn_fp128_convert(16, fpconv, f0, f2,
florian78d5ef72013-05-11 15:02:58 +00002713 f4, INVALID_HREG, r1, rm));
2714 /* (f0, f2) --> destination */
2715 *dst_hi = newVRegF(env);
2716 *dst_lo = newVRegF(env);
2717 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2718 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2719
2720 return;
2721 }
2722
2723 case Iop_F128toD128: {
2724 IRExpr *irrm;
2725 IRExpr *left;
2726 s390_dfp_round_t rm;
2727 HReg op_hi, op_lo;
2728 HReg f0, f2, f4, f6, r1; /* real registers used by PFPO */
2729
2730 f4 = make_fpr(4); /* source */
2731 f6 = make_fpr(6); /* source */
2732 f0 = make_fpr(0); /* destination */
2733 f2 = make_fpr(2); /* destination */
2734 r1 = make_gpr(1); /* GPR #1 clobbered */
2735
2736 irrm = expr->Iex.Binop.arg1;
2737 left = expr->Iex.Binop.arg2;
2738 rm = get_dfp_rounding_mode(env, irrm);
2739 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
2740 /* operand --> (f4, f6) */
2741 addInstr(env, s390_insn_move(8, f4, op_hi));
2742 addInstr(env, s390_insn_move(8, f6, op_lo));
2743 addInstr(env, s390_insn_fp128_convert(16, S390_FP_F128_TO_D128, f0, f2,
2744 f4, f6, r1, rm));
2745 /* (f0, f2) --> destination */
2746 *dst_hi = newVRegF(env);
2747 *dst_lo = newVRegF(env);
2748 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2749 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2750
2751 return;
2752 }
2753
floriane38f6412012-12-21 17:32:12 +00002754 default:
2755 goto irreducible;
2756 }
2757 }
2758
2759 /* --------- UNARY OP --------- */
2760 case Iex_Unop: {
2761 IRExpr *left = expr->Iex.Unop.arg;
2762 s390_dfp_conv_t conv;
floriane38f6412012-12-21 17:32:12 +00002763 HReg op, f12, f14;
2764
floriana887acd2013-02-08 23:32:54 +00002765 /* We use non-virtual registers as pairs (f12, f14)) */
floriane38f6412012-12-21 17:32:12 +00002766 f12 = make_fpr(12);
floriane38f6412012-12-21 17:32:12 +00002767 f14 = make_fpr(14);
floriane38f6412012-12-21 17:32:12 +00002768
2769 switch (expr->Iex.Unop.op) {
2770 case Iop_D64toD128: conv = S390_DFP_D64_TO_D128; goto convert_dfp;
florian5f034622013-01-13 02:29:05 +00002771 case Iop_I32StoD128: conv = S390_DFP_I32_TO_D128; goto convert_int;
floriana887acd2013-02-08 23:32:54 +00002772 case Iop_I64StoD128: conv = S390_DFP_I64_TO_D128; goto convert_int;
florian5f034622013-01-13 02:29:05 +00002773 case Iop_I32UtoD128: conv = S390_DFP_U32_TO_D128; goto convert_int;
2774 case Iop_I64UtoD128: conv = S390_DFP_U64_TO_D128; goto convert_int;
floriane38f6412012-12-21 17:32:12 +00002775 default:
2776 goto irreducible;
2777 }
2778
2779 convert_dfp:
2780 op = s390_isel_dfp_expr(env, left);
2781 addInstr(env, s390_insn_dfp128_convert_to(16, conv, f12, f14, op));
2782 goto move_dst;
2783
florian5f034622013-01-13 02:29:05 +00002784 convert_int:
2785 op = s390_isel_int_expr(env, left);
2786 addInstr(env, s390_insn_dfp128_convert_to(16, conv, f12, f14, op));
2787 goto move_dst;
2788
floriane38f6412012-12-21 17:32:12 +00002789 move_dst:
2790 /* Move result to virtual destination registers */
2791 *dst_hi = newVRegF(env);
2792 *dst_lo = newVRegF(env);
2793 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2794 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2795 return;
2796 }
2797
2798 default:
2799 goto irreducible;
2800 }
2801
2802 /* We get here if no pattern matched. */
2803 irreducible:
2804 ppIRExpr(expr);
2805 vpanic("s390_isel_dfp128_expr_wrk: cannot reduce tree");
2806
2807}
2808
2809
2810/* Compute a 128-bit value into two 64-bit registers. These may be either
2811 real or virtual regs; in any case they must not be changed by subsequent
2812 code emitted by the caller. */
2813static void
2814s390_isel_dfp128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
2815{
2816 s390_isel_dfp128_expr_wrk(dst_hi, dst_lo, env, expr);
2817
2818 /* Sanity checks ... */
2819 vassert(hregIsVirtual(*dst_hi));
2820 vassert(hregIsVirtual(*dst_lo));
2821 vassert(hregClass(*dst_hi) == HRcFlt64);
2822 vassert(hregClass(*dst_lo) == HRcFlt64);
2823}
2824
2825
2826/*---------------------------------------------------------*/
florian12390202012-11-10 22:34:14 +00002827/*--- ISEL: Decimal point expressions (64 bit) ---*/
2828/*---------------------------------------------------------*/
2829
2830static HReg
2831s390_isel_dfp_expr_wrk(ISelEnv *env, IRExpr *expr)
2832{
2833 IRType ty = typeOfIRExpr(env->type_env, expr);
2834 UChar size;
2835
floriane38f6412012-12-21 17:32:12 +00002836 vassert(ty == Ity_D64 || ty == Ity_D32);
florian12390202012-11-10 22:34:14 +00002837
2838 size = sizeofIRType(ty);
2839
2840 switch (expr->tag) {
2841 case Iex_RdTmp:
2842 /* Return the virtual register that holds the temporary. */
2843 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
2844
2845 /* --------- LOAD --------- */
2846 case Iex_Load: {
2847 HReg dst = newVRegF(env);
2848 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
2849
2850 if (expr->Iex.Load.end != Iend_BE)
2851 goto irreducible;
2852
2853 addInstr(env, s390_insn_load(size, dst, am));
2854
2855 return dst;
2856 }
2857
2858 /* --------- GET --------- */
2859 case Iex_Get: {
2860 HReg dst = newVRegF(env);
2861 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
2862
2863 addInstr(env, s390_insn_load(size, dst, am));
2864
2865 return dst;
2866 }
2867
floriane38f6412012-12-21 17:32:12 +00002868 /* --------- BINARY OP --------- */
2869 case Iex_Binop: {
2870 IROp op = expr->Iex.Binop.op;
2871 IRExpr *irrm = expr->Iex.Binop.arg1;
2872 IRExpr *left = expr->Iex.Binop.arg2;
2873 HReg h1, dst;
2874 s390_dfp_conv_t conv;
florian78d5ef72013-05-11 15:02:58 +00002875 s390_fp_conv_t fpconv;
floriane38f6412012-12-21 17:32:12 +00002876
2877 switch (op) {
2878 case Iop_D64toD32: conv = S390_DFP_D64_TO_D32; goto convert_dfp;
floriana887acd2013-02-08 23:32:54 +00002879 case Iop_I64StoD64: conv = S390_DFP_I64_TO_D64; goto convert_int;
florian5f034622013-01-13 02:29:05 +00002880 case Iop_I64UtoD64: conv = S390_DFP_U64_TO_D64; goto convert_int;
florian7ab421d2013-06-17 21:03:56 +00002881 case Iop_F32toD32: fpconv = S390_FP_F32_TO_D32; goto convert_bfp;
2882 case Iop_F32toD64: fpconv = S390_FP_F32_TO_D64; goto convert_bfp;
2883 case Iop_F64toD32: fpconv = S390_FP_F64_TO_D32; goto convert_bfp;
florian78d5ef72013-05-11 15:02:58 +00002884 case Iop_F64toD64: fpconv = S390_FP_F64_TO_D64; goto convert_bfp;
florian7ab421d2013-06-17 21:03:56 +00002885 case Iop_F128toD32: fpconv = S390_FP_F128_TO_D32; goto convert_bfp128;
2886 case Iop_F128toD64: fpconv = S390_FP_F128_TO_D64; goto convert_bfp128;
floriane38f6412012-12-21 17:32:12 +00002887
2888 convert_dfp:
2889 h1 = s390_isel_dfp_expr(env, left);
2890 goto convert;
2891
florian5f034622013-01-13 02:29:05 +00002892 convert_int:
2893 h1 = s390_isel_int_expr(env, left);
2894 goto convert;
2895
floriane38f6412012-12-21 17:32:12 +00002896 convert: {
2897 s390_dfp_round_t rounding_mode;
2898 /* convert-from-fixed and load-rounded have a rounding mode field
2899 when the floating point extension facility is installed. */
2900 dst = newVRegF(env);
2901 if (s390_host_has_fpext) {
2902 rounding_mode = get_dfp_rounding_mode(env, irrm);
2903 } else {
2904 set_dfp_rounding_mode_in_fpc(env, irrm);
2905 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2906 }
2907 addInstr(env, s390_insn_dfp_convert(size, conv, dst, h1,
2908 rounding_mode));
2909 return dst;
2910 }
floriane38f6412012-12-21 17:32:12 +00002911
florian78d5ef72013-05-11 15:02:58 +00002912 convert_bfp: {
2913 s390_dfp_round_t rm;
2914 HReg f0, f4, r1; /* real registers used by PFPO */
2915
2916 f4 = make_fpr(4); /* source */
2917 f0 = make_fpr(0); /* destination */
2918 r1 = make_gpr(1); /* GPR #1 clobbered */
2919 h1 = s390_isel_float_expr(env, left);
2920 dst = newVRegF(env);
2921 rm = get_dfp_rounding_mode(env, irrm);
2922 /* operand --> f4 */
2923 addInstr(env, s390_insn_move(8, f4, h1));
2924 addInstr(env, s390_insn_fp_convert(size, fpconv, f0, f4, r1, rm));
2925 /* f0 --> destination */
2926 addInstr(env, s390_insn_move(8, dst, f0));
2927 return dst;
2928 }
2929
florian7ab421d2013-06-17 21:03:56 +00002930 convert_bfp128: {
2931 s390_dfp_round_t rm;
2932 HReg op_hi, op_lo;
2933 HReg f0, f4, f6, r1; /* real registers used by PFPO */
2934
2935 f4 = make_fpr(4); /* source */
2936 f6 = make_fpr(6); /* source */
2937 f0 = make_fpr(0); /* destination */
2938 r1 = make_gpr(1); /* GPR #1 clobbered */
2939 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
2940 dst = newVRegF(env);
2941 rm = get_dfp_rounding_mode(env, irrm);
2942 /* operand --> (f4, f6) */
2943 addInstr(env, s390_insn_move(8, f4, op_hi));
2944 addInstr(env, s390_insn_move(8, f6, op_lo));
2945 addInstr(env, s390_insn_fp128_convert(16, fpconv, f0, INVALID_HREG,
2946 f4, f6, r1, rm));
2947 /* f0 --> destination */
2948 addInstr(env, s390_insn_move(8, dst, f0));
2949 return dst;
2950 }
2951
floriane38f6412012-12-21 17:32:12 +00002952 case Iop_D128toD64: {
2953 HReg op_hi, op_lo, f13, f15;
2954 s390_dfp_round_t rounding_mode;
2955
2956 conv = S390_DFP_D128_TO_D64;
2957
2958 s390_isel_dfp128_expr(&op_hi, &op_lo, env, left);
2959
2960 /* We use non-virtual registers as pairs (f13, f15) */
2961 f13 = make_fpr(13);
2962 f15 = make_fpr(15);
2963
2964 /* operand --> (f13, f15) */
2965 addInstr(env, s390_insn_move(8, f13, op_hi));
2966 addInstr(env, s390_insn_move(8, f15, op_lo));
2967
2968 dst = newVRegF(env);
2969 /* load-rounded has a rounding mode field when the floating point
2970 extension facility is installed. */
2971 if (s390_host_has_fpext) {
2972 rounding_mode = get_dfp_rounding_mode(env, irrm);
2973 } else {
2974 set_dfp_rounding_mode_in_fpc(env, irrm);
2975 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2976 }
2977 addInstr(env, s390_insn_dfp128_convert_from(size, conv, dst, f13, f15,
2978 rounding_mode));
2979 return dst;
2980 }
2981
florian1b901d42013-01-01 22:19:24 +00002982 case Iop_ShlD64:
florian5c539732013-02-14 14:27:12 +00002983 case Iop_ShrD64:
2984 case Iop_InsertExpD64: {
florian1b901d42013-01-01 22:19:24 +00002985 HReg op2;
2986 HReg op3;
florian5c539732013-02-14 14:27:12 +00002987 IRExpr *dfp_op;
2988 IRExpr *int_op;
florian1b901d42013-01-01 22:19:24 +00002989 s390_dfp_intop_t intop;
florian1b901d42013-01-01 22:19:24 +00002990
2991 switch (expr->Iex.Binop.op) {
florian5c539732013-02-14 14:27:12 +00002992 case Iop_ShlD64: /* (D64, I64) -> D64 */
2993 intop = S390_DFP_SHIFT_LEFT;
2994 dfp_op = expr->Iex.Binop.arg1;
2995 int_op = expr->Iex.Binop.arg2;
2996 break;
2997 case Iop_ShrD64: /* (D64, I64) -> D64 */
2998 intop = S390_DFP_SHIFT_RIGHT;
2999 dfp_op = expr->Iex.Binop.arg1;
3000 int_op = expr->Iex.Binop.arg2;
3001 break;
3002 case Iop_InsertExpD64: /* (I64, D64) -> D64 */
3003 intop = S390_DFP_INSERT_EXP;
3004 int_op = expr->Iex.Binop.arg1;
3005 dfp_op = expr->Iex.Binop.arg2;
3006 break;
florian1b901d42013-01-01 22:19:24 +00003007 default: goto irreducible;
3008 }
3009
florian5c539732013-02-14 14:27:12 +00003010 op2 = s390_isel_int_expr(env, int_op);
3011 op3 = s390_isel_dfp_expr(env, dfp_op);
florian1b901d42013-01-01 22:19:24 +00003012 dst = newVRegF(env);
3013
3014 addInstr(env, s390_insn_dfp_intop(size, intop, dst, op2, op3));
3015 return dst;
3016 }
3017
3018 default:
3019 goto irreducible;
floriane38f6412012-12-21 17:32:12 +00003020 }
3021 }
3022
3023 /* --------- UNARY OP --------- */
3024 case Iex_Unop: {
3025 IROp op = expr->Iex.Unop.op;
3026 IRExpr *left = expr->Iex.Unop.arg;
3027 s390_dfp_conv_t conv;
3028 HReg h1, dst;
3029
3030 if (op == Iop_D128HItoD64 || op == Iop_D128LOtoD64) {
3031 HReg dst_hi, dst_lo;
3032
3033 s390_isel_dfp128_expr(&dst_hi, &dst_lo, env, left);
3034 return op == Iop_D128LOtoD64 ? dst_lo : dst_hi;
3035 }
3036
3037 if (op == Iop_ReinterpI64asD64) {
3038 dst = newVRegF(env);
3039 h1 = s390_isel_int_expr(env, left); /* Process the operand */
3040 addInstr(env, s390_insn_move(size, dst, h1));
3041
3042 return dst;
3043 }
3044
3045 switch (op) {
3046 case Iop_D32toD64: conv = S390_DFP_D32_TO_D64; goto convert_dfp1;
florian5f034622013-01-13 02:29:05 +00003047 case Iop_I32StoD64: conv = S390_DFP_I32_TO_D64; goto convert_int1;
3048 case Iop_I32UtoD64: conv = S390_DFP_U32_TO_D64; goto convert_int1;
floriane38f6412012-12-21 17:32:12 +00003049
3050 convert_dfp1:
3051 h1 = s390_isel_dfp_expr(env, left);
3052 goto convert1;
3053
florian5f034622013-01-13 02:29:05 +00003054 convert_int1:
3055 h1 = s390_isel_int_expr(env, left);
3056 goto convert1;
3057
floriane38f6412012-12-21 17:32:12 +00003058 convert1:
3059 dst = newVRegF(env);
3060 /* No rounding mode is needed for these conversions. Just stick
3061 one in. It won't be used later on. */
3062 addInstr(env, s390_insn_dfp_convert(size, conv, dst, h1,
3063 S390_DFP_ROUND_NEAREST_EVEN_4));
3064 return dst;
3065
3066 default:
3067 goto irreducible;
3068 }
3069 }
3070
florian12390202012-11-10 22:34:14 +00003071 /* --------- TERNARY OP --------- */
3072 case Iex_Triop: {
3073 IRTriop *triop = expr->Iex.Triop.details;
3074 IROp op = triop->op;
3075 IRExpr *irrm = triop->arg1;
3076 IRExpr *left = triop->arg2;
3077 IRExpr *right = triop->arg3;
3078 s390_dfp_round_t rounding_mode;
3079 s390_dfp_binop_t dfpop;
3080 HReg op2, op3, dst;
3081
florian12390202012-11-10 22:34:14 +00003082 switch (op) {
florian5c539732013-02-14 14:27:12 +00003083 case Iop_AddD64: dfpop = S390_DFP_ADD; goto evaluate_dfp;
3084 case Iop_SubD64: dfpop = S390_DFP_SUB; goto evaluate_dfp;
3085 case Iop_MulD64: dfpop = S390_DFP_MUL; goto evaluate_dfp;
3086 case Iop_DivD64: dfpop = S390_DFP_DIV; goto evaluate_dfp;
3087 case Iop_QuantizeD64: dfpop = S390_DFP_QUANTIZE; goto evaluate_dfp;
3088
3089 evaluate_dfp: {
3090 op2 = s390_isel_dfp_expr(env, left); /* Process 1st operand */
3091 op3 = s390_isel_dfp_expr(env, right); /* Process 2nd operand */
3092 dst = newVRegF(env);
3093 /* DFP arithmetic ops take rounding mode only when fpext is
3094 installed. But, DFP quantize operation takes rm irrespective
3095 of fpext facility . */
3096 if (s390_host_has_fpext || dfpop == S390_DFP_QUANTIZE) {
3097 rounding_mode = get_dfp_rounding_mode(env, irrm);
3098 } else {
3099 set_dfp_rounding_mode_in_fpc(env, irrm);
3100 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
3101 }
3102 addInstr(env, s390_insn_dfp_binop(size, dfpop, dst, op2, op3,
3103 rounding_mode));
3104 return dst;
3105 }
3106
3107 case Iop_SignificanceRoundD64:
3108 op2 = s390_isel_int_expr(env, left); /* Process 1st operand */
3109 op3 = s390_isel_dfp_expr(env, right); /* Process 2nd operand */
3110 dst = newVRegF(env);
3111 rounding_mode = get_dfp_rounding_mode(env, irrm);
3112 addInstr(env, s390_insn_dfp_reround(size, dst, op2, op3,
3113 rounding_mode));
3114 return dst;
3115
florian12390202012-11-10 22:34:14 +00003116 default:
3117 goto irreducible;
3118 }
florian12390202012-11-10 22:34:14 +00003119 }
3120
3121 default:
3122 goto irreducible;
3123 }
3124
3125 /* We get here if no pattern matched. */
3126 irreducible:
3127 ppIRExpr(expr);
3128 vpanic("s390_isel_dfp_expr: cannot reduce tree");
3129}
3130
3131static HReg
3132s390_isel_dfp_expr(ISelEnv *env, IRExpr *expr)
3133{
3134 HReg dst = s390_isel_dfp_expr_wrk(env, expr);
3135
3136 /* Sanity checks ... */
3137 vassert(hregClass(dst) == HRcFlt64);
3138 vassert(hregIsVirtual(dst));
3139
3140 return dst;
3141}
3142
3143
3144/*---------------------------------------------------------*/
sewardj2019a972011-03-07 16:04:07 +00003145/*--- ISEL: Condition Code ---*/
3146/*---------------------------------------------------------*/
3147
3148/* This function handles all operators that produce a 1-bit result */
3149static s390_cc_t
3150s390_isel_cc(ISelEnv *env, IRExpr *cond)
3151{
3152 UChar size;
3153
3154 vassert(typeOfIRExpr(env->type_env, cond) == Ity_I1);
3155
3156 /* Constant: either 1 or 0 */
3157 if (cond->tag == Iex_Const) {
3158 vassert(cond->Iex.Const.con->tag == Ico_U1);
3159 vassert(cond->Iex.Const.con->Ico.U1 == True
3160 || cond->Iex.Const.con->Ico.U1 == False);
3161
3162 return cond->Iex.Const.con->Ico.U1 == True ? S390_CC_ALWAYS : S390_CC_NEVER;
3163 }
3164
3165 /* Variable: values are 1 or 0 */
3166 if (cond->tag == Iex_RdTmp) {
3167 IRTemp tmp = cond->Iex.RdTmp.tmp;
3168 HReg reg = lookupIRTemp(env, tmp);
3169
3170 /* Load-and-test does not modify REG; so this is OK. */
3171 if (typeOfIRTemp(env->type_env, tmp) == Ity_I1)
3172 size = 4;
3173 else
3174 size = sizeofIRType(typeOfIRTemp(env->type_env, tmp));
3175 addInstr(env, s390_insn_test(size, s390_opnd_reg(reg)));
3176 return S390_CC_NE;
3177 }
3178
3179 /* Unary operators */
3180 if (cond->tag == Iex_Unop) {
3181 IRExpr *arg = cond->Iex.Unop.arg;
3182
3183 switch (cond->Iex.Unop.op) {
3184 case Iop_Not1: /* Not1(cond) */
3185 /* Generate code for EXPR, and negate the test condition */
3186 return s390_cc_invert(s390_isel_cc(env, arg));
3187
3188 /* Iop_32/64to1 select the LSB from their operand */
3189 case Iop_32to1:
3190 case Iop_64to1: {
florianf366a802012-08-03 00:42:18 +00003191 HReg dst = newVRegI(env);
3192 HReg h1 = s390_isel_int_expr(env, arg);
sewardj2019a972011-03-07 16:04:07 +00003193
3194 size = sizeofIRType(typeOfIRExpr(env->type_env, arg));
3195
florianf366a802012-08-03 00:42:18 +00003196 addInstr(env, s390_insn_move(size, dst, h1));
sewardj2019a972011-03-07 16:04:07 +00003197 addInstr(env, s390_insn_alu(size, S390_ALU_AND, dst, s390_opnd_imm(1)));
3198 addInstr(env, s390_insn_test(size, s390_opnd_reg(dst)));
3199 return S390_CC_NE;
3200 }
3201
3202 case Iop_CmpNEZ8:
3203 case Iop_CmpNEZ16: {
3204 s390_opnd_RMI src;
3205 s390_unop_t op;
3206 HReg dst;
3207
3208 op = (cond->Iex.Unop.op == Iop_CmpNEZ8) ? S390_ZERO_EXTEND_8
3209 : S390_ZERO_EXTEND_16;
3210 dst = newVRegI(env);
3211 src = s390_isel_int_expr_RMI(env, arg);
3212 addInstr(env, s390_insn_unop(4, op, dst, src));
3213 addInstr(env, s390_insn_test(4, s390_opnd_reg(dst)));
3214 return S390_CC_NE;
3215 }
3216
3217 case Iop_CmpNEZ32:
3218 case Iop_CmpNEZ64: {
3219 s390_opnd_RMI src;
3220
3221 src = s390_isel_int_expr_RMI(env, arg);
3222 size = sizeofIRType(typeOfIRExpr(env->type_env, arg));
3223 addInstr(env, s390_insn_test(size, src));
3224 return S390_CC_NE;
3225 }
3226
3227 default:
3228 goto fail;
3229 }
3230 }
3231
3232 /* Binary operators */
3233 if (cond->tag == Iex_Binop) {
3234 IRExpr *arg1 = cond->Iex.Binop.arg1;
3235 IRExpr *arg2 = cond->Iex.Binop.arg2;
3236 HReg reg1, reg2;
3237
3238 size = sizeofIRType(typeOfIRExpr(env->type_env, arg1));
3239
3240 switch (cond->Iex.Binop.op) {
3241 s390_unop_t op;
3242 s390_cc_t result;
3243
3244 case Iop_CmpEQ8:
3245 case Iop_CasCmpEQ8:
3246 op = S390_ZERO_EXTEND_8;
3247 result = S390_CC_E;
3248 goto do_compare_ze;
3249
3250 case Iop_CmpNE8:
3251 case Iop_CasCmpNE8:
3252 op = S390_ZERO_EXTEND_8;
3253 result = S390_CC_NE;
3254 goto do_compare_ze;
3255
3256 case Iop_CmpEQ16:
3257 case Iop_CasCmpEQ16:
3258 op = S390_ZERO_EXTEND_16;
3259 result = S390_CC_E;
3260 goto do_compare_ze;
3261
3262 case Iop_CmpNE16:
3263 case Iop_CasCmpNE16:
3264 op = S390_ZERO_EXTEND_16;
3265 result = S390_CC_NE;
3266 goto do_compare_ze;
3267
3268 do_compare_ze: {
3269 s390_opnd_RMI op1, op2;
3270
3271 op1 = s390_isel_int_expr_RMI(env, arg1);
3272 reg1 = newVRegI(env);
3273 addInstr(env, s390_insn_unop(4, op, reg1, op1));
3274
3275 op2 = s390_isel_int_expr_RMI(env, arg2);
3276 reg2 = newVRegI(env);
3277 addInstr(env, s390_insn_unop(4, op, reg2, op2)); /* zero extend */
3278
3279 op2 = s390_opnd_reg(reg2);
3280 addInstr(env, s390_insn_compare(4, reg1, op2, False));
3281
3282 return result;
3283 }
3284
3285 case Iop_CmpEQ32:
3286 case Iop_CmpEQ64:
3287 case Iop_CasCmpEQ32:
3288 case Iop_CasCmpEQ64:
3289 result = S390_CC_E;
3290 goto do_compare;
3291
3292 case Iop_CmpNE32:
3293 case Iop_CmpNE64:
3294 case Iop_CasCmpNE32:
3295 case Iop_CasCmpNE64:
3296 result = S390_CC_NE;
3297 goto do_compare;
3298
3299 do_compare: {
3300 HReg op1;
3301 s390_opnd_RMI op2;
3302
3303 order_commutative_operands(arg1, arg2);
3304
3305 op1 = s390_isel_int_expr(env, arg1);
3306 op2 = s390_isel_int_expr_RMI(env, arg2);
3307
3308 addInstr(env, s390_insn_compare(size, op1, op2, False));
3309
3310 return result;
3311 }
3312
3313 case Iop_CmpLT32S:
3314 case Iop_CmpLE32S:
3315 case Iop_CmpLT64S:
3316 case Iop_CmpLE64S: {
3317 HReg op1;
3318 s390_opnd_RMI op2;
3319
3320 op1 = s390_isel_int_expr(env, arg1);
3321 op2 = s390_isel_int_expr_RMI(env, arg2);
3322
3323 addInstr(env, s390_insn_compare(size, op1, op2, True));
3324
3325 return (cond->Iex.Binop.op == Iop_CmpLT32S ||
3326 cond->Iex.Binop.op == Iop_CmpLT64S) ? S390_CC_L : S390_CC_LE;
3327 }
3328
3329 case Iop_CmpLT32U:
3330 case Iop_CmpLE32U:
3331 case Iop_CmpLT64U:
3332 case Iop_CmpLE64U: {
3333 HReg op1;
3334 s390_opnd_RMI op2;
3335
3336 op1 = s390_isel_int_expr(env, arg1);
3337 op2 = s390_isel_int_expr_RMI(env, arg2);
3338
3339 addInstr(env, s390_insn_compare(size, op1, op2, False));
3340
3341 return (cond->Iex.Binop.op == Iop_CmpLT32U ||
3342 cond->Iex.Binop.op == Iop_CmpLT64U) ? S390_CC_L : S390_CC_LE;
3343 }
3344
3345 default:
3346 goto fail;
3347 }
3348 }
3349
3350 fail:
3351 ppIRExpr(cond);
3352 vpanic("s390_isel_cc: unexpected operator");
3353}
3354
3355
3356/*---------------------------------------------------------*/
3357/*--- ISEL: Statements ---*/
3358/*---------------------------------------------------------*/
3359
3360static void
3361s390_isel_stmt(ISelEnv *env, IRStmt *stmt)
3362{
3363 if (vex_traceflags & VEX_TRACE_VCODE) {
3364 vex_printf("\n -- ");
3365 ppIRStmt(stmt);
3366 vex_printf("\n");
3367 }
3368
3369 switch (stmt->tag) {
3370
3371 /* --------- STORE --------- */
3372 case Ist_Store: {
3373 IRType tyd = typeOfIRExpr(env->type_env, stmt->Ist.Store.data);
3374 s390_amode *am;
3375 HReg src;
3376
3377 if (stmt->Ist.Store.end != Iend_BE) goto stmt_fail;
3378
3379 am = s390_isel_amode(env, stmt->Ist.Store.addr);
3380
3381 switch (tyd) {
3382 case Ity_I8:
3383 case Ity_I16:
3384 case Ity_I32:
3385 case Ity_I64:
florianf85fe3e2012-12-22 02:28:25 +00003386 /* fixs390: We could check for INSN_MADD here. */
florian09bbba82012-12-11 04:09:43 +00003387 if (am->tag == S390_AMODE_B12 &&
florianb93348d2012-12-27 00:59:43 +00003388 stmt->Ist.Store.data->tag == Iex_Const) {
3389 ULong value =
3390 get_const_value_as_ulong(stmt->Ist.Store.data->Iex.Const.con);
3391 addInstr(env, s390_insn_mimm(sizeofIRType(tyd), am, value));
florian09bbba82012-12-11 04:09:43 +00003392 return;
3393 }
floriancec3a8a2013-02-02 00:16:58 +00003394 /* Check whether we can use a memcpy here. Currently, the restriction
3395 is that both amodes need to be B12, so MVC can be emitted.
3396 We do not consider a store whose data expression is a load because
3397 we don't want to deal with overlapping locations. */
3398 /* store(get) never overlaps*/
3399 if (am->tag == S390_AMODE_B12 &&
3400 stmt->Ist.Store.data->tag == Iex_Get) {
3401 UInt offset = stmt->Ist.Store.data->Iex.Get.offset;
3402 s390_amode *from = s390_amode_for_guest_state(offset);
3403 addInstr(env, s390_insn_memcpy(sizeofIRType(tyd), am, from));
3404 return;
3405 }
3406 /* General case: compile data into a register */
sewardj2019a972011-03-07 16:04:07 +00003407 src = s390_isel_int_expr(env, stmt->Ist.Store.data);
3408 break;
3409
3410 case Ity_F32:
3411 case Ity_F64:
3412 src = s390_isel_float_expr(env, stmt->Ist.Store.data);
3413 break;
3414
florianeb981ae2012-12-21 18:55:03 +00003415 case Ity_D32:
3416 case Ity_D64:
3417 src = s390_isel_dfp_expr(env, stmt->Ist.Store.data);
3418 break;
3419
sewardj2019a972011-03-07 16:04:07 +00003420 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003421 case Ity_D128:
sewardj2019a972011-03-07 16:04:07 +00003422 /* Cannot occur. No such instruction */
floriane38f6412012-12-21 17:32:12 +00003423 vpanic("Ist_Store with 128-bit floating point data");
sewardj2019a972011-03-07 16:04:07 +00003424
3425 default:
3426 goto stmt_fail;
3427 }
3428
3429 addInstr(env, s390_insn_store(sizeofIRType(tyd), am, src));
3430 return;
3431 }
3432
3433 /* --------- PUT --------- */
3434 case Ist_Put: {
3435 IRType tyd = typeOfIRExpr(env->type_env, stmt->Ist.Put.data);
3436 HReg src;
3437 s390_amode *am;
florianad43b3a2012-02-20 15:01:14 +00003438 ULong new_value, old_value, difference;
sewardj2019a972011-03-07 16:04:07 +00003439
florianad43b3a2012-02-20 15:01:14 +00003440 /* Detect updates to certain guest registers. We track the contents
3441 of those registers as long as they contain constants. If the new
3442 constant is either zero or in the 8-bit neighbourhood of the
3443 current value we can use a memory-to-memory insn to do the update. */
3444
3445 Int offset = stmt->Ist.Put.offset;
3446
3447 /* Check necessary conditions:
3448 (1) must be one of the registers we care about
3449 (2) assigned value must be a constant */
3450 Int guest_reg = get_guest_reg(offset);
3451
3452 if (guest_reg == GUEST_UNKNOWN) goto not_special;
3453
florianad43b3a2012-02-20 15:01:14 +00003454 if (stmt->Ist.Put.data->tag != Iex_Const) {
3455 /* Invalidate guest register contents */
3456 env->old_value_valid[guest_reg] = False;
3457 goto not_special;
3458 }
3459
cborntraaf7ad282012-08-08 14:11:33 +00003460 /* We can only handle Ity_I64, but the CC_DEPS field can have floats */
3461 if (tyd != Ity_I64)
3462 goto not_special;
florianad43b3a2012-02-20 15:01:14 +00003463
cborntraaf7ad282012-08-08 14:11:33 +00003464 /* OK. Necessary conditions are satisfied. */
florianad43b3a2012-02-20 15:01:14 +00003465
3466 old_value = env->old_value[guest_reg];
3467 new_value = stmt->Ist.Put.data->Iex.Const.con->Ico.U64;
3468 env->old_value[guest_reg] = new_value;
3469
3470 Bool old_value_is_valid = env->old_value_valid[guest_reg];
3471 env->old_value_valid[guest_reg] = True;
3472
3473 /* If the register already contains the new value, there is nothing
florian9f42ab42012-12-23 01:09:16 +00003474 to do here. */
florianad43b3a2012-02-20 15:01:14 +00003475 if (old_value_is_valid && new_value == old_value) {
florian9f42ab42012-12-23 01:09:16 +00003476 return;
florianad43b3a2012-02-20 15:01:14 +00003477 }
3478
florianad43b3a2012-02-20 15:01:14 +00003479 if (old_value_is_valid == False) goto not_special;
3480
3481 /* If the new value is in the neighbourhood of the old value
3482 we can use a memory-to-memory insn */
3483 difference = new_value - old_value;
3484
3485 if (s390_host_has_gie && ulong_fits_signed_8bit(difference)) {
florianf85fe3e2012-12-22 02:28:25 +00003486 am = s390_amode_for_guest_state(offset);
3487 addInstr(env, s390_insn_madd(sizeofIRType(tyd), am,
florianad43b3a2012-02-20 15:01:14 +00003488 (difference & 0xFF), new_value));
3489 return;
3490 }
3491
florianb93348d2012-12-27 00:59:43 +00003492 /* If the high word is the same it is sufficient to load the low word. */
florianad43b3a2012-02-20 15:01:14 +00003493 if ((old_value >> 32) == (new_value >> 32)) {
florianf85fe3e2012-12-22 02:28:25 +00003494 am = s390_amode_for_guest_state(offset + 4);
florianb93348d2012-12-27 00:59:43 +00003495 addInstr(env, s390_insn_mimm(4, am, new_value & 0xFFFFFFFF));
florianad43b3a2012-02-20 15:01:14 +00003496 return;
3497 }
3498
3499 /* No special case applies... fall through */
3500
3501 not_special:
florianb93348d2012-12-27 00:59:43 +00003502 am = s390_amode_for_guest_state(offset);
sewardj2019a972011-03-07 16:04:07 +00003503
3504 switch (tyd) {
3505 case Ity_I8:
3506 case Ity_I16:
3507 case Ity_I32:
3508 case Ity_I64:
florian09bbba82012-12-11 04:09:43 +00003509 if (am->tag == S390_AMODE_B12 &&
florianb93348d2012-12-27 00:59:43 +00003510 stmt->Ist.Put.data->tag == Iex_Const) {
3511 ULong value =
3512 get_const_value_as_ulong(stmt->Ist.Put.data->Iex.Const.con);
3513 addInstr(env, s390_insn_mimm(sizeofIRType(tyd), am, value));
florian09bbba82012-12-11 04:09:43 +00003514 return;
3515 }
floriancec3a8a2013-02-02 00:16:58 +00003516 /* Check whether we can use a memcpy here. Currently, the restriction
3517 is that both amodes need to be B12, so MVC can be emitted. */
3518 /* put(load) never overlaps */
3519 if (am->tag == S390_AMODE_B12 &&
3520 stmt->Ist.Put.data->tag == Iex_Load) {
3521 if (stmt->Ist.Put.data->Iex.Load.end != Iend_BE) goto stmt_fail;
3522 IRExpr *data = stmt->Ist.Put.data->Iex.Load.addr;
3523 s390_amode *from = s390_isel_amode(env, data);
3524 UInt size = sizeofIRType(tyd);
3525
3526 if (from->tag == S390_AMODE_B12) {
3527 /* Source can be compiled into a B12 amode. */
3528 addInstr(env, s390_insn_memcpy(size, am, from));
3529 return;
3530 }
3531
3532 src = newVRegI(env);
3533 addInstr(env, s390_insn_load(size, src, from));
3534 break;
3535 }
3536 /* put(get) */
3537 if (am->tag == S390_AMODE_B12 &&
3538 stmt->Ist.Put.data->tag == Iex_Get) {
3539 UInt put_offset = am->d;
3540 UInt get_offset = stmt->Ist.Put.data->Iex.Get.offset;
3541 UInt size = sizeofIRType(tyd);
3542 /* don't memcpy in case of overlap */
3543 if (put_offset + size <= get_offset ||
3544 get_offset + size <= put_offset) {
3545 s390_amode *from = s390_amode_for_guest_state(get_offset);
3546 addInstr(env, s390_insn_memcpy(size, am, from));
3547 return;
3548 }
3549 goto no_memcpy_put;
3550 }
3551 /* General case: compile data into a register */
3552no_memcpy_put:
sewardj2019a972011-03-07 16:04:07 +00003553 src = s390_isel_int_expr(env, stmt->Ist.Put.data);
3554 break;
3555
3556 case Ity_F32:
3557 case Ity_F64:
3558 src = s390_isel_float_expr(env, stmt->Ist.Put.data);
3559 break;
3560
3561 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003562 case Ity_D128:
3563 /* Does not occur. See function put_(f|d)pr_pair. */
3564 vpanic("Ist_Put with 128-bit floating point data");
sewardj2019a972011-03-07 16:04:07 +00003565
floriane38f6412012-12-21 17:32:12 +00003566 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003567 case Ity_D64:
3568 src = s390_isel_dfp_expr(env, stmt->Ist.Put.data);
3569 break;
3570
sewardj2019a972011-03-07 16:04:07 +00003571 default:
3572 goto stmt_fail;
3573 }
3574
3575 addInstr(env, s390_insn_store(sizeofIRType(tyd), am, src));
3576 return;
3577 }
3578
3579 /* --------- TMP --------- */
3580 case Ist_WrTmp: {
3581 IRTemp tmp = stmt->Ist.WrTmp.tmp;
3582 IRType tyd = typeOfIRTemp(env->type_env, tmp);
3583 HReg src, dst;
3584
3585 switch (tyd) {
3586 case Ity_I128: {
3587 HReg dst_hi, dst_lo, res_hi, res_lo;
3588
3589 s390_isel_int128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3590 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3591
3592 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3593 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3594 return;
3595 }
3596
3597 case Ity_I8:
3598 case Ity_I16:
3599 case Ity_I32:
3600 case Ity_I64:
3601 src = s390_isel_int_expr(env, stmt->Ist.WrTmp.data);
3602 dst = lookupIRTemp(env, tmp);
3603 break;
3604
3605 case Ity_I1: {
3606 s390_cc_t cond = s390_isel_cc(env, stmt->Ist.WrTmp.data);
3607 dst = lookupIRTemp(env, tmp);
3608 addInstr(env, s390_insn_cc2bool(dst, cond));
3609 return;
3610 }
3611
3612 case Ity_F32:
3613 case Ity_F64:
3614 src = s390_isel_float_expr(env, stmt->Ist.WrTmp.data);
3615 dst = lookupIRTemp(env, tmp);
3616 break;
3617
3618 case Ity_F128: {
3619 HReg dst_hi, dst_lo, res_hi, res_lo;
3620
3621 s390_isel_float128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3622 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3623
3624 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3625 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3626 return;
3627 }
3628
floriane38f6412012-12-21 17:32:12 +00003629 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003630 case Ity_D64:
3631 src = s390_isel_dfp_expr(env, stmt->Ist.WrTmp.data);
3632 dst = lookupIRTemp(env, tmp);
3633 break;
3634
floriane38f6412012-12-21 17:32:12 +00003635 case Ity_D128: {
3636 HReg dst_hi, dst_lo, res_hi, res_lo;
3637
3638 s390_isel_dfp128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3639 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3640
3641 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3642 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3643 return;
3644 }
3645
sewardj2019a972011-03-07 16:04:07 +00003646 default:
3647 goto stmt_fail;
3648 }
3649
3650 addInstr(env, s390_insn_move(sizeofIRType(tyd), dst, src));
3651 return;
3652 }
3653
3654 /* --------- Call to DIRTY helper --------- */
3655 case Ist_Dirty: {
3656 IRType retty;
3657 IRDirty* d = stmt->Ist.Dirty.details;
3658 Bool passBBP;
florian01ed6e72012-05-27 16:52:43 +00003659 HReg dst;
florianad43b3a2012-02-20 15:01:14 +00003660 Int i;
3661
3662 /* Invalidate tracked values of those guest state registers that are
3663 modified by this helper. */
3664 for (i = 0; i < d->nFxState; ++i) {
sewardjc9069f22012-06-01 16:09:50 +00003665 /* JRS 1 June 2012: AFAICS, s390 guest doesn't use 'repeat'
3666 descriptors in guest state effect descriptions. Hence: */
3667 vassert(d->fxState[i].nRepeats == 0 && d->fxState[i].repeatLen == 0);
florianad43b3a2012-02-20 15:01:14 +00003668 if ((d->fxState[i].fx == Ifx_Write || d->fxState[i].fx == Ifx_Modify)) {
3669 Int guest_reg = get_guest_reg(d->fxState[i].offset);
3670 if (guest_reg != GUEST_UNKNOWN)
3671 env->old_value_valid[guest_reg] = False;
3672 }
3673 }
sewardj2019a972011-03-07 16:04:07 +00003674
3675 if (d->nFxState == 0)
3676 vassert(!d->needsBBP);
3677
3678 passBBP = toBool(d->nFxState > 0 && d->needsBBP);
3679
florian01ed6e72012-05-27 16:52:43 +00003680 if (d->tmp == IRTemp_INVALID) {
3681 /* No return value. */
3682 dst = INVALID_HREG;
3683 doHelperCall(env, passBBP, d->guard, d->cee, d->args, dst);
sewardj2019a972011-03-07 16:04:07 +00003684 return;
florian01ed6e72012-05-27 16:52:43 +00003685 }
sewardj2019a972011-03-07 16:04:07 +00003686
3687 retty = typeOfIRTemp(env->type_env, d->tmp);
3688 if (retty == Ity_I64 || retty == Ity_I32
3689 || retty == Ity_I16 || retty == Ity_I8) {
florian297b6062012-05-08 20:16:17 +00003690 /* Move the returned value to the destination register */
florian01ed6e72012-05-27 16:52:43 +00003691 dst = lookupIRTemp(env, d->tmp);
3692 doHelperCall(env, passBBP, d->guard, d->cee, d->args, dst);
sewardj2019a972011-03-07 16:04:07 +00003693 return;
3694 }
3695 break;
3696 }
3697
3698 case Ist_CAS:
3699 if (stmt->Ist.CAS.details->oldHi == IRTemp_INVALID) {
3700 IRCAS *cas = stmt->Ist.CAS.details;
3701 s390_amode *op2 = s390_isel_amode(env, cas->addr);
3702 HReg op3 = s390_isel_int_expr(env, cas->dataLo); /* new value */
3703 HReg op1 = s390_isel_int_expr(env, cas->expdLo); /* expected value */
3704 HReg old = lookupIRTemp(env, cas->oldLo);
3705
3706 if (typeOfIRTemp(env->type_env, cas->oldLo) == Ity_I32) {
3707 addInstr(env, s390_insn_cas(4, op1, op2, op3, old));
3708 } else {
3709 addInstr(env, s390_insn_cas(8, op1, op2, op3, old));
3710 }
3711 return;
3712 } else {
florian448cbba2012-06-06 02:26:01 +00003713 IRCAS *cas = stmt->Ist.CAS.details;
3714 s390_amode *op2 = s390_isel_amode(env, cas->addr);
3715 HReg r8, r9, r10, r11, r1;
3716 HReg op3_high = s390_isel_int_expr(env, cas->dataHi); /* new value */
3717 HReg op3_low = s390_isel_int_expr(env, cas->dataLo); /* new value */
3718 HReg op1_high = s390_isel_int_expr(env, cas->expdHi); /* expected value */
3719 HReg op1_low = s390_isel_int_expr(env, cas->expdLo); /* expected value */
3720 HReg old_low = lookupIRTemp(env, cas->oldLo);
3721 HReg old_high = lookupIRTemp(env, cas->oldHi);
3722
3723 /* Use non-virtual registers r8 and r9 as pair for op1
3724 and move op1 there */
3725 r8 = make_gpr(8);
3726 r9 = make_gpr(9);
3727 addInstr(env, s390_insn_move(8, r8, op1_high));
3728 addInstr(env, s390_insn_move(8, r9, op1_low));
3729
3730 /* Use non-virtual registers r10 and r11 as pair for op3
3731 and move op3 there */
3732 r10 = make_gpr(10);
3733 r11 = make_gpr(11);
3734 addInstr(env, s390_insn_move(8, r10, op3_high));
3735 addInstr(env, s390_insn_move(8, r11, op3_low));
3736
3737 /* Register r1 is used as a scratch register */
3738 r1 = make_gpr(1);
3739
3740 if (typeOfIRTemp(env->type_env, cas->oldLo) == Ity_I32) {
3741 addInstr(env, s390_insn_cdas(4, r8, r9, op2, r10, r11,
3742 old_high, old_low, r1));
3743 } else {
3744 addInstr(env, s390_insn_cdas(8, r8, r9, op2, r10, r11,
3745 old_high, old_low, r1));
3746 }
3747 addInstr(env, s390_insn_move(8, op1_high, r8));
3748 addInstr(env, s390_insn_move(8, op1_low, r9));
3749 addInstr(env, s390_insn_move(8, op3_high, r10));
3750 addInstr(env, s390_insn_move(8, op3_low, r11));
3751 return;
sewardj2019a972011-03-07 16:04:07 +00003752 }
3753 break;
3754
3755 /* --------- EXIT --------- */
3756 case Ist_Exit: {
sewardj2019a972011-03-07 16:04:07 +00003757 s390_cc_t cond;
3758 IRConstTag tag = stmt->Ist.Exit.dst->tag;
3759
3760 if (tag != Ico_U64)
3761 vpanic("s390_isel_stmt: Ist_Exit: dst is not a 64-bit value");
3762
florian8844a632012-04-13 04:04:06 +00003763 s390_amode *guest_IA = s390_amode_for_guest_state(stmt->Ist.Exit.offsIP);
sewardj2019a972011-03-07 16:04:07 +00003764 cond = s390_isel_cc(env, stmt->Ist.Exit.guard);
florian8844a632012-04-13 04:04:06 +00003765
3766 /* Case: boring transfer to known address */
3767 if (stmt->Ist.Exit.jk == Ijk_Boring) {
3768 if (env->chaining_allowed) {
3769 /* .. almost always true .. */
3770 /* Skip the event check at the dst if this is a forwards
3771 edge. */
3772 Bool to_fast_entry
3773 = ((Addr64)stmt->Ist.Exit.dst->Ico.U64) > env->max_ga;
3774 if (0) vex_printf("%s", to_fast_entry ? "Y" : ",");
3775 addInstr(env, s390_insn_xdirect(cond, stmt->Ist.Exit.dst->Ico.U64,
3776 guest_IA, to_fast_entry));
3777 } else {
3778 /* .. very occasionally .. */
3779 /* We can't use chaining, so ask for an assisted transfer,
3780 as that's the only alternative that is allowable. */
3781 HReg dst = s390_isel_int_expr(env,
3782 IRExpr_Const(stmt->Ist.Exit.dst));
3783 addInstr(env, s390_insn_xassisted(cond, dst, guest_IA, Ijk_Boring));
3784 }
3785 return;
3786 }
3787
3788 /* Case: assisted transfer to arbitrary address */
3789 switch (stmt->Ist.Exit.jk) {
florian4e0083e2012-08-26 03:41:56 +00003790 case Ijk_EmFail:
florian4b8efad2012-09-02 18:07:08 +00003791 case Ijk_EmWarn:
florian65b5b3f2012-04-22 02:51:27 +00003792 case Ijk_NoDecode:
florian8844a632012-04-13 04:04:06 +00003793 case Ijk_TInval:
florian2d98d892012-04-14 20:35:17 +00003794 case Ijk_Sys_syscall:
3795 case Ijk_ClientReq:
3796 case Ijk_NoRedir:
3797 case Ijk_Yield:
3798 case Ijk_SigTRAP: {
florian8844a632012-04-13 04:04:06 +00003799 HReg dst = s390_isel_int_expr(env, IRExpr_Const(stmt->Ist.Exit.dst));
3800 addInstr(env, s390_insn_xassisted(cond, dst, guest_IA,
3801 stmt->Ist.Exit.jk));
3802 return;
3803 }
3804 default:
3805 break;
3806 }
3807
3808 /* Do we ever expect to see any other kind? */
3809 goto stmt_fail;
sewardj2019a972011-03-07 16:04:07 +00003810 }
3811
3812 /* --------- MEM FENCE --------- */
sewardja52e37e2011-04-28 18:48:06 +00003813 case Ist_MBE:
3814 switch (stmt->Ist.MBE.event) {
3815 case Imbe_Fence:
3816 addInstr(env, s390_insn_mfence());
3817 return;
3818 default:
3819 break;
3820 }
sewardj2019a972011-03-07 16:04:07 +00003821 break;
3822
3823 /* --------- Miscellaneous --------- */
3824
3825 case Ist_PutI: /* Not needed */
3826 case Ist_IMark: /* Doesn't generate any executable code */
3827 case Ist_NoOp: /* Doesn't generate any executable code */
3828 case Ist_AbiHint: /* Meaningless in IR */
3829 return;
3830
3831 default:
3832 break;
3833 }
3834
3835 stmt_fail:
3836 ppIRStmt(stmt);
3837 vpanic("s390_isel_stmt");
3838}
3839
3840
3841/*---------------------------------------------------------*/
3842/*--- ISEL: Basic block terminators (Nexts) ---*/
3843/*---------------------------------------------------------*/
3844
3845static void
florianffbd84d2012-12-09 02:06:29 +00003846iselNext(ISelEnv *env, IRExpr *next, IRJumpKind jk, Int offsIP)
sewardj2019a972011-03-07 16:04:07 +00003847{
sewardj2019a972011-03-07 16:04:07 +00003848 if (vex_traceflags & VEX_TRACE_VCODE) {
florian8844a632012-04-13 04:04:06 +00003849 vex_printf("\n-- PUT(%d) = ", offsIP);
sewardj2019a972011-03-07 16:04:07 +00003850 ppIRExpr(next);
florian8844a632012-04-13 04:04:06 +00003851 vex_printf("; exit-");
3852 ppIRJumpKind(jk);
sewardj2019a972011-03-07 16:04:07 +00003853 vex_printf("\n");
3854 }
3855
florian8844a632012-04-13 04:04:06 +00003856 s390_amode *guest_IA = s390_amode_for_guest_state(offsIP);
3857
3858 /* Case: boring transfer to known address */
3859 if (next->tag == Iex_Const) {
3860 IRConst *cdst = next->Iex.Const.con;
3861 vassert(cdst->tag == Ico_U64);
3862 if (jk == Ijk_Boring || jk == Ijk_Call) {
3863 /* Boring transfer to known address */
3864 if (env->chaining_allowed) {
3865 /* .. almost always true .. */
3866 /* Skip the event check at the dst if this is a forwards
3867 edge. */
3868 Bool to_fast_entry
3869 = ((Addr64)cdst->Ico.U64) > env->max_ga;
3870 if (0) vex_printf("%s", to_fast_entry ? "X" : ".");
3871 addInstr(env, s390_insn_xdirect(S390_CC_ALWAYS, cdst->Ico.U64,
3872 guest_IA, to_fast_entry));
3873 } else {
3874 /* .. very occasionally .. */
3875 /* We can't use chaining, so ask for an indirect transfer,
3876 as that's the cheapest alternative that is allowable. */
3877 HReg dst = s390_isel_int_expr(env, next);
3878 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA,
3879 Ijk_Boring));
3880 }
3881 return;
3882 }
3883 }
3884
3885 /* Case: call/return (==boring) transfer to any address */
3886 switch (jk) {
3887 case Ijk_Boring:
3888 case Ijk_Ret:
3889 case Ijk_Call: {
3890 HReg dst = s390_isel_int_expr(env, next);
3891 if (env->chaining_allowed) {
3892 addInstr(env, s390_insn_xindir(S390_CC_ALWAYS, dst, guest_IA));
3893 } else {
3894 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA,
3895 Ijk_Boring));
3896 }
3897 return;
3898 }
3899 default:
3900 break;
3901 }
3902
3903 /* Case: some other kind of transfer to any address */
3904 switch (jk) {
florian4e0083e2012-08-26 03:41:56 +00003905 case Ijk_EmFail:
florian4b8efad2012-09-02 18:07:08 +00003906 case Ijk_EmWarn:
florian65b5b3f2012-04-22 02:51:27 +00003907 case Ijk_NoDecode:
florian2d98d892012-04-14 20:35:17 +00003908 case Ijk_TInval:
florian8844a632012-04-13 04:04:06 +00003909 case Ijk_Sys_syscall:
3910 case Ijk_ClientReq:
3911 case Ijk_NoRedir:
3912 case Ijk_Yield:
3913 case Ijk_SigTRAP: {
3914 HReg dst = s390_isel_int_expr(env, next);
3915 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA, jk));
3916 return;
3917 }
3918 default:
3919 break;
3920 }
3921
3922 vpanic("iselNext");
sewardj2019a972011-03-07 16:04:07 +00003923}
3924
3925
3926/*---------------------------------------------------------*/
3927/*--- Insn selector top-level ---*/
3928/*---------------------------------------------------------*/
3929
florianf26994a2012-04-21 03:34:54 +00003930/* Translate an entire SB to s390 code.
3931 Note: archinfo_host is a pointer to a stack-allocated variable.
3932 Do not assign it to a global variable! */
sewardj2019a972011-03-07 16:04:07 +00003933
3934HInstrArray *
3935iselSB_S390(IRSB *bb, VexArch arch_host, VexArchInfo *archinfo_host,
florian8844a632012-04-13 04:04:06 +00003936 VexAbiInfo *vbi, Int offset_host_evcheck_counter,
3937 Int offset_host_evcheck_fail_addr, Bool chaining_allowed,
3938 Bool add_profinc, Addr64 max_ga)
sewardj2019a972011-03-07 16:04:07 +00003939{
3940 UInt i, j;
3941 HReg hreg, hregHI;
3942 ISelEnv *env;
3943 UInt hwcaps_host = archinfo_host->hwcaps;
3944
florianf26994a2012-04-21 03:34:54 +00003945 /* KLUDGE: export hwcaps. */
3946 s390_host_hwcaps = hwcaps_host;
sewardj2019a972011-03-07 16:04:07 +00003947
sewardj2019a972011-03-07 16:04:07 +00003948 /* Do some sanity checks */
sewardj652b56a2011-04-13 15:38:17 +00003949 vassert((VEX_HWCAPS_S390X(hwcaps_host) & ~(VEX_HWCAPS_S390X_ALL)) == 0);
sewardj2019a972011-03-07 16:04:07 +00003950
3951 /* Make up an initial environment to use. */
3952 env = LibVEX_Alloc(sizeof(ISelEnv));
3953 env->vreg_ctr = 0;
3954
3955 /* Set up output code array. */
3956 env->code = newHInstrArray();
3957
3958 /* Copy BB's type env. */
3959 env->type_env = bb->tyenv;
3960
florianad43b3a2012-02-20 15:01:14 +00003961 /* Set up data structures for tracking guest register values. */
florianad43b3a2012-02-20 15:01:14 +00003962 for (i = 0; i < NUM_TRACKED_REGS; ++i) {
3963 env->old_value[i] = 0; /* just something to have a defined value */
3964 env->old_value_valid[i] = False;
3965 }
3966
sewardj2019a972011-03-07 16:04:07 +00003967 /* Make up an IRTemp -> virtual HReg mapping. This doesn't
3968 change as we go along. For some reason types_used has Int type -- but
3969 it should be unsigned. Internally we use an unsigned type; so we
3970 assert it here. */
3971 vassert(bb->tyenv->types_used >= 0);
3972
3973 env->n_vregmap = bb->tyenv->types_used;
3974 env->vregmap = LibVEX_Alloc(env->n_vregmap * sizeof(HReg));
3975 env->vregmapHI = LibVEX_Alloc(env->n_vregmap * sizeof(HReg));
3976
florian2c74d242012-09-12 19:38:42 +00003977 env->previous_bfp_rounding_mode = NULL;
florianc8e4f562012-10-27 16:19:31 +00003978 env->previous_dfp_rounding_mode = NULL;
florian2c74d242012-09-12 19:38:42 +00003979
sewardj2019a972011-03-07 16:04:07 +00003980 /* and finally ... */
3981 env->hwcaps = hwcaps_host;
3982
florian8844a632012-04-13 04:04:06 +00003983 env->max_ga = max_ga;
3984 env->chaining_allowed = chaining_allowed;
3985
sewardj2019a972011-03-07 16:04:07 +00003986 /* For each IR temporary, allocate a suitably-kinded virtual
3987 register. */
3988 j = 0;
3989 for (i = 0; i < env->n_vregmap; i++) {
3990 hregHI = hreg = INVALID_HREG;
3991 switch (bb->tyenv->types[i]) {
3992 case Ity_I1:
3993 case Ity_I8:
3994 case Ity_I16:
3995 case Ity_I32:
3996 hreg = mkHReg(j++, HRcInt64, True);
3997 break;
3998
3999 case Ity_I64:
4000 hreg = mkHReg(j++, HRcInt64, True);
4001 break;
4002
4003 case Ity_I128:
4004 hreg = mkHReg(j++, HRcInt64, True);
4005 hregHI = mkHReg(j++, HRcInt64, True);
4006 break;
4007
4008 case Ity_F32:
4009 case Ity_F64:
floriane38f6412012-12-21 17:32:12 +00004010 case Ity_D32:
florian12390202012-11-10 22:34:14 +00004011 case Ity_D64:
sewardj2019a972011-03-07 16:04:07 +00004012 hreg = mkHReg(j++, HRcFlt64, True);
4013 break;
4014
4015 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00004016 case Ity_D128:
sewardj2019a972011-03-07 16:04:07 +00004017 hreg = mkHReg(j++, HRcFlt64, True);
4018 hregHI = mkHReg(j++, HRcFlt64, True);
4019 break;
4020
4021 case Ity_V128: /* fall through */
4022 default:
4023 ppIRType(bb->tyenv->types[i]);
florian4ebaa772012-12-20 19:44:18 +00004024 vpanic("iselSB_S390: IRTemp type");
sewardj2019a972011-03-07 16:04:07 +00004025 }
4026
4027 env->vregmap[i] = hreg;
4028 env->vregmapHI[i] = hregHI;
4029 }
4030 env->vreg_ctr = j;
4031
florian8844a632012-04-13 04:04:06 +00004032 /* The very first instruction must be an event check. */
4033 s390_amode *counter, *fail_addr;
4034 counter = s390_amode_for_guest_state(offset_host_evcheck_counter);
4035 fail_addr = s390_amode_for_guest_state(offset_host_evcheck_fail_addr);
4036 addInstr(env, s390_insn_evcheck(counter, fail_addr));
4037
4038 /* Possibly a block counter increment (for profiling). At this
4039 point we don't know the address of the counter, so just pretend
4040 it is zero. It will have to be patched later, but before this
4041 translation is used, by a call to LibVEX_patchProfInc. */
4042 if (add_profinc) {
4043 addInstr(env, s390_insn_profinc());
4044 }
4045
sewardj2019a972011-03-07 16:04:07 +00004046 /* Ok, finally we can iterate over the statements. */
4047 for (i = 0; i < bb->stmts_used; i++)
4048 if (bb->stmts[i])
4049 s390_isel_stmt(env, bb->stmts[i]);
4050
florian8844a632012-04-13 04:04:06 +00004051 iselNext(env, bb->next, bb->jumpkind, bb->offsIP);
sewardj2019a972011-03-07 16:04:07 +00004052
4053 /* Record the number of vregs we used. */
4054 env->code->n_vregs = env->vreg_ctr;
4055
4056 return env->code;
4057}
4058
4059/*---------------------------------------------------------------*/
4060/*--- end host_s390_isel.c ---*/
4061/*---------------------------------------------------------------*/