blob: 9322a0515d34a6d4368433e0b91ceb46982776bb [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
Elliott Hughesed398002017-06-21 14:41:24 -070011 Copyright IBM Corp. 2010-2017
12 Copyright (C) 2012-2017 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 *);
florian406ac942014-11-22 20:10:21 +0000130static s390_amode *s390_isel_amode_b12_b20(ISelEnv *, IRExpr *);
sewardj2019a972011-03-07 16:04:07 +0000131static s390_cc_t s390_isel_cc(ISelEnv *, IRExpr *);
132static s390_opnd_RMI s390_isel_int_expr_RMI(ISelEnv *, IRExpr *);
133static void s390_isel_int128_expr(HReg *, HReg *, ISelEnv *, IRExpr *);
134static HReg s390_isel_float_expr(ISelEnv *, IRExpr *);
135static void s390_isel_float128_expr(HReg *, HReg *, ISelEnv *, IRExpr *);
florian12390202012-11-10 22:34:14 +0000136static HReg s390_isel_dfp_expr(ISelEnv *, IRExpr *);
floriane38f6412012-12-21 17:32:12 +0000137static void s390_isel_dfp128_expr(HReg *, HReg *, ISelEnv *, IRExpr *);
sewardj2019a972011-03-07 16:04:07 +0000138
139
florianad43b3a2012-02-20 15:01:14 +0000140static Int
141get_guest_reg(Int offset)
142{
143 switch (offset) {
florian428dfdd2012-03-27 03:09:49 +0000144 case S390X_GUEST_OFFSET(guest_IA): return GUEST_IA;
145 case S390X_GUEST_OFFSET(guest_CC_OP): return GUEST_CC_OP;
146 case S390X_GUEST_OFFSET(guest_CC_DEP1): return GUEST_CC_DEP1;
147 case S390X_GUEST_OFFSET(guest_CC_DEP2): return GUEST_CC_DEP2;
148 case S390X_GUEST_OFFSET(guest_CC_NDEP): return GUEST_CC_NDEP;
149 case S390X_GUEST_OFFSET(guest_SYSNO): return GUEST_SYSNO;
florian7d117ba2012-05-06 03:34:55 +0000150 case S390X_GUEST_OFFSET(guest_counter): return GUEST_COUNTER;
florianad43b3a2012-02-20 15:01:14 +0000151
152 /* Also make sure there is never a partial write to one of
153 these registers. That would complicate matters. */
florian428dfdd2012-03-27 03:09:49 +0000154 case S390X_GUEST_OFFSET(guest_IA)+1 ... S390X_GUEST_OFFSET(guest_IA)+7:
155 case S390X_GUEST_OFFSET(guest_CC_OP)+1 ... S390X_GUEST_OFFSET(guest_CC_OP)+7:
156 case S390X_GUEST_OFFSET(guest_CC_DEP1)+1 ... S390X_GUEST_OFFSET(guest_CC_DEP1)+7:
157 case S390X_GUEST_OFFSET(guest_CC_DEP2)+1 ... S390X_GUEST_OFFSET(guest_CC_DEP2)+7:
158 case S390X_GUEST_OFFSET(guest_CC_NDEP)+1 ... S390X_GUEST_OFFSET(guest_CC_NDEP)+7:
florian7d117ba2012-05-06 03:34:55 +0000159 case S390X_GUEST_OFFSET(guest_SYSNO)+1 ... S390X_GUEST_OFFSET(guest_SYSNO)+7:
160 /* counter is used both as 4-byte and as 8-byte entity */
161 case S390X_GUEST_OFFSET(guest_counter)+1 ... S390X_GUEST_OFFSET(guest_counter)+3:
162 case S390X_GUEST_OFFSET(guest_counter)+5 ... S390X_GUEST_OFFSET(guest_counter)+7:
florianaf50a192012-07-13 14:13:06 +0000163 vpanic("partial update of this guest state register is not allowed");
florianad43b3a2012-02-20 15:01:14 +0000164 break;
165
166 default: break;
167 }
168
169 return GUEST_UNKNOWN;
170}
171
sewardj2019a972011-03-07 16:04:07 +0000172/* Add an instruction */
173static void
174addInstr(ISelEnv *env, s390_insn *insn)
175{
176 addHInstr(env->code, insn);
177
178 if (vex_traceflags & VEX_TRACE_VCODE) {
179 vex_printf("%s\n", s390_insn_as_string(insn));
180 }
181}
182
183
184static __inline__ IRExpr *
185mkU64(ULong value)
186{
187 return IRExpr_Const(IRConst_U64(value));
188}
189
190
191/*---------------------------------------------------------*/
192/*--- Registers ---*/
193/*---------------------------------------------------------*/
194
195/* Return the virtual register to which a given IRTemp is mapped. */
196static HReg
197lookupIRTemp(ISelEnv *env, IRTemp tmp)
198{
199 vassert(tmp < env->n_vregmap);
florian79efdc62013-02-11 00:47:35 +0000200 vassert(! hregIsInvalid(env->vregmap[tmp]));
sewardj2019a972011-03-07 16:04:07 +0000201
202 return env->vregmap[tmp];
203}
204
205
206/* Return the two virtual registers to which the IRTemp is mapped. */
207static void
208lookupIRTemp128(HReg *hi, HReg *lo, ISelEnv *env, IRTemp tmp)
209{
210 vassert(tmp < env->n_vregmap);
florian79efdc62013-02-11 00:47:35 +0000211 vassert(! hregIsInvalid(env->vregmapHI[tmp]));
sewardj2019a972011-03-07 16:04:07 +0000212
213 *lo = env->vregmap[tmp];
214 *hi = env->vregmapHI[tmp];
215}
216
217
sewardja5b50222015-03-26 07:18:32 +0000218/* Allocate a new virtual integer register */
219static __inline__ HReg
220mkVRegI(UInt ix)
221{
222 return mkHReg(/*virtual*/True, HRcInt64, /*encoding*/0, ix);
223}
224
225static __inline__ HReg
sewardj2019a972011-03-07 16:04:07 +0000226newVRegI(ISelEnv *env)
227{
sewardja5b50222015-03-26 07:18:32 +0000228 return mkVRegI(env->vreg_ctr++);
sewardj2019a972011-03-07 16:04:07 +0000229}
230
231
sewardja5b50222015-03-26 07:18:32 +0000232/* Allocate a new virtual floating point register */
233static __inline__ HReg
234mkVRegF(UInt ix)
235{
236 return mkHReg(/*virtual*/True, HRcFlt64, /*encoding*/0, ix);
237}
238
239static __inline__ HReg
sewardj2019a972011-03-07 16:04:07 +0000240newVRegF(ISelEnv *env)
241{
sewardja5b50222015-03-26 07:18:32 +0000242 return mkVRegF(env->vreg_ctr++);
sewardj2019a972011-03-07 16:04:07 +0000243}
244
245
246/* Construct a non-virtual general purpose register */
247static __inline__ HReg
florian297b6062012-05-08 20:16:17 +0000248make_gpr(UInt regno)
sewardj2019a972011-03-07 16:04:07 +0000249{
sewardja5b50222015-03-26 07:18:32 +0000250 return s390_hreg_gpr(regno);
sewardj2019a972011-03-07 16:04:07 +0000251}
252
253
254/* Construct a non-virtual floating point register */
255static __inline__ HReg
256make_fpr(UInt regno)
257{
sewardja5b50222015-03-26 07:18:32 +0000258 return s390_hreg_fpr(regno);
sewardj2019a972011-03-07 16:04:07 +0000259}
260
261
262/*---------------------------------------------------------*/
263/*--- Amode ---*/
264/*---------------------------------------------------------*/
265
266static __inline__ Bool
267ulong_fits_unsigned_12bit(ULong val)
268{
269 return (val & 0xFFFu) == val;
270}
271
272
273static __inline__ Bool
274ulong_fits_signed_20bit(ULong val)
275{
florian8cf66372015-02-09 23:21:07 +0000276 ULong v = val & 0xFFFFFu;
sewardj2019a972011-03-07 16:04:07 +0000277
florian8cf66372015-02-09 23:21:07 +0000278 v = (Long)(v << 44) >> 44; /* sign extend */
sewardj2019a972011-03-07 16:04:07 +0000279
florian8cf66372015-02-09 23:21:07 +0000280 return val == v;
sewardj2019a972011-03-07 16:04:07 +0000281}
282
283
florianad43b3a2012-02-20 15:01:14 +0000284static __inline__ Bool
285ulong_fits_signed_8bit(ULong val)
286{
florian8cf66372015-02-09 23:21:07 +0000287 ULong v = val & 0xFFu;
florianad43b3a2012-02-20 15:01:14 +0000288
florian8cf66372015-02-09 23:21:07 +0000289 v = (Long)(v << 56) >> 56; /* sign extend */
florianad43b3a2012-02-20 15:01:14 +0000290
florian8cf66372015-02-09 23:21:07 +0000291 return val == v;
florianad43b3a2012-02-20 15:01:14 +0000292}
293
sewardj2019a972011-03-07 16:04:07 +0000294/* EXPR is an expression that is used as an address. Return an s390_amode
florian406ac942014-11-22 20:10:21 +0000295 for it. If select_b12_b20_only is true the returned amode must be either
296 S390_AMODE_B12 or S390_AMODE_B20. */
sewardj2019a972011-03-07 16:04:07 +0000297static s390_amode *
florian406ac942014-11-22 20:10:21 +0000298s390_isel_amode_wrk(ISelEnv *env, IRExpr *expr,
299 Bool select_b12_b20_only __attribute__((unused)))
sewardj2019a972011-03-07 16:04:07 +0000300{
301 if (expr->tag == Iex_Binop && expr->Iex.Binop.op == Iop_Add64) {
302 IRExpr *arg1 = expr->Iex.Binop.arg1;
303 IRExpr *arg2 = expr->Iex.Binop.arg2;
304
305 /* Move constant into right subtree */
306 if (arg1->tag == Iex_Const) {
307 IRExpr *tmp;
308 tmp = arg1;
309 arg1 = arg2;
310 arg2 = tmp;
311 }
312
313 /* r + constant: Check for b12 first, then b20 */
314 if (arg2->tag == Iex_Const && arg2->Iex.Const.con->tag == Ico_U64) {
315 ULong value = arg2->Iex.Const.con->Ico.U64;
316
317 if (ulong_fits_unsigned_12bit(value)) {
318 return s390_amode_b12((Int)value, s390_isel_int_expr(env, arg1));
319 }
floriandc6e7472014-12-08 14:01:33 +0000320 if (ulong_fits_signed_20bit(value)) {
sewardj2019a972011-03-07 16:04:07 +0000321 return s390_amode_b20((Int)value, s390_isel_int_expr(env, arg1));
322 }
323 }
324 }
325
326 /* Doesn't match anything in particular. Generate it into
327 a register and use that. */
328 return s390_amode_b12(0, s390_isel_int_expr(env, expr));
329}
330
331
332static s390_amode *
333s390_isel_amode(ISelEnv *env, IRExpr *expr)
334{
florian35da8612011-06-25 02:25:41 +0000335 s390_amode *am;
sewardj2019a972011-03-07 16:04:07 +0000336
337 /* Address computation should yield a 64-bit value */
338 vassert(typeOfIRExpr(env->type_env, expr) == Ity_I64);
339
florian406ac942014-11-22 20:10:21 +0000340 am = s390_isel_amode_wrk(env, expr, /* B12, B20 only */ False);
sewardj2019a972011-03-07 16:04:07 +0000341
342 /* Check post-condition */
343 vassert(s390_amode_is_sane(am));
344
345 return am;
346}
347
348
florian406ac942014-11-22 20:10:21 +0000349/* Sometimes we must compile an expression into an amode that is either
350 S390_AMODE_B12 or S390_AMODE_B20. An example is the compare-and-swap
351 opcode. These opcodes do not have a variant hat accepts an addressing
352 mode with an index register.
353 Now, in theory we could, when emitting the compare-and-swap insn,
354 hack a, say, BX12 amode into a B12 amode like so:
355
356 r0 = b # save away base register
357 b = b + x # add index register to base register
358 cas(b,d,...) # emit compare-and-swap using b12 amode
359 b = r0 # restore base register
360
361 Unfortunately, emitting the compare-and-swap insn already utilises r0
362 under the covers, so the trick above is off limits, sadly. */
363static s390_amode *
364s390_isel_amode_b12_b20(ISelEnv *env, IRExpr *expr)
365{
366 s390_amode *am;
367
368 /* Address computation should yield a 64-bit value */
369 vassert(typeOfIRExpr(env->type_env, expr) == Ity_I64);
370
371 am = s390_isel_amode_wrk(env, expr, /* B12, B20 only */ True);
372
373 /* Check post-condition */
374 vassert(s390_amode_is_sane(am) &&
375 (am->tag == S390_AMODE_B12 || am->tag == S390_AMODE_B20));
376
377 return am;
378}
379
380
sewardj2019a972011-03-07 16:04:07 +0000381/*---------------------------------------------------------*/
382/*--- Helper functions ---*/
383/*---------------------------------------------------------*/
384
385/* Constants and memory accesses should be right operands */
386#define order_commutative_operands(left, right) \
387 do { \
388 if (left->tag == Iex_Const || left->tag == Iex_Load || \
389 left->tag == Iex_Get) { \
390 IRExpr *tmp; \
391 tmp = left; \
392 left = right; \
393 right = tmp; \
394 } \
395 } while (0)
396
397
398/* Copy an RMI operand to the DST register */
399static s390_insn *
400s390_opnd_copy(UChar size, HReg dst, s390_opnd_RMI opnd)
401{
402 switch (opnd.tag) {
403 case S390_OPND_AMODE:
404 return s390_insn_load(size, dst, opnd.variant.am);
405
406 case S390_OPND_REG:
407 return s390_insn_move(size, dst, opnd.variant.reg);
408
409 case S390_OPND_IMMEDIATE:
410 return s390_insn_load_immediate(size, dst, opnd.variant.imm);
411
412 default:
413 vpanic("s390_opnd_copy");
414 }
415}
416
417
418/* Construct a RMI operand for a register */
419static __inline__ s390_opnd_RMI
420s390_opnd_reg(HReg reg)
421{
422 s390_opnd_RMI opnd;
423
424 opnd.tag = S390_OPND_REG;
425 opnd.variant.reg = reg;
426
427 return opnd;
428}
429
430
431/* Construct a RMI operand for an immediate constant */
432static __inline__ s390_opnd_RMI
433s390_opnd_imm(ULong value)
434{
435 s390_opnd_RMI opnd;
436
437 opnd.tag = S390_OPND_IMMEDIATE;
438 opnd.variant.imm = value;
439
440 return opnd;
441}
442
443
florianffbd84d2012-12-09 02:06:29 +0000444/* Return 1, if EXPR represents the constant 0 */
445static Bool
sewardj2019a972011-03-07 16:04:07 +0000446s390_expr_is_const_zero(IRExpr *expr)
447{
448 ULong value;
449
450 if (expr->tag == Iex_Const) {
451 switch (expr->Iex.Const.con->tag) {
452 case Ico_U1: value = expr->Iex.Const.con->Ico.U1; break;
453 case Ico_U8: value = expr->Iex.Const.con->Ico.U8; break;
454 case Ico_U16: value = expr->Iex.Const.con->Ico.U16; break;
455 case Ico_U32: value = expr->Iex.Const.con->Ico.U32; break;
456 case Ico_U64: value = expr->Iex.Const.con->Ico.U64; break;
457 default:
458 vpanic("s390_expr_is_const_zero");
459 }
460 return value == 0;
461 }
462
463 return 0;
464}
465
466
florianb93348d2012-12-27 00:59:43 +0000467/* Return the value of CON as a sign-exteded ULong value */
468static ULong
469get_const_value_as_ulong(const IRConst *con)
470{
florian8cf66372015-02-09 23:21:07 +0000471 ULong value;
florianb93348d2012-12-27 00:59:43 +0000472
473 switch (con->tag) {
florian8cf66372015-02-09 23:21:07 +0000474 case Ico_U1: value = con->Ico.U1; return ((Long)(value << 63) >> 63);
475 case Ico_U8: value = con->Ico.U8; return ((Long)(value << 56) >> 56);
476 case Ico_U16: value = con->Ico.U16; return ((Long)(value << 48) >> 48);
477 case Ico_U32: value = con->Ico.U32; return ((Long)(value << 32) >> 32);
florianb93348d2012-12-27 00:59:43 +0000478 case Ico_U64: return con->Ico.U64;
479 default:
480 vpanic("get_const_value_as_ulong");
481 }
482}
483
484
sewardj2019a972011-03-07 16:04:07 +0000485/* Call a helper (clean or dirty)
486 Arguments must satisfy the following conditions:
floriane0654362012-05-09 13:31:09 +0000487
sewardj2019a972011-03-07 16:04:07 +0000488 (a) they are expressions yielding an integer result
489 (b) there can be no more than S390_NUM_GPRPARMS arguments
floriane0654362012-05-09 13:31:09 +0000490
491 guard is a Ity_Bit expression indicating whether or not the
492 call happens. If guard == NULL, the call is unconditional.
florian52af7bc2012-05-12 03:44:49 +0000493
494 Calling the helper function proceeds as follows:
495
496 (1) The helper arguments are evaluated and their value stored in
497 virtual registers.
498 (2) The condition code is evaluated
499 (3) The argument values are copied from the virtual registers to the
500 registers mandated by the ABI.
501 (4) Call the helper function.
502
503 This is not the most efficient way as step 3 generates register-to-register
504 moves. But it is the least fragile way as the only hidden dependency here
505 is that register-to-register moves (step 3) must not clobber the condition
506 code. Other schemes (e.g. VEX r2326) that attempt to avoid the register-
507 to-register add more such dependencies. Not good. Besides, it's the job
508 of the register allocator to throw out those reg-to-reg moves.
sewardj2019a972011-03-07 16:04:07 +0000509*/
510static void
sewardj74142b82013-08-08 10:28:59 +0000511doHelperCall(/*OUT*/UInt *stackAdjustAfterCall,
512 /*OUT*/RetLoc *retloc,
513 ISelEnv *env, IRExpr *guard,
514 IRCallee *callee, IRType retTy, IRExpr **args)
sewardj2019a972011-03-07 16:04:07 +0000515{
florian52af7bc2012-05-12 03:44:49 +0000516 UInt n_args, i, argreg, size;
florian93a09742015-01-07 20:14:48 +0000517 Addr64 target;
sewardj2019a972011-03-07 16:04:07 +0000518 HReg tmpregs[S390_NUM_GPRPARMS];
519 s390_cc_t cc;
520
sewardj74142b82013-08-08 10:28:59 +0000521 /* Set default returns. We'll update them later if needed. */
522 *stackAdjustAfterCall = 0;
523 *retloc = mk_RetLoc_INVALID();
524
525 /* The return type can be I{64,32,16,8} or V{128,256}. In the
526 latter two cases, it is expected that |args| will contain the
florian608e5602014-11-21 21:40:45 +0000527 special node IRExpr_VECRET(). For s390, however, V128 and V256 return
528 values do not occur as we generally do not support vector types.
sewardj74142b82013-08-08 10:28:59 +0000529
Elliott Hughesed398002017-06-21 14:41:24 -0700530 |args| may also contain IRExpr_GSPTR(), in which case the value
sewardj74142b82013-08-08 10:28:59 +0000531 in the guest state pointer register is passed as the
532 corresponding argument.
533
534 These are used for cross-checking that IR-level constraints on
Elliott Hughesed398002017-06-21 14:41:24 -0700535 the use of IRExpr_VECRET() and IRExpr_GSPTR() are observed. */
sewardj74142b82013-08-08 10:28:59 +0000536 UInt nVECRETs = 0;
Elliott Hughesed398002017-06-21 14:41:24 -0700537 UInt nGSPTRs = 0;
sewardj74142b82013-08-08 10:28:59 +0000538
sewardj2019a972011-03-07 16:04:07 +0000539 n_args = 0;
540 for (i = 0; args[i]; i++)
541 ++n_args;
542
sewardj74142b82013-08-08 10:28:59 +0000543 if (n_args > S390_NUM_GPRPARMS) {
sewardj2019a972011-03-07 16:04:07 +0000544 vpanic("doHelperCall: too many arguments");
545 }
546
florian11b8ee82012-08-06 13:35:33 +0000547 /* All arguments must have Ity_I64. For two reasons:
548 (1) We do not handle floating point arguments.
549 (2) The ABI requires that integer values are sign- or zero-extended
550 to 64 bit.
551 */
552 Int arg_errors = 0;
553 for (i = 0; i < n_args; ++i) {
florian90419562013-08-15 20:54:52 +0000554 if (UNLIKELY(args[i]->tag == Iex_VECRET)) {
sewardj74142b82013-08-08 10:28:59 +0000555 nVECRETs++;
Elliott Hughesed398002017-06-21 14:41:24 -0700556 } else if (UNLIKELY(args[i]->tag == Iex_GSPTR)) {
557 nGSPTRs++;
sewardj74142b82013-08-08 10:28:59 +0000558 } else {
559 IRType type = typeOfIRExpr(env->type_env, args[i]);
560 if (type != Ity_I64) {
561 ++arg_errors;
florianb1737742015-08-03 16:03:13 +0000562 vex_printf("calling %s: argument #%u has type ", callee->name, i);
sewardj74142b82013-08-08 10:28:59 +0000563 ppIRType(type);
564 vex_printf("; Ity_I64 is required\n");
565 }
florian11b8ee82012-08-06 13:35:33 +0000566 }
567 }
568
569 if (arg_errors)
570 vpanic("cannot continue due to errors in argument passing");
571
florian608e5602014-11-21 21:40:45 +0000572 /* If these fail, the IR is ill-formed */
Elliott Hughesed398002017-06-21 14:41:24 -0700573 vassert(nGSPTRs == 0 || nGSPTRs == 1);
florian608e5602014-11-21 21:40:45 +0000574 vassert(nVECRETs == 0);
florian52af7bc2012-05-12 03:44:49 +0000575
sewardj74142b82013-08-08 10:28:59 +0000576 argreg = 0;
577
florian52af7bc2012-05-12 03:44:49 +0000578 /* Compute the function arguments into a temporary register each */
579 for (i = 0; i < n_args; i++) {
sewardj74142b82013-08-08 10:28:59 +0000580 IRExpr *arg = args[i];
Elliott Hughesed398002017-06-21 14:41:24 -0700581 if (UNLIKELY(arg->tag == Iex_GSPTR)) {
sewardj74142b82013-08-08 10:28:59 +0000582 /* If we need the guest state pointer put it in a temporary arg reg */
583 tmpregs[argreg] = newVRegI(env);
584 addInstr(env, s390_insn_move(sizeof(ULong), tmpregs[argreg],
585 s390_hreg_guest_state_pointer()));
586 } else {
587 tmpregs[argreg] = s390_isel_int_expr(env, args[i]);
588 }
florian52af7bc2012-05-12 03:44:49 +0000589 argreg++;
590 }
591
sewardj2019a972011-03-07 16:04:07 +0000592 /* Compute the condition */
593 cc = S390_CC_ALWAYS;
594 if (guard) {
595 if (guard->tag == Iex_Const
596 && guard->Iex.Const.con->tag == Ico_U1
597 && guard->Iex.Const.con->Ico.U1 == True) {
598 /* unconditional -- do nothing */
599 } else {
600 cc = s390_isel_cc(env, guard);
601 }
602 }
603
florian52af7bc2012-05-12 03:44:49 +0000604 /* Move the args to the final register. It is paramount, that the
605 code to move the registers does not clobber the condition code ! */
floriane0654362012-05-09 13:31:09 +0000606 for (i = 0; i < argreg; i++) {
florian52af7bc2012-05-12 03:44:49 +0000607 HReg finalreg;
608
609 finalreg = make_gpr(s390_gprno_from_arg_index(i));
610 size = sizeofIRType(Ity_I64);
611 addInstr(env, s390_insn_move(size, finalreg, tmpregs[i]));
sewardj2019a972011-03-07 16:04:07 +0000612 }
613
florian93a09742015-01-07 20:14:48 +0000614 target = (Addr)callee->addr;
sewardj2019a972011-03-07 16:04:07 +0000615
sewardj74142b82013-08-08 10:28:59 +0000616 /* Do final checks, set the return values, and generate the call
617 instruction proper. */
618 vassert(*stackAdjustAfterCall == 0);
619 vassert(is_RetLoc_INVALID(*retloc));
620 switch (retTy) {
621 case Ity_INVALID:
622 /* Function doesn't return a value. */
623 *retloc = mk_RetLoc_simple(RLPri_None);
624 break;
625 case Ity_I64: case Ity_I32: case Ity_I16: case Ity_I8:
626 *retloc = mk_RetLoc_simple(RLPri_Int);
627 break;
sewardj74142b82013-08-08 10:28:59 +0000628 default:
629 /* IR can denote other possible return types, but we don't
630 handle those here. */
florian608e5602014-11-21 21:40:45 +0000631 vex_printf("calling %s: return type is ", callee->name);
632 ppIRType(retTy);
633 vex_printf("; an integer type is required\n");
sewardj74142b82013-08-08 10:28:59 +0000634 vassert(0);
635 }
636
sewardj2019a972011-03-07 16:04:07 +0000637 /* Finally, the call itself. */
florian93a09742015-01-07 20:14:48 +0000638 addInstr(env, s390_insn_helper_call(cc, target, n_args,
sewardj74142b82013-08-08 10:28:59 +0000639 callee->name, *retloc));
sewardj2019a972011-03-07 16:04:07 +0000640}
641
642
florian2c74d242012-09-12 19:38:42 +0000643/*---------------------------------------------------------*/
644/*--- BFP helper functions ---*/
645/*---------------------------------------------------------*/
646
647/* Set the BFP rounding mode in the FPC. This function is called for
648 all non-conversion BFP instructions as those will always get the
649 rounding mode from the FPC. */
650static void
651set_bfp_rounding_mode_in_fpc(ISelEnv *env, IRExpr *irrm)
sewardj2019a972011-03-07 16:04:07 +0000652{
florian2c74d242012-09-12 19:38:42 +0000653 vassert(typeOfIRExpr(env->type_env, irrm) == Ity_I32);
654
655 /* Do we need to do anything? */
656 if (env->previous_bfp_rounding_mode &&
657 env->previous_bfp_rounding_mode->tag == Iex_RdTmp &&
658 irrm->tag == Iex_RdTmp &&
659 env->previous_bfp_rounding_mode->Iex.RdTmp.tmp == irrm->Iex.RdTmp.tmp) {
660 /* No - new mode is identical to previous mode. */
661 return;
662 }
663
664 /* No luck - we better set it, and remember what we set it to. */
665 env->previous_bfp_rounding_mode = irrm;
666
667 /* The incoming rounding mode is in VEX IR encoding. Need to change
668 to s390.
669
670 rounding mode | s390 | IR
671 -------------------------
672 to nearest | 00 | 00
673 to zero | 01 | 11
674 to +infinity | 10 | 10
675 to -infinity | 11 | 01
676
677 So: s390 = (4 - IR) & 3
678 */
679 HReg ir = s390_isel_int_expr(env, irrm);
680
681 HReg mode = newVRegI(env);
682
683 addInstr(env, s390_insn_load_immediate(4, mode, 4));
684 addInstr(env, s390_insn_alu(4, S390_ALU_SUB, mode, s390_opnd_reg(ir)));
685 addInstr(env, s390_insn_alu(4, S390_ALU_AND, mode, s390_opnd_imm(3)));
686
florian125e20d2012-10-07 15:42:37 +0000687 addInstr(env, s390_insn_set_fpc_bfprm(4, mode));
florian2c74d242012-09-12 19:38:42 +0000688}
689
690
691/* This function is invoked for insns that support a specification of
692 a rounding mode in the insn itself. In that case there is no need to
693 stick the rounding mode into the FPC -- a good thing. However, the
694 rounding mode must be known. */
florian125e20d2012-10-07 15:42:37 +0000695static s390_bfp_round_t
florian2c74d242012-09-12 19:38:42 +0000696get_bfp_rounding_mode(ISelEnv *env, IRExpr *irrm)
697{
698 if (irrm->tag == Iex_Const) { /* rounding mode is known */
699 vassert(irrm->Iex.Const.con->tag == Ico_U32);
700 IRRoundingMode mode = irrm->Iex.Const.con->Ico.U32;
sewardj2019a972011-03-07 16:04:07 +0000701
702 switch (mode) {
florian125e20d2012-10-07 15:42:37 +0000703 case Irrm_NEAREST: return S390_BFP_ROUND_NEAREST_EVEN;
704 case Irrm_ZERO: return S390_BFP_ROUND_ZERO;
705 case Irrm_PosINF: return S390_BFP_ROUND_POSINF;
706 case Irrm_NegINF: return S390_BFP_ROUND_NEGINF;
florian2c74d242012-09-12 19:38:42 +0000707 default:
708 vpanic("get_bfp_rounding_mode");
sewardj2019a972011-03-07 16:04:07 +0000709 }
710 }
711
florian2c74d242012-09-12 19:38:42 +0000712 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +0000713 return S390_BFP_ROUND_PER_FPC;
sewardj2019a972011-03-07 16:04:07 +0000714}
715
716
florianc8e4f562012-10-27 16:19:31 +0000717/*---------------------------------------------------------*/
718/*--- DFP helper functions ---*/
719/*---------------------------------------------------------*/
720
721/* Set the DFP rounding mode in the FPC. This function is called for
722 all non-conversion DFP instructions as those will always get the
723 rounding mode from the FPC. */
florianc8e4f562012-10-27 16:19:31 +0000724static void
725set_dfp_rounding_mode_in_fpc(ISelEnv *env, IRExpr *irrm)
726{
727 vassert(typeOfIRExpr(env->type_env, irrm) == Ity_I32);
728
729 /* Do we need to do anything? */
730 if (env->previous_dfp_rounding_mode &&
731 env->previous_dfp_rounding_mode->tag == Iex_RdTmp &&
732 irrm->tag == Iex_RdTmp &&
733 env->previous_dfp_rounding_mode->Iex.RdTmp.tmp == irrm->Iex.RdTmp.tmp) {
734 /* No - new mode is identical to previous mode. */
735 return;
736 }
737
738 /* No luck - we better set it, and remember what we set it to. */
739 env->previous_dfp_rounding_mode = irrm;
740
741 /* The incoming rounding mode is in VEX IR encoding. Need to change
742 to s390.
743
744 rounding mode | S390 | IR
745 -----------------------------------------------
746 to nearest, ties to even | 000 | 000
747 to zero | 001 | 011
748 to +infinity | 010 | 010
749 to -infinity | 011 | 001
750 to nearest, ties away from 0 | 100 | 100
751 to nearest, ties toward 0 | 101 | 111
752 to away from 0 | 110 | 110
753 to prepare for shorter precision | 111 | 101
754
755 So: s390 = (IR ^ ((IR << 1) & 2))
756 */
757 HReg ir = s390_isel_int_expr(env, irrm);
758
759 HReg mode = newVRegI(env);
760
761 addInstr(env, s390_insn_move(4, mode, ir));
762 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, mode, s390_opnd_imm(1)));
763 addInstr(env, s390_insn_alu(4, S390_ALU_AND, mode, s390_opnd_imm(2)));
764 addInstr(env, s390_insn_alu(4, S390_ALU_XOR, mode, s390_opnd_reg(ir)));
765
766 addInstr(env, s390_insn_set_fpc_dfprm(4, mode));
767}
768
769
770/* This function is invoked for insns that support a specification of
771 a rounding mode in the insn itself. In that case there is no need to
772 stick the rounding mode into the FPC -- a good thing. However, the
773 rounding mode must be known.
florianff9000d2013-02-08 20:22:03 +0000774
florian79e5a482013-06-06 19:12:46 +0000775 When mapping an Irrm_XYZ value to an S390_DFP_ROUND_ value there is
776 often a choice. For instance, Irrm_ZERO could be mapped to either
florianff9000d2013-02-08 20:22:03 +0000777 S390_DFP_ROUND_ZERO_5 or S390_DFP_ROUND_ZERO_9. The difference between
778 those two is that with S390_DFP_ROUND_ZERO_9 the recognition of the
779 quantum exception is suppressed whereas with S390_DFP_ROUND_ZERO_5 it
780 is not. As the quantum exception is not modelled we can choose either
781 value. The choice is to use S390_DFP_ROUND_.. values in the range [8:15],
782 because values in the range [1:7] have unpredictable rounding behaviour
783 when the floating point exception facility is not installed.
florianc8e4f562012-10-27 16:19:31 +0000784
785 Translation table of
786 s390 DFP rounding mode to IRRoundingMode to s390 DFP rounding mode
787
florian79e5a482013-06-06 19:12:46 +0000788 s390(S390_DFP_ROUND_) | IR(Irrm_) | s390(S390_DFP_ROUND_)
florianc8e4f562012-10-27 16:19:31 +0000789 --------------------------------------------------------------------
florianff9000d2013-02-08 20:22:03 +0000790 NEAREST_TIE_AWAY_0_1 | NEAREST_TIE_AWAY_0 | NEAREST_TIE_AWAY_0_12
florianc8e4f562012-10-27 16:19:31 +0000791 NEAREST_TIE_AWAY_0_12 | " | "
florianff9000d2013-02-08 20:22:03 +0000792 PREPARE_SHORT_3 | PREPARE_SHORTER | PREPARE_SHORT_15
florianc8e4f562012-10-27 16:19:31 +0000793 PREPARE_SHORT_15 | " | "
florianff9000d2013-02-08 20:22:03 +0000794 NEAREST_EVEN_4 | NEAREST | NEAREST_EVEN_8
florianc8e4f562012-10-27 16:19:31 +0000795 NEAREST_EVEN_8 | " | "
florianff9000d2013-02-08 20:22:03 +0000796 ZERO_5 | ZERO | ZERO_9
florianc8e4f562012-10-27 16:19:31 +0000797 ZERO_9 | " | "
florianff9000d2013-02-08 20:22:03 +0000798 POSINF_6 | PosINF | POSINF_10
florianc8e4f562012-10-27 16:19:31 +0000799 POSINF_10 | " | "
florianff9000d2013-02-08 20:22:03 +0000800 NEGINF_7 | NegINF | NEGINF_11
florianc8e4f562012-10-27 16:19:31 +0000801 NEGINF_11 | " | "
802 NEAREST_TIE_TOWARD_0 | NEAREST_TIE_TOWARD_0| NEAREST_TIE_TOWARD_0
803 AWAY_0 | AWAY_FROM_ZERO | AWAY_0
804*/
805static s390_dfp_round_t
806get_dfp_rounding_mode(ISelEnv *env, IRExpr *irrm)
807{
808 if (irrm->tag == Iex_Const) { /* rounding mode is known */
809 vassert(irrm->Iex.Const.con->tag == Ico_U32);
florian79e5a482013-06-06 19:12:46 +0000810 IRRoundingMode mode = irrm->Iex.Const.con->Ico.U32;
florianc8e4f562012-10-27 16:19:31 +0000811
812 switch (mode) {
florian79e5a482013-06-06 19:12:46 +0000813 case Irrm_NEAREST:
florianff9000d2013-02-08 20:22:03 +0000814 return S390_DFP_ROUND_NEAREST_EVEN_8;
florian79e5a482013-06-06 19:12:46 +0000815 case Irrm_NegINF:
florianff9000d2013-02-08 20:22:03 +0000816 return S390_DFP_ROUND_NEGINF_11;
florian79e5a482013-06-06 19:12:46 +0000817 case Irrm_PosINF:
florianff9000d2013-02-08 20:22:03 +0000818 return S390_DFP_ROUND_POSINF_10;
florian79e5a482013-06-06 19:12:46 +0000819 case Irrm_ZERO:
florianff9000d2013-02-08 20:22:03 +0000820 return S390_DFP_ROUND_ZERO_9;
florian79e5a482013-06-06 19:12:46 +0000821 case Irrm_NEAREST_TIE_AWAY_0:
florianff9000d2013-02-08 20:22:03 +0000822 return S390_DFP_ROUND_NEAREST_TIE_AWAY_0_12;
florian79e5a482013-06-06 19:12:46 +0000823 case Irrm_PREPARE_SHORTER:
florianff9000d2013-02-08 20:22:03 +0000824 return S390_DFP_ROUND_PREPARE_SHORT_15;
florian79e5a482013-06-06 19:12:46 +0000825 case Irrm_AWAY_FROM_ZERO:
florianc8e4f562012-10-27 16:19:31 +0000826 return S390_DFP_ROUND_AWAY_0;
florian79e5a482013-06-06 19:12:46 +0000827 case Irrm_NEAREST_TIE_TOWARD_0:
florianc8e4f562012-10-27 16:19:31 +0000828 return S390_DFP_ROUND_NEAREST_TIE_TOWARD_0;
829 default:
830 vpanic("get_dfp_rounding_mode");
831 }
832 }
833
834 set_dfp_rounding_mode_in_fpc(env, irrm);
835 return S390_DFP_ROUND_PER_FPC_0;
836}
florianc8e4f562012-10-27 16:19:31 +0000837
florian2d3d87f2012-12-21 21:05:17 +0000838
839/*---------------------------------------------------------*/
840/*--- Condition code helper functions ---*/
841/*---------------------------------------------------------*/
842
sewardj2019a972011-03-07 16:04:07 +0000843/* CC_S390 holds the condition code in s390 encoding. Convert it to
florian2d3d87f2012-12-21 21:05:17 +0000844 VEX encoding (IRCmpFResult)
sewardj2019a972011-03-07 16:04:07 +0000845
846 s390 VEX b6 b2 b0 cc.1 cc.0
847 0 0x40 EQ 1 0 0 0 0
848 1 0x01 LT 0 0 1 0 1
849 2 0x00 GT 0 0 0 1 0
850 3 0x45 Unordered 1 1 1 1 1
851
852 b0 = cc.0
853 b2 = cc.0 & cc.1
854 b6 = ~(cc.0 ^ cc.1) // ((cc.0 - cc.1) + 0x1 ) & 0x1
855
856 VEX = b0 | (b2 << 2) | (b6 << 6);
857*/
858static HReg
florian2d3d87f2012-12-21 21:05:17 +0000859convert_s390_to_vex_bfpcc(ISelEnv *env, HReg cc_s390)
sewardj2019a972011-03-07 16:04:07 +0000860{
861 HReg cc0, cc1, b2, b6, cc_vex;
862
863 cc0 = newVRegI(env);
864 addInstr(env, s390_insn_move(4, cc0, cc_s390));
865 addInstr(env, s390_insn_alu(4, S390_ALU_AND, cc0, s390_opnd_imm(1)));
866
867 cc1 = newVRegI(env);
868 addInstr(env, s390_insn_move(4, cc1, cc_s390));
869 addInstr(env, s390_insn_alu(4, S390_ALU_RSH, cc1, s390_opnd_imm(1)));
870
871 b2 = newVRegI(env);
872 addInstr(env, s390_insn_move(4, b2, cc0));
873 addInstr(env, s390_insn_alu(4, S390_ALU_AND, b2, s390_opnd_reg(cc1)));
874 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, b2, s390_opnd_imm(2)));
875
876 b6 = newVRegI(env);
877 addInstr(env, s390_insn_move(4, b6, cc0));
878 addInstr(env, s390_insn_alu(4, S390_ALU_SUB, b6, s390_opnd_reg(cc1)));
879 addInstr(env, s390_insn_alu(4, S390_ALU_ADD, b6, s390_opnd_imm(1)));
880 addInstr(env, s390_insn_alu(4, S390_ALU_AND, b6, s390_opnd_imm(1)));
881 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, b6, s390_opnd_imm(6)));
882
883 cc_vex = newVRegI(env);
884 addInstr(env, s390_insn_move(4, cc_vex, cc0));
885 addInstr(env, s390_insn_alu(4, S390_ALU_OR, cc_vex, s390_opnd_reg(b2)));
886 addInstr(env, s390_insn_alu(4, S390_ALU_OR, cc_vex, s390_opnd_reg(b6)));
887
888 return cc_vex;
889}
890
florian2d3d87f2012-12-21 21:05:17 +0000891/* CC_S390 holds the condition code in s390 encoding. Convert it to
892 VEX encoding (IRCmpDResult) */
893static HReg
894convert_s390_to_vex_dfpcc(ISelEnv *env, HReg cc_s390)
895{
896 /* The encodings for IRCmpFResult and IRCmpDResult are the same/ */
897 return convert_s390_to_vex_bfpcc(env, cc_s390);
898}
899
sewardj2019a972011-03-07 16:04:07 +0000900
901/*---------------------------------------------------------*/
902/*--- ISEL: Integer expressions (128 bit) ---*/
903/*---------------------------------------------------------*/
904static void
905s390_isel_int128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
906 IRExpr *expr)
907{
908 IRType ty = typeOfIRExpr(env->type_env, expr);
909
910 vassert(ty == Ity_I128);
911
912 /* No need to consider the following
913 - 128-bit constants (they do not exist in VEX)
914 - 128-bit loads from memory (will not be generated)
915 */
916
917 /* Read 128-bit IRTemp */
918 if (expr->tag == Iex_RdTmp) {
919 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
920 return;
921 }
922
923 if (expr->tag == Iex_Binop) {
924 IRExpr *arg1 = expr->Iex.Binop.arg1;
925 IRExpr *arg2 = expr->Iex.Binop.arg2;
926 Bool is_signed_multiply, is_signed_divide;
927
928 switch (expr->Iex.Binop.op) {
929 case Iop_MullU64:
930 is_signed_multiply = False;
931 goto do_multiply64;
932
933 case Iop_MullS64:
934 is_signed_multiply = True;
935 goto do_multiply64;
936
937 case Iop_DivModU128to64:
938 is_signed_divide = False;
939 goto do_divide64;
940
941 case Iop_DivModS128to64:
942 is_signed_divide = True;
943 goto do_divide64;
944
945 case Iop_64HLto128:
946 *dst_hi = s390_isel_int_expr(env, arg1);
947 *dst_lo = s390_isel_int_expr(env, arg2);
948 return;
949
950 case Iop_DivModS64to64: {
951 HReg r10, r11, h1;
952 s390_opnd_RMI op2;
953
954 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
955 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
956
957 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000958 r10 = make_gpr(10);
959 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000960
961 /* Move 1st operand into r11 and */
962 addInstr(env, s390_insn_move(8, r11, h1));
963
964 /* Divide */
965 addInstr(env, s390_insn_divs(8, r10, r11, op2));
966
967 /* The result is in registers r10 (remainder) and r11 (quotient).
968 Move the result into the reg pair that is being returned such
969 such that the low 64 bits are the quotient and the upper 64 bits
970 are the remainder. (see libvex_ir.h). */
971 *dst_hi = newVRegI(env);
972 *dst_lo = newVRegI(env);
973 addInstr(env, s390_insn_move(8, *dst_hi, r10));
974 addInstr(env, s390_insn_move(8, *dst_lo, r11));
975 return;
976 }
977
978 default:
979 break;
980
981 do_multiply64: {
982 HReg r10, r11, h1;
983 s390_opnd_RMI op2;
984
985 order_commutative_operands(arg1, arg2);
986
987 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
988 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
989
990 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +0000991 r10 = make_gpr(10);
992 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +0000993
994 /* Move the first operand to r11 */
995 addInstr(env, s390_insn_move(8, r11, h1));
996
997 /* Multiply */
998 addInstr(env, s390_insn_mul(8, r10, r11, op2, is_signed_multiply));
999
1000 /* The result is in registers r10 and r11. Assign to two virtual regs
1001 and return. */
1002 *dst_hi = newVRegI(env);
1003 *dst_lo = newVRegI(env);
1004 addInstr(env, s390_insn_move(8, *dst_hi, r10));
1005 addInstr(env, s390_insn_move(8, *dst_lo, r11));
1006 return;
1007 }
1008
1009 do_divide64: {
1010 HReg r10, r11, hi, lo;
1011 s390_opnd_RMI op2;
1012
1013 s390_isel_int128_expr(&hi, &lo, env, arg1);
1014 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1015
1016 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001017 r10 = make_gpr(10);
1018 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001019
1020 /* Move high 64 bits of the 1st operand into r10 and
1021 the low 64 bits into r11. */
1022 addInstr(env, s390_insn_move(8, r10, hi));
1023 addInstr(env, s390_insn_move(8, r11, lo));
1024
1025 /* Divide */
1026 addInstr(env, s390_insn_div(8, r10, r11, op2, is_signed_divide));
1027
1028 /* The result is in registers r10 (remainder) and r11 (quotient).
1029 Move the result into the reg pair that is being returned such
1030 such that the low 64 bits are the quotient and the upper 64 bits
1031 are the remainder. (see libvex_ir.h). */
1032 *dst_hi = newVRegI(env);
1033 *dst_lo = newVRegI(env);
1034 addInstr(env, s390_insn_move(8, *dst_hi, r10));
1035 addInstr(env, s390_insn_move(8, *dst_lo, r11));
1036 return;
1037 }
1038 }
1039 }
1040
1041 vpanic("s390_isel_int128_expr");
1042}
1043
1044
1045/* Compute a 128-bit value into two 64-bit registers. These may be either
1046 real or virtual regs; in any case they must not be changed by subsequent
1047 code emitted by the caller. */
1048static void
1049s390_isel_int128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
1050{
1051 s390_isel_int128_expr_wrk(dst_hi, dst_lo, env, expr);
1052
1053 /* Sanity checks ... */
1054 vassert(hregIsVirtual(*dst_hi));
1055 vassert(hregIsVirtual(*dst_lo));
1056 vassert(hregClass(*dst_hi) == HRcInt64);
1057 vassert(hregClass(*dst_lo) == HRcInt64);
1058}
1059
1060
1061/*---------------------------------------------------------*/
1062/*--- ISEL: Integer expressions (64/32/16/8 bit) ---*/
1063/*---------------------------------------------------------*/
1064
1065/* Select insns for an integer-typed expression, and add them to the
1066 code list. Return a reg holding the result. This reg will be a
1067 virtual register. THE RETURNED REG MUST NOT BE MODIFIED. If you
1068 want to modify it, ask for a new vreg, copy it in there, and modify
1069 the copy. The register allocator will do its best to map both
1070 vregs to the same real register, so the copies will often disappear
1071 later in the game.
1072
1073 This should handle expressions of 64, 32, 16 and 8-bit type.
1074 All results are returned in a 64bit register.
1075 For 16- and 8-bit expressions, the upper (32/48/56 : 16/24) bits
1076 are arbitrary, so you should mask or sign extend partial values
1077 if necessary.
1078*/
1079
1080/* DO NOT CALL THIS DIRECTLY ! */
1081static HReg
1082s390_isel_int_expr_wrk(ISelEnv *env, IRExpr *expr)
1083{
1084 IRType ty = typeOfIRExpr(env->type_env, expr);
1085 UChar size;
florian6dc90242012-12-21 21:43:00 +00001086 s390_bfp_conv_t conv;
florian67a171c2013-01-20 03:08:04 +00001087 s390_dfp_conv_t dconv;
sewardj2019a972011-03-07 16:04:07 +00001088
1089 vassert(ty == Ity_I8 || ty == Ity_I16 || ty == Ity_I32 || ty == Ity_I64);
1090
1091 size = sizeofIRType(ty); /* size of the result after evaluating EXPR */
1092
1093 switch (expr->tag) {
1094
1095 /* --------- TEMP --------- */
1096 case Iex_RdTmp:
1097 /* Return the virtual register that holds the temporary. */
1098 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
1099
1100 /* --------- LOAD --------- */
1101 case Iex_Load: {
1102 HReg dst = newVRegI(env);
1103 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
1104
1105 if (expr->Iex.Load.end != Iend_BE)
1106 goto irreducible;
1107
1108 addInstr(env, s390_insn_load(size, dst, am));
1109
1110 return dst;
1111 }
1112
1113 /* --------- BINARY OP --------- */
1114 case Iex_Binop: {
1115 IRExpr *arg1 = expr->Iex.Binop.arg1;
1116 IRExpr *arg2 = expr->Iex.Binop.arg2;
1117 HReg h1, res;
1118 s390_alu_t opkind;
1119 s390_opnd_RMI op2, value, opnd;
1120 s390_insn *insn;
1121 Bool is_commutative, is_signed_multiply, is_signed_divide;
1122
1123 is_commutative = True;
1124
1125 switch (expr->Iex.Binop.op) {
1126 case Iop_MullU8:
1127 case Iop_MullU16:
1128 case Iop_MullU32:
1129 is_signed_multiply = False;
1130 goto do_multiply;
1131
1132 case Iop_MullS8:
1133 case Iop_MullS16:
1134 case Iop_MullS32:
1135 is_signed_multiply = True;
1136 goto do_multiply;
1137
1138 do_multiply: {
1139 HReg r10, r11;
1140 UInt arg_size = size / 2;
1141
1142 order_commutative_operands(arg1, arg2);
1143
1144 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1145 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1146
1147 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001148 r10 = make_gpr(10);
1149 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001150
1151 /* Move the first operand to r11 */
1152 addInstr(env, s390_insn_move(arg_size, r11, h1));
1153
1154 /* Multiply */
1155 addInstr(env, s390_insn_mul(arg_size, r10, r11, op2, is_signed_multiply));
1156
1157 /* The result is in registers r10 and r11. Combine them into a SIZE-bit
1158 value into the destination register. */
1159 res = newVRegI(env);
1160 addInstr(env, s390_insn_move(arg_size, res, r10));
1161 value = s390_opnd_imm(arg_size * 8);
1162 addInstr(env, s390_insn_alu(size, S390_ALU_LSH, res, value));
1163 value = s390_opnd_imm((((ULong)1) << arg_size * 8) - 1);
1164 addInstr(env, s390_insn_alu(size, S390_ALU_AND, r11, value));
1165 opnd = s390_opnd_reg(r11);
1166 addInstr(env, s390_insn_alu(size, S390_ALU_OR, res, opnd));
1167 return res;
1168 }
1169
1170 case Iop_DivModS64to32:
1171 is_signed_divide = True;
1172 goto do_divide;
1173
1174 case Iop_DivModU64to32:
1175 is_signed_divide = False;
1176 goto do_divide;
1177
1178 do_divide: {
1179 HReg r10, r11;
1180
1181 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1182 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1183
1184 /* We use non-virtual registers r10 and r11 as pair */
florian297b6062012-05-08 20:16:17 +00001185 r10 = make_gpr(10);
1186 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001187
1188 /* Split the first operand and put the high 32 bits into r10 and
1189 the low 32 bits into r11. */
1190 addInstr(env, s390_insn_move(8, r10, h1));
1191 addInstr(env, s390_insn_move(8, r11, h1));
1192 value = s390_opnd_imm(32);
1193 addInstr(env, s390_insn_alu(8, S390_ALU_RSH, r10, value));
1194
1195 /* Divide */
1196 addInstr(env, s390_insn_div(4, r10, r11, op2, is_signed_divide));
1197
1198 /* The result is in registers r10 (remainder) and r11 (quotient).
1199 Combine them into a 64-bit value such that the low 32 bits are
1200 the quotient and the upper 32 bits are the remainder. (see
1201 libvex_ir.h). */
1202 res = newVRegI(env);
1203 addInstr(env, s390_insn_move(8, res, r10));
1204 value = s390_opnd_imm(32);
1205 addInstr(env, s390_insn_alu(8, S390_ALU_LSH, res, value));
1206 value = s390_opnd_imm((((ULong)1) << 32) - 1);
1207 addInstr(env, s390_insn_alu(8, S390_ALU_AND, r11, value));
1208 opnd = s390_opnd_reg(r11);
1209 addInstr(env, s390_insn_alu(8, S390_ALU_OR, res, opnd));
1210 return res;
1211 }
1212
florian9fcff4c2012-09-10 03:09:04 +00001213 case Iop_F32toI32S: conv = S390_BFP_F32_TO_I32; goto do_convert;
1214 case Iop_F32toI64S: conv = S390_BFP_F32_TO_I64; goto do_convert;
1215 case Iop_F32toI32U: conv = S390_BFP_F32_TO_U32; goto do_convert;
1216 case Iop_F32toI64U: conv = S390_BFP_F32_TO_U64; goto do_convert;
1217 case Iop_F64toI32S: conv = S390_BFP_F64_TO_I32; goto do_convert;
1218 case Iop_F64toI64S: conv = S390_BFP_F64_TO_I64; goto do_convert;
1219 case Iop_F64toI32U: conv = S390_BFP_F64_TO_U32; goto do_convert;
1220 case Iop_F64toI64U: conv = S390_BFP_F64_TO_U64; goto do_convert;
1221 case Iop_F128toI32S: conv = S390_BFP_F128_TO_I32; goto do_convert_128;
1222 case Iop_F128toI64S: conv = S390_BFP_F128_TO_I64; goto do_convert_128;
1223 case Iop_F128toI32U: conv = S390_BFP_F128_TO_U32; goto do_convert_128;
1224 case Iop_F128toI64U: conv = S390_BFP_F128_TO_U64; goto do_convert_128;
florian67a171c2013-01-20 03:08:04 +00001225
1226 case Iop_D64toI32S: dconv = S390_DFP_D64_TO_I32; goto do_convert_dfp;
floriana887acd2013-02-08 23:32:54 +00001227 case Iop_D64toI64S: dconv = S390_DFP_D64_TO_I64; goto do_convert_dfp;
florian67a171c2013-01-20 03:08:04 +00001228 case Iop_D64toI32U: dconv = S390_DFP_D64_TO_U32; goto do_convert_dfp;
1229 case Iop_D64toI64U: dconv = S390_DFP_D64_TO_U64; goto do_convert_dfp;
1230 case Iop_D128toI32S: dconv = S390_DFP_D128_TO_I32; goto do_convert_dfp128;
floriana887acd2013-02-08 23:32:54 +00001231 case Iop_D128toI64S: dconv = S390_DFP_D128_TO_I64; goto do_convert_dfp128;
florian67a171c2013-01-20 03:08:04 +00001232 case Iop_D128toI32U: dconv = S390_DFP_D128_TO_U32; goto do_convert_dfp128;
1233 case Iop_D128toI64U: dconv = S390_DFP_D128_TO_U64; goto do_convert_dfp128;
sewardj2019a972011-03-07 16:04:07 +00001234
1235 do_convert: {
florian125e20d2012-10-07 15:42:37 +00001236 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00001237
1238 res = newVRegI(env);
1239 h1 = s390_isel_float_expr(env, arg2); /* Process operand */
1240
florian2c74d242012-09-12 19:38:42 +00001241 rounding_mode = get_bfp_rounding_mode(env, arg1);
1242 addInstr(env, s390_insn_bfp_convert(size, conv, res, h1,
1243 rounding_mode));
sewardj2019a972011-03-07 16:04:07 +00001244 return res;
1245 }
1246
1247 do_convert_128: {
florian125e20d2012-10-07 15:42:37 +00001248 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00001249 HReg op_hi, op_lo, f13, f15;
1250
1251 res = newVRegI(env);
1252 s390_isel_float128_expr(&op_hi, &op_lo, env, arg2); /* operand */
1253
1254 /* We use non-virtual registers r13 and r15 as pair */
1255 f13 = make_fpr(13);
1256 f15 = make_fpr(15);
1257
1258 /* operand --> (f13, f15) */
1259 addInstr(env, s390_insn_move(8, f13, op_hi));
1260 addInstr(env, s390_insn_move(8, f15, op_lo));
1261
florian2c74d242012-09-12 19:38:42 +00001262 rounding_mode = get_bfp_rounding_mode(env, arg1);
floriana2039c52013-12-10 16:51:15 +00001263 addInstr(env, s390_insn_bfp128_convert_from(size, conv, res,
1264 INVALID_HREG, f13, f15,
sewardj2019a972011-03-07 16:04:07 +00001265 rounding_mode));
1266 return res;
1267 }
1268
florian5f034622013-01-13 02:29:05 +00001269 do_convert_dfp: {
1270 s390_dfp_round_t rounding_mode;
1271
1272 res = newVRegI(env);
1273 h1 = s390_isel_dfp_expr(env, arg2); /* Process operand */
1274
1275 rounding_mode = get_dfp_rounding_mode(env, arg1);
florian67a171c2013-01-20 03:08:04 +00001276 addInstr(env, s390_insn_dfp_convert(size, dconv, res, h1,
florian5f034622013-01-13 02:29:05 +00001277 rounding_mode));
1278 return res;
1279 }
1280
1281 do_convert_dfp128: {
1282 s390_dfp_round_t rounding_mode;
1283 HReg op_hi, op_lo, f13, f15;
1284
1285 res = newVRegI(env);
1286 s390_isel_dfp128_expr(&op_hi, &op_lo, env, arg2); /* operand */
1287
1288 /* We use non-virtual registers r13 and r15 as pair */
1289 f13 = make_fpr(13);
1290 f15 = make_fpr(15);
1291
1292 /* operand --> (f13, f15) */
1293 addInstr(env, s390_insn_move(8, f13, op_hi));
1294 addInstr(env, s390_insn_move(8, f15, op_lo));
1295
1296 rounding_mode = get_dfp_rounding_mode(env, arg1);
floriana2039c52013-12-10 16:51:15 +00001297 addInstr(env, s390_insn_dfp128_convert_from(size, dconv, res,
1298 INVALID_HREG, f13,
florian5f034622013-01-13 02:29:05 +00001299 f15, rounding_mode));
1300 return res;
1301 }
1302
sewardj2019a972011-03-07 16:04:07 +00001303 case Iop_8HLto16:
1304 case Iop_16HLto32:
1305 case Iop_32HLto64: {
1306 HReg h2;
1307 UInt arg_size = size / 2;
1308
1309 res = newVRegI(env);
1310 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1311 h2 = s390_isel_int_expr(env, arg2); /* Process 2nd operand */
1312
1313 addInstr(env, s390_insn_move(arg_size, res, h1));
1314 value = s390_opnd_imm(arg_size * 8);
1315 addInstr(env, s390_insn_alu(size, S390_ALU_LSH, res, value));
1316 value = s390_opnd_imm((((ULong)1) << arg_size * 8) - 1);
1317 addInstr(env, s390_insn_alu(size, S390_ALU_AND, h2, value));
1318 opnd = s390_opnd_reg(h2);
1319 addInstr(env, s390_insn_alu(size, S390_ALU_OR, res, opnd));
1320 return res;
1321 }
1322
1323 case Iop_Max32U: {
1324 /* arg1 > arg2 ? arg1 : arg2 using uint32_t arguments */
1325 res = newVRegI(env);
1326 h1 = s390_isel_int_expr(env, arg1);
1327 op2 = s390_isel_int_expr_RMI(env, arg2);
1328
1329 addInstr(env, s390_insn_move(size, res, h1));
1330 addInstr(env, s390_insn_compare(size, res, op2, False /* signed */));
1331 addInstr(env, s390_insn_cond_move(size, S390_CC_L, res, op2));
1332 return res;
1333 }
1334
1335 case Iop_CmpF32:
1336 case Iop_CmpF64: {
1337 HReg cc_s390, h2;
1338
1339 h1 = s390_isel_float_expr(env, arg1);
1340 h2 = s390_isel_float_expr(env, arg2);
1341 cc_s390 = newVRegI(env);
1342
1343 size = (expr->Iex.Binop.op == Iop_CmpF32) ? 4 : 8;
1344
1345 addInstr(env, s390_insn_bfp_compare(size, cc_s390, h1, h2));
1346
florian2d3d87f2012-12-21 21:05:17 +00001347 return convert_s390_to_vex_bfpcc(env, cc_s390);
sewardj2019a972011-03-07 16:04:07 +00001348 }
1349
1350 case Iop_CmpF128: {
1351 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15, cc_s390;
1352
1353 s390_isel_float128_expr(&op1_hi, &op1_lo, env, arg1); /* 1st operand */
1354 s390_isel_float128_expr(&op2_hi, &op2_lo, env, arg2); /* 2nd operand */
1355 cc_s390 = newVRegI(env);
1356
1357 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1358 f12 = make_fpr(12);
1359 f13 = make_fpr(13);
1360 f14 = make_fpr(14);
1361 f15 = make_fpr(15);
1362
1363 /* 1st operand --> (f12, f14) */
1364 addInstr(env, s390_insn_move(8, f12, op1_hi));
1365 addInstr(env, s390_insn_move(8, f14, op1_lo));
1366
1367 /* 2nd operand --> (f13, f15) */
1368 addInstr(env, s390_insn_move(8, f13, op2_hi));
1369 addInstr(env, s390_insn_move(8, f15, op2_lo));
1370
1371 res = newVRegI(env);
1372 addInstr(env, s390_insn_bfp128_compare(16, cc_s390, f12, f14, f13, f15));
1373
florian2d3d87f2012-12-21 21:05:17 +00001374 return convert_s390_to_vex_bfpcc(env, cc_s390);
sewardj2019a972011-03-07 16:04:07 +00001375 }
1376
florian20c6bca2012-12-26 17:47:19 +00001377 case Iop_CmpD64:
1378 case Iop_CmpExpD64: {
floriane38f6412012-12-21 17:32:12 +00001379 HReg cc_s390, h2;
florian20c6bca2012-12-26 17:47:19 +00001380 s390_dfp_cmp_t cmp;
floriane38f6412012-12-21 17:32:12 +00001381
1382 h1 = s390_isel_dfp_expr(env, arg1);
1383 h2 = s390_isel_dfp_expr(env, arg2);
1384 cc_s390 = newVRegI(env);
floriane38f6412012-12-21 17:32:12 +00001385
florian20c6bca2012-12-26 17:47:19 +00001386 switch(expr->Iex.Binop.op) {
1387 case Iop_CmpD64: cmp = S390_DFP_COMPARE; break;
1388 case Iop_CmpExpD64: cmp = S390_DFP_COMPARE_EXP; break;
1389 default: goto irreducible;
1390 }
1391 addInstr(env, s390_insn_dfp_compare(8, cmp, cc_s390, h1, h2));
floriane38f6412012-12-21 17:32:12 +00001392
florian2d3d87f2012-12-21 21:05:17 +00001393 return convert_s390_to_vex_dfpcc(env, cc_s390);
floriane38f6412012-12-21 17:32:12 +00001394 }
1395
florian20c6bca2012-12-26 17:47:19 +00001396 case Iop_CmpD128:
1397 case Iop_CmpExpD128: {
floriane38f6412012-12-21 17:32:12 +00001398 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15, cc_s390;
florian20c6bca2012-12-26 17:47:19 +00001399 s390_dfp_cmp_t cmp;
floriane38f6412012-12-21 17:32:12 +00001400
1401 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, arg1); /* 1st operand */
1402 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, arg2); /* 2nd operand */
1403 cc_s390 = newVRegI(env);
1404
1405 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
1406 f12 = make_fpr(12);
1407 f13 = make_fpr(13);
1408 f14 = make_fpr(14);
1409 f15 = make_fpr(15);
1410
1411 /* 1st operand --> (f12, f14) */
1412 addInstr(env, s390_insn_move(8, f12, op1_hi));
1413 addInstr(env, s390_insn_move(8, f14, op1_lo));
1414
1415 /* 2nd operand --> (f13, f15) */
1416 addInstr(env, s390_insn_move(8, f13, op2_hi));
1417 addInstr(env, s390_insn_move(8, f15, op2_lo));
1418
florian20c6bca2012-12-26 17:47:19 +00001419 switch(expr->Iex.Binop.op) {
1420 case Iop_CmpD128: cmp = S390_DFP_COMPARE; break;
1421 case Iop_CmpExpD128: cmp = S390_DFP_COMPARE_EXP; break;
1422 default: goto irreducible;
1423 }
1424 addInstr(env, s390_insn_dfp128_compare(16, cmp, cc_s390, f12, f14,
1425 f13, f15));
floriane38f6412012-12-21 17:32:12 +00001426
florian2d3d87f2012-12-21 21:05:17 +00001427 return convert_s390_to_vex_dfpcc(env, cc_s390);
floriane38f6412012-12-21 17:32:12 +00001428 }
1429
sewardj2019a972011-03-07 16:04:07 +00001430 case Iop_Add8:
1431 case Iop_Add16:
1432 case Iop_Add32:
1433 case Iop_Add64:
1434 opkind = S390_ALU_ADD;
1435 break;
1436
1437 case Iop_Sub8:
1438 case Iop_Sub16:
1439 case Iop_Sub32:
1440 case Iop_Sub64:
1441 opkind = S390_ALU_SUB;
1442 is_commutative = False;
1443 break;
1444
1445 case Iop_And8:
1446 case Iop_And16:
1447 case Iop_And32:
1448 case Iop_And64:
1449 opkind = S390_ALU_AND;
1450 break;
1451
1452 case Iop_Or8:
1453 case Iop_Or16:
1454 case Iop_Or32:
1455 case Iop_Or64:
1456 opkind = S390_ALU_OR;
1457 break;
1458
1459 case Iop_Xor8:
1460 case Iop_Xor16:
1461 case Iop_Xor32:
1462 case Iop_Xor64:
1463 opkind = S390_ALU_XOR;
1464 break;
1465
1466 case Iop_Shl8:
1467 case Iop_Shl16:
1468 case Iop_Shl32:
1469 case Iop_Shl64:
1470 opkind = S390_ALU_LSH;
1471 is_commutative = False;
1472 break;
1473
1474 case Iop_Shr8:
1475 case Iop_Shr16:
1476 case Iop_Shr32:
1477 case Iop_Shr64:
1478 opkind = S390_ALU_RSH;
1479 is_commutative = False;
1480 break;
1481
1482 case Iop_Sar8:
1483 case Iop_Sar16:
1484 case Iop_Sar32:
1485 case Iop_Sar64:
1486 opkind = S390_ALU_RSHA;
1487 is_commutative = False;
1488 break;
1489
1490 default:
1491 goto irreducible;
1492 }
1493
1494 /* Pattern match: 0 - arg1 --> -arg1 */
1495 if (opkind == S390_ALU_SUB && s390_expr_is_const_zero(arg1)) {
1496 res = newVRegI(env);
1497 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1498 insn = s390_insn_unop(size, S390_NEGATE, res, op2);
1499 addInstr(env, insn);
1500
1501 return res;
1502 }
1503
1504 if (is_commutative) {
1505 order_commutative_operands(arg1, arg2);
1506 }
1507
1508 h1 = s390_isel_int_expr(env, arg1); /* Process 1st operand */
1509 op2 = s390_isel_int_expr_RMI(env, arg2); /* Process 2nd operand */
1510 res = newVRegI(env);
florian5e0f2042012-08-20 13:44:29 +00001511
1512 /* As right shifts of one/two byte opreands are implemented using a
1513 4-byte shift op, we first need to zero/sign-extend the shiftee. */
1514 switch (expr->Iex.Binop.op) {
1515 case Iop_Shr8:
1516 insn = s390_insn_unop(4, S390_ZERO_EXTEND_8, res, s390_opnd_reg(h1));
1517 break;
1518 case Iop_Shr16:
1519 insn = s390_insn_unop(4, S390_ZERO_EXTEND_16, res, s390_opnd_reg(h1));
1520 break;
1521 case Iop_Sar8:
1522 insn = s390_insn_unop(4, S390_SIGN_EXTEND_8, res, s390_opnd_reg(h1));
1523 break;
1524 case Iop_Sar16:
1525 insn = s390_insn_unop(4, S390_SIGN_EXTEND_16, res, s390_opnd_reg(h1));
1526 break;
1527 default:
1528 insn = s390_insn_move(size, res, h1);
1529 break;
1530 }
1531 addInstr(env, insn);
1532
sewardj2019a972011-03-07 16:04:07 +00001533 insn = s390_insn_alu(size, opkind, res, op2);
1534
1535 addInstr(env, insn);
1536
1537 return res;
1538 }
1539
1540 /* --------- UNARY OP --------- */
1541 case Iex_Unop: {
1542 static s390_opnd_RMI mask = { S390_OPND_IMMEDIATE };
1543 static s390_opnd_RMI shift = { S390_OPND_IMMEDIATE };
1544 s390_opnd_RMI opnd;
1545 s390_insn *insn;
1546 IRExpr *arg;
1547 HReg dst, h1;
1548 IROp unop, binop;
1549
1550 arg = expr->Iex.Unop.arg;
1551
1552 /* Special cases are handled here */
1553
1554 /* 32-bit multiply with 32-bit result or
1555 64-bit multiply with 64-bit result */
1556 unop = expr->Iex.Unop.op;
1557 binop = arg->Iex.Binop.op;
1558
1559 if ((arg->tag == Iex_Binop &&
1560 ((unop == Iop_64to32 &&
1561 (binop == Iop_MullS32 || binop == Iop_MullU32)) ||
1562 (unop == Iop_128to64 &&
1563 (binop == Iop_MullS64 || binop == Iop_MullU64))))) {
1564 h1 = s390_isel_int_expr(env, arg->Iex.Binop.arg1); /* 1st opnd */
1565 opnd = s390_isel_int_expr_RMI(env, arg->Iex.Binop.arg2); /* 2nd opnd */
1566 dst = newVRegI(env); /* Result goes into a new register */
1567 addInstr(env, s390_insn_move(size, dst, h1));
1568 addInstr(env, s390_insn_alu(size, S390_ALU_MUL, dst, opnd));
1569
1570 return dst;
1571 }
1572
florian4d71a082011-12-18 00:08:17 +00001573 if (unop == Iop_ReinterpF64asI64 || unop == Iop_ReinterpF32asI32) {
sewardj2019a972011-03-07 16:04:07 +00001574 dst = newVRegI(env);
1575 h1 = s390_isel_float_expr(env, arg); /* Process the operand */
1576 addInstr(env, s390_insn_move(size, dst, h1));
1577
1578 return dst;
1579 }
1580
floriane38f6412012-12-21 17:32:12 +00001581 if (unop == Iop_ReinterpD64asI64) {
1582 dst = newVRegI(env);
1583 h1 = s390_isel_dfp_expr(env, arg); /* Process the operand */
1584 addInstr(env, s390_insn_move(size, dst, h1));
1585
1586 return dst;
1587 }
1588
florian5c539732013-02-14 14:27:12 +00001589 if (unop == Iop_ExtractExpD64 || unop == Iop_ExtractSigD64) {
1590 s390_dfp_unop_t dfpop;
1591 switch(unop) {
1592 case Iop_ExtractExpD64: dfpop = S390_DFP_EXTRACT_EXP_D64; break;
1593 case Iop_ExtractSigD64: dfpop = S390_DFP_EXTRACT_SIG_D64; break;
1594 default: goto irreducible;
1595 }
floriance9e3db2012-12-27 20:14:03 +00001596 dst = newVRegI(env);
1597 h1 = s390_isel_dfp_expr(env, arg); /* Process the operand */
florian5c539732013-02-14 14:27:12 +00001598 addInstr(env, s390_insn_dfp_unop(size, dfpop, dst, h1));
floriance9e3db2012-12-27 20:14:03 +00001599 return dst;
1600 }
1601
florian5c539732013-02-14 14:27:12 +00001602 if (unop == Iop_ExtractExpD128 || unop == Iop_ExtractSigD128) {
1603 s390_dfp_unop_t dfpop;
floriance9e3db2012-12-27 20:14:03 +00001604 HReg op_hi, op_lo, f13, f15;
florian5c539732013-02-14 14:27:12 +00001605
1606 switch(unop) {
1607 case Iop_ExtractExpD128: dfpop = S390_DFP_EXTRACT_EXP_D128; break;
1608 case Iop_ExtractSigD128: dfpop = S390_DFP_EXTRACT_SIG_D128; break;
1609 default: goto irreducible;
1610 }
floriance9e3db2012-12-27 20:14:03 +00001611 dst = newVRegI(env);
1612 s390_isel_dfp128_expr(&op_hi, &op_lo, env, arg); /* Process operand */
1613
1614 /* We use non-virtual registers r13 and r15 as pair */
1615 f13 = make_fpr(13);
1616 f15 = make_fpr(15);
1617
1618 /* operand --> (f13, f15) */
1619 addInstr(env, s390_insn_move(8, f13, op_hi));
1620 addInstr(env, s390_insn_move(8, f15, op_lo));
1621
florian5c539732013-02-14 14:27:12 +00001622 addInstr(env, s390_insn_dfp128_unop(size, dfpop, dst, f13, f15));
floriance9e3db2012-12-27 20:14:03 +00001623 return dst;
1624 }
1625
sewardj2019a972011-03-07 16:04:07 +00001626 /* Expressions whose argument is 1-bit wide */
1627 if (typeOfIRExpr(env->type_env, arg) == Ity_I1) {
1628 s390_cc_t cond = s390_isel_cc(env, arg);
1629 dst = newVRegI(env); /* Result goes into a new register */
1630 addInstr(env, s390_insn_cc2bool(dst, cond));
1631
1632 switch (unop) {
1633 case Iop_1Uto8:
1634 case Iop_1Uto32:
florian5f27dcf2012-08-04 04:25:30 +00001635 /* Zero extend */
1636 mask.variant.imm = 1;
1637 addInstr(env, s390_insn_alu(4, S390_ALU_AND, dst, mask));
1638 break;
1639
sewardj2019a972011-03-07 16:04:07 +00001640 case Iop_1Uto64:
florian5f27dcf2012-08-04 04:25:30 +00001641 /* Zero extend */
1642 mask.variant.imm = 1;
1643 addInstr(env, s390_insn_alu(8, S390_ALU_AND, dst, mask));
sewardj2019a972011-03-07 16:04:07 +00001644 break;
1645
1646 case Iop_1Sto8:
1647 case Iop_1Sto16:
1648 case Iop_1Sto32:
1649 shift.variant.imm = 31;
1650 addInstr(env, s390_insn_alu(4, S390_ALU_LSH, dst, shift));
1651 addInstr(env, s390_insn_alu(4, S390_ALU_RSHA, dst, shift));
1652 break;
1653
1654 case Iop_1Sto64:
1655 shift.variant.imm = 63;
1656 addInstr(env, s390_insn_alu(8, S390_ALU_LSH, dst, shift));
1657 addInstr(env, s390_insn_alu(8, S390_ALU_RSHA, dst, shift));
1658 break;
1659
1660 default:
1661 goto irreducible;
1662 }
1663
1664 return dst;
1665 }
1666
1667 /* Regular processing */
1668
1669 if (unop == Iop_128to64) {
1670 HReg dst_hi, dst_lo;
1671
1672 s390_isel_int128_expr(&dst_hi, &dst_lo, env, arg);
1673 return dst_lo;
1674 }
1675
1676 if (unop == Iop_128HIto64) {
1677 HReg dst_hi, dst_lo;
1678
1679 s390_isel_int128_expr(&dst_hi, &dst_lo, env, arg);
1680 return dst_hi;
1681 }
1682
1683 dst = newVRegI(env); /* Result goes into a new register */
1684 opnd = s390_isel_int_expr_RMI(env, arg); /* Process the operand */
1685
1686 switch (unop) {
1687 case Iop_8Uto16:
1688 case Iop_8Uto32:
1689 case Iop_8Uto64:
1690 insn = s390_insn_unop(size, S390_ZERO_EXTEND_8, dst, opnd);
1691 break;
1692
1693 case Iop_16Uto32:
1694 case Iop_16Uto64:
1695 insn = s390_insn_unop(size, S390_ZERO_EXTEND_16, dst, opnd);
1696 break;
1697
1698 case Iop_32Uto64:
1699 insn = s390_insn_unop(size, S390_ZERO_EXTEND_32, dst, opnd);
1700 break;
1701
1702 case Iop_8Sto16:
1703 case Iop_8Sto32:
1704 case Iop_8Sto64:
1705 insn = s390_insn_unop(size, S390_SIGN_EXTEND_8, dst, opnd);
1706 break;
1707
1708 case Iop_16Sto32:
1709 case Iop_16Sto64:
1710 insn = s390_insn_unop(size, S390_SIGN_EXTEND_16, dst, opnd);
1711 break;
1712
1713 case Iop_32Sto64:
1714 insn = s390_insn_unop(size, S390_SIGN_EXTEND_32, dst, opnd);
1715 break;
1716
1717 case Iop_64to8:
1718 case Iop_64to16:
1719 case Iop_64to32:
1720 case Iop_32to8:
1721 case Iop_32to16:
1722 case Iop_16to8:
1723 /* Down-casts are no-ops. Upstream operations will only look at
1724 the bytes that make up the result of the down-cast. So there
1725 is no point setting the other bytes to 0. */
1726 insn = s390_opnd_copy(8, dst, opnd);
1727 break;
1728
1729 case Iop_64HIto32:
1730 addInstr(env, s390_opnd_copy(8, dst, opnd));
1731 shift.variant.imm = 32;
1732 insn = s390_insn_alu(8, S390_ALU_RSH, dst, shift);
1733 break;
1734
1735 case Iop_32HIto16:
1736 addInstr(env, s390_opnd_copy(4, dst, opnd));
1737 shift.variant.imm = 16;
1738 insn = s390_insn_alu(4, S390_ALU_RSH, dst, shift);
1739 break;
1740
1741 case Iop_16HIto8:
1742 addInstr(env, s390_opnd_copy(2, dst, opnd));
1743 shift.variant.imm = 8;
1744 insn = s390_insn_alu(2, S390_ALU_RSH, dst, shift);
1745 break;
1746
1747 case Iop_Not8:
1748 case Iop_Not16:
1749 case Iop_Not32:
1750 case Iop_Not64:
1751 /* XOR with ffff... */
1752 mask.variant.imm = ~(ULong)0;
1753 addInstr(env, s390_opnd_copy(size, dst, opnd));
1754 insn = s390_insn_alu(size, S390_ALU_XOR, dst, mask);
1755 break;
1756
1757 case Iop_Left8:
1758 case Iop_Left16:
1759 case Iop_Left32:
1760 case Iop_Left64:
1761 addInstr(env, s390_insn_unop(size, S390_NEGATE, dst, opnd));
1762 insn = s390_insn_alu(size, S390_ALU_OR, dst, opnd);
1763 break;
1764
1765 case Iop_CmpwNEZ32:
1766 case Iop_CmpwNEZ64: {
1767 /* Use the fact that x | -x == 0 iff x == 0. Otherwise, either X
1768 or -X will have a 1 in the MSB. */
1769 addInstr(env, s390_insn_unop(size, S390_NEGATE, dst, opnd));
1770 addInstr(env, s390_insn_alu(size, S390_ALU_OR, dst, opnd));
1771 shift.variant.imm = (unop == Iop_CmpwNEZ32) ? 31 : 63;
1772 addInstr(env, s390_insn_alu(size, S390_ALU_RSHA, dst, shift));
1773 return dst;
1774 }
1775
1776 case Iop_Clz64: {
1777 HReg r10, r11;
1778
sewardj611b06e2011-03-24 08:57:29 +00001779 /* This will be implemented using FLOGR, if possible. So we need to
1780 set aside a pair of non-virtual registers. The result (number of
1781 left-most zero bits) will be in r10. The value in r11 is unspecified
1782 and must not be used. */
florian297b6062012-05-08 20:16:17 +00001783 r10 = make_gpr(10);
1784 r11 = make_gpr(11);
sewardj2019a972011-03-07 16:04:07 +00001785
sewardj611b06e2011-03-24 08:57:29 +00001786 addInstr(env, s390_insn_clz(8, r10, r11, opnd));
sewardj2019a972011-03-07 16:04:07 +00001787 addInstr(env, s390_insn_move(8, dst, r10));
1788 return dst;
1789 }
1790
1791 default:
1792 goto irreducible;
1793 }
1794
1795 addInstr(env, insn);
1796
1797 return dst;
1798 }
1799
1800 /* --------- GET --------- */
1801 case Iex_Get: {
1802 HReg dst = newVRegI(env);
1803 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
1804
1805 /* We never load more than 8 bytes from the guest state, because the
1806 floating point register pair is not contiguous. */
1807 vassert(size <= 8);
1808
1809 addInstr(env, s390_insn_load(size, dst, am));
1810
1811 return dst;
1812 }
1813
1814 case Iex_GetI:
1815 /* not needed */
1816 break;
1817
1818 /* --------- CCALL --------- */
1819 case Iex_CCall: {
1820 HReg dst = newVRegI(env);
sewardj74142b82013-08-08 10:28:59 +00001821 HReg ret = make_gpr(S390_REGNO_RETURN_VALUE);
1822 UInt addToSp = 0;
1823 RetLoc rloc = mk_RetLoc_INVALID();
sewardj2019a972011-03-07 16:04:07 +00001824
sewardj74142b82013-08-08 10:28:59 +00001825 doHelperCall(&addToSp, &rloc, env, NULL, expr->Iex.CCall.cee,
1826 expr->Iex.CCall.retty, expr->Iex.CCall.args);
1827 vassert(is_sane_RetLoc(rloc));
1828 vassert(rloc.pri == RLPri_Int);
1829 vassert(addToSp == 0);
1830 addInstr(env, s390_insn_move(sizeof(ULong), dst, ret));
1831
sewardj2019a972011-03-07 16:04:07 +00001832 return dst;
1833 }
1834
1835 /* --------- LITERAL --------- */
1836
1837 /* Load a literal into a register. Create a "load immediate"
1838 v-insn and return the register. */
1839 case Iex_Const: {
1840 ULong value;
1841 HReg dst = newVRegI(env);
1842 const IRConst *con = expr->Iex.Const.con;
1843
1844 /* Bitwise copy of the value. No sign/zero-extension */
1845 switch (con->tag) {
1846 case Ico_U64: value = con->Ico.U64; break;
1847 case Ico_U32: value = con->Ico.U32; break;
1848 case Ico_U16: value = con->Ico.U16; break;
1849 case Ico_U8: value = con->Ico.U8; break;
1850 default: vpanic("s390_isel_int_expr: invalid constant");
1851 }
1852
1853 addInstr(env, s390_insn_load_immediate(size, dst, value));
1854
1855 return dst;
1856 }
1857
1858 /* --------- MULTIPLEX --------- */
florian99dd03e2013-01-29 03:56:06 +00001859 case Iex_ITE: {
sewardj2019a972011-03-07 16:04:07 +00001860 IRExpr *cond_expr;
florian99dd03e2013-01-29 03:56:06 +00001861 HReg dst, r1;
sewardj009230b2013-01-26 11:47:55 +00001862 s390_opnd_RMI r0;
sewardj2019a972011-03-07 16:04:07 +00001863
florian99dd03e2013-01-29 03:56:06 +00001864 cond_expr = expr->Iex.ITE.cond;
sewardj2019a972011-03-07 16:04:07 +00001865
sewardj009230b2013-01-26 11:47:55 +00001866 vassert(typeOfIRExpr(env->type_env, cond_expr) == Ity_I1);
1867
sewardj2019a972011-03-07 16:04:07 +00001868 dst = newVRegI(env);
florian99dd03e2013-01-29 03:56:06 +00001869 r0 = s390_isel_int_expr_RMI(env, expr->Iex.ITE.iffalse);
1870 r1 = s390_isel_int_expr(env, expr->Iex.ITE.iftrue);
1871 size = sizeofIRType(typeOfIRExpr(env->type_env, expr->Iex.ITE.iftrue));
sewardj2019a972011-03-07 16:04:07 +00001872
sewardj009230b2013-01-26 11:47:55 +00001873 s390_cc_t cc = s390_isel_cc(env, cond_expr);
sewardj2019a972011-03-07 16:04:07 +00001874
florian99dd03e2013-01-29 03:56:06 +00001875 addInstr(env, s390_insn_move(size, dst, r1));
sewardj009230b2013-01-26 11:47:55 +00001876 addInstr(env, s390_insn_cond_move(size, s390_cc_invert(cc), dst, r0));
sewardj2019a972011-03-07 16:04:07 +00001877 return dst;
1878 }
1879
1880 default:
1881 break;
1882 }
1883
1884 /* We get here if no pattern matched. */
1885 irreducible:
1886 ppIRExpr(expr);
1887 vpanic("s390_isel_int_expr: cannot reduce tree");
1888}
1889
1890
1891static HReg
1892s390_isel_int_expr(ISelEnv *env, IRExpr *expr)
1893{
1894 HReg dst = s390_isel_int_expr_wrk(env, expr);
1895
1896 /* Sanity checks ... */
1897 vassert(hregClass(dst) == HRcInt64);
1898 vassert(hregIsVirtual(dst));
1899
1900 return dst;
1901}
1902
1903
1904static s390_opnd_RMI
1905s390_isel_int_expr_RMI(ISelEnv *env, IRExpr *expr)
1906{
1907 IRType ty = typeOfIRExpr(env->type_env, expr);
1908 s390_opnd_RMI dst;
1909
1910 vassert(ty == Ity_I8 || ty == Ity_I16 || ty == Ity_I32 ||
1911 ty == Ity_I64);
1912
1913 if (expr->tag == Iex_Load) {
1914 dst.tag = S390_OPND_AMODE;
1915 dst.variant.am = s390_isel_amode(env, expr->Iex.Load.addr);
1916 } else if (expr->tag == Iex_Get) {
1917 dst.tag = S390_OPND_AMODE;
1918 dst.variant.am = s390_amode_for_guest_state(expr->Iex.Get.offset);
1919 } else if (expr->tag == Iex_Const) {
1920 ULong value;
1921
1922 /* The bit pattern for the value will be stored as is in the least
1923 significant bits of VALUE. */
1924 switch (expr->Iex.Const.con->tag) {
1925 case Ico_U1: value = expr->Iex.Const.con->Ico.U1; break;
1926 case Ico_U8: value = expr->Iex.Const.con->Ico.U8; break;
1927 case Ico_U16: value = expr->Iex.Const.con->Ico.U16; break;
1928 case Ico_U32: value = expr->Iex.Const.con->Ico.U32; break;
1929 case Ico_U64: value = expr->Iex.Const.con->Ico.U64; break;
1930 default:
1931 vpanic("s390_isel_int_expr_RMI");
1932 }
1933
1934 dst.tag = S390_OPND_IMMEDIATE;
1935 dst.variant.imm = value;
1936 } else {
1937 dst.tag = S390_OPND_REG;
1938 dst.variant.reg = s390_isel_int_expr(env, expr);
1939 }
1940
1941 return dst;
1942}
1943
1944
1945/*---------------------------------------------------------*/
1946/*--- ISEL: Floating point expressions (128 bit) ---*/
1947/*---------------------------------------------------------*/
1948static void
1949s390_isel_float128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
1950 IRExpr *expr)
1951{
1952 IRType ty = typeOfIRExpr(env->type_env, expr);
1953
1954 vassert(ty == Ity_F128);
1955
sewardj2019a972011-03-07 16:04:07 +00001956 switch (expr->tag) {
1957 case Iex_RdTmp:
1958 /* Return the virtual registers that hold the temporary. */
1959 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
1960 return;
1961
1962 /* --------- LOAD --------- */
1963 case Iex_Load: {
1964 IRExpr *addr_hi, *addr_lo;
1965 s390_amode *am_hi, *am_lo;
1966
1967 if (expr->Iex.Load.end != Iend_BE)
1968 goto irreducible;
1969
1970 addr_hi = expr->Iex.Load.addr;
1971 addr_lo = IRExpr_Binop(Iop_Add64, addr_hi, mkU64(8));
1972
1973 am_hi = s390_isel_amode(env, addr_hi);
1974 am_lo = s390_isel_amode(env, addr_lo);
1975
1976 *dst_hi = newVRegF(env);
1977 *dst_lo = newVRegF(env);
1978 addInstr(env, s390_insn_load(8, *dst_hi, am_hi));
1979 addInstr(env, s390_insn_load(8, *dst_hi, am_lo));
1980 return;
1981 }
1982
1983
1984 /* --------- GET --------- */
1985 case Iex_Get:
1986 /* This is not supported because loading 128-bit from the guest
1987 state is almost certainly wrong. Use get_fpr_pair instead. */
1988 vpanic("Iex_Get with F128 data");
1989
1990 /* --------- 4-ary OP --------- */
1991 case Iex_Qop:
1992 vpanic("Iex_Qop with F128 data");
1993
1994 /* --------- TERNARY OP --------- */
1995 case Iex_Triop: {
florian420bfa92012-06-02 20:29:22 +00001996 IRTriop *triop = expr->Iex.Triop.details;
1997 IROp op = triop->op;
1998 IRExpr *left = triop->arg2;
1999 IRExpr *right = triop->arg3;
sewardj2019a972011-03-07 16:04:07 +00002000 s390_bfp_binop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002001 HReg op1_hi, op1_lo, op2_hi, op2_lo, f12, f13, f14, f15;
2002
2003 s390_isel_float128_expr(&op1_hi, &op1_lo, env, left); /* 1st operand */
2004 s390_isel_float128_expr(&op2_hi, &op2_lo, env, right); /* 2nd operand */
2005
2006 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
2007 f12 = make_fpr(12);
2008 f13 = make_fpr(13);
2009 f14 = make_fpr(14);
2010 f15 = make_fpr(15);
2011
2012 /* 1st operand --> (f12, f14) */
2013 addInstr(env, s390_insn_move(8, f12, op1_hi));
2014 addInstr(env, s390_insn_move(8, f14, op1_lo));
2015
2016 /* 2nd operand --> (f13, f15) */
2017 addInstr(env, s390_insn_move(8, f13, op2_hi));
2018 addInstr(env, s390_insn_move(8, f15, op2_lo));
2019
2020 switch (op) {
2021 case Iop_AddF128: bfpop = S390_BFP_ADD; break;
2022 case Iop_SubF128: bfpop = S390_BFP_SUB; break;
2023 case Iop_MulF128: bfpop = S390_BFP_MUL; break;
2024 case Iop_DivF128: bfpop = S390_BFP_DIV; break;
2025 default:
2026 goto irreducible;
2027 }
2028
florian2c74d242012-09-12 19:38:42 +00002029 set_bfp_rounding_mode_in_fpc(env, triop->arg1);
2030 addInstr(env, s390_insn_bfp128_binop(16, bfpop, f12, f14, f13, f15));
sewardj2019a972011-03-07 16:04:07 +00002031
2032 /* Move result to virtual destination register */
2033 *dst_hi = newVRegF(env);
2034 *dst_lo = newVRegF(env);
2035 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2036 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2037
2038 return;
2039 }
2040
2041 /* --------- BINARY OP --------- */
2042 case Iex_Binop: {
sewardj2019a972011-03-07 16:04:07 +00002043 switch (expr->Iex.Binop.op) {
florian78d5ef72013-05-11 15:02:58 +00002044 case Iop_SqrtF128: {
2045 HReg op_hi, op_lo, f12, f13, f14, f15;
2046
2047 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
2048 f12 = make_fpr(12);
2049 f13 = make_fpr(13);
2050 f14 = make_fpr(14);
2051 f15 = make_fpr(15);
2052
sewardj2019a972011-03-07 16:04:07 +00002053 s390_isel_float128_expr(&op_hi, &op_lo, env, expr->Iex.Binop.arg2);
2054
2055 /* operand --> (f13, f15) */
2056 addInstr(env, s390_insn_move(8, f13, op_hi));
2057 addInstr(env, s390_insn_move(8, f15, op_lo));
2058
florian2c74d242012-09-12 19:38:42 +00002059 set_bfp_rounding_mode_in_fpc(env, expr->Iex.Binop.arg1);
2060 addInstr(env, s390_insn_bfp128_unop(16, S390_BFP_SQRT, f12, f14,
2061 f13, f15));
sewardj2019a972011-03-07 16:04:07 +00002062
2063 /* Move result to virtual destination registers */
2064 *dst_hi = newVRegF(env);
2065 *dst_lo = newVRegF(env);
2066 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2067 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2068 return;
florian78d5ef72013-05-11 15:02:58 +00002069 }
sewardj2019a972011-03-07 16:04:07 +00002070
2071 case Iop_F64HLtoF128:
2072 *dst_hi = s390_isel_float_expr(env, expr->Iex.Binop.arg1);
2073 *dst_lo = s390_isel_float_expr(env, expr->Iex.Binop.arg2);
2074 return;
2075
florian7ab421d2013-06-17 21:03:56 +00002076 case Iop_D32toF128:
2077 case Iop_D64toF128: {
2078 IRExpr *irrm;
2079 IRExpr *left;
2080 s390_dfp_round_t rm;
2081 HReg h1; /* virtual reg. to hold source */
2082 HReg f0, f2, f4, r1; /* real registers used by PFPO */
2083 s390_fp_conv_t fpconv;
2084
2085 switch (expr->Iex.Binop.op) {
2086 case Iop_D32toF128:
2087 fpconv = S390_FP_D32_TO_F128;
2088 break;
2089 case Iop_D64toF128:
2090 fpconv = S390_FP_D64_TO_F128;
2091 break;
2092 default: goto irreducible;
2093 }
2094
2095 f4 = make_fpr(4); /* source */
2096 f0 = make_fpr(0); /* destination */
2097 f2 = make_fpr(2); /* destination */
2098 r1 = make_gpr(1); /* GPR #1 clobbered */
2099 irrm = expr->Iex.Binop.arg1;
2100 left = expr->Iex.Binop.arg2;
2101 rm = get_dfp_rounding_mode(env, irrm);
2102 h1 = s390_isel_dfp_expr(env, left);
2103 addInstr(env, s390_insn_move(8, f4, h1));
2104 addInstr(env, s390_insn_fp128_convert(16, fpconv, f0, f2,
2105 f4, INVALID_HREG, r1, rm));
2106 /* (f0, f2) --> destination */
2107 *dst_hi = newVRegF(env);
2108 *dst_lo = newVRegF(env);
2109 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2110 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2111
2112 return;
2113 }
2114
florian78d5ef72013-05-11 15:02:58 +00002115 case Iop_D128toF128: {
2116 IRExpr *irrm;
2117 IRExpr *left;
2118 s390_dfp_round_t rm;
2119 HReg op_hi, op_lo;
2120 HReg f0, f2, f4, f6, r1; /* real registers used by PFPO */
2121
2122 f4 = make_fpr(4); /* source */
2123 f6 = make_fpr(6); /* source */
2124 f0 = make_fpr(0); /* destination */
2125 f2 = make_fpr(2); /* destination */
2126 r1 = make_gpr(1); /* GPR #1 clobbered */
2127
2128 irrm = expr->Iex.Binop.arg1;
2129 left = expr->Iex.Binop.arg2;
2130 rm = get_dfp_rounding_mode(env, irrm);
2131 s390_isel_dfp128_expr(&op_hi, &op_lo, env, left);
2132 /* operand --> (f4, f6) */
2133 addInstr(env, s390_insn_move(8, f4, op_hi));
2134 addInstr(env, s390_insn_move(8, f6, op_lo));
2135 addInstr(env, s390_insn_fp128_convert(16, S390_FP_D128_TO_F128, f0, f2,
2136 f4, f6, r1, rm));
2137 /* (f0, f2) --> destination */
2138 *dst_hi = newVRegF(env);
2139 *dst_lo = newVRegF(env);
2140 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2141 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2142
2143 return;
2144 }
2145
florianb53f9482015-09-05 20:35:52 +00002146 case Iop_RoundF128toInt: {
2147 IRExpr *irrm;
2148 IRExpr *left;
2149 s390_bfp_round_t rm;
2150 HReg op_hi, op_lo;
2151 HReg f0, f2, f4, f6; /* real registers */
2152
2153 f4 = make_fpr(4); /* source */
2154 f6 = make_fpr(6); /* source */
2155 f0 = make_fpr(0); /* destination */
2156 f2 = make_fpr(2); /* destination */
2157
2158 irrm = expr->Iex.Binop.arg1;
2159 left = expr->Iex.Binop.arg2;
2160
2161 if (s390_host_has_fpext) {
2162 rm = get_bfp_rounding_mode(env, irrm);
2163 } else {
2164 set_bfp_rounding_mode_in_fpc(env, irrm);
2165 rm = S390_BFP_ROUND_PER_FPC;
2166 }
2167
2168 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
2169 /* operand --> (f4, f6) */
2170 addInstr(env, s390_insn_move(8, f4, op_hi));
2171 addInstr(env, s390_insn_move(8, f6, op_lo));
2172 addInstr(env, s390_insn_bfp128_convert(16, S390_BFP_F128_TO_F128I,
2173 f0, f2, f4, f6, rm));
2174 /* (f0, f2) --> destination */
2175 *dst_hi = newVRegF(env);
2176 *dst_lo = newVRegF(env);
2177 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2178 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2179 return;
2180 }
2181
sewardj2019a972011-03-07 16:04:07 +00002182 default:
2183 goto irreducible;
2184 }
2185 }
2186
2187 /* --------- UNARY OP --------- */
2188 case Iex_Unop: {
florian66e596d2012-09-07 15:00:53 +00002189 IRExpr *left = expr->Iex.Unop.arg;
sewardj2019a972011-03-07 16:04:07 +00002190 s390_bfp_unop_t bfpop;
florian6dc90242012-12-21 21:43:00 +00002191 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00002192 HReg op_hi, op_lo, op, f12, f13, f14, f15;
2193
2194 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
2195 f12 = make_fpr(12);
2196 f13 = make_fpr(13);
2197 f14 = make_fpr(14);
2198 f15 = make_fpr(15);
2199
florian66e596d2012-09-07 15:00:53 +00002200 switch (expr->Iex.Unop.op) {
florian3f3e50d2012-09-13 03:13:26 +00002201 case Iop_NegF128:
2202 if (left->tag == Iex_Unop &&
2203 (left->Iex.Unop.op == Iop_AbsF32 ||
2204 left->Iex.Unop.op == Iop_AbsF64))
2205 bfpop = S390_BFP_NABS;
2206 else
2207 bfpop = S390_BFP_NEG;
2208 goto float128_opnd;
florian9fcff4c2012-09-10 03:09:04 +00002209 case Iop_AbsF128: bfpop = S390_BFP_ABS; goto float128_opnd;
2210 case Iop_I32StoF128: conv = S390_BFP_I32_TO_F128; goto convert_int;
2211 case Iop_I64StoF128: conv = S390_BFP_I64_TO_F128; goto convert_int;
2212 case Iop_I32UtoF128: conv = S390_BFP_U32_TO_F128; goto convert_int;
2213 case Iop_I64UtoF128: conv = S390_BFP_U64_TO_F128; goto convert_int;
2214 case Iop_F32toF128: conv = S390_BFP_F32_TO_F128; goto convert_float;
2215 case Iop_F64toF128: conv = S390_BFP_F64_TO_F128; goto convert_float;
sewardj2019a972011-03-07 16:04:07 +00002216 default:
2217 goto irreducible;
2218 }
2219
2220 float128_opnd:
2221 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
2222
2223 /* operand --> (f13, f15) */
2224 addInstr(env, s390_insn_move(8, f13, op_hi));
2225 addInstr(env, s390_insn_move(8, f15, op_lo));
2226
florian2c74d242012-09-12 19:38:42 +00002227 addInstr(env, s390_insn_bfp128_unop(16, bfpop, f12, f14, f13, f15));
sewardj2019a972011-03-07 16:04:07 +00002228 goto move_dst;
2229
2230 convert_float:
2231 op = s390_isel_float_expr(env, left);
florian9fcff4c2012-09-10 03:09:04 +00002232 addInstr(env, s390_insn_bfp128_convert_to(16, conv, f12, f14, op));
sewardj2019a972011-03-07 16:04:07 +00002233 goto move_dst;
2234
2235 convert_int:
2236 op = s390_isel_int_expr(env, left);
florian9fcff4c2012-09-10 03:09:04 +00002237 addInstr(env, s390_insn_bfp128_convert_to(16, conv, f12, f14, op));
sewardj2019a972011-03-07 16:04:07 +00002238 goto move_dst;
2239
2240 move_dst:
2241 /* Move result to virtual destination registers */
2242 *dst_hi = newVRegF(env);
2243 *dst_lo = newVRegF(env);
2244 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2245 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2246 return;
2247 }
2248
2249 default:
2250 goto irreducible;
2251 }
2252
2253 /* We get here if no pattern matched. */
2254 irreducible:
2255 ppIRExpr(expr);
florian4ebaa772012-12-20 19:44:18 +00002256 vpanic("s390_isel_float128_expr: cannot reduce tree");
sewardj2019a972011-03-07 16:04:07 +00002257}
2258
2259/* Compute a 128-bit value into two 64-bit registers. These may be either
2260 real or virtual regs; in any case they must not be changed by subsequent
2261 code emitted by the caller. */
2262static void
2263s390_isel_float128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
2264{
2265 s390_isel_float128_expr_wrk(dst_hi, dst_lo, env, expr);
2266
2267 /* Sanity checks ... */
2268 vassert(hregIsVirtual(*dst_hi));
2269 vassert(hregIsVirtual(*dst_lo));
2270 vassert(hregClass(*dst_hi) == HRcFlt64);
2271 vassert(hregClass(*dst_lo) == HRcFlt64);
2272}
2273
2274
2275/*---------------------------------------------------------*/
2276/*--- ISEL: Floating point expressions (64 bit) ---*/
2277/*---------------------------------------------------------*/
2278
2279static HReg
2280s390_isel_float_expr_wrk(ISelEnv *env, IRExpr *expr)
2281{
2282 IRType ty = typeOfIRExpr(env->type_env, expr);
2283 UChar size;
2284
2285 vassert(ty == Ity_F32 || ty == Ity_F64);
2286
2287 size = sizeofIRType(ty);
2288
2289 switch (expr->tag) {
2290 case Iex_RdTmp:
2291 /* Return the virtual register that holds the temporary. */
2292 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
2293
2294 /* --------- LOAD --------- */
2295 case Iex_Load: {
2296 HReg dst = newVRegF(env);
2297 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
2298
2299 if (expr->Iex.Load.end != Iend_BE)
2300 goto irreducible;
2301
2302 addInstr(env, s390_insn_load(size, dst, am));
2303
2304 return dst;
2305 }
2306
2307 /* --------- GET --------- */
2308 case Iex_Get: {
2309 HReg dst = newVRegF(env);
2310 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
2311
2312 addInstr(env, s390_insn_load(size, dst, am));
2313
2314 return dst;
2315 }
2316
2317 /* --------- LITERAL --------- */
2318
2319 /* Load a literal into a register. Create a "load immediate"
2320 v-insn and return the register. */
2321 case Iex_Const: {
2322 ULong value;
2323 HReg dst = newVRegF(env);
2324 const IRConst *con = expr->Iex.Const.con;
2325
2326 /* Bitwise copy of the value. No sign/zero-extension */
2327 switch (con->tag) {
2328 case Ico_F32i: value = con->Ico.F32i; break;
2329 case Ico_F64i: value = con->Ico.F64i; break;
2330 default: vpanic("s390_isel_float_expr: invalid constant");
2331 }
2332
2333 if (value != 0) vpanic("cannot load immediate floating point constant");
2334
2335 addInstr(env, s390_insn_load_immediate(size, dst, value));
2336
2337 return dst;
2338 }
2339
2340 /* --------- 4-ary OP --------- */
2341 case Iex_Qop: {
2342 HReg op1, op2, op3, dst;
2343 s390_bfp_triop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002344
florian5906a6b2012-10-16 02:53:33 +00002345 op3 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg2);
florian96d7cc32012-06-01 20:41:24 +00002346 op2 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg3);
florian5906a6b2012-10-16 02:53:33 +00002347 op1 = s390_isel_float_expr(env, expr->Iex.Qop.details->arg4);
sewardj2019a972011-03-07 16:04:07 +00002348 dst = newVRegF(env);
2349 addInstr(env, s390_insn_move(size, dst, op1));
2350
florian96d7cc32012-06-01 20:41:24 +00002351 switch (expr->Iex.Qop.details->op) {
sewardj2019a972011-03-07 16:04:07 +00002352 case Iop_MAddF32:
2353 case Iop_MAddF64: bfpop = S390_BFP_MADD; break;
2354 case Iop_MSubF32:
2355 case Iop_MSubF64: bfpop = S390_BFP_MSUB; break;
2356
2357 default:
2358 goto irreducible;
2359 }
2360
florian2c74d242012-09-12 19:38:42 +00002361 set_bfp_rounding_mode_in_fpc(env, expr->Iex.Qop.details->arg1);
2362 addInstr(env, s390_insn_bfp_triop(size, bfpop, dst, op2, op3));
sewardj2019a972011-03-07 16:04:07 +00002363 return dst;
2364 }
2365
2366 /* --------- TERNARY OP --------- */
2367 case Iex_Triop: {
florian420bfa92012-06-02 20:29:22 +00002368 IRTriop *triop = expr->Iex.Triop.details;
2369 IROp op = triop->op;
2370 IRExpr *left = triop->arg2;
2371 IRExpr *right = triop->arg3;
sewardj2019a972011-03-07 16:04:07 +00002372 s390_bfp_binop_t bfpop;
sewardj2019a972011-03-07 16:04:07 +00002373 HReg h1, op2, dst;
2374
2375 h1 = s390_isel_float_expr(env, left); /* Process 1st operand */
2376 op2 = s390_isel_float_expr(env, right); /* Process 2nd operand */
2377 dst = newVRegF(env);
2378 addInstr(env, s390_insn_move(size, dst, h1));
2379 switch (op) {
2380 case Iop_AddF32:
2381 case Iop_AddF64: bfpop = S390_BFP_ADD; break;
2382 case Iop_SubF32:
2383 case Iop_SubF64: bfpop = S390_BFP_SUB; break;
2384 case Iop_MulF32:
2385 case Iop_MulF64: bfpop = S390_BFP_MUL; break;
2386 case Iop_DivF32:
2387 case Iop_DivF64: bfpop = S390_BFP_DIV; break;
2388
2389 default:
2390 goto irreducible;
2391 }
2392
florian2c74d242012-09-12 19:38:42 +00002393 set_bfp_rounding_mode_in_fpc(env, triop->arg1);
2394 addInstr(env, s390_insn_bfp_binop(size, bfpop, dst, op2));
sewardj2019a972011-03-07 16:04:07 +00002395 return dst;
2396 }
2397
2398 /* --------- BINARY OP --------- */
2399 case Iex_Binop: {
2400 IROp op = expr->Iex.Binop.op;
florian9fcff4c2012-09-10 03:09:04 +00002401 IRExpr *irrm = expr->Iex.Binop.arg1;
sewardj2019a972011-03-07 16:04:07 +00002402 IRExpr *left = expr->Iex.Binop.arg2;
2403 HReg h1, dst;
florian6dc90242012-12-21 21:43:00 +00002404 s390_bfp_conv_t conv;
florian78d5ef72013-05-11 15:02:58 +00002405 s390_fp_conv_t fpconv;
sewardj2019a972011-03-07 16:04:07 +00002406
2407 switch (op) {
2408 case Iop_SqrtF32:
2409 case Iop_SqrtF64:
florian9fcff4c2012-09-10 03:09:04 +00002410 h1 = s390_isel_float_expr(env, left);
2411 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002412 set_bfp_rounding_mode_in_fpc(env, irrm);
2413 addInstr(env, s390_insn_bfp_unop(size, S390_BFP_SQRT, dst, h1));
florian9fcff4c2012-09-10 03:09:04 +00002414 return dst;
sewardj2019a972011-03-07 16:04:07 +00002415
florian9fcff4c2012-09-10 03:09:04 +00002416 case Iop_F64toF32: conv = S390_BFP_F64_TO_F32; goto convert_float;
florian6d0b0152015-07-09 20:59:24 +00002417 case Iop_RoundF32toInt: conv = S390_BFP_F32_TO_F32I; goto convert_float;
2418 case Iop_RoundF64toInt: conv = S390_BFP_F64_TO_F64I; goto convert_float;
florian9fcff4c2012-09-10 03:09:04 +00002419 case Iop_I32StoF32: conv = S390_BFP_I32_TO_F32; goto convert_int;
2420 case Iop_I32UtoF32: conv = S390_BFP_U32_TO_F32; goto convert_int;
2421 case Iop_I64StoF32: conv = S390_BFP_I64_TO_F32; goto convert_int;
2422 case Iop_I64StoF64: conv = S390_BFP_I64_TO_F64; goto convert_int;
2423 case Iop_I64UtoF32: conv = S390_BFP_U64_TO_F32; goto convert_int;
2424 case Iop_I64UtoF64: conv = S390_BFP_U64_TO_F64; goto convert_int;
florian7ab421d2013-06-17 21:03:56 +00002425 case Iop_D32toF32: fpconv = S390_FP_D32_TO_F32; goto convert_dfp;
2426 case Iop_D32toF64: fpconv = S390_FP_D32_TO_F64; goto convert_dfp;
2427 case Iop_D64toF32: fpconv = S390_FP_D64_TO_F32; goto convert_dfp;
florian78d5ef72013-05-11 15:02:58 +00002428 case Iop_D64toF64: fpconv = S390_FP_D64_TO_F64; goto convert_dfp;
florian7ab421d2013-06-17 21:03:56 +00002429 case Iop_D128toF32: fpconv = S390_FP_D128_TO_F32; goto convert_dfp128;
florian78d5ef72013-05-11 15:02:58 +00002430 case Iop_D128toF64: fpconv = S390_FP_D128_TO_F64; goto convert_dfp128;
sewardj2019a972011-03-07 16:04:07 +00002431
florian9fcff4c2012-09-10 03:09:04 +00002432 convert_float:
2433 h1 = s390_isel_float_expr(env, left);
2434 goto convert;
florian1c8f7ff2012-09-01 00:12:11 +00002435
florian9fcff4c2012-09-10 03:09:04 +00002436 convert_int:
2437 h1 = s390_isel_int_expr(env, left);
2438 goto convert;
2439
florian2c74d242012-09-12 19:38:42 +00002440 convert: {
florian125e20d2012-10-07 15:42:37 +00002441 s390_bfp_round_t rounding_mode;
florian2c74d242012-09-12 19:38:42 +00002442 /* convert-from-fixed and load-rounded have a rounding mode field
2443 when the floating point extension facility is installed. */
florian9fcff4c2012-09-10 03:09:04 +00002444 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002445 if (s390_host_has_fpext) {
2446 rounding_mode = get_bfp_rounding_mode(env, irrm);
2447 } else {
2448 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +00002449 rounding_mode = S390_BFP_ROUND_PER_FPC;
florian2c74d242012-09-12 19:38:42 +00002450 }
florian9fcff4c2012-09-10 03:09:04 +00002451 addInstr(env, s390_insn_bfp_convert(size, conv, dst, h1,
2452 rounding_mode));
2453 return dst;
florian2c74d242012-09-12 19:38:42 +00002454 }
florian78d5ef72013-05-11 15:02:58 +00002455
2456 convert_dfp: {
2457 s390_dfp_round_t rm;
2458 HReg f0, f4, r1; /* real registers used by PFPO */
2459
2460 f4 = make_fpr(4); /* source */
2461 f0 = make_fpr(0); /* destination */
2462 r1 = make_gpr(1); /* GPR #1 clobbered */
2463 h1 = s390_isel_dfp_expr(env, left);
2464 dst = newVRegF(env);
2465 rm = get_dfp_rounding_mode(env, irrm);
2466 /* operand --> f4 */
2467 addInstr(env, s390_insn_move(8, f4, h1));
2468 addInstr(env, s390_insn_fp_convert(size, fpconv, f0, f4, r1, rm));
2469 /* f0 --> destination */
2470 addInstr(env, s390_insn_move(8, dst, f0));
2471 return dst;
2472 }
2473
2474 convert_dfp128: {
2475 s390_dfp_round_t rm;
2476 HReg op_hi, op_lo;
2477 HReg f0, f4, f6, r1; /* real registers used by PFPO */
2478
2479 f4 = make_fpr(4); /* source */
2480 f6 = make_fpr(6); /* source */
2481 f0 = make_fpr(0); /* destination */
2482 r1 = make_gpr(1); /* GPR #1 clobbered */
2483 s390_isel_dfp128_expr(&op_hi, &op_lo, env, left);
2484 dst = newVRegF(env);
2485 rm = get_dfp_rounding_mode(env, irrm);
2486 /* operand --> (f4, f6) */
2487 addInstr(env, s390_insn_move(8, f4, op_hi));
2488 addInstr(env, s390_insn_move(8, f6, op_lo));
2489 addInstr(env, s390_insn_fp128_convert(16, fpconv, f0, INVALID_HREG,
2490 f4, f6, r1, rm));
2491 /* f0 --> destination */
2492 addInstr(env, s390_insn_move(8, dst, f0));
2493 return dst;
2494 }
2495
sewardj2019a972011-03-07 16:04:07 +00002496 default:
2497 goto irreducible;
2498
2499 case Iop_F128toF64:
2500 case Iop_F128toF32: {
floriana2039c52013-12-10 16:51:15 +00002501 HReg op_hi, op_lo, f12, f13, f14, f15;
florian125e20d2012-10-07 15:42:37 +00002502 s390_bfp_round_t rounding_mode;
sewardj2019a972011-03-07 16:04:07 +00002503
florian9fcff4c2012-09-10 03:09:04 +00002504 conv = op == Iop_F128toF32 ? S390_BFP_F128_TO_F32
2505 : S390_BFP_F128_TO_F64;
sewardj2019a972011-03-07 16:04:07 +00002506
florian9fcff4c2012-09-10 03:09:04 +00002507 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
sewardj2019a972011-03-07 16:04:07 +00002508
floriana2039c52013-12-10 16:51:15 +00002509 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14)) */
2510 f12 = make_fpr(12);
sewardj2019a972011-03-07 16:04:07 +00002511 f13 = make_fpr(13);
floriana2039c52013-12-10 16:51:15 +00002512 f14 = make_fpr(14);
sewardj2019a972011-03-07 16:04:07 +00002513 f15 = make_fpr(15);
2514
2515 /* operand --> (f13, f15) */
2516 addInstr(env, s390_insn_move(8, f13, op_hi));
2517 addInstr(env, s390_insn_move(8, f15, op_lo));
2518
floriana2039c52013-12-10 16:51:15 +00002519 /* result --> (f12, f14) */
2520
florian2c74d242012-09-12 19:38:42 +00002521 /* load-rounded has a rounding mode field when the floating point
2522 extension facility is installed. */
2523 if (s390_host_has_fpext) {
2524 rounding_mode = get_bfp_rounding_mode(env, irrm);
2525 } else {
2526 set_bfp_rounding_mode_in_fpc(env, irrm);
florian125e20d2012-10-07 15:42:37 +00002527 rounding_mode = S390_BFP_ROUND_PER_FPC;
florian2c74d242012-09-12 19:38:42 +00002528 }
floriana2039c52013-12-10 16:51:15 +00002529
2530 addInstr(env, s390_insn_bfp128_convert_from(size, conv, f12, f14,
2531 f13, f15, rounding_mode));
2532 dst = newVRegF(env);
2533 addInstr(env, s390_insn_move(8, dst, f12));
2534
sewardj2019a972011-03-07 16:04:07 +00002535 return dst;
2536 }
2537 }
sewardj2019a972011-03-07 16:04:07 +00002538 }
2539
2540 /* --------- UNARY OP --------- */
2541 case Iex_Unop: {
2542 IROp op = expr->Iex.Unop.op;
2543 IRExpr *left = expr->Iex.Unop.arg;
2544 s390_bfp_unop_t bfpop;
florian6dc90242012-12-21 21:43:00 +00002545 s390_bfp_conv_t conv;
sewardj2019a972011-03-07 16:04:07 +00002546 HReg h1, dst;
2547
2548 if (op == Iop_F128HItoF64 || op == Iop_F128LOtoF64) {
2549 HReg dst_hi, dst_lo;
2550
2551 s390_isel_float128_expr(&dst_hi, &dst_lo, env, left);
2552 return op == Iop_F128LOtoF64 ? dst_lo : dst_hi;
2553 }
2554
florian4d71a082011-12-18 00:08:17 +00002555 if (op == Iop_ReinterpI64asF64 || op == Iop_ReinterpI32asF32) {
sewardj2019a972011-03-07 16:04:07 +00002556 dst = newVRegF(env);
2557 h1 = s390_isel_int_expr(env, left); /* Process the operand */
2558 addInstr(env, s390_insn_move(size, dst, h1));
2559
2560 return dst;
2561 }
2562
2563 switch (op) {
2564 case Iop_NegF32:
2565 case Iop_NegF64:
2566 if (left->tag == Iex_Unop &&
florian3f3e50d2012-09-13 03:13:26 +00002567 (left->Iex.Unop.op == Iop_AbsF32 ||
2568 left->Iex.Unop.op == Iop_AbsF64))
sewardj2019a972011-03-07 16:04:07 +00002569 bfpop = S390_BFP_NABS;
2570 else
2571 bfpop = S390_BFP_NEG;
2572 break;
2573
2574 case Iop_AbsF32:
florian9fcff4c2012-09-10 03:09:04 +00002575 case Iop_AbsF64:
2576 bfpop = S390_BFP_ABS;
2577 break;
2578
2579 case Iop_I32StoF64: conv = S390_BFP_I32_TO_F64; goto convert_int1;
2580 case Iop_I32UtoF64: conv = S390_BFP_U32_TO_F64; goto convert_int1;
2581 case Iop_F32toF64: conv = S390_BFP_F32_TO_F64; goto convert_float1;
2582
2583 convert_float1:
2584 h1 = s390_isel_float_expr(env, left);
2585 goto convert1;
2586
2587 convert_int1:
2588 h1 = s390_isel_int_expr(env, left);
2589 goto convert1;
2590
2591 convert1:
2592 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002593 /* No rounding mode is needed for these conversions. Just stick
2594 one in. It won't be used later on. */
2595 addInstr(env, s390_insn_bfp_convert(size, conv, dst, h1,
florian125e20d2012-10-07 15:42:37 +00002596 S390_BFP_ROUND_NEAREST_EVEN));
florian9fcff4c2012-09-10 03:09:04 +00002597 return dst;
2598
sewardj2019a972011-03-07 16:04:07 +00002599 default:
2600 goto irreducible;
2601 }
2602
2603 /* Process operand */
florian9fcff4c2012-09-10 03:09:04 +00002604 h1 = s390_isel_float_expr(env, left);
sewardj2019a972011-03-07 16:04:07 +00002605 dst = newVRegF(env);
florian2c74d242012-09-12 19:38:42 +00002606 addInstr(env, s390_insn_bfp_unop(size, bfpop, dst, h1));
sewardj2019a972011-03-07 16:04:07 +00002607 return dst;
2608 }
2609
2610 default:
2611 goto irreducible;
2612 }
2613
2614 /* We get here if no pattern matched. */
2615 irreducible:
2616 ppIRExpr(expr);
2617 vpanic("s390_isel_float_expr: cannot reduce tree");
2618}
2619
2620
2621static HReg
2622s390_isel_float_expr(ISelEnv *env, IRExpr *expr)
2623{
2624 HReg dst = s390_isel_float_expr_wrk(env, expr);
2625
2626 /* Sanity checks ... */
2627 vassert(hregClass(dst) == HRcFlt64);
2628 vassert(hregIsVirtual(dst));
2629
2630 return dst;
2631}
2632
2633
2634/*---------------------------------------------------------*/
floriane38f6412012-12-21 17:32:12 +00002635/*--- ISEL: Decimal point expressions (128 bit) ---*/
2636/*---------------------------------------------------------*/
2637static void
2638s390_isel_dfp128_expr_wrk(HReg *dst_hi, HReg *dst_lo, ISelEnv *env,
2639 IRExpr *expr)
2640{
2641 IRType ty = typeOfIRExpr(env->type_env, expr);
2642
2643 vassert(ty == Ity_D128);
2644
2645 switch (expr->tag) {
2646 case Iex_RdTmp:
2647 /* Return the virtual registers that hold the temporary. */
2648 lookupIRTemp128(dst_hi, dst_lo, env, expr->Iex.RdTmp.tmp);
2649 return;
2650
2651 /* --------- LOAD --------- */
2652 case Iex_Load: {
2653 IRExpr *addr_hi, *addr_lo;
2654 s390_amode *am_hi, *am_lo;
2655
2656 if (expr->Iex.Load.end != Iend_BE)
2657 goto irreducible;
2658
2659 addr_hi = expr->Iex.Load.addr;
2660 addr_lo = IRExpr_Binop(Iop_Add64, addr_hi, mkU64(8));
2661
2662 am_hi = s390_isel_amode(env, addr_hi);
2663 am_lo = s390_isel_amode(env, addr_lo);
2664
2665 *dst_hi = newVRegF(env);
2666 *dst_lo = newVRegF(env);
2667 addInstr(env, s390_insn_load(8, *dst_hi, am_hi));
2668 addInstr(env, s390_insn_load(8, *dst_hi, am_lo));
2669 return;
2670 }
2671
2672 /* --------- GET --------- */
2673 case Iex_Get:
2674 /* This is not supported because loading 128-bit from the guest
2675 state is almost certainly wrong. Use get_dpr_pair instead. */
2676 vpanic("Iex_Get with D128 data");
2677
2678 /* --------- 4-ary OP --------- */
2679 case Iex_Qop:
2680 vpanic("Iex_Qop with D128 data");
2681
2682 /* --------- TERNARY OP --------- */
2683 case Iex_Triop: {
2684 IRTriop *triop = expr->Iex.Triop.details;
2685 IROp op = triop->op;
2686 IRExpr *irrm = triop->arg1;
2687 IRExpr *left = triop->arg2;
2688 IRExpr *right = triop->arg3;
2689 s390_dfp_round_t rounding_mode;
2690 s390_dfp_binop_t dfpop;
2691 HReg op1_hi, op1_lo, op2_hi, op2_lo, f9, f11, f12, f13, f14, f15;
2692
floriane38f6412012-12-21 17:32:12 +00002693 /* We use non-virtual registers as pairs with (f9, f11) as op1,
2694 (f12, f14) as op2 and (f13, f15) as destination) */
2695 f9 = make_fpr(9);
2696 f11 = make_fpr(11);
2697 f12 = make_fpr(12);
2698 f13 = make_fpr(13);
2699 f14 = make_fpr(14);
2700 f15 = make_fpr(15);
2701
floriane38f6412012-12-21 17:32:12 +00002702 switch (op) {
florian5c539732013-02-14 14:27:12 +00002703 case Iop_AddD128: dfpop = S390_DFP_ADD; goto evaluate_dfp128;
2704 case Iop_SubD128: dfpop = S390_DFP_SUB; goto evaluate_dfp128;
2705 case Iop_MulD128: dfpop = S390_DFP_MUL; goto evaluate_dfp128;
2706 case Iop_DivD128: dfpop = S390_DFP_DIV; goto evaluate_dfp128;
2707 case Iop_QuantizeD128: dfpop = S390_DFP_QUANTIZE; goto evaluate_dfp128;
2708
2709 evaluate_dfp128: {
2710 /* Process 1st operand */
2711 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, left);
2712 /* 1st operand --> (f9, f11) */
2713 addInstr(env, s390_insn_move(8, f9, op1_hi));
2714 addInstr(env, s390_insn_move(8, f11, op1_lo));
2715
2716 /* Process 2nd operand */
2717 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, right);
2718 /* 2nd operand --> (f12, f14) */
2719 addInstr(env, s390_insn_move(8, f12, op2_hi));
2720 addInstr(env, s390_insn_move(8, f14, op2_lo));
2721
2722 /* DFP arithmetic ops take rounding mode only when fpext is
2723 installed. But, DFP quantize operation takes rm irrespective
2724 of fpext facility . */
floriand18287d2013-02-21 03:03:05 +00002725 if (s390_host_has_fpext || op == Iop_QuantizeD128) {
florian5c539732013-02-14 14:27:12 +00002726 rounding_mode = get_dfp_rounding_mode(env, irrm);
2727 } else {
2728 set_dfp_rounding_mode_in_fpc(env, irrm);
2729 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
2730 }
2731 addInstr(env, s390_insn_dfp128_binop(16, dfpop, f13, f15, f9, f11,
2732 f12, f14, rounding_mode));
2733 /* Move result to virtual destination register */
2734 *dst_hi = newVRegF(env);
2735 *dst_lo = newVRegF(env);
2736 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2737 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2738 return;
2739 }
2740
2741 case Iop_SignificanceRoundD128: {
2742 /* Process 1st operand */
2743 HReg op1 = s390_isel_int_expr(env, left);
2744 /* Process 2nd operand */
2745 s390_isel_dfp128_expr(&op2_hi, &op2_lo, env, right);
2746 /* 2nd operand --> (f12, f14) */
2747 addInstr(env, s390_insn_move(8, f12, op2_hi));
2748 addInstr(env, s390_insn_move(8, f14, op2_lo));
2749
2750 rounding_mode = get_dfp_rounding_mode(env, irrm);
2751 addInstr(env, s390_insn_dfp128_reround(16, f13, f15, op1, f12, f14,
2752 rounding_mode));
2753 /* Move result to virtual destination register */
2754 *dst_hi = newVRegF(env);
2755 *dst_lo = newVRegF(env);
2756 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2757 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2758 return;
2759 }
2760
floriane38f6412012-12-21 17:32:12 +00002761 default:
2762 goto irreducible;
2763 }
floriane38f6412012-12-21 17:32:12 +00002764 }
2765
2766 /* --------- BINARY OP --------- */
2767 case Iex_Binop: {
florian1b901d42013-01-01 22:19:24 +00002768
floriane38f6412012-12-21 17:32:12 +00002769 switch (expr->Iex.Binop.op) {
2770 case Iop_D64HLtoD128:
2771 *dst_hi = s390_isel_dfp_expr(env, expr->Iex.Binop.arg1);
2772 *dst_lo = s390_isel_dfp_expr(env, expr->Iex.Binop.arg2);
2773 return;
2774
florian1b901d42013-01-01 22:19:24 +00002775 case Iop_ShlD128:
florian5c539732013-02-14 14:27:12 +00002776 case Iop_ShrD128:
2777 case Iop_InsertExpD128: {
florian1b901d42013-01-01 22:19:24 +00002778 HReg op1_hi, op1_lo, op2, f9, f11, f13, f15;
2779 s390_dfp_intop_t intop;
florian5c539732013-02-14 14:27:12 +00002780 IRExpr *dfp_op;
2781 IRExpr *int_op;
florian1b901d42013-01-01 22:19:24 +00002782
2783 switch (expr->Iex.Binop.op) {
florian5c539732013-02-14 14:27:12 +00002784 case Iop_ShlD128: /* (D128, I64) -> D128 */
2785 intop = S390_DFP_SHIFT_LEFT;
2786 dfp_op = expr->Iex.Binop.arg1;
2787 int_op = expr->Iex.Binop.arg2;
2788 break;
2789 case Iop_ShrD128: /* (D128, I64) -> D128 */
2790 intop = S390_DFP_SHIFT_RIGHT;
2791 dfp_op = expr->Iex.Binop.arg1;
2792 int_op = expr->Iex.Binop.arg2;
2793 break;
2794 case Iop_InsertExpD128: /* (I64, D128) -> D128 */
2795 intop = S390_DFP_INSERT_EXP;
2796 int_op = expr->Iex.Binop.arg1;
2797 dfp_op = expr->Iex.Binop.arg2;
2798 break;
florian1b901d42013-01-01 22:19:24 +00002799 default: goto irreducible;
2800 }
2801
2802 /* We use non-virtual registers as pairs (f9, f11) and (f13, f15)) */
2803 f9 = make_fpr(9); /* 128 bit dfp operand */
2804 f11 = make_fpr(11);
2805
2806 f13 = make_fpr(13); /* 128 bit dfp destination */
2807 f15 = make_fpr(15);
2808
florian5c539732013-02-14 14:27:12 +00002809 /* Process dfp operand */
2810 s390_isel_dfp128_expr(&op1_hi, &op1_lo, env, dfp_op);
2811 /* op1 -> (f9,f11) */
florian1b901d42013-01-01 22:19:24 +00002812 addInstr(env, s390_insn_move(8, f9, op1_hi));
2813 addInstr(env, s390_insn_move(8, f11, op1_lo));
2814
florian5c539732013-02-14 14:27:12 +00002815 op2 = s390_isel_int_expr(env, int_op); /* int operand */
florian1b901d42013-01-01 22:19:24 +00002816
2817 addInstr(env,
2818 s390_insn_dfp128_intop(16, intop, f13, f15, op2, f9, f11));
2819
2820 /* Move result to virtual destination register */
2821 *dst_hi = newVRegF(env);
2822 *dst_lo = newVRegF(env);
2823 addInstr(env, s390_insn_move(8, *dst_hi, f13));
2824 addInstr(env, s390_insn_move(8, *dst_lo, f15));
2825 return;
2826 }
2827
florian7ab421d2013-06-17 21:03:56 +00002828 case Iop_F32toD128:
florian78d5ef72013-05-11 15:02:58 +00002829 case Iop_F64toD128: {
2830 IRExpr *irrm;
2831 IRExpr *left;
2832 s390_dfp_round_t rm;
2833 HReg h1; /* virtual reg. to hold source */
2834 HReg f0, f2, f4, r1; /* real registers used by PFPO */
florian7ab421d2013-06-17 21:03:56 +00002835 s390_fp_conv_t fpconv;
2836
2837 switch (expr->Iex.Binop.op) {
2838 case Iop_F32toD128: /* (D128, I64) -> D128 */
2839 fpconv = S390_FP_F32_TO_D128;
2840 break;
2841 case Iop_F64toD128: /* (D128, I64) -> D128 */
2842 fpconv = S390_FP_F64_TO_D128;
2843 break;
2844 default: goto irreducible;
2845 }
florian78d5ef72013-05-11 15:02:58 +00002846
2847 f4 = make_fpr(4); /* source */
2848 f0 = make_fpr(0); /* destination */
2849 f2 = make_fpr(2); /* destination */
2850 r1 = make_gpr(1); /* GPR #1 clobbered */
2851 irrm = expr->Iex.Binop.arg1;
2852 left = expr->Iex.Binop.arg2;
2853 rm = get_dfp_rounding_mode(env, irrm);
2854 h1 = s390_isel_float_expr(env, left);
2855 addInstr(env, s390_insn_move(8, f4, h1));
florian7ab421d2013-06-17 21:03:56 +00002856 addInstr(env, s390_insn_fp128_convert(16, fpconv, f0, f2,
florian78d5ef72013-05-11 15:02:58 +00002857 f4, INVALID_HREG, r1, rm));
2858 /* (f0, f2) --> destination */
2859 *dst_hi = newVRegF(env);
2860 *dst_lo = newVRegF(env);
2861 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2862 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2863
2864 return;
2865 }
2866
2867 case Iop_F128toD128: {
2868 IRExpr *irrm;
2869 IRExpr *left;
2870 s390_dfp_round_t rm;
2871 HReg op_hi, op_lo;
2872 HReg f0, f2, f4, f6, r1; /* real registers used by PFPO */
2873
2874 f4 = make_fpr(4); /* source */
2875 f6 = make_fpr(6); /* source */
2876 f0 = make_fpr(0); /* destination */
2877 f2 = make_fpr(2); /* destination */
2878 r1 = make_gpr(1); /* GPR #1 clobbered */
2879
2880 irrm = expr->Iex.Binop.arg1;
2881 left = expr->Iex.Binop.arg2;
2882 rm = get_dfp_rounding_mode(env, irrm);
2883 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
2884 /* operand --> (f4, f6) */
2885 addInstr(env, s390_insn_move(8, f4, op_hi));
2886 addInstr(env, s390_insn_move(8, f6, op_lo));
2887 addInstr(env, s390_insn_fp128_convert(16, S390_FP_F128_TO_D128, f0, f2,
2888 f4, f6, r1, rm));
2889 /* (f0, f2) --> destination */
2890 *dst_hi = newVRegF(env);
2891 *dst_lo = newVRegF(env);
2892 addInstr(env, s390_insn_move(8, *dst_hi, f0));
2893 addInstr(env, s390_insn_move(8, *dst_lo, f2));
2894
2895 return;
2896 }
2897
floriane38f6412012-12-21 17:32:12 +00002898 default:
2899 goto irreducible;
2900 }
2901 }
2902
2903 /* --------- UNARY OP --------- */
2904 case Iex_Unop: {
2905 IRExpr *left = expr->Iex.Unop.arg;
2906 s390_dfp_conv_t conv;
floriane38f6412012-12-21 17:32:12 +00002907 HReg op, f12, f14;
2908
floriana887acd2013-02-08 23:32:54 +00002909 /* We use non-virtual registers as pairs (f12, f14)) */
floriane38f6412012-12-21 17:32:12 +00002910 f12 = make_fpr(12);
floriane38f6412012-12-21 17:32:12 +00002911 f14 = make_fpr(14);
floriane38f6412012-12-21 17:32:12 +00002912
2913 switch (expr->Iex.Unop.op) {
2914 case Iop_D64toD128: conv = S390_DFP_D64_TO_D128; goto convert_dfp;
florian5f034622013-01-13 02:29:05 +00002915 case Iop_I32StoD128: conv = S390_DFP_I32_TO_D128; goto convert_int;
floriana887acd2013-02-08 23:32:54 +00002916 case Iop_I64StoD128: conv = S390_DFP_I64_TO_D128; goto convert_int;
florian5f034622013-01-13 02:29:05 +00002917 case Iop_I32UtoD128: conv = S390_DFP_U32_TO_D128; goto convert_int;
2918 case Iop_I64UtoD128: conv = S390_DFP_U64_TO_D128; goto convert_int;
floriane38f6412012-12-21 17:32:12 +00002919 default:
2920 goto irreducible;
2921 }
2922
2923 convert_dfp:
2924 op = s390_isel_dfp_expr(env, left);
2925 addInstr(env, s390_insn_dfp128_convert_to(16, conv, f12, f14, op));
2926 goto move_dst;
2927
florian5f034622013-01-13 02:29:05 +00002928 convert_int:
2929 op = s390_isel_int_expr(env, left);
2930 addInstr(env, s390_insn_dfp128_convert_to(16, conv, f12, f14, op));
2931 goto move_dst;
2932
floriane38f6412012-12-21 17:32:12 +00002933 move_dst:
2934 /* Move result to virtual destination registers */
2935 *dst_hi = newVRegF(env);
2936 *dst_lo = newVRegF(env);
2937 addInstr(env, s390_insn_move(8, *dst_hi, f12));
2938 addInstr(env, s390_insn_move(8, *dst_lo, f14));
2939 return;
2940 }
2941
2942 default:
2943 goto irreducible;
2944 }
2945
2946 /* We get here if no pattern matched. */
2947 irreducible:
2948 ppIRExpr(expr);
2949 vpanic("s390_isel_dfp128_expr_wrk: cannot reduce tree");
2950
2951}
2952
2953
2954/* Compute a 128-bit value into two 64-bit registers. These may be either
2955 real or virtual regs; in any case they must not be changed by subsequent
2956 code emitted by the caller. */
2957static void
2958s390_isel_dfp128_expr(HReg *dst_hi, HReg *dst_lo, ISelEnv *env, IRExpr *expr)
2959{
2960 s390_isel_dfp128_expr_wrk(dst_hi, dst_lo, env, expr);
2961
2962 /* Sanity checks ... */
2963 vassert(hregIsVirtual(*dst_hi));
2964 vassert(hregIsVirtual(*dst_lo));
2965 vassert(hregClass(*dst_hi) == HRcFlt64);
2966 vassert(hregClass(*dst_lo) == HRcFlt64);
2967}
2968
2969
2970/*---------------------------------------------------------*/
florian12390202012-11-10 22:34:14 +00002971/*--- ISEL: Decimal point expressions (64 bit) ---*/
2972/*---------------------------------------------------------*/
2973
2974static HReg
2975s390_isel_dfp_expr_wrk(ISelEnv *env, IRExpr *expr)
2976{
2977 IRType ty = typeOfIRExpr(env->type_env, expr);
2978 UChar size;
2979
floriane38f6412012-12-21 17:32:12 +00002980 vassert(ty == Ity_D64 || ty == Ity_D32);
florian12390202012-11-10 22:34:14 +00002981
2982 size = sizeofIRType(ty);
2983
2984 switch (expr->tag) {
2985 case Iex_RdTmp:
2986 /* Return the virtual register that holds the temporary. */
2987 return lookupIRTemp(env, expr->Iex.RdTmp.tmp);
2988
2989 /* --------- LOAD --------- */
2990 case Iex_Load: {
2991 HReg dst = newVRegF(env);
2992 s390_amode *am = s390_isel_amode(env, expr->Iex.Load.addr);
2993
2994 if (expr->Iex.Load.end != Iend_BE)
2995 goto irreducible;
2996
2997 addInstr(env, s390_insn_load(size, dst, am));
2998
2999 return dst;
3000 }
3001
3002 /* --------- GET --------- */
3003 case Iex_Get: {
3004 HReg dst = newVRegF(env);
3005 s390_amode *am = s390_amode_for_guest_state(expr->Iex.Get.offset);
3006
3007 addInstr(env, s390_insn_load(size, dst, am));
3008
3009 return dst;
3010 }
3011
floriane38f6412012-12-21 17:32:12 +00003012 /* --------- BINARY OP --------- */
3013 case Iex_Binop: {
3014 IROp op = expr->Iex.Binop.op;
3015 IRExpr *irrm = expr->Iex.Binop.arg1;
3016 IRExpr *left = expr->Iex.Binop.arg2;
3017 HReg h1, dst;
3018 s390_dfp_conv_t conv;
florian78d5ef72013-05-11 15:02:58 +00003019 s390_fp_conv_t fpconv;
floriane38f6412012-12-21 17:32:12 +00003020
3021 switch (op) {
3022 case Iop_D64toD32: conv = S390_DFP_D64_TO_D32; goto convert_dfp;
floriana887acd2013-02-08 23:32:54 +00003023 case Iop_I64StoD64: conv = S390_DFP_I64_TO_D64; goto convert_int;
florian5f034622013-01-13 02:29:05 +00003024 case Iop_I64UtoD64: conv = S390_DFP_U64_TO_D64; goto convert_int;
florian7ab421d2013-06-17 21:03:56 +00003025 case Iop_F32toD32: fpconv = S390_FP_F32_TO_D32; goto convert_bfp;
3026 case Iop_F32toD64: fpconv = S390_FP_F32_TO_D64; goto convert_bfp;
3027 case Iop_F64toD32: fpconv = S390_FP_F64_TO_D32; goto convert_bfp;
florian78d5ef72013-05-11 15:02:58 +00003028 case Iop_F64toD64: fpconv = S390_FP_F64_TO_D64; goto convert_bfp;
florian7ab421d2013-06-17 21:03:56 +00003029 case Iop_F128toD32: fpconv = S390_FP_F128_TO_D32; goto convert_bfp128;
3030 case Iop_F128toD64: fpconv = S390_FP_F128_TO_D64; goto convert_bfp128;
floriane38f6412012-12-21 17:32:12 +00003031
3032 convert_dfp:
3033 h1 = s390_isel_dfp_expr(env, left);
3034 goto convert;
3035
florian5f034622013-01-13 02:29:05 +00003036 convert_int:
3037 h1 = s390_isel_int_expr(env, left);
3038 goto convert;
3039
floriane38f6412012-12-21 17:32:12 +00003040 convert: {
3041 s390_dfp_round_t rounding_mode;
3042 /* convert-from-fixed and load-rounded have a rounding mode field
3043 when the floating point extension facility is installed. */
3044 dst = newVRegF(env);
3045 if (s390_host_has_fpext) {
3046 rounding_mode = get_dfp_rounding_mode(env, irrm);
3047 } else {
3048 set_dfp_rounding_mode_in_fpc(env, irrm);
3049 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
3050 }
3051 addInstr(env, s390_insn_dfp_convert(size, conv, dst, h1,
3052 rounding_mode));
3053 return dst;
3054 }
floriane38f6412012-12-21 17:32:12 +00003055
florian78d5ef72013-05-11 15:02:58 +00003056 convert_bfp: {
3057 s390_dfp_round_t rm;
3058 HReg f0, f4, r1; /* real registers used by PFPO */
3059
3060 f4 = make_fpr(4); /* source */
3061 f0 = make_fpr(0); /* destination */
3062 r1 = make_gpr(1); /* GPR #1 clobbered */
3063 h1 = s390_isel_float_expr(env, left);
3064 dst = newVRegF(env);
3065 rm = get_dfp_rounding_mode(env, irrm);
3066 /* operand --> f4 */
3067 addInstr(env, s390_insn_move(8, f4, h1));
3068 addInstr(env, s390_insn_fp_convert(size, fpconv, f0, f4, r1, rm));
3069 /* f0 --> destination */
3070 addInstr(env, s390_insn_move(8, dst, f0));
3071 return dst;
3072 }
3073
florian7ab421d2013-06-17 21:03:56 +00003074 convert_bfp128: {
3075 s390_dfp_round_t rm;
3076 HReg op_hi, op_lo;
3077 HReg f0, f4, f6, r1; /* real registers used by PFPO */
3078
3079 f4 = make_fpr(4); /* source */
3080 f6 = make_fpr(6); /* source */
3081 f0 = make_fpr(0); /* destination */
3082 r1 = make_gpr(1); /* GPR #1 clobbered */
3083 s390_isel_float128_expr(&op_hi, &op_lo, env, left);
3084 dst = newVRegF(env);
3085 rm = get_dfp_rounding_mode(env, irrm);
3086 /* operand --> (f4, f6) */
3087 addInstr(env, s390_insn_move(8, f4, op_hi));
3088 addInstr(env, s390_insn_move(8, f6, op_lo));
3089 addInstr(env, s390_insn_fp128_convert(16, fpconv, f0, INVALID_HREG,
3090 f4, f6, r1, rm));
3091 /* f0 --> destination */
3092 addInstr(env, s390_insn_move(8, dst, f0));
3093 return dst;
3094 }
3095
floriane38f6412012-12-21 17:32:12 +00003096 case Iop_D128toD64: {
floriana2039c52013-12-10 16:51:15 +00003097 HReg op_hi, op_lo, f12, f13, f14, f15;
floriane38f6412012-12-21 17:32:12 +00003098 s390_dfp_round_t rounding_mode;
3099
3100 conv = S390_DFP_D128_TO_D64;
3101
3102 s390_isel_dfp128_expr(&op_hi, &op_lo, env, left);
3103
floriana2039c52013-12-10 16:51:15 +00003104 /* We use non-virtual registers as pairs (f13, f15) and (f12, f14) */
3105 f12 = make_fpr(12);
floriane38f6412012-12-21 17:32:12 +00003106 f13 = make_fpr(13);
floriana2039c52013-12-10 16:51:15 +00003107 f14 = make_fpr(14);
floriane38f6412012-12-21 17:32:12 +00003108 f15 = make_fpr(15);
3109
3110 /* operand --> (f13, f15) */
3111 addInstr(env, s390_insn_move(8, f13, op_hi));
3112 addInstr(env, s390_insn_move(8, f15, op_lo));
3113
floriana2039c52013-12-10 16:51:15 +00003114 /* result --> (f12, f14) */
3115
floriane38f6412012-12-21 17:32:12 +00003116 /* load-rounded has a rounding mode field when the floating point
3117 extension facility is installed. */
3118 if (s390_host_has_fpext) {
3119 rounding_mode = get_dfp_rounding_mode(env, irrm);
3120 } else {
3121 set_dfp_rounding_mode_in_fpc(env, irrm);
3122 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
3123 }
floriana2039c52013-12-10 16:51:15 +00003124 addInstr(env, s390_insn_dfp128_convert_from(size, conv, f12, f14,
3125 f13, f15, rounding_mode));
3126 dst = newVRegF(env);
3127 addInstr(env, s390_insn_move(8, dst, f12));
3128
floriane38f6412012-12-21 17:32:12 +00003129 return dst;
3130 }
3131
florian1b901d42013-01-01 22:19:24 +00003132 case Iop_ShlD64:
florian5c539732013-02-14 14:27:12 +00003133 case Iop_ShrD64:
3134 case Iop_InsertExpD64: {
florian1b901d42013-01-01 22:19:24 +00003135 HReg op2;
3136 HReg op3;
florian5c539732013-02-14 14:27:12 +00003137 IRExpr *dfp_op;
3138 IRExpr *int_op;
florian1b901d42013-01-01 22:19:24 +00003139 s390_dfp_intop_t intop;
florian1b901d42013-01-01 22:19:24 +00003140
3141 switch (expr->Iex.Binop.op) {
florian5c539732013-02-14 14:27:12 +00003142 case Iop_ShlD64: /* (D64, I64) -> D64 */
3143 intop = S390_DFP_SHIFT_LEFT;
3144 dfp_op = expr->Iex.Binop.arg1;
3145 int_op = expr->Iex.Binop.arg2;
3146 break;
3147 case Iop_ShrD64: /* (D64, I64) -> D64 */
3148 intop = S390_DFP_SHIFT_RIGHT;
3149 dfp_op = expr->Iex.Binop.arg1;
3150 int_op = expr->Iex.Binop.arg2;
3151 break;
3152 case Iop_InsertExpD64: /* (I64, D64) -> D64 */
3153 intop = S390_DFP_INSERT_EXP;
3154 int_op = expr->Iex.Binop.arg1;
3155 dfp_op = expr->Iex.Binop.arg2;
3156 break;
florian1b901d42013-01-01 22:19:24 +00003157 default: goto irreducible;
3158 }
3159
florian5c539732013-02-14 14:27:12 +00003160 op2 = s390_isel_int_expr(env, int_op);
3161 op3 = s390_isel_dfp_expr(env, dfp_op);
florian1b901d42013-01-01 22:19:24 +00003162 dst = newVRegF(env);
3163
3164 addInstr(env, s390_insn_dfp_intop(size, intop, dst, op2, op3));
3165 return dst;
3166 }
3167
3168 default:
3169 goto irreducible;
floriane38f6412012-12-21 17:32:12 +00003170 }
3171 }
3172
3173 /* --------- UNARY OP --------- */
3174 case Iex_Unop: {
3175 IROp op = expr->Iex.Unop.op;
3176 IRExpr *left = expr->Iex.Unop.arg;
3177 s390_dfp_conv_t conv;
3178 HReg h1, dst;
3179
3180 if (op == Iop_D128HItoD64 || op == Iop_D128LOtoD64) {
3181 HReg dst_hi, dst_lo;
3182
3183 s390_isel_dfp128_expr(&dst_hi, &dst_lo, env, left);
3184 return op == Iop_D128LOtoD64 ? dst_lo : dst_hi;
3185 }
3186
3187 if (op == Iop_ReinterpI64asD64) {
3188 dst = newVRegF(env);
3189 h1 = s390_isel_int_expr(env, left); /* Process the operand */
3190 addInstr(env, s390_insn_move(size, dst, h1));
3191
3192 return dst;
3193 }
3194
3195 switch (op) {
3196 case Iop_D32toD64: conv = S390_DFP_D32_TO_D64; goto convert_dfp1;
florian5f034622013-01-13 02:29:05 +00003197 case Iop_I32StoD64: conv = S390_DFP_I32_TO_D64; goto convert_int1;
3198 case Iop_I32UtoD64: conv = S390_DFP_U32_TO_D64; goto convert_int1;
floriane38f6412012-12-21 17:32:12 +00003199
3200 convert_dfp1:
3201 h1 = s390_isel_dfp_expr(env, left);
3202 goto convert1;
3203
florian5f034622013-01-13 02:29:05 +00003204 convert_int1:
3205 h1 = s390_isel_int_expr(env, left);
3206 goto convert1;
3207
floriane38f6412012-12-21 17:32:12 +00003208 convert1:
3209 dst = newVRegF(env);
3210 /* No rounding mode is needed for these conversions. Just stick
3211 one in. It won't be used later on. */
3212 addInstr(env, s390_insn_dfp_convert(size, conv, dst, h1,
3213 S390_DFP_ROUND_NEAREST_EVEN_4));
3214 return dst;
3215
3216 default:
3217 goto irreducible;
3218 }
3219 }
3220
florian12390202012-11-10 22:34:14 +00003221 /* --------- TERNARY OP --------- */
3222 case Iex_Triop: {
3223 IRTriop *triop = expr->Iex.Triop.details;
3224 IROp op = triop->op;
3225 IRExpr *irrm = triop->arg1;
3226 IRExpr *left = triop->arg2;
3227 IRExpr *right = triop->arg3;
3228 s390_dfp_round_t rounding_mode;
3229 s390_dfp_binop_t dfpop;
3230 HReg op2, op3, dst;
3231
florian12390202012-11-10 22:34:14 +00003232 switch (op) {
florian5c539732013-02-14 14:27:12 +00003233 case Iop_AddD64: dfpop = S390_DFP_ADD; goto evaluate_dfp;
3234 case Iop_SubD64: dfpop = S390_DFP_SUB; goto evaluate_dfp;
3235 case Iop_MulD64: dfpop = S390_DFP_MUL; goto evaluate_dfp;
3236 case Iop_DivD64: dfpop = S390_DFP_DIV; goto evaluate_dfp;
3237 case Iop_QuantizeD64: dfpop = S390_DFP_QUANTIZE; goto evaluate_dfp;
3238
3239 evaluate_dfp: {
3240 op2 = s390_isel_dfp_expr(env, left); /* Process 1st operand */
3241 op3 = s390_isel_dfp_expr(env, right); /* Process 2nd operand */
3242 dst = newVRegF(env);
3243 /* DFP arithmetic ops take rounding mode only when fpext is
3244 installed. But, DFP quantize operation takes rm irrespective
3245 of fpext facility . */
3246 if (s390_host_has_fpext || dfpop == S390_DFP_QUANTIZE) {
3247 rounding_mode = get_dfp_rounding_mode(env, irrm);
3248 } else {
3249 set_dfp_rounding_mode_in_fpc(env, irrm);
3250 rounding_mode = S390_DFP_ROUND_PER_FPC_0;
3251 }
3252 addInstr(env, s390_insn_dfp_binop(size, dfpop, dst, op2, op3,
3253 rounding_mode));
3254 return dst;
3255 }
3256
3257 case Iop_SignificanceRoundD64:
3258 op2 = s390_isel_int_expr(env, left); /* Process 1st operand */
3259 op3 = s390_isel_dfp_expr(env, right); /* Process 2nd operand */
3260 dst = newVRegF(env);
3261 rounding_mode = get_dfp_rounding_mode(env, irrm);
3262 addInstr(env, s390_insn_dfp_reround(size, dst, op2, op3,
3263 rounding_mode));
3264 return dst;
3265
florian12390202012-11-10 22:34:14 +00003266 default:
3267 goto irreducible;
3268 }
florian12390202012-11-10 22:34:14 +00003269 }
3270
3271 default:
3272 goto irreducible;
3273 }
3274
3275 /* We get here if no pattern matched. */
3276 irreducible:
3277 ppIRExpr(expr);
3278 vpanic("s390_isel_dfp_expr: cannot reduce tree");
3279}
3280
3281static HReg
3282s390_isel_dfp_expr(ISelEnv *env, IRExpr *expr)
3283{
3284 HReg dst = s390_isel_dfp_expr_wrk(env, expr);
3285
3286 /* Sanity checks ... */
3287 vassert(hregClass(dst) == HRcFlt64);
3288 vassert(hregIsVirtual(dst));
3289
3290 return dst;
3291}
3292
3293
3294/*---------------------------------------------------------*/
sewardj2019a972011-03-07 16:04:07 +00003295/*--- ISEL: Condition Code ---*/
3296/*---------------------------------------------------------*/
3297
3298/* This function handles all operators that produce a 1-bit result */
3299static s390_cc_t
3300s390_isel_cc(ISelEnv *env, IRExpr *cond)
3301{
3302 UChar size;
3303
3304 vassert(typeOfIRExpr(env->type_env, cond) == Ity_I1);
3305
3306 /* Constant: either 1 or 0 */
3307 if (cond->tag == Iex_Const) {
3308 vassert(cond->Iex.Const.con->tag == Ico_U1);
3309 vassert(cond->Iex.Const.con->Ico.U1 == True
3310 || cond->Iex.Const.con->Ico.U1 == False);
3311
3312 return cond->Iex.Const.con->Ico.U1 == True ? S390_CC_ALWAYS : S390_CC_NEVER;
3313 }
3314
3315 /* Variable: values are 1 or 0 */
3316 if (cond->tag == Iex_RdTmp) {
3317 IRTemp tmp = cond->Iex.RdTmp.tmp;
3318 HReg reg = lookupIRTemp(env, tmp);
3319
3320 /* Load-and-test does not modify REG; so this is OK. */
3321 if (typeOfIRTemp(env->type_env, tmp) == Ity_I1)
3322 size = 4;
3323 else
3324 size = sizeofIRType(typeOfIRTemp(env->type_env, tmp));
3325 addInstr(env, s390_insn_test(size, s390_opnd_reg(reg)));
3326 return S390_CC_NE;
3327 }
3328
3329 /* Unary operators */
3330 if (cond->tag == Iex_Unop) {
3331 IRExpr *arg = cond->Iex.Unop.arg;
3332
3333 switch (cond->Iex.Unop.op) {
3334 case Iop_Not1: /* Not1(cond) */
3335 /* Generate code for EXPR, and negate the test condition */
3336 return s390_cc_invert(s390_isel_cc(env, arg));
3337
3338 /* Iop_32/64to1 select the LSB from their operand */
3339 case Iop_32to1:
3340 case Iop_64to1: {
florianf366a802012-08-03 00:42:18 +00003341 HReg dst = newVRegI(env);
3342 HReg h1 = s390_isel_int_expr(env, arg);
sewardj2019a972011-03-07 16:04:07 +00003343
3344 size = sizeofIRType(typeOfIRExpr(env->type_env, arg));
3345
florianf366a802012-08-03 00:42:18 +00003346 addInstr(env, s390_insn_move(size, dst, h1));
sewardj2019a972011-03-07 16:04:07 +00003347 addInstr(env, s390_insn_alu(size, S390_ALU_AND, dst, s390_opnd_imm(1)));
3348 addInstr(env, s390_insn_test(size, s390_opnd_reg(dst)));
3349 return S390_CC_NE;
3350 }
3351
3352 case Iop_CmpNEZ8:
3353 case Iop_CmpNEZ16: {
3354 s390_opnd_RMI src;
3355 s390_unop_t op;
3356 HReg dst;
3357
3358 op = (cond->Iex.Unop.op == Iop_CmpNEZ8) ? S390_ZERO_EXTEND_8
3359 : S390_ZERO_EXTEND_16;
3360 dst = newVRegI(env);
3361 src = s390_isel_int_expr_RMI(env, arg);
3362 addInstr(env, s390_insn_unop(4, op, dst, src));
3363 addInstr(env, s390_insn_test(4, s390_opnd_reg(dst)));
3364 return S390_CC_NE;
3365 }
3366
3367 case Iop_CmpNEZ32:
3368 case Iop_CmpNEZ64: {
3369 s390_opnd_RMI src;
3370
3371 src = s390_isel_int_expr_RMI(env, arg);
3372 size = sizeofIRType(typeOfIRExpr(env->type_env, arg));
3373 addInstr(env, s390_insn_test(size, src));
3374 return S390_CC_NE;
3375 }
3376
3377 default:
3378 goto fail;
3379 }
3380 }
3381
3382 /* Binary operators */
3383 if (cond->tag == Iex_Binop) {
3384 IRExpr *arg1 = cond->Iex.Binop.arg1;
3385 IRExpr *arg2 = cond->Iex.Binop.arg2;
3386 HReg reg1, reg2;
3387
3388 size = sizeofIRType(typeOfIRExpr(env->type_env, arg1));
3389
3390 switch (cond->Iex.Binop.op) {
3391 s390_unop_t op;
3392 s390_cc_t result;
3393
3394 case Iop_CmpEQ8:
3395 case Iop_CasCmpEQ8:
3396 op = S390_ZERO_EXTEND_8;
3397 result = S390_CC_E;
3398 goto do_compare_ze;
3399
3400 case Iop_CmpNE8:
3401 case Iop_CasCmpNE8:
3402 op = S390_ZERO_EXTEND_8;
3403 result = S390_CC_NE;
3404 goto do_compare_ze;
3405
3406 case Iop_CmpEQ16:
3407 case Iop_CasCmpEQ16:
3408 op = S390_ZERO_EXTEND_16;
3409 result = S390_CC_E;
3410 goto do_compare_ze;
3411
3412 case Iop_CmpNE16:
3413 case Iop_CasCmpNE16:
3414 op = S390_ZERO_EXTEND_16;
3415 result = S390_CC_NE;
3416 goto do_compare_ze;
3417
3418 do_compare_ze: {
3419 s390_opnd_RMI op1, op2;
3420
3421 op1 = s390_isel_int_expr_RMI(env, arg1);
3422 reg1 = newVRegI(env);
3423 addInstr(env, s390_insn_unop(4, op, reg1, op1));
3424
3425 op2 = s390_isel_int_expr_RMI(env, arg2);
3426 reg2 = newVRegI(env);
3427 addInstr(env, s390_insn_unop(4, op, reg2, op2)); /* zero extend */
3428
3429 op2 = s390_opnd_reg(reg2);
3430 addInstr(env, s390_insn_compare(4, reg1, op2, False));
3431
3432 return result;
3433 }
3434
3435 case Iop_CmpEQ32:
3436 case Iop_CmpEQ64:
3437 case Iop_CasCmpEQ32:
3438 case Iop_CasCmpEQ64:
3439 result = S390_CC_E;
3440 goto do_compare;
3441
3442 case Iop_CmpNE32:
3443 case Iop_CmpNE64:
3444 case Iop_CasCmpNE32:
3445 case Iop_CasCmpNE64:
3446 result = S390_CC_NE;
3447 goto do_compare;
3448
3449 do_compare: {
3450 HReg op1;
3451 s390_opnd_RMI op2;
3452
3453 order_commutative_operands(arg1, arg2);
3454
3455 op1 = s390_isel_int_expr(env, arg1);
3456 op2 = s390_isel_int_expr_RMI(env, arg2);
3457
3458 addInstr(env, s390_insn_compare(size, op1, op2, False));
3459
3460 return result;
3461 }
3462
3463 case Iop_CmpLT32S:
3464 case Iop_CmpLE32S:
3465 case Iop_CmpLT64S:
3466 case Iop_CmpLE64S: {
3467 HReg op1;
3468 s390_opnd_RMI op2;
3469
3470 op1 = s390_isel_int_expr(env, arg1);
3471 op2 = s390_isel_int_expr_RMI(env, arg2);
3472
3473 addInstr(env, s390_insn_compare(size, op1, op2, True));
3474
3475 return (cond->Iex.Binop.op == Iop_CmpLT32S ||
3476 cond->Iex.Binop.op == Iop_CmpLT64S) ? S390_CC_L : S390_CC_LE;
3477 }
3478
3479 case Iop_CmpLT32U:
3480 case Iop_CmpLE32U:
3481 case Iop_CmpLT64U:
3482 case Iop_CmpLE64U: {
3483 HReg op1;
3484 s390_opnd_RMI op2;
3485
3486 op1 = s390_isel_int_expr(env, arg1);
3487 op2 = s390_isel_int_expr_RMI(env, arg2);
3488
3489 addInstr(env, s390_insn_compare(size, op1, op2, False));
3490
3491 return (cond->Iex.Binop.op == Iop_CmpLT32U ||
3492 cond->Iex.Binop.op == Iop_CmpLT64U) ? S390_CC_L : S390_CC_LE;
3493 }
3494
3495 default:
3496 goto fail;
3497 }
3498 }
3499
3500 fail:
3501 ppIRExpr(cond);
3502 vpanic("s390_isel_cc: unexpected operator");
3503}
3504
3505
3506/*---------------------------------------------------------*/
3507/*--- ISEL: Statements ---*/
3508/*---------------------------------------------------------*/
3509
3510static void
3511s390_isel_stmt(ISelEnv *env, IRStmt *stmt)
3512{
3513 if (vex_traceflags & VEX_TRACE_VCODE) {
3514 vex_printf("\n -- ");
3515 ppIRStmt(stmt);
3516 vex_printf("\n");
3517 }
3518
3519 switch (stmt->tag) {
3520
3521 /* --------- STORE --------- */
3522 case Ist_Store: {
3523 IRType tyd = typeOfIRExpr(env->type_env, stmt->Ist.Store.data);
3524 s390_amode *am;
3525 HReg src;
3526
3527 if (stmt->Ist.Store.end != Iend_BE) goto stmt_fail;
3528
3529 am = s390_isel_amode(env, stmt->Ist.Store.addr);
3530
3531 switch (tyd) {
3532 case Ity_I8:
3533 case Ity_I16:
3534 case Ity_I32:
3535 case Ity_I64:
florianf85fe3e2012-12-22 02:28:25 +00003536 /* fixs390: We could check for INSN_MADD here. */
florian09bbba82012-12-11 04:09:43 +00003537 if (am->tag == S390_AMODE_B12 &&
florianb93348d2012-12-27 00:59:43 +00003538 stmt->Ist.Store.data->tag == Iex_Const) {
3539 ULong value =
3540 get_const_value_as_ulong(stmt->Ist.Store.data->Iex.Const.con);
3541 addInstr(env, s390_insn_mimm(sizeofIRType(tyd), am, value));
florian09bbba82012-12-11 04:09:43 +00003542 return;
3543 }
floriancec3a8a2013-02-02 00:16:58 +00003544 /* Check whether we can use a memcpy here. Currently, the restriction
3545 is that both amodes need to be B12, so MVC can be emitted.
3546 We do not consider a store whose data expression is a load because
3547 we don't want to deal with overlapping locations. */
3548 /* store(get) never overlaps*/
3549 if (am->tag == S390_AMODE_B12 &&
3550 stmt->Ist.Store.data->tag == Iex_Get) {
3551 UInt offset = stmt->Ist.Store.data->Iex.Get.offset;
3552 s390_amode *from = s390_amode_for_guest_state(offset);
3553 addInstr(env, s390_insn_memcpy(sizeofIRType(tyd), am, from));
3554 return;
3555 }
3556 /* General case: compile data into a register */
sewardj2019a972011-03-07 16:04:07 +00003557 src = s390_isel_int_expr(env, stmt->Ist.Store.data);
3558 break;
3559
3560 case Ity_F32:
3561 case Ity_F64:
3562 src = s390_isel_float_expr(env, stmt->Ist.Store.data);
3563 break;
3564
florianeb981ae2012-12-21 18:55:03 +00003565 case Ity_D32:
3566 case Ity_D64:
3567 src = s390_isel_dfp_expr(env, stmt->Ist.Store.data);
3568 break;
3569
sewardj2019a972011-03-07 16:04:07 +00003570 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003571 case Ity_D128:
sewardj2019a972011-03-07 16:04:07 +00003572 /* Cannot occur. No such instruction */
floriane38f6412012-12-21 17:32:12 +00003573 vpanic("Ist_Store with 128-bit floating point data");
sewardj2019a972011-03-07 16:04:07 +00003574
3575 default:
3576 goto stmt_fail;
3577 }
3578
3579 addInstr(env, s390_insn_store(sizeofIRType(tyd), am, src));
3580 return;
3581 }
3582
3583 /* --------- PUT --------- */
3584 case Ist_Put: {
3585 IRType tyd = typeOfIRExpr(env->type_env, stmt->Ist.Put.data);
3586 HReg src;
3587 s390_amode *am;
florianad43b3a2012-02-20 15:01:14 +00003588 ULong new_value, old_value, difference;
sewardj2019a972011-03-07 16:04:07 +00003589
florianad43b3a2012-02-20 15:01:14 +00003590 /* Detect updates to certain guest registers. We track the contents
3591 of those registers as long as they contain constants. If the new
3592 constant is either zero or in the 8-bit neighbourhood of the
3593 current value we can use a memory-to-memory insn to do the update. */
3594
3595 Int offset = stmt->Ist.Put.offset;
3596
3597 /* Check necessary conditions:
3598 (1) must be one of the registers we care about
3599 (2) assigned value must be a constant */
3600 Int guest_reg = get_guest_reg(offset);
3601
3602 if (guest_reg == GUEST_UNKNOWN) goto not_special;
3603
florianad43b3a2012-02-20 15:01:14 +00003604 if (stmt->Ist.Put.data->tag != Iex_Const) {
3605 /* Invalidate guest register contents */
3606 env->old_value_valid[guest_reg] = False;
3607 goto not_special;
3608 }
3609
cborntraaf7ad282012-08-08 14:11:33 +00003610 /* We can only handle Ity_I64, but the CC_DEPS field can have floats */
3611 if (tyd != Ity_I64)
3612 goto not_special;
florianad43b3a2012-02-20 15:01:14 +00003613
cborntraaf7ad282012-08-08 14:11:33 +00003614 /* OK. Necessary conditions are satisfied. */
florianad43b3a2012-02-20 15:01:14 +00003615
3616 old_value = env->old_value[guest_reg];
3617 new_value = stmt->Ist.Put.data->Iex.Const.con->Ico.U64;
3618 env->old_value[guest_reg] = new_value;
3619
3620 Bool old_value_is_valid = env->old_value_valid[guest_reg];
3621 env->old_value_valid[guest_reg] = True;
3622
3623 /* If the register already contains the new value, there is nothing
florian9f42ab42012-12-23 01:09:16 +00003624 to do here. */
florianad43b3a2012-02-20 15:01:14 +00003625 if (old_value_is_valid && new_value == old_value) {
florian9f42ab42012-12-23 01:09:16 +00003626 return;
florianad43b3a2012-02-20 15:01:14 +00003627 }
3628
florianad43b3a2012-02-20 15:01:14 +00003629 if (old_value_is_valid == False) goto not_special;
3630
3631 /* If the new value is in the neighbourhood of the old value
3632 we can use a memory-to-memory insn */
3633 difference = new_value - old_value;
3634
3635 if (s390_host_has_gie && ulong_fits_signed_8bit(difference)) {
florianf85fe3e2012-12-22 02:28:25 +00003636 am = s390_amode_for_guest_state(offset);
3637 addInstr(env, s390_insn_madd(sizeofIRType(tyd), am,
florianad43b3a2012-02-20 15:01:14 +00003638 (difference & 0xFF), new_value));
3639 return;
3640 }
3641
florianb93348d2012-12-27 00:59:43 +00003642 /* If the high word is the same it is sufficient to load the low word. */
florianad43b3a2012-02-20 15:01:14 +00003643 if ((old_value >> 32) == (new_value >> 32)) {
florianf85fe3e2012-12-22 02:28:25 +00003644 am = s390_amode_for_guest_state(offset + 4);
florianb93348d2012-12-27 00:59:43 +00003645 addInstr(env, s390_insn_mimm(4, am, new_value & 0xFFFFFFFF));
florianad43b3a2012-02-20 15:01:14 +00003646 return;
3647 }
3648
3649 /* No special case applies... fall through */
3650
3651 not_special:
florianb93348d2012-12-27 00:59:43 +00003652 am = s390_amode_for_guest_state(offset);
sewardj2019a972011-03-07 16:04:07 +00003653
3654 switch (tyd) {
3655 case Ity_I8:
3656 case Ity_I16:
3657 case Ity_I32:
3658 case Ity_I64:
florian09bbba82012-12-11 04:09:43 +00003659 if (am->tag == S390_AMODE_B12 &&
florianb93348d2012-12-27 00:59:43 +00003660 stmt->Ist.Put.data->tag == Iex_Const) {
3661 ULong value =
3662 get_const_value_as_ulong(stmt->Ist.Put.data->Iex.Const.con);
3663 addInstr(env, s390_insn_mimm(sizeofIRType(tyd), am, value));
florian09bbba82012-12-11 04:09:43 +00003664 return;
3665 }
floriancec3a8a2013-02-02 00:16:58 +00003666 /* Check whether we can use a memcpy here. Currently, the restriction
3667 is that both amodes need to be B12, so MVC can be emitted. */
3668 /* put(load) never overlaps */
3669 if (am->tag == S390_AMODE_B12 &&
3670 stmt->Ist.Put.data->tag == Iex_Load) {
3671 if (stmt->Ist.Put.data->Iex.Load.end != Iend_BE) goto stmt_fail;
3672 IRExpr *data = stmt->Ist.Put.data->Iex.Load.addr;
3673 s390_amode *from = s390_isel_amode(env, data);
3674 UInt size = sizeofIRType(tyd);
3675
3676 if (from->tag == S390_AMODE_B12) {
3677 /* Source can be compiled into a B12 amode. */
3678 addInstr(env, s390_insn_memcpy(size, am, from));
3679 return;
3680 }
3681
3682 src = newVRegI(env);
3683 addInstr(env, s390_insn_load(size, src, from));
3684 break;
3685 }
3686 /* put(get) */
3687 if (am->tag == S390_AMODE_B12 &&
3688 stmt->Ist.Put.data->tag == Iex_Get) {
3689 UInt put_offset = am->d;
3690 UInt get_offset = stmt->Ist.Put.data->Iex.Get.offset;
3691 UInt size = sizeofIRType(tyd);
3692 /* don't memcpy in case of overlap */
3693 if (put_offset + size <= get_offset ||
3694 get_offset + size <= put_offset) {
3695 s390_amode *from = s390_amode_for_guest_state(get_offset);
3696 addInstr(env, s390_insn_memcpy(size, am, from));
3697 return;
3698 }
3699 goto no_memcpy_put;
3700 }
3701 /* General case: compile data into a register */
3702no_memcpy_put:
sewardj2019a972011-03-07 16:04:07 +00003703 src = s390_isel_int_expr(env, stmt->Ist.Put.data);
3704 break;
3705
3706 case Ity_F32:
3707 case Ity_F64:
3708 src = s390_isel_float_expr(env, stmt->Ist.Put.data);
3709 break;
3710
3711 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00003712 case Ity_D128:
3713 /* Does not occur. See function put_(f|d)pr_pair. */
3714 vpanic("Ist_Put with 128-bit floating point data");
sewardj2019a972011-03-07 16:04:07 +00003715
floriane38f6412012-12-21 17:32:12 +00003716 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003717 case Ity_D64:
3718 src = s390_isel_dfp_expr(env, stmt->Ist.Put.data);
3719 break;
3720
sewardj2019a972011-03-07 16:04:07 +00003721 default:
3722 goto stmt_fail;
3723 }
3724
3725 addInstr(env, s390_insn_store(sizeofIRType(tyd), am, src));
3726 return;
3727 }
3728
3729 /* --------- TMP --------- */
3730 case Ist_WrTmp: {
3731 IRTemp tmp = stmt->Ist.WrTmp.tmp;
3732 IRType tyd = typeOfIRTemp(env->type_env, tmp);
3733 HReg src, dst;
3734
3735 switch (tyd) {
3736 case Ity_I128: {
3737 HReg dst_hi, dst_lo, res_hi, res_lo;
3738
3739 s390_isel_int128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3740 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3741
3742 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3743 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3744 return;
3745 }
3746
3747 case Ity_I8:
3748 case Ity_I16:
3749 case Ity_I32:
3750 case Ity_I64:
3751 src = s390_isel_int_expr(env, stmt->Ist.WrTmp.data);
3752 dst = lookupIRTemp(env, tmp);
3753 break;
3754
3755 case Ity_I1: {
3756 s390_cc_t cond = s390_isel_cc(env, stmt->Ist.WrTmp.data);
3757 dst = lookupIRTemp(env, tmp);
3758 addInstr(env, s390_insn_cc2bool(dst, cond));
3759 return;
3760 }
3761
3762 case Ity_F32:
3763 case Ity_F64:
3764 src = s390_isel_float_expr(env, stmt->Ist.WrTmp.data);
3765 dst = lookupIRTemp(env, tmp);
3766 break;
3767
3768 case Ity_F128: {
3769 HReg dst_hi, dst_lo, res_hi, res_lo;
3770
3771 s390_isel_float128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3772 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3773
3774 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3775 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3776 return;
3777 }
3778
floriane38f6412012-12-21 17:32:12 +00003779 case Ity_D32:
florian12390202012-11-10 22:34:14 +00003780 case Ity_D64:
3781 src = s390_isel_dfp_expr(env, stmt->Ist.WrTmp.data);
3782 dst = lookupIRTemp(env, tmp);
3783 break;
3784
floriane38f6412012-12-21 17:32:12 +00003785 case Ity_D128: {
3786 HReg dst_hi, dst_lo, res_hi, res_lo;
3787
3788 s390_isel_dfp128_expr(&res_hi, &res_lo, env, stmt->Ist.WrTmp.data);
3789 lookupIRTemp128(&dst_hi, &dst_lo, env, tmp);
3790
3791 addInstr(env, s390_insn_move(8, dst_hi, res_hi));
3792 addInstr(env, s390_insn_move(8, dst_lo, res_lo));
3793 return;
3794 }
3795
sewardj2019a972011-03-07 16:04:07 +00003796 default:
3797 goto stmt_fail;
3798 }
3799
3800 addInstr(env, s390_insn_move(sizeofIRType(tyd), dst, src));
3801 return;
3802 }
3803
3804 /* --------- Call to DIRTY helper --------- */
3805 case Ist_Dirty: {
3806 IRType retty;
3807 IRDirty* d = stmt->Ist.Dirty.details;
florian01ed6e72012-05-27 16:52:43 +00003808 HReg dst;
sewardj74142b82013-08-08 10:28:59 +00003809 RetLoc rloc = mk_RetLoc_INVALID();
3810 UInt addToSp = 0;
florianad43b3a2012-02-20 15:01:14 +00003811 Int i;
3812
3813 /* Invalidate tracked values of those guest state registers that are
3814 modified by this helper. */
3815 for (i = 0; i < d->nFxState; ++i) {
sewardjc9069f22012-06-01 16:09:50 +00003816 /* JRS 1 June 2012: AFAICS, s390 guest doesn't use 'repeat'
3817 descriptors in guest state effect descriptions. Hence: */
3818 vassert(d->fxState[i].nRepeats == 0 && d->fxState[i].repeatLen == 0);
florianad43b3a2012-02-20 15:01:14 +00003819 if ((d->fxState[i].fx == Ifx_Write || d->fxState[i].fx == Ifx_Modify)) {
3820 Int guest_reg = get_guest_reg(d->fxState[i].offset);
3821 if (guest_reg != GUEST_UNKNOWN)
3822 env->old_value_valid[guest_reg] = False;
3823 }
3824 }
sewardj2019a972011-03-07 16:04:07 +00003825
florian01ed6e72012-05-27 16:52:43 +00003826 if (d->tmp == IRTemp_INVALID) {
3827 /* No return value. */
sewardj74142b82013-08-08 10:28:59 +00003828 retty = Ity_INVALID;
3829 doHelperCall(&addToSp, &rloc, env, d->guard, d->cee, retty,
3830 d->args);
3831 vassert(is_sane_RetLoc(rloc));
3832 vassert(rloc.pri == RLPri_None);
3833 vassert(addToSp == 0);
3834
sewardj2019a972011-03-07 16:04:07 +00003835 return;
florian01ed6e72012-05-27 16:52:43 +00003836 }
sewardj2019a972011-03-07 16:04:07 +00003837
3838 retty = typeOfIRTemp(env->type_env, d->tmp);
3839 if (retty == Ity_I64 || retty == Ity_I32
3840 || retty == Ity_I16 || retty == Ity_I8) {
florian297b6062012-05-08 20:16:17 +00003841 /* Move the returned value to the destination register */
sewardj74142b82013-08-08 10:28:59 +00003842 HReg ret = make_gpr(S390_REGNO_RETURN_VALUE);
3843
florian01ed6e72012-05-27 16:52:43 +00003844 dst = lookupIRTemp(env, d->tmp);
sewardj74142b82013-08-08 10:28:59 +00003845 doHelperCall(&addToSp, &rloc, env, d->guard, d->cee, retty,
3846 d->args);
3847 vassert(is_sane_RetLoc(rloc));
3848 vassert(rloc.pri == RLPri_Int);
3849 vassert(addToSp == 0);
3850 addInstr(env, s390_insn_move(sizeof(ULong), dst, ret));
3851
sewardj2019a972011-03-07 16:04:07 +00003852 return;
3853 }
3854 break;
3855 }
3856
3857 case Ist_CAS:
3858 if (stmt->Ist.CAS.details->oldHi == IRTemp_INVALID) {
3859 IRCAS *cas = stmt->Ist.CAS.details;
florian406ac942014-11-22 20:10:21 +00003860 s390_amode *op2 = s390_isel_amode_b12_b20(env, cas->addr);
sewardj2019a972011-03-07 16:04:07 +00003861 HReg op3 = s390_isel_int_expr(env, cas->dataLo); /* new value */
3862 HReg op1 = s390_isel_int_expr(env, cas->expdLo); /* expected value */
3863 HReg old = lookupIRTemp(env, cas->oldLo);
3864
3865 if (typeOfIRTemp(env->type_env, cas->oldLo) == Ity_I32) {
3866 addInstr(env, s390_insn_cas(4, op1, op2, op3, old));
3867 } else {
3868 addInstr(env, s390_insn_cas(8, op1, op2, op3, old));
3869 }
3870 return;
3871 } else {
florian448cbba2012-06-06 02:26:01 +00003872 IRCAS *cas = stmt->Ist.CAS.details;
florian406ac942014-11-22 20:10:21 +00003873 s390_amode *op2 = s390_isel_amode_b12_b20(env, cas->addr);
florian448cbba2012-06-06 02:26:01 +00003874 HReg r8, r9, r10, r11, r1;
3875 HReg op3_high = s390_isel_int_expr(env, cas->dataHi); /* new value */
3876 HReg op3_low = s390_isel_int_expr(env, cas->dataLo); /* new value */
3877 HReg op1_high = s390_isel_int_expr(env, cas->expdHi); /* expected value */
3878 HReg op1_low = s390_isel_int_expr(env, cas->expdLo); /* expected value */
3879 HReg old_low = lookupIRTemp(env, cas->oldLo);
3880 HReg old_high = lookupIRTemp(env, cas->oldHi);
3881
3882 /* Use non-virtual registers r8 and r9 as pair for op1
3883 and move op1 there */
3884 r8 = make_gpr(8);
3885 r9 = make_gpr(9);
3886 addInstr(env, s390_insn_move(8, r8, op1_high));
3887 addInstr(env, s390_insn_move(8, r9, op1_low));
3888
3889 /* Use non-virtual registers r10 and r11 as pair for op3
3890 and move op3 there */
3891 r10 = make_gpr(10);
3892 r11 = make_gpr(11);
3893 addInstr(env, s390_insn_move(8, r10, op3_high));
3894 addInstr(env, s390_insn_move(8, r11, op3_low));
3895
3896 /* Register r1 is used as a scratch register */
3897 r1 = make_gpr(1);
3898
3899 if (typeOfIRTemp(env->type_env, cas->oldLo) == Ity_I32) {
3900 addInstr(env, s390_insn_cdas(4, r8, r9, op2, r10, r11,
3901 old_high, old_low, r1));
3902 } else {
3903 addInstr(env, s390_insn_cdas(8, r8, r9, op2, r10, r11,
3904 old_high, old_low, r1));
3905 }
3906 addInstr(env, s390_insn_move(8, op1_high, r8));
3907 addInstr(env, s390_insn_move(8, op1_low, r9));
3908 addInstr(env, s390_insn_move(8, op3_high, r10));
3909 addInstr(env, s390_insn_move(8, op3_low, r11));
3910 return;
sewardj2019a972011-03-07 16:04:07 +00003911 }
3912 break;
3913
3914 /* --------- EXIT --------- */
3915 case Ist_Exit: {
sewardj2019a972011-03-07 16:04:07 +00003916 s390_cc_t cond;
3917 IRConstTag tag = stmt->Ist.Exit.dst->tag;
3918
3919 if (tag != Ico_U64)
3920 vpanic("s390_isel_stmt: Ist_Exit: dst is not a 64-bit value");
3921
florian8844a632012-04-13 04:04:06 +00003922 s390_amode *guest_IA = s390_amode_for_guest_state(stmt->Ist.Exit.offsIP);
sewardj2019a972011-03-07 16:04:07 +00003923 cond = s390_isel_cc(env, stmt->Ist.Exit.guard);
florian8844a632012-04-13 04:04:06 +00003924
3925 /* Case: boring transfer to known address */
3926 if (stmt->Ist.Exit.jk == Ijk_Boring) {
3927 if (env->chaining_allowed) {
3928 /* .. almost always true .. */
3929 /* Skip the event check at the dst if this is a forwards
3930 edge. */
3931 Bool to_fast_entry
3932 = ((Addr64)stmt->Ist.Exit.dst->Ico.U64) > env->max_ga;
3933 if (0) vex_printf("%s", to_fast_entry ? "Y" : ",");
3934 addInstr(env, s390_insn_xdirect(cond, stmt->Ist.Exit.dst->Ico.U64,
3935 guest_IA, to_fast_entry));
3936 } else {
3937 /* .. very occasionally .. */
3938 /* We can't use chaining, so ask for an assisted transfer,
3939 as that's the only alternative that is allowable. */
3940 HReg dst = s390_isel_int_expr(env,
3941 IRExpr_Const(stmt->Ist.Exit.dst));
3942 addInstr(env, s390_insn_xassisted(cond, dst, guest_IA, Ijk_Boring));
3943 }
3944 return;
3945 }
3946
3947 /* Case: assisted transfer to arbitrary address */
3948 switch (stmt->Ist.Exit.jk) {
florian4e0083e2012-08-26 03:41:56 +00003949 case Ijk_EmFail:
florian4b8efad2012-09-02 18:07:08 +00003950 case Ijk_EmWarn:
florian65b5b3f2012-04-22 02:51:27 +00003951 case Ijk_NoDecode:
sewardj05f5e012014-05-04 10:52:11 +00003952 case Ijk_InvalICache:
florian2d98d892012-04-14 20:35:17 +00003953 case Ijk_Sys_syscall:
3954 case Ijk_ClientReq:
3955 case Ijk_NoRedir:
3956 case Ijk_Yield:
3957 case Ijk_SigTRAP: {
florian8844a632012-04-13 04:04:06 +00003958 HReg dst = s390_isel_int_expr(env, IRExpr_Const(stmt->Ist.Exit.dst));
3959 addInstr(env, s390_insn_xassisted(cond, dst, guest_IA,
3960 stmt->Ist.Exit.jk));
3961 return;
3962 }
3963 default:
3964 break;
3965 }
3966
3967 /* Do we ever expect to see any other kind? */
3968 goto stmt_fail;
sewardj2019a972011-03-07 16:04:07 +00003969 }
3970
3971 /* --------- MEM FENCE --------- */
sewardja52e37e2011-04-28 18:48:06 +00003972 case Ist_MBE:
3973 switch (stmt->Ist.MBE.event) {
3974 case Imbe_Fence:
3975 addInstr(env, s390_insn_mfence());
3976 return;
3977 default:
3978 break;
3979 }
sewardj2019a972011-03-07 16:04:07 +00003980 break;
3981
3982 /* --------- Miscellaneous --------- */
3983
3984 case Ist_PutI: /* Not needed */
3985 case Ist_IMark: /* Doesn't generate any executable code */
3986 case Ist_NoOp: /* Doesn't generate any executable code */
3987 case Ist_AbiHint: /* Meaningless in IR */
3988 return;
3989
3990 default:
3991 break;
3992 }
3993
3994 stmt_fail:
3995 ppIRStmt(stmt);
3996 vpanic("s390_isel_stmt");
3997}
3998
3999
4000/*---------------------------------------------------------*/
4001/*--- ISEL: Basic block terminators (Nexts) ---*/
4002/*---------------------------------------------------------*/
4003
4004static void
florianffbd84d2012-12-09 02:06:29 +00004005iselNext(ISelEnv *env, IRExpr *next, IRJumpKind jk, Int offsIP)
sewardj2019a972011-03-07 16:04:07 +00004006{
sewardj2019a972011-03-07 16:04:07 +00004007 if (vex_traceflags & VEX_TRACE_VCODE) {
florian8844a632012-04-13 04:04:06 +00004008 vex_printf("\n-- PUT(%d) = ", offsIP);
sewardj2019a972011-03-07 16:04:07 +00004009 ppIRExpr(next);
florian8844a632012-04-13 04:04:06 +00004010 vex_printf("; exit-");
4011 ppIRJumpKind(jk);
sewardj2019a972011-03-07 16:04:07 +00004012 vex_printf("\n");
4013 }
4014
florian8844a632012-04-13 04:04:06 +00004015 s390_amode *guest_IA = s390_amode_for_guest_state(offsIP);
4016
4017 /* Case: boring transfer to known address */
4018 if (next->tag == Iex_Const) {
4019 IRConst *cdst = next->Iex.Const.con;
4020 vassert(cdst->tag == Ico_U64);
4021 if (jk == Ijk_Boring || jk == Ijk_Call) {
4022 /* Boring transfer to known address */
4023 if (env->chaining_allowed) {
4024 /* .. almost always true .. */
4025 /* Skip the event check at the dst if this is a forwards
4026 edge. */
4027 Bool to_fast_entry
4028 = ((Addr64)cdst->Ico.U64) > env->max_ga;
4029 if (0) vex_printf("%s", to_fast_entry ? "X" : ".");
4030 addInstr(env, s390_insn_xdirect(S390_CC_ALWAYS, cdst->Ico.U64,
4031 guest_IA, to_fast_entry));
4032 } else {
4033 /* .. very occasionally .. */
4034 /* We can't use chaining, so ask for an indirect transfer,
4035 as that's the cheapest alternative that is allowable. */
4036 HReg dst = s390_isel_int_expr(env, next);
4037 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA,
4038 Ijk_Boring));
4039 }
4040 return;
4041 }
4042 }
4043
4044 /* Case: call/return (==boring) transfer to any address */
4045 switch (jk) {
4046 case Ijk_Boring:
4047 case Ijk_Ret:
4048 case Ijk_Call: {
4049 HReg dst = s390_isel_int_expr(env, next);
4050 if (env->chaining_allowed) {
4051 addInstr(env, s390_insn_xindir(S390_CC_ALWAYS, dst, guest_IA));
4052 } else {
4053 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA,
4054 Ijk_Boring));
4055 }
4056 return;
4057 }
4058 default:
4059 break;
4060 }
4061
4062 /* Case: some other kind of transfer to any address */
4063 switch (jk) {
florian4e0083e2012-08-26 03:41:56 +00004064 case Ijk_EmFail:
florian4b8efad2012-09-02 18:07:08 +00004065 case Ijk_EmWarn:
florian65b5b3f2012-04-22 02:51:27 +00004066 case Ijk_NoDecode:
sewardj05f5e012014-05-04 10:52:11 +00004067 case Ijk_InvalICache:
florian8844a632012-04-13 04:04:06 +00004068 case Ijk_Sys_syscall:
4069 case Ijk_ClientReq:
4070 case Ijk_NoRedir:
4071 case Ijk_Yield:
4072 case Ijk_SigTRAP: {
4073 HReg dst = s390_isel_int_expr(env, next);
4074 addInstr(env, s390_insn_xassisted(S390_CC_ALWAYS, dst, guest_IA, jk));
4075 return;
4076 }
4077 default:
4078 break;
4079 }
4080
4081 vpanic("iselNext");
sewardj2019a972011-03-07 16:04:07 +00004082}
4083
4084
4085/*---------------------------------------------------------*/
4086/*--- Insn selector top-level ---*/
4087/*---------------------------------------------------------*/
4088
florianf26994a2012-04-21 03:34:54 +00004089/* Translate an entire SB to s390 code.
4090 Note: archinfo_host is a pointer to a stack-allocated variable.
4091 Do not assign it to a global variable! */
sewardj2019a972011-03-07 16:04:07 +00004092
4093HInstrArray *
floriancacba8e2014-12-15 18:58:07 +00004094iselSB_S390(const IRSB *bb, VexArch arch_host, const VexArchInfo *archinfo_host,
floriand8c64e02014-10-08 08:54:44 +00004095 const VexAbiInfo *vbi, Int offset_host_evcheck_counter,
florian8844a632012-04-13 04:04:06 +00004096 Int offset_host_evcheck_fail_addr, Bool chaining_allowed,
floriandcd6d232015-01-02 17:32:21 +00004097 Bool add_profinc, Addr max_ga)
sewardj2019a972011-03-07 16:04:07 +00004098{
4099 UInt i, j;
4100 HReg hreg, hregHI;
4101 ISelEnv *env;
4102 UInt hwcaps_host = archinfo_host->hwcaps;
4103
sewardj2019a972011-03-07 16:04:07 +00004104 /* Do some sanity checks */
sewardj652b56a2011-04-13 15:38:17 +00004105 vassert((VEX_HWCAPS_S390X(hwcaps_host) & ~(VEX_HWCAPS_S390X_ALL)) == 0);
sewardj2019a972011-03-07 16:04:07 +00004106
sewardj9b769162014-07-24 12:42:03 +00004107 /* Check that the host's endianness is as expected. */
4108 vassert(archinfo_host->endness == VexEndnessBE);
4109
sewardj2019a972011-03-07 16:04:07 +00004110 /* Make up an initial environment to use. */
floriand8e3eca2015-03-13 12:46:49 +00004111 env = LibVEX_Alloc_inline(sizeof(ISelEnv));
sewardj2019a972011-03-07 16:04:07 +00004112 env->vreg_ctr = 0;
4113
4114 /* Set up output code array. */
4115 env->code = newHInstrArray();
4116
4117 /* Copy BB's type env. */
4118 env->type_env = bb->tyenv;
4119
florianad43b3a2012-02-20 15:01:14 +00004120 /* Set up data structures for tracking guest register values. */
florianad43b3a2012-02-20 15:01:14 +00004121 for (i = 0; i < NUM_TRACKED_REGS; ++i) {
4122 env->old_value[i] = 0; /* just something to have a defined value */
4123 env->old_value_valid[i] = False;
4124 }
4125
sewardj2019a972011-03-07 16:04:07 +00004126 /* Make up an IRTemp -> virtual HReg mapping. This doesn't
4127 change as we go along. For some reason types_used has Int type -- but
4128 it should be unsigned. Internally we use an unsigned type; so we
4129 assert it here. */
4130 vassert(bb->tyenv->types_used >= 0);
4131
4132 env->n_vregmap = bb->tyenv->types_used;
floriand8e3eca2015-03-13 12:46:49 +00004133 env->vregmap = LibVEX_Alloc_inline(env->n_vregmap * sizeof(HReg));
4134 env->vregmapHI = LibVEX_Alloc_inline(env->n_vregmap * sizeof(HReg));
sewardj2019a972011-03-07 16:04:07 +00004135
florian2c74d242012-09-12 19:38:42 +00004136 env->previous_bfp_rounding_mode = NULL;
florianc8e4f562012-10-27 16:19:31 +00004137 env->previous_dfp_rounding_mode = NULL;
florian2c74d242012-09-12 19:38:42 +00004138
sewardj2019a972011-03-07 16:04:07 +00004139 /* and finally ... */
4140 env->hwcaps = hwcaps_host;
4141
florian8844a632012-04-13 04:04:06 +00004142 env->max_ga = max_ga;
4143 env->chaining_allowed = chaining_allowed;
4144
sewardj2019a972011-03-07 16:04:07 +00004145 /* For each IR temporary, allocate a suitably-kinded virtual
4146 register. */
4147 j = 0;
4148 for (i = 0; i < env->n_vregmap; i++) {
4149 hregHI = hreg = INVALID_HREG;
4150 switch (bb->tyenv->types[i]) {
4151 case Ity_I1:
4152 case Ity_I8:
4153 case Ity_I16:
4154 case Ity_I32:
sewardj2019a972011-03-07 16:04:07 +00004155 case Ity_I64:
sewardja5b50222015-03-26 07:18:32 +00004156 hreg = mkVRegI(j++);
sewardj2019a972011-03-07 16:04:07 +00004157 break;
4158
4159 case Ity_I128:
sewardja5b50222015-03-26 07:18:32 +00004160 hreg = mkVRegI(j++);
4161 hregHI = mkVRegI(j++);
sewardj2019a972011-03-07 16:04:07 +00004162 break;
4163
4164 case Ity_F32:
4165 case Ity_F64:
floriane38f6412012-12-21 17:32:12 +00004166 case Ity_D32:
florian12390202012-11-10 22:34:14 +00004167 case Ity_D64:
sewardja5b50222015-03-26 07:18:32 +00004168 hreg = mkVRegF(j++);
sewardj2019a972011-03-07 16:04:07 +00004169 break;
4170
4171 case Ity_F128:
floriane38f6412012-12-21 17:32:12 +00004172 case Ity_D128:
sewardja5b50222015-03-26 07:18:32 +00004173 hreg = mkVRegF(j++);
4174 hregHI = mkVRegF(j++);
sewardj2019a972011-03-07 16:04:07 +00004175 break;
4176
4177 case Ity_V128: /* fall through */
4178 default:
4179 ppIRType(bb->tyenv->types[i]);
florian4ebaa772012-12-20 19:44:18 +00004180 vpanic("iselSB_S390: IRTemp type");
sewardj2019a972011-03-07 16:04:07 +00004181 }
4182
4183 env->vregmap[i] = hreg;
4184 env->vregmapHI[i] = hregHI;
4185 }
4186 env->vreg_ctr = j;
4187
florian8844a632012-04-13 04:04:06 +00004188 /* The very first instruction must be an event check. */
4189 s390_amode *counter, *fail_addr;
4190 counter = s390_amode_for_guest_state(offset_host_evcheck_counter);
4191 fail_addr = s390_amode_for_guest_state(offset_host_evcheck_fail_addr);
4192 addInstr(env, s390_insn_evcheck(counter, fail_addr));
4193
4194 /* Possibly a block counter increment (for profiling). At this
4195 point we don't know the address of the counter, so just pretend
4196 it is zero. It will have to be patched later, but before this
4197 translation is used, by a call to LibVEX_patchProfInc. */
4198 if (add_profinc) {
4199 addInstr(env, s390_insn_profinc());
4200 }
4201
sewardj2019a972011-03-07 16:04:07 +00004202 /* Ok, finally we can iterate over the statements. */
4203 for (i = 0; i < bb->stmts_used; i++)
4204 if (bb->stmts[i])
4205 s390_isel_stmt(env, bb->stmts[i]);
4206
florian8844a632012-04-13 04:04:06 +00004207 iselNext(env, bb->next, bb->jumpkind, bb->offsIP);
sewardj2019a972011-03-07 16:04:07 +00004208
4209 /* Record the number of vregs we used. */
4210 env->code->n_vregs = env->vreg_ctr;
4211
4212 return env->code;
4213}
4214
4215/*---------------------------------------------------------------*/
4216/*--- end host_s390_isel.c ---*/
4217/*---------------------------------------------------------------*/