2 /*---------------------------------------------------------------*/
3 /*--- begin host_mips_isel.c ---*/
4 /*---------------------------------------------------------------*/
7 This file is part of Valgrind, a dynamic binary instrumentation
10 Copyright (C) 2010-2017 RT-RK
11 mips-valgrind@rt-rk.com
13 This program is free software; you can redistribute it and/or
14 modify it under the terms of the GNU General Public License as
15 published by the Free Software Foundation; either version 2 of the
16 License, or (at your option) any later version.
18 This program is distributed in the hope that it will be useful, but
19 WITHOUT ANY WARRANTY; without even the implied warranty of
20 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
21 General Public License for more details.
23 You should have received a copy of the GNU General Public License
24 along with this program; if not, write to the Free Software
25 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
28 The GNU General Public License is contained in the file COPYING.
31 #include "libvex_basictypes.h"
32 #include "libvex_ir.h"
35 #include "main_util.h"
36 #include "main_globals.h"
37 #include "host_generic_regs.h"
38 #include "host_generic_simd64.h" /* for 64-bit SIMD helpers */
39 #include "host_mips_defs.h"
41 /*---------------------------------------------------------*/
42 /*--- Register Usage Conventions ---*/
43 /*---------------------------------------------------------*/
53 static Bool mode64
= False
;
55 /* Host CPU has FPU and 32 dbl. prec. FP registers. */
56 static Bool fp_mode64
= False
;
59 static UInt hwcaps_host
= 0;
61 /* Host CPU has MSA ASE */
62 static Bool has_msa
= False
;
64 /* GPR register class for mips32/64 */
65 #define HRcGPR(_mode64) ((_mode64) ? HRcInt64 : HRcInt32)
67 /* FPR register class for mips32/64 */
68 #define HRcFPR(_mode64) ((_mode64) ? HRcFlt64 : HRcFlt32)
70 /*---------------------------------------------------------*/
72 /*---------------------------------------------------------*/
74 /* This carries around:
76 - A mapping from IRTemp to IRType, giving the type of any IRTemp we
77 might encounter. This is computed before insn selection starts,
80 - A mapping from IRTemp to HReg. This tells the insn selector
81 which virtual register(s) are associated with each IRTemp
82 temporary. This is computed before insn selection starts, and
83 does not change. We expect this mapping to map precisely the
84 same set of IRTemps as the type mapping does.
86 - vregmap holds the primary register for the IRTemp.
87 - vregmapHI is only used for 64-bit integer-typed
88 IRTemps. It holds the identity of a second
89 32-bit virtual HReg, which holds the high half
92 - The code array, that is, the insns selected so far.
94 - A counter, for generating new virtual registers.
96 - The host subarchitecture we are selecting insns for.
97 This is set at the start and does not change.
99 - A Bool for indicating whether we may generate chain-me
100 instructions for control flow transfers, or whether we must use
103 - The maximum guest address of any guest insn in this block.
104 Actually, the address of the highest-addressed byte from any insn
105 in this block. Is set at the start and does not change. This is
106 used for detecting jumps which are definitely forward-edges from
107 this block, and therefore can be made (chained) to the fast entry
108 point of the destination, thereby avoiding the destination's
111 Note, this is all (well, mostly) host-independent.
116 /* Constant -- are set at the start and do not change. */
127 Bool chainingAllowed
;
130 /* These are modified as we go along. */
136 static HReg
lookupIRTemp(ISelEnv
* env
, IRTemp tmp
)
138 vassert(tmp
< env
->n_vregmap
);
139 return env
->vregmap
[tmp
];
142 static void lookupIRTemp64(HReg
* vrHI
, HReg
* vrLO
, ISelEnv
* env
, IRTemp tmp
)
144 vassert(tmp
< env
->n_vregmap
);
145 vassert(! hregIsInvalid(env
->vregmapHI
[tmp
]));
146 *vrLO
= env
->vregmap
[tmp
];
147 *vrHI
= env
->vregmapHI
[tmp
];
151 lookupIRTempPair(HReg
* vrHI
, HReg
* vrLO
, ISelEnv
* env
, IRTemp tmp
)
153 vassert(env
->mode64
);
154 vassert(tmp
< env
->n_vregmap
);
155 vassert(! hregIsInvalid(env
->vregmapHI
[tmp
]));
156 *vrLO
= env
->vregmap
[tmp
];
157 *vrHI
= env
->vregmapHI
[tmp
];
160 static void addInstr(ISelEnv
* env
, MIPSInstr
* instr
)
162 addHInstr(env
->code
, instr
);
163 if (vex_traceflags
& VEX_TRACE_VCODE
) {
164 ppMIPSInstr(instr
, mode64
);
169 static HReg
newVRegI(ISelEnv
* env
)
171 HReg reg
= mkHReg(True
/*virtual reg*/,
172 HRcGPR(env
->mode64
), 0/*enc*/, env
->vreg_ctr
);
177 static HReg
newVRegD(ISelEnv
* env
)
179 HReg reg
= mkHReg(True
/*virtual reg*/,
180 HRcFlt64
, 0/*enc*/, env
->vreg_ctr
);
185 static HReg
newVRegF(ISelEnv
* env
)
187 HReg reg
= mkHReg(True
/*virtual reg*/,
188 HRcFPR(env
->mode64
), 0/*enc*/, env
->vreg_ctr
);
193 static HReg
newVRegV ( ISelEnv
* env
)
195 HReg reg
= mkHReg(True
/*virtual reg*/, HRcVec128
, 0, env
->vreg_ctr
);
200 static void add_to_sp(ISelEnv
* env
, UInt n
)
202 HReg sp
= StackPointer(mode64
);
203 vassert(n
< 256 && (n
% 8) == 0);
205 addInstr(env
, MIPSInstr_Alu(Malu_DADD
, sp
, sp
, MIPSRH_Imm(True
,
208 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, sp
, sp
, MIPSRH_Imm(True
,
212 static void sub_from_sp(ISelEnv
* env
, UInt n
)
214 HReg sp
= StackPointer(mode64
);
215 vassert(n
< 256 && (n
% 8) == 0);
217 addInstr(env
, MIPSInstr_Alu(Malu_DSUB
, sp
, sp
,
218 MIPSRH_Imm(True
, toUShort(n
))));
220 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, sp
, sp
,
221 MIPSRH_Imm(True
, toUShort(n
))));
224 /*---------------------------------------------------------*/
225 /*--- ISEL: Forward declarations ---*/
226 /*---------------------------------------------------------*/
228 /* These are organised as iselXXX and iselXXX_wrk pairs. The
229 iselXXX_wrk do the real work, but are not to be called directly.
230 For each XXX, iselXXX calls its iselXXX_wrk counterpart, then
231 checks that all returned registers are virtual. You should not
232 call the _wrk version directly.
234 /* 32-bit mode: Compute an I8/I16/I32 into a RH
235 (reg-or-halfword-immediate).
236 It's important to specify whether the immediate is to be regarded
237 as signed or not. If yes, this will never return -32768 as an
238 immediate; this guaranteed that all signed immediates that are
239 return can have their sign inverted if need be.
241 static MIPSRH
*iselWordExpr_RH_wrk(ISelEnv
* env
, Bool syned
, IRExpr
* e
);
242 static MIPSRH
*iselWordExpr_RH(ISelEnv
* env
, Bool syned
, IRExpr
* e
);
244 /* Compute an I8 into a reg-or-5-bit-unsigned-immediate, the latter being an
245 immediate in the range 1 .. 31 inclusive. Used for doing shift amounts. */
246 static MIPSRH
*iselWordExpr_RH5u_wrk(ISelEnv
* env
, IRExpr
* e
);
247 static MIPSRH
*iselWordExpr_RH5u(ISelEnv
* env
, IRExpr
* e
);
249 /* Compute an I8 into a reg-or-6-bit-unsigned-immediate, the latter being an
250 immediate in the range 1 .. 63 inclusive. Used for doing shift amounts. */
251 static MIPSRH
*iselWordExpr_RH6u_wrk(ISelEnv
* env
, IRExpr
* e
);
252 static MIPSRH
*iselWordExpr_RH6u(ISelEnv
* env
, IRExpr
* e
);
254 /* Compute an I8 into a reg-or-7-bit-unsigned-immediate, the latter being an
255 immediate in the range 1 .. 127 inclusive. Used for doing shift amounts. */
256 static MIPSRH
*iselWordExpr_RH7u_wrk(ISelEnv
* env
, IRExpr
* e
);
257 static MIPSRH
*iselWordExpr_RH7u(ISelEnv
* env
, IRExpr
* e
);
259 /* compute an I8/I16/I32 into a GPR*/
260 static HReg
iselWordExpr_R_wrk(ISelEnv
* env
, IRExpr
* e
);
261 static HReg
iselWordExpr_R(ISelEnv
* env
, IRExpr
* e
);
263 /* compute an I32 into an AMode. */
264 static MIPSAMode
*iselWordExpr_AMode_wrk(ISelEnv
* env
, IRExpr
* e
,
266 static MIPSAMode
*iselWordExpr_AMode(ISelEnv
* env
, IRExpr
* e
, IRType xferTy
);
268 static void iselInt64Expr_wrk(HReg
* rHi
, HReg
* rLo
, ISelEnv
* env
,
270 static void iselInt64Expr(HReg
* rHi
, HReg
* rLo
, ISelEnv
* env
, IRExpr
* e
);
272 /* 64-bit mode ONLY: compute an I128 into a GPR64 pair. */
273 static void iselInt128Expr_wrk(HReg
* rHi
, HReg
* rLo
,
274 ISelEnv
* env
, IRExpr
* e
);
275 static void iselInt128Expr(HReg
* rHi
, HReg
* rLo
, ISelEnv
* env
, IRExpr
* e
);
277 static HReg
iselV128Expr( ISelEnv
* env
, IRExpr
* e
);
278 static HReg
iselV128Expr_wrk( ISelEnv
* env
, IRExpr
* e
);
280 static MIPSCondCode
iselCondCode_wrk(ISelEnv
* env
, IRExpr
* e
);
281 static MIPSCondCode
iselCondCode(ISelEnv
* env
, IRExpr
* e
);
283 static HReg
iselDblExpr_wrk(ISelEnv
* env
, IRExpr
* e
);
284 static HReg
iselDblExpr(ISelEnv
* env
, IRExpr
* e
);
286 static HReg
iselFltExpr_wrk(ISelEnv
* env
, IRExpr
* e
);
287 static HReg
iselFltExpr(ISelEnv
* env
, IRExpr
* e
);
289 static void set_MIPS_rounding_mode(ISelEnv
* env
, IRExpr
* mode
)
292 rounding mode | MIPS | IR
293 ------------------------
296 to +infinity | 10 | 10
297 to -infinity | 11 | 01
299 /* rm_MIPS32 = XOR(rm_IR , (rm_IR << 1)) & 3 */
300 HReg irrm
= iselWordExpr_R(env
, mode
);
301 HReg tmp
= newVRegI(env
);
302 HReg fcsr_old
= newVRegI(env
);
305 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, tmp
, irrm
,
306 MIPSRH_Imm(False
, 1)));
307 addInstr(env
, MIPSInstr_Alu(Malu_XOR
, tmp
, irrm
, MIPSRH_Reg(tmp
)));
308 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
, MIPSRH_Imm(False
, 3)));
309 /* save old value of FCSR */
310 addInstr(env
, MIPSInstr_MfFCSR(fcsr_old
));
311 sub_from_sp(env
, 8); /* Move SP down 8 bytes */
312 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
314 /* store old FCSR to stack */
315 addInstr(env
, MIPSInstr_Store(4, am_addr
, fcsr_old
, mode64
));
317 /* set new value of FCSR */
318 addInstr(env
, MIPSInstr_MtFCSR(tmp
));
321 static void set_MIPS_rounding_mode_MSA(ISelEnv
* env
, IRExpr
* mode
) {
323 rounding mode | MIPS | IR
324 ------------------------
327 to +infinity | 10 | 10
328 to -infinity | 11 | 01
330 /* rm_MIPS32 = XOR(rm_IR , (rm_IR << 1)) & 3 */
331 HReg irrm
= iselWordExpr_R(env
, mode
);
332 HReg tmp
= newVRegI(env
);
333 HReg msacsr_old
= newVRegI(env
);
335 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, tmp
, irrm
,
336 MIPSRH_Imm(False
, 1)));
337 addInstr(env
, MIPSInstr_Alu(Malu_XOR
, tmp
, irrm
, MIPSRH_Reg(tmp
)));
338 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
, MIPSRH_Imm(False
, 3)));
339 /* save old value of MSACSR */
340 addInstr(env
, MIPSInstr_MsaElm(MSA_CFCMSA
, hregMIPS_GPR0(mode64
), msacsr_old
,
342 sub_from_sp(env
, 8); /* Move SP down 8 bytes */
343 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
344 /* store old MSACSR to stack */
345 addInstr(env
, MIPSInstr_Store(4, am_addr
, msacsr_old
, mode64
));
346 /* set new value of MSACSR */
347 addInstr(env
, MIPSInstr_MsaElm(MSA_CTCMSA
, tmp
, hregMIPS_GPR0(mode64
),
352 static void set_guest_MIPS_rounding_mode_MSA(ISelEnv
* env
) {
354 rounding mode | MIPS | IR
355 ------------------------
358 to +infinity | 10 | 10
359 to -infinity | 11 | 01
361 /* rm_MIPS32 = XOR(rm_IR , (rm_IR << 1)) & 3 */
362 HReg irrm
= newVRegI(env
);
363 HReg msacsr_old
= newVRegI(env
);
365 MIPSAMode
*rm_addr
= MIPSAMode_IR(MSACSR_OFFSET(mode64
),
366 GuestStatePointer(mode64
));
367 addInstr(env
, MIPSInstr_Load(4, irrm
, rm_addr
, mode64
));
368 /* save old value of MSACSR */
369 addInstr(env
, MIPSInstr_MsaElm(MSA_CFCMSA
, hregMIPS_GPR0(mode64
), msacsr_old
,
371 sub_from_sp(env
, 8); /* Move SP down 8 bytes */
372 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
373 /* store old MSACSR to stack */
374 addInstr(env
, MIPSInstr_Store(4, am_addr
, msacsr_old
, mode64
));
375 /* set new value of MSACSR */
376 addInstr(env
, MIPSInstr_MsaElm(MSA_CTCMSA
, irrm
, hregMIPS_GPR0(mode64
),
381 static void set_MIPS_rounding_default(ISelEnv
* env
)
383 HReg fcsr
= newVRegI(env
);
386 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
388 addInstr(env
, MIPSInstr_Load(4, fcsr
, am_addr
, mode64
));
390 add_to_sp(env
, 8); /* Reset SP */
392 /* set new value of FCSR*/
393 addInstr(env
, MIPSInstr_MtFCSR(fcsr
));
396 static void set_MIPS_rounding_default_MSA(ISelEnv
* env
) {
397 HReg msacsr
= newVRegI(env
);
400 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
401 addInstr(env
, MIPSInstr_Load(4, msacsr
, am_addr
, mode64
));
402 add_to_sp(env
, 8); /* Reset SP */
403 /* set new value of FCSR*/
404 addInstr(env
, MIPSInstr_MsaElm(MSA_CTCMSA
, msacsr
, hregMIPS_GPR0(mode64
),
408 /*---------------------------------------------------------*/
409 /*--- ISEL: Misc helpers ---*/
410 /*---------------------------------------------------------*/
412 /* Make an int reg-reg move. */
413 static MIPSInstr
*mk_iMOVds_RR(HReg r_dst
, HReg r_src
)
415 vassert(hregClass(r_dst
) == hregClass(r_src
));
416 vassert(hregClass(r_src
) == HRcInt32
|| hregClass(r_src
) == HRcInt64
);
417 return MIPSInstr_Alu(Malu_OR
, r_dst
, r_src
, MIPSRH_Reg(r_src
));
420 /*---------------------------------------------------------*/
421 /*--- ISEL: Function call helpers ---*/
422 /*---------------------------------------------------------*/
424 /* Used only in doHelperCall. See big comment in doHelperCall re
425 handling of register-parameter args. This function figures out
426 whether evaluation of an expression might require use of a fixed
427 register. If in doubt return True (safe but suboptimal).
429 static Bool
mightRequireFixedRegs(IRExpr
* e
)
441 /* Load 2*I32 regs to fp reg */
442 static HReg
mk_LoadRR32toFPR(ISelEnv
* env
, HReg r_srcHi
, HReg r_srcLo
)
444 HReg fr_dst
= newVRegD(env
);
445 MIPSAMode
*am_addr0
, *am_addr1
;
447 vassert(hregClass(r_srcHi
) == HRcInt32
);
448 vassert(hregClass(r_srcLo
) == HRcInt32
);
450 sub_from_sp(env
, 16); /* Move SP down 16 bytes */
451 am_addr0
= MIPSAMode_IR(0, StackPointer(mode64
));
452 am_addr1
= MIPSAMode_IR(4, StackPointer(mode64
));
454 /* store hi,lo as Ity_I32's */
455 #if defined (_MIPSEL)
456 addInstr(env
, MIPSInstr_Store(4, am_addr0
, r_srcLo
, mode64
));
457 addInstr(env
, MIPSInstr_Store(4, am_addr1
, r_srcHi
, mode64
));
458 #elif defined (_MIPSEB)
459 addInstr(env
, MIPSInstr_Store(4, am_addr0
, r_srcHi
, mode64
));
460 addInstr(env
, MIPSInstr_Store(4, am_addr1
, r_srcLo
, mode64
));
462 /* Stop gcc on other platforms complaining about am_addr1 being set
468 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */ , 8, fr_dst
, am_addr0
));
470 add_to_sp(env
, 16); /* Reset SP */
474 /* Do a complete function call. |guard| is a Ity_Bit expression
475 indicating whether or not the call happens. If guard==NULL, the
476 call is unconditional. |retloc| is set to indicate where the
477 return value is after the call. The caller (of this fn) must
478 generate code to add |stackAdjustAfterCall| to the stack pointer
479 after the call is done. */
481 static void doHelperCall(/*OUT*/UInt
* stackAdjustAfterCall
,
482 /*OUT*/RetLoc
* retloc
,
485 IRCallee
* cee
, IRType retTy
, IRExpr
** args
)
491 Int n_args
, i
, argreg
;
493 HReg src
= INVALID_HREG
;
495 /* Set default returns. We'll update them later if needed. */
496 *stackAdjustAfterCall
= 0;
497 *retloc
= mk_RetLoc_INVALID();
499 /* These are used for cross-checking that IR-level constraints on
500 the use of IRExpr_VECRET() and IRExpr_GSPTR() are observed. */
504 /* MIPS O32 calling convention: up to four registers ($a0 ... $a3)
505 are allowed to be used for passing integer arguments. They correspond
506 to regs GPR4 ... GPR7. Note that the cee->regparms field is meaningless
507 on MIPS host (since we only implement one calling convention) and so we
510 /* MIPS 64 calling convention: up to four registers ($a0 ... $a7)
511 are allowed to be used for passing integer arguments. They correspond
512 to regs GPR4 ... GPR11. Note that the cee->regparms field is meaningless
513 on MIPS host (since we only implement one calling convention) and so we
516 /* The return type can be I{64,32,16,8} or V{128,256}. In the
517 latter two cases, it is expected that |args| will contain the
518 special node IRExpr_VECRET(), in which case this routine
519 generates code to allocate space on the stack for the vector
520 return value. Since we are not passing any scalars on the
521 stack, it is enough to preallocate the return space before
522 marshalling any arguments, in this case.
524 |args| may also contain IRExpr_GSPTR(), in which case the value
525 in the guest state pointer register is passed as the
526 corresponding argument. */
529 for (i
= 0; args
[i
]; i
++) {
530 IRExpr
* arg
= args
[i
];
531 if (UNLIKELY(arg
->tag
== Iex_VECRET
)) {
533 } else if (UNLIKELY(arg
->tag
== Iex_GSPTR
)) {
539 if (n_args
> MIPS_N_REGPARMS
) {
540 vpanic("doHelperCall(MIPS): cannot currently handle > 4 or 8 args");
543 argregs
[0] = hregMIPS_GPR4(mode64
);
544 argregs
[1] = hregMIPS_GPR5(mode64
);
545 argregs
[2] = hregMIPS_GPR6(mode64
);
546 argregs
[3] = hregMIPS_GPR7(mode64
);
547 argregs
[4] = hregMIPS_GPR8(mode64
);
548 argregs
[5] = hregMIPS_GPR9(mode64
);
549 argregs
[6] = hregMIPS_GPR10(mode64
);
550 argregs
[7] = hregMIPS_GPR11(mode64
);
552 tmpregs
[0] = tmpregs
[1] = tmpregs
[2] =
553 tmpregs
[3] = tmpregs
[4] = tmpregs
[5] =
554 tmpregs
[6] = tmpregs
[7] = INVALID_HREG
;
556 argregs
[0] = hregMIPS_GPR4(mode64
);
557 argregs
[1] = hregMIPS_GPR5(mode64
);
558 argregs
[2] = hregMIPS_GPR6(mode64
);
559 argregs
[3] = hregMIPS_GPR7(mode64
);
561 tmpregs
[0] = tmpregs
[1] = tmpregs
[2] = tmpregs
[3] = INVALID_HREG
;
564 /* First decide which scheme (slow or fast) is to be used. First assume the
565 fast scheme, and select slow if any contraindications (wow) appear. */
569 /* We'll need space on the stack for the return value. Avoid
570 possible complications with nested calls by using the slow
572 if (retTy
== Ity_V128
|| retTy
== Ity_V256
)
575 if (go_fast
&& guard
) {
576 if (guard
->tag
== Iex_Const
&& guard
->Iex
.Const
.con
->tag
== Ico_U1
577 && guard
->Iex
.Const
.con
->Ico
.U1
== True
) {
580 /* Not manifestly unconditional -- be conservative. */
586 for (i
= 0; i
< n_args
; i
++) {
587 if (mightRequireFixedRegs(args
[i
])) {
594 /* At this point the scheme to use has been established. Generate
595 code to get the arg values into the argument rregs. */
600 for (i
= 0; i
< n_args
; i
++) {
601 IRExpr
* arg
= args
[i
];
602 vassert(argreg
< MIPS_N_REGPARMS
);
604 IRType aTy
= Ity_INVALID
;
605 if (LIKELY(!is_IRExpr_VECRET_or_GSPTR(arg
)))
606 aTy
= typeOfIRExpr(env
->type_env
, arg
);
608 if (aTy
== Ity_I32
|| (mode64
&& aTy
!= Ity_INVALID
)) {
609 argiregs
|= (1 << (argreg
+ 4));
610 addInstr(env
, mk_iMOVds_RR(argregs
[argreg
],
611 iselWordExpr_R(env
, arg
)));
613 } else if (aTy
== Ity_I64
) { /* Ity_I64 */
616 argiregs
|= (1 << (argreg
+ 4));
619 iselInt64Expr(&rHi
, &rLo
, env
, arg
);
620 argiregs
|= (1 << (argreg
+ 4));
621 addInstr(env
, mk_iMOVds_RR( argregs
[argreg
++], rLo
));
622 argiregs
|= (1 << (argreg
+ 4));
623 addInstr(env
, mk_iMOVds_RR( argregs
[argreg
], rHi
));
625 } else if (arg
->tag
== Iex_GSPTR
) {
627 addInstr(env
, mk_iMOVds_RR(argregs
[argreg
],
628 GuestStatePointer(mode64
)));
630 } else if (arg
->tag
== Iex_VECRET
) {
631 // If this happens, it denotes ill-formed IR.
635 /* Fast scheme only applies for unconditional calls. Hence: */
638 /* SLOW SCHEME; move via temporaries */
641 for (i
= 0; i
< n_args
; i
++) {
642 vassert(argreg
< MIPS_N_REGPARMS
);
643 IRExpr
* arg
= args
[i
];
645 IRType aTy
= Ity_INVALID
;
646 if (LIKELY(!is_IRExpr_VECRET_or_GSPTR(arg
)))
647 aTy
= typeOfIRExpr(env
->type_env
, arg
);
649 if (aTy
== Ity_I32
|| (mode64
&& aTy
!= Ity_INVALID
)) {
650 tmpregs
[argreg
] = iselWordExpr_R(env
, arg
);
652 } else if (aTy
== Ity_I64
) { /* Ity_I64 */
655 if (argreg
+ 1 >= MIPS_N_REGPARMS
)
656 vassert(0); /* out of argregs */
658 iselInt64Expr(&raHi
, &raLo
, env
, arg
);
659 tmpregs
[argreg
] = raLo
;
661 tmpregs
[argreg
] = raHi
;
663 } else if (arg
->tag
== Iex_GSPTR
) {
664 tmpregs
[argreg
] = GuestStatePointer(mode64
);
667 else if (arg
->tag
== Iex_VECRET
) {
668 tmpregs
[argreg
++] = StackPointer(mode64
);
669 sub_from_sp(env
, 16); /* Move SP down 16 bytes */
673 /* Now we can compute the condition. We can't do it earlier
674 because the argument computations could trash the condition
675 codes. Be a bit clever to handle the common case where the
679 if (guard
->tag
== Iex_Const
&& guard
->Iex
.Const
.con
->tag
== Ico_U1
680 && guard
->Iex
.Const
.con
->Ico
.U1
== True
) {
681 /* unconditional -- do nothing */
683 cc
= iselCondCode(env
, guard
);
684 src
= iselWordExpr_R(env
, guard
);
687 /* Move the args to their final destinations. */
688 for (i
= 0; i
< argreg
; i
++) {
689 if (hregIsInvalid(tmpregs
[i
])) /* Skip invalid regs */
691 /* None of these insns, including any spill code that might
692 be generated, may alter the condition codes. */
693 argiregs
|= (1 << (i
+ 4));
694 addInstr(env
, mk_iMOVds_RR(argregs
[i
], tmpregs
[i
]));
698 /* Do final checks, set the return values, and generate the call
699 instruction proper. */
700 vassert(nGSPTRs
== 0 || nGSPTRs
== 1);
701 vassert(nVECRETs
== ((retTy
== Ity_V128
|| retTy
== Ity_V256
) ? 1 : 0));
702 vassert(*stackAdjustAfterCall
== 0);
703 vassert(is_RetLoc_INVALID(*retloc
));
706 /* Function doesn't return a value. */
707 *retloc
= mk_RetLoc_simple(RLPri_None
);
710 *retloc
= mk_RetLoc_simple(mode64
? RLPri_Int
: RLPri_2Int
);
712 case Ity_I32
: case Ity_I16
: case Ity_I8
:
713 *retloc
= mk_RetLoc_simple(RLPri_Int
);
716 *retloc
= mk_RetLoc_spRel(RLPri_V128SpRel
, 0);
717 *stackAdjustAfterCall
= 16;
721 *retloc
= mk_RetLoc_spRel(RLPri_V256SpRel
, 0);
722 *stackAdjustAfterCall
= 32;
725 /* IR can denote other possible return types, but we don't
726 handle those here. */
730 Addr64 target
= mode64
? (Addr
)cee
->addr
:
731 toUInt((Addr
)cee
->addr
);
733 /* Finally, generate the call itself. This needs the *retloc value
734 set in the switch above, which is why it's at the end. */
736 addInstr(env
, MIPSInstr_CallAlways(cc
, target
, argiregs
,
739 addInstr(env
, MIPSInstr_Call(cc
, target
, argiregs
, src
, *retloc
));
742 /*---------------------------------------------------------*/
743 /*--- ISEL: Integer expression auxiliaries ---*/
744 /*---------------------------------------------------------*/
746 /* --------------------- AMODEs --------------------- */
748 /* Return an AMode which computes the value of the specified
749 expression, possibly also adding insns to the code list as a
750 result. The expression may only be a word-size one.
753 static Bool
uInt_fits_in_16_bits(UInt u
)
758 return toBool(u
== (UInt
) i
);
761 static Bool
uLong_fits_in_16_bits ( ULong u
)
763 Long i
= u
& 0xFFFFULL
;
766 return toBool(u
== (ULong
) i
);
769 static Bool
uLong_is_4_aligned ( ULong u
)
771 return toBool((u
& 3ULL) == 0);
774 static Bool
sane_AMode(ISelEnv
* env
, MIPSAMode
* am
)
778 return toBool(hregClass(am
->Mam
.IR
.base
) == HRcGPR(mode64
) &&
779 hregIsVirtual(am
->Mam
.IR
.base
) &&
780 uInt_fits_in_16_bits(am
->Mam
.IR
.index
));
782 return toBool(hregClass(am
->Mam
.RR
.base
) == HRcGPR(mode64
) &&
783 hregIsVirtual(am
->Mam
.RR
.base
) &&
784 hregClass(am
->Mam
.RR
.index
) == HRcGPR(mode64
) &&
785 hregIsVirtual(am
->Mam
.RR
.index
));
787 vpanic("sane_AMode: unknown mips amode tag");
791 static MIPSAMode
*iselWordExpr_AMode(ISelEnv
* env
, IRExpr
* e
, IRType xferTy
)
793 MIPSAMode
*am
= iselWordExpr_AMode_wrk(env
, e
, xferTy
);
794 vassert(sane_AMode(env
, am
));
798 /* DO NOT CALL THIS DIRECTLY ! */
799 static MIPSAMode
*iselWordExpr_AMode_wrk(ISelEnv
* env
, IRExpr
* e
,
802 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
804 Bool aligned4imm
= toBool(xferTy
== Ity_I32
|| xferTy
== Ity_I64
);
805 vassert(ty
== Ity_I64
);
807 /* Add64(expr,i), where i == sign-extend of (i & 0xFFFF) */
808 if (e
->tag
== Iex_Binop
&& e
->Iex
.Binop
.op
== Iop_Add64
809 && e
->Iex
.Binop
.arg2
->tag
== Iex_Const
810 && e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U64
812 uLong_is_4_aligned(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U64
) : True
)
813 && uLong_fits_in_16_bits(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U64
)) {
814 return MIPSAMode_IR((Int
) e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U64
,
815 iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
));
818 /* Add64(expr,expr) */
819 if (e
->tag
== Iex_Binop
&& e
->Iex
.Binop
.op
== Iop_Add64
) {
820 HReg r_base
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
821 HReg r_idx
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
822 return MIPSAMode_RR(r_idx
, r_base
);
825 vassert(ty
== Ity_I32
);
827 /* Add32(expr,i), where i == sign-extend of (i & 0xFFFF) */
828 if (e
->tag
== Iex_Binop
829 && e
->Iex
.Binop
.op
== Iop_Add32
830 && e
->Iex
.Binop
.arg2
->tag
== Iex_Const
831 && e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U32
832 && uInt_fits_in_16_bits(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
-> Ico
.U32
)) {
833 return MIPSAMode_IR((Int
) e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U32
,
834 iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
));
837 /* Add32(expr,expr) */
838 if (e
->tag
== Iex_Binop
&& e
->Iex
.Binop
.op
== Iop_Add32
) {
839 HReg r_base
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
840 HReg r_idx
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
842 return MIPSAMode_RR(r_idx
, r_base
);
846 /* Doesn't match anything in particular. Generate it into
847 a register and use that. */
848 return MIPSAMode_IR(0, iselWordExpr_R(env
, e
));
851 /*---------------------------------------------------------*/
852 /*--- ISEL: Integer expressions (64/32/16/8 bit) ---*/
853 /*---------------------------------------------------------*/
855 /* Select insns for an integer-typed expression, and add them to the
856 code list. Return a reg holding the result. This reg will be a
857 virtual register. THE RETURNED REG MUST NOT BE MODIFIED. If you
858 want to modify it, ask for a new vreg, copy it in there, and modify
859 the copy. The register allocator will do its best to map both
860 vregs to the same real register, so the copies will often disappear
863 This should handle expressions of 64, 32, 16 and 8-bit type.
864 All results are returned in a (mode64 ? 64bit : 32bit) register.
865 For 16- and 8-bit expressions, the upper (32/48/56 : 16/24) bits
866 are arbitrary, so you should mask or sign extend partial values
869 static HReg
iselWordExpr_R(ISelEnv
* env
, IRExpr
* e
)
871 HReg r
= iselWordExpr_R_wrk(env
, e
);
872 /* sanity checks ... */
874 vassert(hregClass(r
) == HRcGPR(env
->mode64
));
875 vassert(hregIsVirtual(r
));
879 /* DO NOT CALL THIS DIRECTLY ! */
880 static HReg
iselWordExpr_R_wrk(ISelEnv
* env
, IRExpr
* e
)
883 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
884 vassert(ty
== Ity_I8
|| ty
== Ity_I16
|| ty
== Ity_I32
|| ty
== Ity_I1
885 || ty
== Ity_F32
|| (ty
== Ity_I64
&& mode64
)
886 || (ty
== Ity_I128
&& mode64
));
889 /* --------- TEMP --------- */
891 return lookupIRTemp(env
, e
->Iex
.RdTmp
.tmp
);
893 /* --------- LOAD --------- */
895 HReg r_dst
= newVRegI(env
);
896 MIPSAMode
*am_addr
= iselWordExpr_AMode(env
, e
->Iex
.Load
.addr
, ty
);
898 if (e
->Iex
.Load
.end
!= Iend_LE
899 && e
->Iex
.Load
.end
!= Iend_BE
)
902 addInstr(env
, MIPSInstr_Load(toUChar(sizeofIRType(ty
)),
903 r_dst
, am_addr
, mode64
));
907 /* --------- BINARY OP --------- */
912 /* Is it an addition or logical style op? */
913 switch (e
->Iex
.Binop
.op
) {
956 aluOp
= Malu_INVALID
;
960 /* For commutative ops we assume any literal
961 values are on the second operand. */
962 if (aluOp
!= Malu_INVALID
) {
963 HReg r_dst
= newVRegI(env
);
964 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
965 MIPSRH
*ri_srcR
= NULL
;
966 /* get right arg into an RH, in the appropriate way */
972 ri_srcR
= iselWordExpr_RH(env
, True
/*signed */ ,
978 ri_srcR
= iselWordExpr_RH(env
, False
/*unsigned */,
982 vpanic("iselWordExpr_R_wrk-aluOp-arg2");
984 addInstr(env
, MIPSInstr_Alu(aluOp
, r_dst
, r_srcL
, ri_srcR
));
989 switch (e
->Iex
.Binop
.op
) {
1005 shftOp
= Mshft_INVALID
;
1009 /* we assume any literal values are on the second operand. */
1010 if (shftOp
!= Mshft_INVALID
) {
1011 HReg r_dst
= newVRegI(env
);
1012 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1015 ri_srcR
= iselWordExpr_RH6u(env
, e
->Iex
.Binop
.arg2
);
1017 ri_srcR
= iselWordExpr_RH5u(env
, e
->Iex
.Binop
.arg2
);
1021 } else if (ty
== Ity_I16
) {
1022 if (shftOp
== Mshft_SRA
) {
1023 HReg tmp
= newVRegI(env
);
1024 HReg r_srcL_se
= newVRegI(env
);
1025 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, tmp
,
1026 r_srcL
, MIPSRH_Imm(False
, 16)));
1027 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
, r_srcL_se
,
1028 tmp
, MIPSRH_Imm(False
, 16)));
1029 addInstr(env
, MIPSInstr_Shft(shftOp
, True
,
1030 r_dst
, r_srcL_se
, ri_srcR
));
1031 } else if (shftOp
== Mshft_SRL
) {
1032 HReg r_srcL_se
= newVRegI(env
);
1033 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_srcL_se
, r_srcL
,
1034 MIPSRH_Imm(False
, 0xFFFF)));
1035 addInstr(env
, MIPSInstr_Shft(shftOp
, True
,
1036 r_dst
, r_srcL_se
, ri_srcR
));
1040 } else if (ty
== Ity_I32
) {
1041 if (mode64
&& (shftOp
== Mshft_SRA
|| shftOp
== Mshft_SRL
)) {
1042 HReg tmp
= newVRegI(env
);
1043 HReg r_srcL_se
= newVRegI(env
);
1044 /* SRA, SRAV, SRL, SRLV: On 64-bit processors, if GPR rt does
1045 not contain a sign-extended 32-bit value (bits 63..31
1046 equal), then the result of the operation is UNPREDICTABLE.
1047 So we need to sign-extend r_srcL:
1048 DSLLV tmp, r_srcL, 32
1049 DSRAV r_srcL_se, tmp, 32
1051 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, False
, tmp
,
1052 r_srcL
, MIPSRH_Imm(False
, 32)));
1053 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, False
, r_srcL_se
,
1054 tmp
, MIPSRH_Imm(False
, 32)));
1055 /* And finally do the shift. */
1056 addInstr(env
, MIPSInstr_Shft(shftOp
, True
/*32bit shift */,
1057 r_dst
, r_srcL_se
, ri_srcR
));
1059 addInstr(env
, MIPSInstr_Shft(shftOp
, True
/*32bit shift */,
1060 r_dst
, r_srcL
, ri_srcR
));
1061 } else if (ty
== Ity_I64
) {
1063 addInstr(env
, MIPSInstr_Shft(shftOp
, False
/*64bit shift */,
1064 r_dst
, r_srcL
, ri_srcR
));
1070 if (!mode64
&& (e
->Iex
.Binop
.op
== Iop_CasCmpEQ64
1071 || e
->Iex
.Binop
.op
== Iop_CmpEQ64
)) {
1072 HReg tmp1
, tmp2
, tmp3
, tmp4
;
1073 HReg dst1
= newVRegI(env
);
1074 HReg dst2
= newVRegI(env
);
1075 iselInt64Expr(&tmp1
, &tmp2
, env
, e
->Iex
.Binop
.arg1
);
1076 iselInt64Expr(&tmp3
, &tmp4
, env
, e
->Iex
.Binop
.arg2
);
1077 addInstr(env
, MIPSInstr_Cmp(False
, True
, dst1
, tmp1
, tmp3
, MIPScc_EQ
));
1078 addInstr(env
, MIPSInstr_Cmp(False
, True
, dst2
, tmp2
, tmp4
, MIPScc_EQ
));
1079 addInstr(env
, MIPSInstr_Alu(Malu_AND
, dst1
, dst1
, MIPSRH_Reg(dst2
)));
1083 /* Cmp*32*(x,y) ? */
1084 if (e
->Iex
.Binop
.op
== Iop_CmpEQ32
1085 || e
->Iex
.Binop
.op
== Iop_CmpEQ8
1086 || e
->Iex
.Binop
.op
== Iop_CmpEQ16
1087 || e
->Iex
.Binop
.op
== Iop_CmpNE32
1088 || e
->Iex
.Binop
.op
== Iop_CmpNE64
1089 || e
->Iex
.Binop
.op
== Iop_CmpLT32S
1090 || e
->Iex
.Binop
.op
== Iop_CmpLT32U
1091 || e
->Iex
.Binop
.op
== Iop_CmpLT64U
1092 || e
->Iex
.Binop
.op
== Iop_CmpLE32U
1093 || e
->Iex
.Binop
.op
== Iop_CmpLE32S
1094 || e
->Iex
.Binop
.op
== Iop_CmpLE64S
1095 || e
->Iex
.Binop
.op
== Iop_CmpLT64S
1096 || e
->Iex
.Binop
.op
== Iop_CmpEQ64
1097 || e
->Iex
.Binop
.op
== Iop_CasCmpEQ32
1098 || e
->Iex
.Binop
.op
== Iop_CasCmpEQ64
) {
1100 Bool syned
= (e
->Iex
.Binop
.op
== Iop_CmpLT32S
1101 || e
->Iex
.Binop
.op
== Iop_CmpLE32S
1102 || e
->Iex
.Binop
.op
== Iop_CmpLT64S
1103 || e
->Iex
.Binop
.op
== Iop_CmpLE64S
);
1105 HReg dst
= newVRegI(env
);
1106 HReg r1
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1107 HReg r2
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1111 switch (e
->Iex
.Binop
.op
) {
1113 case Iop_CasCmpEQ32
:
1159 case Iop_CasCmpEQ64
:
1164 vpanic("iselCondCode(mips): CmpXX32 or CmpXX64");
1167 addInstr(env
, MIPSInstr_Cmp(syned
, size32
, dst
, r1
, r2
, cc
));
1171 if (e
->Iex
.Binop
.op
== Iop_Max32U
) {
1172 HReg tmp
= newVRegI(env
);
1173 HReg r_dst
= newVRegI(env
);
1174 HReg argL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1175 HReg argR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1176 MIPSRH
*argRH
= MIPSRH_Reg(argR
);
1182 addInstr(env
, MIPSInstr_Alu(Malu_SLT
, tmp
, argL
, argRH
));
1183 #if (__mips_isa_rev >= 6)
1185 HReg r_temp
= newVRegI(env
);
1186 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, r_dst
, argL
, tmp
));
1187 addInstr(env
, MIPSInstr_MoveCond(MSelnez
, r_temp
, argR
, tmp
));
1188 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dst
, r_dst
,
1189 MIPSRH_Reg(r_temp
)));
1193 addInstr(env
, mk_iMOVds_RR(r_dst
, argL
));
1194 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, r_dst
, argR
, tmp
));
1199 if (e
->Iex
.Binop
.op
== Iop_Mul32
) {
1200 HReg r_dst
= newVRegI(env
);
1201 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1202 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1203 #if (__mips_isa_rev >= 6)
1204 addInstr(env
, MIPSInstr_Mulr6(False
, True
, True
,
1205 r_dst
, r_srcL
, r_srcR
));
1207 addInstr(env
, MIPSInstr_Mul(r_dst
, r_srcL
, r_srcR
));
1212 if (e
->Iex
.Binop
.op
== Iop_Mul64
||
1213 e
->Iex
.Binop
.op
== Iop_MullS32
) {
1215 HReg r_dst
= newVRegI(env
);
1216 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1217 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1218 #if (__mips_isa_rev >= 6)
1219 addInstr(env
, MIPSInstr_Mulr6(False
, False
, True
,
1220 r_dst
, r_srcL
, r_srcR
));
1222 addInstr(env
, MIPSInstr_Mult(True
, r_srcL
, r_srcR
));
1223 addInstr(env
, MIPSInstr_Mflo(r_dst
));
1228 if (e
->Iex
.Binop
.op
== Iop_MullU32
) {
1230 HReg r_tmpL
= newVRegI(env
);
1231 HReg r_tmpR
= newVRegI(env
);
1232 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1233 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1234 #if (__mips_isa_rev >= 6)
1235 addInstr(env
, MIPSInstr_Ext(r_tmpL
, r_srcL
, 0, 32));
1236 addInstr(env
, MIPSInstr_Ext(r_tmpR
, r_srcR
, 0, 32));
1237 addInstr(env
, MIPSInstr_Mulr6(True
, False
, True
,
1238 r_tmpR
, r_tmpL
, r_tmpR
));
1240 if (VEX_MIPS_CPU_HAS_MIPS64R2(hwcaps_host
)) {
1241 addInstr(env
, MIPSInstr_Ext(r_tmpL
, r_srcL
, 0, 32));
1242 addInstr(env
, MIPSInstr_Ext(r_tmpR
, r_srcR
, 0, 32));
1244 addInstr(env
, MIPSInstr_LI(r_tmpL
, 0xFFFFFFFF));
1245 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_tmpR
, r_srcR
,
1246 MIPSRH_Reg(r_tmpL
)));
1247 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_tmpL
, r_srcL
,
1248 MIPSRH_Reg(r_tmpL
)));
1250 addInstr(env
, MIPSInstr_Mult(False
, r_tmpL
, r_tmpR
));
1251 addInstr(env
, MIPSInstr_Mflo(r_tmpR
));
1256 if (e
->Iex
.Binop
.op
== Iop_MullU8
||
1257 e
->Iex
.Binop
.op
== Iop_MullS8
||
1258 e
->Iex
.Binop
.op
== Iop_MullU16
||
1259 e
->Iex
.Binop
.op
== Iop_MullS16
) {
1260 Bool syned
= toBool((e
->Iex
.Binop
.op
== Iop_MullS8
) ||
1261 (e
->Iex
.Binop
.op
== Iop_MullS16
));
1262 HReg r_dst
= newVRegI(env
);
1263 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1264 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1265 #if (__mips_isa_rev >= 6)
1267 Int no_bits
= (e
->Iex
.Binop
.op
== Iop_MullS16
) ? 16 : 24;
1268 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
,
1270 MIPSRH_Imm(False
, no_bits
)));
1271 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
,
1273 MIPSRH_Imm(False
, no_bits
)));
1274 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
,
1276 MIPSRH_Imm(False
, no_bits
)));
1277 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
,
1279 MIPSRH_Imm(False
, no_bits
)));
1281 addInstr(env
, MIPSInstr_Mulr6(syned
, True
, True
,
1282 r_dst
, r_srcL
, r_srcR
));
1285 Int no_bits
= (e
->Iex
.Binop
.op
== Iop_MullS16
) ? 16 : 24;
1286 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
,
1288 MIPSRH_Imm(False
, no_bits
)));
1289 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
,
1291 MIPSRH_Imm(False
, no_bits
)));
1292 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
,
1294 MIPSRH_Imm(False
, no_bits
)));
1295 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
,
1297 MIPSRH_Imm(False
, no_bits
)));
1298 addInstr(env
, MIPSInstr_Mul(r_dst
, r_srcL
, r_srcR
));
1301 addInstr(env
, MIPSInstr_Mult(syned
, r_srcL
, r_srcR
));
1302 addInstr(env
, MIPSInstr_Mflo(r_dst
));
1308 if (e
->Iex
.Binop
.op
== Iop_CmpF64
) {
1309 HReg r_srcL
, r_srcR
;
1311 r_srcL
= iselFltExpr(env
, e
->Iex
.Binop
.arg1
);
1312 r_srcR
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
1314 r_srcL
= iselDblExpr(env
, e
->Iex
.Binop
.arg1
);
1315 r_srcR
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
1317 #if (__mips_isa_rev >= 6)
1318 HReg tmp
= newVRegI(env
);
1320 HReg result
= newVRegI(env
);
1321 if (mode64
) tmpf
= newVRegF(env
);
1322 else tmpf
= newVRegD(env
);
1323 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_UN
, tmpf
, r_srcL
, r_srcR
));
1324 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, tmp
, tmpf
));
1325 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
,
1326 MIPSRH_Imm(False
, 0x45)));
1327 addInstr(env
, MIPSInstr_Alu(Malu_OR
, result
,
1328 hregMIPS_GPR0(env
->mode64
),
1330 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_LT
, tmpf
, r_srcL
, r_srcR
));
1331 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, tmp
, tmpf
));
1332 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
,
1333 MIPSRH_Imm(False
, 0x1)));
1334 addInstr(env
, MIPSInstr_Alu(Malu_OR
, result
, result
,
1336 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_EQ
, tmpf
, r_srcL
, r_srcR
));
1337 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, tmp
, tmpf
));
1338 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
,
1339 MIPSRH_Imm(False
, 0x40)));
1340 addInstr(env
, MIPSInstr_Alu(Malu_OR
, result
, result
,
1344 HReg tmp
= newVRegI(env
);
1345 HReg r_ccMIPS
= newVRegI(env
);
1346 HReg r_ccIR
= newVRegI(env
);
1347 HReg r_ccIR_b0
= newVRegI(env
);
1348 HReg r_ccIR_b2
= newVRegI(env
);
1349 HReg r_ccIR_b6
= newVRegI(env
);
1351 /* Create in dst, the IRCmpF64Result encoded result. */
1353 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_EQ
, tmp
, r_srcL
, r_srcR
));
1354 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, r_ccMIPS
, tmp
,
1355 MIPSRH_Imm(False
, 1)));
1357 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_UN
, tmp
, r_srcL
, r_srcR
));
1358 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_ccMIPS
, r_ccMIPS
,
1361 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_LT
, tmp
, r_srcL
, r_srcR
));
1362 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, tmp
,
1363 tmp
, MIPSRH_Imm(False
, 2)));
1364 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_ccMIPS
, r_ccMIPS
,
1367 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_NGT
,
1368 tmp
, r_srcL
, r_srcR
));
1369 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, tmp
, tmp
,
1370 MIPSRH_Imm(False
, 3)));
1372 addInstr(env
, MIPSInstr_Alu(Malu_NOR
, tmp
, tmp
, MIPSRH_Reg(tmp
)));
1373 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
,
1374 MIPSRH_Imm(False
, 8)));
1375 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_ccMIPS
, r_ccMIPS
,
1377 /* Map compare result from MIPS to IR,
1378 conforming to CmpF64 definition.
1379 FP cmp result | MIPS | IR
1380 --------------------------
1387 /* r_ccIR_b0 = r_ccMIPS[0] | r_ccMIPS[3] */
1388 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
, r_ccIR_b0
, r_ccMIPS
,
1389 MIPSRH_Imm(False
, 0x3)));
1390 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_ccIR_b0
, r_ccMIPS
,
1391 MIPSRH_Reg(r_ccIR_b0
)));
1392 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_ccIR_b0
, r_ccIR_b0
,
1393 MIPSRH_Imm(False
, 0x1)));
1395 /* r_ccIR_b2 = r_ccMIPS[0] */
1396 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, r_ccIR_b2
, r_ccMIPS
,
1397 MIPSRH_Imm(False
, 0x2)));
1398 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_ccIR_b2
, r_ccIR_b2
,
1399 MIPSRH_Imm(False
, 0x4)));
1401 /* r_ccIR_b6 = r_ccMIPS[0] | r_ccMIPS[1] */
1402 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
, r_ccIR_b6
,
1403 r_ccMIPS
, MIPSRH_Imm(False
, 0x1)));
1404 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_ccIR_b6
, r_ccMIPS
,
1405 MIPSRH_Reg(r_ccIR_b6
)));
1406 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, r_ccIR_b6
, r_ccIR_b6
,
1407 MIPSRH_Imm(False
, 0x6)));
1408 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_ccIR_b6
, r_ccIR_b6
,
1409 MIPSRH_Imm(False
, 0x40)));
1411 /* r_ccIR = r_ccIR_b0 | r_ccIR_b2 | r_ccIR_b6 */
1412 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_ccIR
, r_ccIR_b0
,
1413 MIPSRH_Reg(r_ccIR_b2
)));
1414 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_ccIR
, r_ccIR
,
1415 MIPSRH_Reg(r_ccIR_b6
)));
1420 if (e
->Iex
.Binop
.op
== Iop_CmpF32
) {
1421 #if (__mips_isa_rev >= 6)
1422 HReg r_srcL
= iselFltExpr(env
, e
->Iex
.Binop
.arg1
);
1423 HReg r_srcR
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
1424 HReg tmp
= newVRegI(env
);
1426 HReg result
= newVRegI(env
);
1427 if (mode64
) tmpf
= newVRegF(env
);
1428 else tmpf
= newVRegD(env
);
1429 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_UN_S
, tmpf
, r_srcL
, r_srcR
));
1430 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, tmp
, tmpf
));
1431 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
,
1432 MIPSRH_Imm(False
, 0x45)));
1433 addInstr(env
, MIPSInstr_Alu(Malu_OR
, result
,
1434 hregMIPS_GPR0(env
->mode64
),
1436 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_LT_S
, tmpf
, r_srcL
, r_srcR
));
1437 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, tmp
, tmpf
));
1438 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
,
1439 MIPSRH_Imm(False
, 0x1)));
1440 addInstr(env
, MIPSInstr_Alu(Malu_OR
, result
, result
,
1442 addInstr(env
, MIPSInstr_FpCompare(Mfp_CMP_EQ_S
, tmpf
, r_srcL
, r_srcR
));
1443 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, tmp
, tmpf
));
1444 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, tmp
,
1445 MIPSRH_Imm(False
, 0x40)));
1446 addInstr(env
, MIPSInstr_Alu(Malu_OR
, result
, result
,
1452 if (e
->Iex
.Binop
.op
== Iop_DivModU32to32
||
1453 e
->Iex
.Binop
.op
== Iop_DivModS32to32
) {
1454 HReg tLo
= newVRegI(env
);
1455 HReg tHi
= newVRegI(env
);
1456 HReg mask
= newVRegI(env
);
1457 HReg tLo_1
= newVRegI(env
);
1458 HReg tHi_1
= newVRegI(env
);
1459 HReg r_dst
= newVRegI(env
);
1460 Bool syned
= toBool(e
->Iex
.Binop
.op
== Iop_DivModS32to32
);
1462 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1463 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1464 #if (__mips_isa_rev >= 6)
1465 addInstr(env
, MIPSInstr_Divr6(syned
/* Unsigned or Signed */ ,
1466 True
/* 32bit or 64bit div */ ,
1468 tLo
, r_srcL
, r_srcR
));
1469 addInstr(env
, MIPSInstr_Divr6(syned
/* Unsigned or Signed */ ,
1470 True
/*3 2bit or 64bit div */ ,
1472 tHi
, r_srcL
, r_srcR
));
1474 addInstr(env
, MIPSInstr_Div(syned
, True
, r_srcL
, r_srcR
));
1475 addInstr(env
, MIPSInstr_Mfhi(tHi
));
1476 addInstr(env
, MIPSInstr_Mflo(tLo
));
1478 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, False
, tHi_1
, tHi
,
1479 MIPSRH_Imm(False
, 32)));
1481 addInstr(env
, MIPSInstr_LI(mask
, 0xffffffff));
1482 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tLo_1
, tLo
,
1485 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dst
, tHi_1
,
1486 MIPSRH_Reg(tLo_1
)));
1491 if (e
->Iex
.Binop
.op
== Iop_DivS32
||
1492 e
->Iex
.Binop
.op
== Iop_DivU32
||
1493 (e
->Iex
.Binop
.op
== Iop_DivS64
&& mode64
) ||
1494 (e
->Iex
.Binop
.op
== Iop_DivU64
&& mode64
)) {
1495 HReg r_dst
= newVRegI(env
);
1496 Bool syned
= toBool(e
->Iex
.Binop
.op
== Iop_DivS32
||
1497 e
->Iex
.Binop
.op
== Iop_DivS64
);
1498 Bool div32
= toBool(e
->Iex
.Binop
.op
== Iop_DivS32
||
1499 e
->Iex
.Binop
.op
== Iop_DivU32
);
1500 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1501 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1502 #if (__mips_isa_rev >= 6)
1503 addInstr(env
, MIPSInstr_Divr6(syned
, div32
, False
,
1504 r_dst
, r_srcL
, r_srcR
));
1506 addInstr(env
, MIPSInstr_Div(syned
, div32
, r_srcL
, r_srcR
));
1507 addInstr(env
, MIPSInstr_Mflo(r_dst
));
1512 if (e
->Iex
.Binop
.op
== Iop_8HLto16
1513 || e
->Iex
.Binop
.op
== Iop_16HLto32
) {
1514 HReg tHi
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1515 HReg tLo
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1516 HReg tLo_1
= newVRegI(env
);
1517 HReg tHi_1
= newVRegI(env
);
1518 HReg r_dst
= newVRegI(env
);
1521 switch (e
->Iex
.Binop
.op
) {
1534 /* sll tHi_1, tHi, shift
1535 and tLo_1, tLo, mask
1536 or r_dst, tHi_1, tLo_1 */
1537 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, tHi_1
, tHi
,
1538 MIPSRH_Imm(False
, shift
)));
1539 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tLo_1
, tLo
,
1540 MIPSRH_Imm(False
, mask
)));
1541 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dst
, tHi_1
,
1542 MIPSRH_Reg(tLo_1
)));
1546 if (e
->Iex
.Binop
.op
== Iop_32HLto64
) {
1548 HReg tHi
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1549 HReg tLo
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1550 HReg tLo_1
= newVRegI(env
);
1551 HReg tHi_1
= newVRegI(env
);
1552 HReg r_dst
= newVRegI(env
);
1553 HReg mask
= newVRegI(env
);
1555 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, False
, tHi_1
, tHi
,
1556 MIPSRH_Imm(False
, 32)));
1558 addInstr(env
, MIPSInstr_LI(mask
, 0xffffffff));
1559 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tLo_1
, tLo
,
1561 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dst
, tHi_1
,
1562 MIPSRH_Reg(tLo_1
)));
1567 if (e
->Iex
.Binop
.op
== Iop_F32toI64S
) {
1569 HReg valS
= newVRegI(env
);
1570 HReg tmpF
= newVRegF(env
);
1571 HReg valF
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
1573 /* CVTLS tmpF, valF */
1574 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
1575 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTLS
, tmpF
, valF
));
1576 set_MIPS_rounding_default(env
);
1578 /* Doubleword Move from Floating Point
1580 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_dmfc1
, valS
, tmpF
));
1585 if (e
->Iex
.Binop
.op
== Iop_F64toI64S
) {
1587 HReg valS
= newVRegI(env
);
1588 HReg tmpF
= newVRegF(env
);
1589 HReg valF
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
1591 /* CVTLS tmpF, valF */
1592 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
1593 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTLD
, tmpF
, valF
));
1594 set_MIPS_rounding_default(env
);
1596 /* Doubleword Move from Floating Point
1598 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_dmfc1
, valS
, tmpF
));
1603 if (e
->Iex
.Binop
.op
== Iop_F64toI32S
) {
1606 valD
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
1608 valD
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
1609 HReg valS
= newVRegF(env
);
1610 HReg r_dst
= newVRegI(env
);
1612 /* CVTWD valS, valD */
1613 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
1614 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTWD
, valS
, valD
));
1615 set_MIPS_rounding_default(env
);
1617 /* Move Word From Floating Point
1619 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, r_dst
, valS
));
1624 if (e
->Iex
.Binop
.op
== Iop_F32toI32U
) {
1625 HReg valF
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
1626 HReg tmpD
= newVRegD(env
);
1627 HReg r_dst
= newVRegI(env
);
1630 /* CVTLS tmpD, valF */
1631 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
1632 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTLS
, tmpD
, valF
));
1633 set_MIPS_rounding_default(env
);
1635 sub_from_sp(env
, 16); /* Move SP down 16 bytes */
1636 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
1639 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 8, tmpD
,
1642 #if defined (_MIPSEL)
1643 addInstr(env
, MIPSInstr_Load(4, r_dst
, am_addr
, mode64
));
1644 #elif defined (_MIPSEB)
1645 addInstr(env
, MIPSInstr_Load(4, r_dst
, nextMIPSAModeFloat(am_addr
),
1655 if (e
->Iex
.Binop
.op
== Iop_F64toI64U
) {
1657 HReg tmp
= newVRegV(env
);
1659 r_src
= iselFltExpr( env
, e
->Iex
.Binop
.arg2
);
1660 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Binop
.arg1
);
1661 addInstr(env
, MIPSInstr_Msa2RF(MSA_FTINT_U
, MSA_F_DW
, tmp
, r_src
));
1662 HReg r_dst
= newVRegI(env
);
1664 MIPSInstr_MsaElm(MSA_COPY_S
, tmp
, r_dst
, MSA_DFN_D
| 0));
1665 set_MIPS_rounding_default_MSA(env
);
1669 if (e
->Iex
.Binop
.op
== Iop_GetElem8x16
) {
1670 HReg v_src
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
1671 HReg r_dst
= newVRegI(env
);
1672 MIPSRH
*tmp
= iselWordExpr_RH(env
, False
, e
->Iex
.Binop
.arg2
);
1677 MIPSInstr_MsaElm(MSA_COPY_U
, v_src
, r_dst
,
1679 (tmp
->Mrh
.Imm
.imm16
& 0x0f)));
1683 HReg v_tmp
= newVRegV(env
);
1685 MIPSInstr_Msa3R(MSA_SPLAT
, MSA_B
, v_tmp
, v_src
,
1688 MIPSInstr_MsaElm(MSA_COPY_U
, v_tmp
, r_dst
,
1698 if (e
->Iex
.Binop
.op
== Iop_GetElem16x8
) {
1699 HReg v_src
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
1700 HReg r_dst
= newVRegI(env
);
1701 MIPSRH
*tmp
= iselWordExpr_RH(env
, False
, e
->Iex
.Binop
.arg2
);
1706 MIPSInstr_MsaElm(MSA_COPY_U
, v_src
, r_dst
,
1708 (tmp
->Mrh
.Imm
.imm16
& 0x07)));
1712 HReg v_tmp
= newVRegV(env
);
1714 MIPSInstr_Msa3R(MSA_SPLAT
, MSA_H
, v_tmp
, v_src
,
1717 MIPSInstr_MsaElm(MSA_COPY_U
, v_tmp
, r_dst
,
1726 if (e
->Iex
.Binop
.op
== Iop_GetElem32x4
) {
1727 HReg v_src
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
1728 HReg r_dst
= newVRegI(env
);
1729 MIPSRH
*tmp
= iselWordExpr_RH(env
, False
, e
->Iex
.Binop
.arg2
);
1733 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, r_dst
,
1735 (tmp
->Mrh
.Imm
.imm16
& 0x03)));
1739 HReg v_tmp
= newVRegV(env
);
1741 MIPSInstr_Msa3R(MSA_SPLAT
, MSA_W
, v_tmp
, v_src
,
1744 MIPSInstr_MsaElm(MSA_COPY_S
, v_tmp
, r_dst
,
1752 if (e
->Iex
.Binop
.op
== Iop_GetElem64x2
) {
1754 HReg v_src
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
1755 HReg r_dst
= newVRegI(env
);
1756 MIPSRH
*tmp
= iselWordExpr_RH(env
, False
, e
->Iex
.Binop
.arg2
);
1761 MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, r_dst
,
1763 (tmp
->Mrh
.Imm
.imm16
& 0x01)));
1767 HReg v_tmp
= newVRegV(env
);
1769 MIPSInstr_Msa3R(MSA_SPLAT
, MSA_D
, v_tmp
, v_src
,
1772 MIPSInstr_MsaElm(MSA_COPY_S
, v_tmp
, r_dst
,
1781 if (e
->Iex
.Binop
.op
== Iop_F32toI32S
) {
1782 HReg valS
= newVRegF(env
);
1783 HReg valF
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
1784 HReg r_dst
= newVRegI(env
);
1786 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
1787 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTWS
, valS
, valF
));
1788 set_MIPS_rounding_default(env
);
1790 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, r_dst
, valS
));
1795 /* -------- DSP ASE -------- */
1796 /* All used cases involving host-side helper calls. */
1798 switch (e
->Iex
.Binop
.op
) {
1800 fn
= &h_generic_calc_HAdd8Ux4
; break;
1802 fn
= &h_generic_calc_HSub8Ux4
; break;
1804 fn
= &h_generic_calc_HSub16Sx2
; break;
1806 fn
= &h_generic_calc_QSub8Ux4
; break;
1811 /* What's the retloc? */
1812 RetLoc rloc
= mk_RetLoc_INVALID();
1813 if (ty
== Ity_I32
) {
1814 rloc
= mk_RetLoc_simple(RLPri_Int
);
1816 else if (ty
== Ity_I64
) {
1817 rloc
= mode64
? mk_RetLoc_simple(RLPri_Int
) :
1818 mk_RetLoc_simple(RLPri_2Int
);
1825 HReg regL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
1826 HReg regR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
1827 HReg res
= newVRegI(env
);
1828 addInstr(env
, mk_iMOVds_RR(hregMIPS_GPR4(env
->mode64
), regL
));
1829 addInstr(env
, mk_iMOVds_RR(hregMIPS_GPR5(env
->mode64
), regR
));
1830 argiregs
|= (1 << 4);
1831 argiregs
|= (1 << 5);
1832 addInstr(env
, MIPSInstr_CallAlways( MIPScc_AL
,
1835 addInstr(env
, mk_iMOVds_RR(res
, hregMIPS_GPR2(env
->mode64
)));
1841 /* --------- UNARY OP --------- */
1843 IROp op_unop
= e
->Iex
.Unop
.op
;
1855 HReg r_dst
= newVRegI(env
);
1856 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
1900 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, sz32
, r_dst
, r_src
,
1901 MIPSRH_Imm(False
, amt
)));
1902 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, sz32
, r_dst
, r_dst
,
1903 MIPSRH_Imm(False
, amt
)));
1907 /* not(x) = nor(x,x) */
1909 HReg r_dst
= newVRegI(env
);
1910 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
1911 MIPSRH
*r_srcR
= MIPSRH_Reg(r_srcL
);
1913 addInstr(env
, MIPSInstr_LI(r_dst
, 0x1));
1914 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, r_dst
, r_dst
, r_srcR
));
1922 HReg r_dst
= newVRegI(env
);
1923 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
1924 MIPSRH
*r_srcR
= MIPSRH_Reg(r_srcL
);
1926 addInstr(env
, MIPSInstr_Alu(Malu_NOR
, r_dst
, r_srcL
, r_srcR
));
1930 case Iop_ReinterpF32asI32
: {
1931 HReg fr_src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
1932 HReg r_dst
= newVRegI(env
);
1934 /* Move Word From Floating Point
1935 mfc1 r_dst, fr_src */
1936 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, r_dst
, fr_src
));
1941 case Iop_ReinterpF64asI64
: {
1943 HReg fr_src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
1944 HReg r_dst
= newVRegI(env
);
1946 /* Doubleword Move from Floating Point
1947 mfc1 r_dst, fr_src */
1948 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_dmfc1
, r_dst
, fr_src
));
1953 case Iop_F64toI32S
: {
1956 valD
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
1958 valD
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
1959 HReg valS
= newVRegF(env
);
1960 HReg r_dst
= newVRegI(env
);
1962 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
1963 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTWD
, valS
, valD
));
1964 set_MIPS_rounding_default(env
);
1966 /* Move Word From Floating Point
1968 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mfc1
, r_dst
, valS
));
1977 return iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
1979 case Iop_32HIto16
: {
1980 HReg r_dst
= newVRegI(env
);
1981 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
1982 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/* 32bit shift */,
1983 r_dst
, r_src
, MIPSRH_Imm(False
, 16)));
1990 UShort mask
= (op_unop
== Iop_64to1
) ? 0x1 : 0xFF;
1991 r_dst
= newVRegI(env
);
1993 r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
1996 iselInt64Expr(&tmp
, &r_src
, env
, e
->Iex
.Unop
.arg
);
1998 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_dst
, r_src
,
1999 MIPSRH_Imm(False
, mask
)));
2004 HReg r_dst
= newVRegI(env
);
2005 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2006 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/* 32bit shift */,
2007 r_dst
, r_src
, MIPSRH_Imm(False
, 8)));
2019 HReg r_dst
= newVRegI(env
);
2020 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2027 mask
= toUShort(0x1);
2033 mask
= toUShort(0xFF);
2038 mask
= toUShort(0xFFFF);
2044 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_dst
, r_src
,
2045 MIPSRH_Imm(False
, mask
)));
2050 HReg r_dst
= newVRegI(env
);
2051 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2053 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, False
/*!32bit shift */,
2054 r_dst
, r_src
, MIPSRH_Imm(False
, 32)));
2055 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, False
/*!32bit shift */,
2056 r_dst
, r_dst
, MIPSRH_Imm(False
, 32)));
2060 case Iop_64HIto32
: {
2062 HReg r_dst
= newVRegI(env
);
2063 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2064 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, False
/*64bit shift */,
2065 r_dst
, r_src
, MIPSRH_Imm(True
, 32)));
2069 iselInt64Expr(&rHi
, &rLo
, env
, e
->Iex
.Unop
.arg
);
2076 HReg r_dst
= newVRegI(env
);
2077 r_dst
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2081 iselInt64Expr(&rHi
, &rLo
, env
, e
->Iex
.Unop
.arg
);
2087 vassert(env
->mode64
);
2088 HReg r_dst
= newVRegI(env
);
2089 r_dst
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2094 HReg r_dst
= newVRegI(env
);
2095 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2097 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
/*!32bit shift */,
2098 r_dst
, r_src
, MIPSRH_Imm(True
, 0)));
2103 case Iop_CmpNEZ16
: {
2104 HReg r_dst
= newVRegI(env
);
2105 HReg tmp
= newVRegI(env
);
2106 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2107 UShort mask
= (op_unop
== Iop_CmpNEZ8
) ? 0xFF : 0xFFFF;
2109 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tmp
, r_src
,
2110 MIPSRH_Imm(False
, mask
)));
2111 addInstr(env
, MIPSInstr_Cmp(False
, True
, r_dst
, tmp
,
2112 hregMIPS_GPR0(mode64
), MIPScc_NE
));
2116 case Iop_CmpNEZ32
: {
2117 HReg r_dst
= newVRegI(env
);
2118 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2120 addInstr(env
, MIPSInstr_Cmp(False
, True
, r_dst
, r_src
,
2121 hregMIPS_GPR0(mode64
), MIPScc_NE
));
2125 case Iop_CmpwNEZ32
: {
2126 HReg r_dst
= newVRegI(env
);
2127 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2129 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, r_dst
, hregMIPS_GPR0(mode64
),
2130 MIPSRH_Reg(r_src
)));
2132 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dst
, r_dst
,
2133 MIPSRH_Reg(r_src
)));
2134 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
, r_dst
, r_dst
,
2135 MIPSRH_Imm(False
, 31)));
2143 if (op_unop
== Iop_Left64
&& !mode64
)
2145 HReg r_dst
= newVRegI(env
);
2146 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2147 MIPSAluOp op
= (op_unop
== Iop_Left64
) ? Malu_DSUB
: Malu_SUB
;
2148 addInstr(env
, MIPSInstr_Alu(op
, r_dst
,
2149 hregMIPS_GPR0(mode64
),
2150 MIPSRH_Reg(r_src
)));
2151 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dst
, r_dst
,
2152 MIPSRH_Reg(r_src
)));
2159 HReg r_dst
= newVRegI(env
);
2160 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2161 MIPSUnaryOp op
= (op_unop
== Iop_Clz64
) ? Mun_DCLZ
: Mun_CLZ
;
2162 addInstr(env
, MIPSInstr_Unary(op
, r_dst
, r_src
));
2166 case Iop_CmpNEZ64
: {
2168 HReg r_dst
= newVRegI(env
);
2171 r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2173 r_src
= newVRegI(env
);
2174 iselInt64Expr(&hi
, &lo
, env
, e
->Iex
.Unop
.arg
);
2175 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_src
, lo
, MIPSRH_Reg(hi
)));
2177 addInstr(env
, MIPSInstr_Cmp(False
, !(env
->mode64
), r_dst
, r_src
,
2178 hregMIPS_GPR0(mode64
), MIPScc_NE
));
2182 case Iop_CmpwNEZ64
: {
2184 HReg tmp2
= newVRegI(env
);
2185 vassert(env
->mode64
);
2186 tmp1
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2188 addInstr(env
, MIPSInstr_Alu(Malu_DSUB
, tmp2
, hregMIPS_GPR0(mode64
),
2191 addInstr(env
, MIPSInstr_Alu(Malu_OR
, tmp2
, tmp2
, MIPSRH_Reg(tmp1
)));
2192 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, False
, tmp2
, tmp2
,
2193 MIPSRH_Imm (False
, 63)));
2197 case Iop_128HIto64
: {
2200 iselInt128Expr(&rHi
, &rLo
, env
, e
->Iex
.Unop
.arg
);
2201 return rHi
; /* and abandon rLo .. poor wee thing :-) */
2207 iselInt128Expr(&rHi
, &rLo
, env
, e
->Iex
.Unop
.arg
);
2208 return rLo
; /* and abandon rLo .. poor wee thing :-) */
2211 case Iop_V128to32
: {
2212 HReg i_dst
= newVRegI(env
);
2213 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2216 MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, i_dst
, MSA_DFN_W
));
2220 case Iop_V128HIto64
: {
2223 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2224 HReg reg
= newVRegI(env
);
2226 MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, reg
, MSA_DFN_D
| 1));
2230 case Iop_V128to64
: {
2233 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2234 HReg reg
= newVRegI(env
);
2236 MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, reg
, MSA_DFN_D
| 0));
2240 case Iop_F32toF16x4
: {
2243 HReg v_arg
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2244 HReg v_src
= newVRegV(env
);
2245 set_guest_MIPS_rounding_mode_MSA(env
);
2247 MIPSInstr_Msa3RF(MSA_FEXDO
, MSA_F_WH
,
2248 v_src
, v_arg
, v_arg
));
2249 set_MIPS_rounding_default_MSA(env
);
2250 HReg reg
= newVRegI(env
);
2252 MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, reg
, MSA_DFN_D
| 0));
2261 /* -------- DSP ASE -------- */
2262 /* All Unop cases involving host-side helper calls. */
2264 switch (e
->Iex
.Unop
.op
) {
2265 case Iop_CmpNEZ16x2
:
2266 fn
= &h_generic_calc_CmpNEZ16x2
; break;
2268 fn
= &h_generic_calc_CmpNEZ8x4
; break;
2273 RetLoc rloc
= mk_RetLoc_INVALID();
2274 if (ty
== Ity_I32
) {
2275 rloc
= mk_RetLoc_simple(RLPri_Int
);
2277 else if (ty
== Ity_I64
) {
2278 rloc
= mode64
? mk_RetLoc_simple(RLPri_Int
) :
2279 mk_RetLoc_simple(RLPri_2Int
);
2286 HReg regL
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2287 HReg res
= newVRegI(env
);
2288 addInstr(env
, mk_iMOVds_RR(hregMIPS_GPR4(env
->mode64
), regL
));
2289 argiregs
|= (1 << 4);
2290 addInstr(env
, MIPSInstr_CallAlways( MIPScc_AL
,
2293 addInstr(env
, mk_iMOVds_RR(res
, hregMIPS_GPR2(env
->mode64
)));
2300 /* --------- GET --------- */
2302 if (ty
== Ity_I8
|| ty
== Ity_I16
|| ty
== Ity_I32
2303 || ((ty
== Ity_I64
) && mode64
)) {
2304 HReg r_dst
= newVRegI(env
);
2306 MIPSAMode
*am_addr
= MIPSAMode_IR(e
->Iex
.Get
.offset
,
2307 GuestStatePointer(mode64
));
2308 addInstr(env
, MIPSInstr_Load(toUChar(sizeofIRType(ty
)), r_dst
, am_addr
,
2315 /* --------- ITE --------- */
2317 if ((ty
== Ity_I8
|| ty
== Ity_I16
||
2318 ty
== Ity_I32
|| ((ty
== Ity_I64
))) &&
2319 typeOfIRExpr(env
->type_env
, e
->Iex
.ITE
.cond
) == Ity_I1
) {
2320 HReg r0
= iselWordExpr_R(env
, e
->Iex
.ITE
.iffalse
);
2321 HReg r1
= iselWordExpr_R(env
, e
->Iex
.ITE
.iftrue
);
2322 HReg r_cond
= iselWordExpr_R(env
, e
->Iex
.ITE
.cond
);
2323 HReg r_dst
= newVRegI(env
);
2326 * movn r_dst, r1, r_cond
2328 #if (__mips_isa_rev >= 6)
2329 HReg r_temp
= newVRegI(env
);
2330 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, r_dst
, r0
, r_cond
));
2331 addInstr(env
, MIPSInstr_MoveCond(MSelnez
, r_temp
, r1
, r_cond
));
2332 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dst
, r_dst
,
2333 MIPSRH_Reg(r_temp
)));
2336 addInstr(env
, mk_iMOVds_RR(r_dst
, r0
));
2337 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, r_dst
, r1
, r_cond
));
2344 /* --------- LITERAL --------- */
2345 /* 32/16/8-bit literals */
2348 HReg r_dst
= newVRegI(env
);
2349 IRConst
*con
= e
->Iex
.Const
.con
;
2354 l
= (Long
) con
->Ico
.U64
;
2357 l
= (Long
) (Int
) con
->Ico
.U32
;
2360 l
= (Long
) (Int
) (Short
) con
->Ico
.U16
;
2363 l
= (Long
) (Int
) (Char
) con
->Ico
.U8
;
2366 vpanic("iselIntExpr_R.const(mips)");
2368 addInstr(env
, MIPSInstr_LI(r_dst
, (ULong
) l
));
2372 /* --------- CCALL --------- */
2374 HReg r_dst
= newVRegI(env
);
2375 vassert(ty
== e
->Iex
.CCall
.retty
);
2377 /* be very restrictive for now. Only 32/64-bit ints allowed for
2378 args, and 64 and 32 bits for return type. Don't forget to change
2379 the RetLoc if more return types are allowed in future. */
2380 if (e
->Iex
.CCall
.retty
!= Ity_I64
&& e
->Iex
.CCall
.retty
!= Ity_I32
)
2383 /* Marshal args, do the call, clear stack. */
2385 RetLoc rloc
= mk_RetLoc_INVALID();
2386 doHelperCall(&addToSp
, &rloc
, env
, NULL
/*guard*/, e
->Iex
.CCall
.cee
,
2387 e
->Iex
.CCall
.retty
, e
->Iex
.CCall
.args
);
2389 vassert(is_sane_RetLoc(rloc
));
2390 vassert(rloc
.pri
== RLPri_Int
);
2391 vassert(addToSp
== 0);
2392 addInstr(env
, mk_iMOVds_RR(r_dst
, hregMIPS_GPR2(mode64
)));
2396 #if (__mips_isa_rev >= 6)
2398 HReg dst
= newVRegI(env
);
2399 HReg src1
= iselWordExpr_R(env
, e
->Iex
.Qop
.details
->arg1
);
2400 HReg src2
= iselWordExpr_R(env
, e
->Iex
.Qop
.details
->arg2
);
2401 HReg src3
= iselWordExpr_R(env
, e
->Iex
.Qop
.details
->arg3
);
2402 HReg src4
= iselWordExpr_R(env
, e
->Iex
.Qop
.details
->arg4
);
2403 switch (e
->Iex
.Qop
.details
->op
) {
2405 addInstr(env
, MIPSInstr_Bitswap(Rotx32
, dst
, src1
, src2
, src3
, src4
));
2408 addInstr(env
, MIPSInstr_Bitswap(Rotx64
, dst
, src1
, src2
, src3
, src4
));
2419 } /* end switch(e->tag) */
2421 /* We get here if no pattern matched. */
2423 vex_printf("--------------->\n");
2424 if (e
->tag
== Iex_RdTmp
)
2425 vex_printf("Iex_RdTmp \n");
2428 vpanic("iselWordExpr_R(mips): cannot reduce tree");
2431 /* --------------------- RH --------------------- */
2433 /* Compute an I8/I16/I32 (and I64, in 64-bit mode) into a RH
2434 (reg-or-halfword-immediate). It's important to specify whether the
2435 immediate is to be regarded as signed or not. If yes, this will
2436 never return -32768 as an immediate; this guaranteed that all
2437 signed immediates that are return can have their sign inverted if
2440 static MIPSRH
*iselWordExpr_RH(ISelEnv
* env
, Bool syned
, IRExpr
* e
)
2442 MIPSRH
*ri
= iselWordExpr_RH_wrk(env
, syned
, e
);
2443 /* sanity checks ... */
2446 vassert(ri
->Mrh
.Imm
.syned
== syned
);
2448 vassert(ri
->Mrh
.Imm
.imm16
!= 0x8000);
2451 vassert(hregClass(ri
->Mrh
.Reg
.reg
) == HRcGPR(env
->mode64
));
2452 vassert(hregIsVirtual(ri
->Mrh
.Reg
.reg
));
2455 vpanic("iselIntExpr_RH: unknown mips RH tag");
2459 /* DO NOT CALL THIS DIRECTLY ! */
2460 static MIPSRH
*iselWordExpr_RH_wrk(ISelEnv
* env
, Bool syned
, IRExpr
* e
)
2464 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
2465 vassert(ty
== Ity_I8
|| ty
== Ity_I16
|| ty
== Ity_I32
||
2466 ((ty
== Ity_I64
) && env
->mode64
));
2468 /* special case: immediate */
2469 if (e
->tag
== Iex_Const
) {
2470 IRConst
*con
= e
->Iex
.Const
.con
;
2471 /* What value are we aiming to generate? */
2473 /* Note: Not sign-extending - we carry 'syned' around */
2475 vassert(env
->mode64
);
2479 u
= 0xFFFFFFFF & con
->Ico
.U32
;
2482 u
= 0x0000FFFF & con
->Ico
.U16
;
2485 u
= 0x000000FF & con
->Ico
.U8
;
2488 vpanic("iselIntExpr_RH.Iex_Const(mips)");
2491 /* Now figure out if it's representable. */
2492 if (!syned
&& u
<= 65535) {
2493 return MIPSRH_Imm(False
/*unsigned */ , toUShort(u
& 0xFFFF));
2495 if (syned
&& l
>= -32767 && l
<= 32767) {
2496 return MIPSRH_Imm(True
/*signed */ , toUShort(u
& 0xFFFF));
2498 /* no luck; use the Slow Way. */
2500 /* default case: calculate into a register and return that */
2501 return MIPSRH_Reg(iselWordExpr_R(env
, e
));
2504 /* --------------------- RH5u --------------------- */
2506 /* Compute an I8 into a reg-or-5-bit-unsigned-immediate, the latter
2507 being an immediate in the range 1 .. 31 inclusive. Used for doing
2510 static MIPSRH
*iselWordExpr_RH5u(ISelEnv
* env
, IRExpr
* e
)
2513 ri
= iselWordExpr_RH5u_wrk(env
, e
);
2514 /* sanity checks ... */
2517 vassert(ri
->Mrh
.Imm
.imm16
>= 1 && ri
->Mrh
.Imm
.imm16
<= 31);
2518 vassert(!ri
->Mrh
.Imm
.syned
);
2521 vassert(hregClass(ri
->Mrh
.Reg
.reg
) == HRcInt32
);
2522 vassert(hregIsVirtual(ri
->Mrh
.Reg
.reg
));
2525 vpanic("iselIntExpr_RH5u: unknown mips RH tag");
2529 /* DO NOT CALL THIS DIRECTLY ! */
2530 static MIPSRH
*iselWordExpr_RH5u_wrk(ISelEnv
* env
, IRExpr
* e
)
2532 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
2533 vassert(ty
== Ity_I8
);
2535 /* special case: immediate */
2536 if (e
->tag
== Iex_Const
2537 && e
->Iex
.Const
.con
->tag
== Ico_U8
2538 && e
->Iex
.Const
.con
->Ico
.U8
>= 1 && e
->Iex
.Const
.con
->Ico
.U8
<= 31) {
2539 return MIPSRH_Imm(False
/*unsigned */ , e
->Iex
.Const
.con
->Ico
.U8
);
2542 /* default case: calculate into a register and return that */
2543 return MIPSRH_Reg(iselWordExpr_R(env
, e
));
2546 /* --------------------- RH6u --------------------- */
2548 static MIPSRH
*iselWordExpr_RH6u ( ISelEnv
* env
, IRExpr
* e
)
2551 ri
= iselWordExpr_RH6u_wrk(env
, e
);
2552 /* sanity checks ... */
2555 vassert(ri
->Mrh
.Imm
.imm16
>= 1 && ri
->Mrh
.Imm
.imm16
<= 63);
2556 vassert(!ri
->Mrh
.Imm
.syned
);
2559 vassert(hregClass(ri
->Mrh
.Reg
.reg
) == HRcGPR(env
->mode64
));
2560 vassert(hregIsVirtual(ri
->Mrh
.Reg
.reg
));
2563 vpanic("iselIntExpr_RH6u: unknown RI tag");
2567 /* DO NOT CALL THIS DIRECTLY ! */
2568 static MIPSRH
*iselWordExpr_RH6u_wrk ( ISelEnv
* env
, IRExpr
* e
)
2570 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
2571 vassert(ty
== Ity_I8
);
2573 /* special case: immediate */
2574 if (e
->tag
== Iex_Const
2575 && e
->Iex
.Const
.con
->tag
== Ico_U8
2576 && e
->Iex
.Const
.con
->Ico
.U8
>= 1 && e
->Iex
.Const
.con
->Ico
.U8
<= 63)
2578 return MIPSRH_Imm(False
/*unsigned */ ,
2579 e
->Iex
.Const
.con
->Ico
.U8
);
2582 /* default case: calculate into a register and return that */
2583 return MIPSRH_Reg(iselWordExpr_R(env
, e
));
2585 /* --------------------- RH7u --------------------- */
2587 static MIPSRH
*iselWordExpr_RH7u ( ISelEnv
* env
, IRExpr
* e
)
2590 ri
= iselWordExpr_RH7u_wrk(env
, e
);
2591 /* sanity checks ... */
2594 vassert(ri
->Mrh
.Imm
.imm16
>= 1 && ri
->Mrh
.Imm
.imm16
<= 127);
2595 vassert(!ri
->Mrh
.Imm
.syned
);
2598 vassert(hregClass(ri
->Mrh
.Reg
.reg
) == HRcGPR(env
->mode64
));
2599 vassert(hregIsVirtual(ri
->Mrh
.Reg
.reg
));
2602 vpanic("iselIntExpr_RH7u: unknown RI tag");
2606 /* DO NOT CALL THIS DIRECTLY ! */
2607 static MIPSRH
*iselWordExpr_RH7u_wrk ( ISelEnv
* env
, IRExpr
* e
)
2609 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
2610 vassert(ty
== Ity_I8
);
2612 /* special case: immediate */
2613 if (e
->tag
== Iex_Const
2614 && e
->Iex
.Const
.con
->tag
== Ico_U8
2615 && e
->Iex
.Const
.con
->Ico
.U8
>= 1 && e
->Iex
.Const
.con
->Ico
.U8
<= 127)
2617 return MIPSRH_Imm(False
/*unsigned */ ,
2618 e
->Iex
.Const
.con
->Ico
.U8
);
2621 /* default case: calculate into a register and return that */
2622 return MIPSRH_Reg(iselWordExpr_R(env
, e
));
2626 /* --------------------- CONDCODE --------------------- */
2628 /* Generate code to evaluated a bit-typed expression, returning the
2629 condition code which would correspond when the expression would
2630 notionally have returned 1. */
2632 static MIPSCondCode
iselCondCode(ISelEnv
* env
, IRExpr
* e
)
2634 MIPSCondCode cc
= iselCondCode_wrk(env
,e
);
2635 vassert(cc
!= MIPScc_NV
);
2639 /* DO NOT CALL THIS DIRECTLY ! */
2640 static MIPSCondCode
iselCondCode_wrk(ISelEnv
* env
, IRExpr
* e
)
2643 vassert(typeOfIRExpr(env
->type_env
, e
) == Ity_I1
);
2644 /* Cmp*32*(x,y) ? */
2645 if (e
->Iex
.Binop
.op
== Iop_CmpEQ32
2646 || e
->Iex
.Binop
.op
== Iop_CmpNE32
2647 || e
->Iex
.Binop
.op
== Iop_CmpNE64
2648 || e
->Iex
.Binop
.op
== Iop_CmpLT32S
2649 || e
->Iex
.Binop
.op
== Iop_CmpLT32U
2650 || e
->Iex
.Binop
.op
== Iop_CmpLT64U
2651 || e
->Iex
.Binop
.op
== Iop_CmpLE32S
2652 || e
->Iex
.Binop
.op
== Iop_CmpLE64S
2653 || e
->Iex
.Binop
.op
== Iop_CmpLT64S
2654 || e
->Iex
.Binop
.op
== Iop_CmpEQ64
2655 || e
->Iex
.Binop
.op
== Iop_CasCmpEQ32
2656 || e
->Iex
.Binop
.op
== Iop_CasCmpEQ64
) {
2658 Bool syned
= (e
->Iex
.Binop
.op
== Iop_CmpLT32S
2659 || e
->Iex
.Binop
.op
== Iop_CmpLE32S
2660 || e
->Iex
.Binop
.op
== Iop_CmpLT64S
2661 || e
->Iex
.Binop
.op
== Iop_CmpLE64S
);
2663 HReg dst
= newVRegI(env
);
2664 HReg r1
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
2665 HReg r2
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
2669 switch (e
->Iex
.Binop
.op
) {
2671 case Iop_CasCmpEQ32
:
2708 case Iop_CasCmpEQ64
:
2713 vpanic("iselCondCode(mips): CmpXX32 or CmpXX64");
2717 addInstr(env
, MIPSInstr_Cmp(syned
, size32
, dst
, r1
, r2
, cc
));
2718 /* Store result to guest_COND */
2719 MIPSAMode
*am_addr
= MIPSAMode_IR(0, GuestStatePointer(mode64
));
2721 addInstr(env
, MIPSInstr_Store(4,
2722 MIPSAMode_IR(am_addr
->Mam
.IR
.index
+ COND_OFFSET(mode64
),
2723 am_addr
->Mam
.IR
.base
),
2727 if (e
->Iex
.Binop
.op
== Iop_Not1
) {
2728 HReg r_dst
= newVRegI(env
);
2729 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
2730 MIPSRH
*r_srcR
= MIPSRH_Reg(r_srcL
);
2732 addInstr(env
, MIPSInstr_LI(r_dst
, 0x1));
2733 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, r_dst
, r_dst
, r_srcR
));
2734 /* Store result to guest_COND */
2735 MIPSAMode
*am_addr
= MIPSAMode_IR(0, GuestStatePointer(mode64
));
2737 addInstr(env
, MIPSInstr_Store(4,
2738 MIPSAMode_IR(am_addr
->Mam
.IR
.index
+ COND_OFFSET(mode64
),
2739 am_addr
->Mam
.IR
.base
),
2743 if (e
->tag
== Iex_RdTmp
|| e
->tag
== Iex_Unop
) {
2744 HReg r_dst
= iselWordExpr_R_wrk(env
, e
);
2745 /* Store result to guest_COND */
2746 MIPSAMode
*am_addr
= MIPSAMode_IR(0, GuestStatePointer(mode64
));
2748 addInstr(env
, MIPSInstr_Store(4,
2749 MIPSAMode_IR(am_addr
->Mam
.IR
.index
+ COND_OFFSET(mode64
),
2750 am_addr
->Mam
.IR
.base
),
2755 vex_printf("iselCondCode(mips): No such tag(%u)\n", e
->tag
);
2757 vpanic("iselCondCode(mips)");
2760 /*---------------------------------------------------------*/
2761 /*--- ISEL: Vector expressions (128 bit - SIMD) ---*/
2762 /*---------------------------------------------------------*/
2764 /* Compute a vector value into vector register. */
2765 static HReg
iselV128Expr (ISelEnv
* env
, IRExpr
* e
) {
2767 HReg r
= iselV128Expr_wrk(env
, e
);
2768 vassert(hregClass(r
) == HRcVec128
);
2769 vassert(hregIsVirtual(r
));
2773 /* DO NOT CALL THIS DIRECTLY ! */
2774 static HReg
iselV128Expr_wrk(ISelEnv
* env
, IRExpr
* e
) {
2775 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
2777 vassert(ty
== Ity_V128
);
2779 if (e
->tag
== Iex_RdTmp
) {
2780 return lookupIRTemp(env
, e
->Iex
.RdTmp
.tmp
);
2783 if (e
->tag
== Iex_Load
) {
2784 vassert (e
->Iex
.Load
.ty
== Ity_V128
);
2785 HReg v_dst
= newVRegV(env
);
2786 addInstr(env
, MIPSInstr_MsaMi10(MSA_LD
, 0, iselWordExpr_R(env
,
2787 e
->Iex
.Load
.addr
), v_dst
, MSA_B
));
2791 if (e
->tag
== Iex_Get
) {
2792 HReg v_dst
= newVRegV(env
);
2793 #if defined(_MIPSEB)
2794 HReg r_addr
= newVRegI(env
);
2795 addInstr(env
, MIPSInstr_Alu(mode64
? Malu_DADD
: Malu_ADD
, r_addr
, GuestStatePointer(mode64
),
2796 MIPSRH_Imm(False
, e
->Iex
.Get
.offset
)));
2797 addInstr(env
, MIPSInstr_MsaMi10(MSA_LD
, 0, r_addr
, v_dst
, MSA_B
));
2799 vassert(!(e
->Iex
.Get
.offset
& 7));
2800 addInstr(env
, MIPSInstr_MsaMi10(MSA_LD
, e
->Iex
.Get
.offset
>> 3,
2801 GuestStatePointer(mode64
), v_dst
, MSA_D
));
2806 if (e
->tag
== Iex_Unop
) {
2807 IROp op_unop
= e
->Iex
.Unop
.op
;
2811 HReg v_dst
= newVRegV(env
);
2812 HReg v_help
= newVRegV(env
);
2813 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2815 MIPSInstr_Msa3R(MSA_SUBV
, MSA_D
, v_help
, v_src
, v_src
));
2817 MIPSInstr_Msa3R(MSA_ADD_A
, MSA_D
,
2818 v_dst
, v_src
, v_help
));
2823 HReg v_dst
= newVRegV(env
);
2824 HReg v_help
= newVRegV(env
);
2825 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2827 MIPSInstr_Msa3R(MSA_SUBV
, MSA_W
, v_help
, v_src
, v_src
));
2829 MIPSInstr_Msa3R(MSA_ADD_A
, MSA_W
,
2830 v_dst
, v_src
, v_help
));
2835 HReg v_dst
= newVRegV(env
);
2836 HReg v_help
= newVRegV(env
);
2837 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2839 MIPSInstr_Msa3R(MSA_SUBV
, MSA_H
, v_help
, v_src
, v_src
));
2841 MIPSInstr_Msa3R(MSA_ADD_A
, MSA_H
,
2842 v_dst
, v_src
, v_help
));
2847 HReg v_dst
= newVRegV(env
);
2848 HReg v_help
= newVRegV(env
);
2849 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2851 MIPSInstr_Msa3R(MSA_SUBV
, MSA_B
, v_help
, v_src
, v_src
));
2853 MIPSInstr_Msa3R(MSA_ADD_A
, MSA_B
,
2854 v_dst
, v_src
, v_help
));
2859 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2860 HReg res
= newVRegV(env
);
2861 addInstr(env
, MIPSInstr_Msa2R(MSA_PCNT
, MSA_B
, v_src
, res
));
2866 HReg v_dst
= newVRegV(env
);
2867 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2868 addInstr(env
, MIPSInstr_MsaVec(MSA_NORV
, v_dst
, v_src
, v_src
));
2872 case Iop_Reverse8sIn16_x8
: {
2873 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2874 HReg v_tmp
= newVRegV(env
);
2876 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_B
, v_tmp
, v_src
, v_src
));
2878 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_B
, v_src
, v_tmp
, v_src
));
2882 case Iop_Reverse8sIn32_x4
: {
2883 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2884 HReg v_tmp
= newVRegV(env
);
2886 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_H
, v_tmp
, v_src
, v_src
));
2888 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_H
, v_src
, v_tmp
, v_src
));
2890 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_B
, v_tmp
, v_src
, v_src
));
2892 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_B
, v_src
, v_tmp
, v_src
));
2896 case Iop_Reverse8sIn64_x2
: {
2897 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2898 HReg v_tmp
= newVRegV(env
);
2900 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_W
, v_tmp
, v_src
, v_src
));
2902 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_W
, v_src
, v_tmp
, v_src
));
2904 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_H
, v_tmp
, v_src
, v_src
));
2906 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_H
, v_src
, v_tmp
, v_src
));
2908 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_B
, v_tmp
, v_src
, v_src
));
2910 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_B
, v_src
, v_tmp
, v_src
));
2915 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2916 HReg v_dst
= newVRegV(env
);
2917 addInstr(env
, MIPSInstr_Msa2R(MSA_NLOC
, MSA_B
, v_src
, v_dst
));
2922 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2923 HReg v_dst
= newVRegV(env
);
2924 addInstr(env
, MIPSInstr_Msa2R(MSA_NLOC
, MSA_H
, v_src
, v_dst
));
2929 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2930 HReg v_dst
= newVRegV(env
);
2931 addInstr(env
, MIPSInstr_Msa2R(MSA_NLOC
, MSA_W
, v_src
, v_dst
));
2936 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2937 HReg v_dst
= newVRegV(env
);
2938 addInstr(env
, MIPSInstr_Msa2R(MSA_NLZC
, MSA_B
, v_src
, v_dst
));
2943 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2944 HReg v_dst
= newVRegV(env
);
2945 addInstr(env
, MIPSInstr_Msa2R(MSA_NLZC
, MSA_H
, v_src
, v_dst
));
2950 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2951 HReg v_dst
= newVRegV(env
);
2952 addInstr(env
, MIPSInstr_Msa2R(MSA_NLZC
, MSA_W
, v_src
, v_dst
));
2957 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2958 HReg v_dst
= newVRegV(env
);
2959 addInstr(env
, MIPSInstr_Msa2R(MSA_NLZC
, MSA_D
, v_src
, v_dst
));
2963 case Iop_Abs32Fx4
: {
2964 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2965 HReg v_dst
= newVRegV(env
);
2966 HReg v_help
= newVRegV(env
);
2968 MIPSInstr_Msa3RF(MSA_FMUL
, MSA_F_WH
,
2969 v_help
, v_src
, v_src
));
2971 MIPSInstr_Msa2RF(MSA_FSQRT
, MSA_F_WH
, v_dst
, v_help
));
2975 case Iop_Abs64Fx2
: {
2976 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2977 HReg v_dst
= newVRegV(env
);
2978 HReg v_help
= newVRegV(env
);
2980 MIPSInstr_Msa3RF(MSA_FMUL
, MSA_F_DW
,
2981 v_help
, v_src
, v_src
));
2983 MIPSInstr_Msa2RF(MSA_FSQRT
, MSA_F_DW
, v_dst
, v_help
));
2987 case Iop_RecipEst32Fx4
: {
2988 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2989 HReg v_dst
= newVRegV(env
);
2990 set_guest_MIPS_rounding_mode_MSA(env
);
2992 MIPSInstr_Msa2RF(MSA_FRCP
, MSA_F_WH
, v_dst
, v_src
));
2993 set_MIPS_rounding_default_MSA(env
);
2997 case Iop_RecipEst64Fx2
: {
2998 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
2999 HReg v_dst
= newVRegV(env
);
3000 set_guest_MIPS_rounding_mode_MSA(env
);
3002 MIPSInstr_Msa2RF(MSA_FRCP
, MSA_F_DW
, v_dst
, v_src
));
3003 set_MIPS_rounding_default_MSA(env
);
3007 case Iop_RSqrtEst32Fx4
: {
3008 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3009 HReg v_dst
= newVRegV(env
);
3010 set_guest_MIPS_rounding_mode_MSA(env
);
3012 MIPSInstr_Msa2RF(MSA_FRSQRT
, MSA_F_WH
, v_dst
, v_src
));
3013 set_MIPS_rounding_default_MSA(env
);
3017 case Iop_RSqrtEst64Fx2
: {
3018 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3019 HReg v_dst
= newVRegV(env
);
3020 set_guest_MIPS_rounding_mode_MSA(env
);
3022 MIPSInstr_Msa2RF(MSA_FRSQRT
, MSA_F_DW
, v_dst
, v_src
));
3023 set_MIPS_rounding_default_MSA(env
);
3027 case Iop_F16toF32x4
: {
3028 HReg v_dst
= newVRegV(env
);
3032 r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
3034 MIPSInstr_Msa2R(MSA_FILL
, MSA_D
, r_src
, v_dst
));
3036 MIPSInstr_MsaElm(MSA_INSERT
, r_src
, v_dst
,
3039 HReg r_srch
, r_srcl
;
3040 iselInt64Expr(&r_srch
, &r_srcl
, env
, e
->Iex
.Unop
.arg
);
3042 MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, r_srcl
, v_dst
));
3044 MIPSInstr_MsaElm(MSA_INSERT
, r_srch
, v_dst
,
3047 MIPSInstr_MsaElm(MSA_INSERT
, r_srcl
, v_dst
,
3050 MIPSInstr_MsaElm(MSA_INSERT
, r_srch
, v_dst
,
3055 MIPSInstr_Msa2RF(MSA_FEXUPR
, MSA_F_WH
, v_dst
, v_dst
));
3059 case Iop_I32UtoFx4
: {
3060 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3061 HReg v_dst
= newVRegV(env
);
3062 set_guest_MIPS_rounding_mode_MSA(env
);
3064 MIPSInstr_Msa2RF(MSA_FFINT_U
, MSA_F_WH
, v_dst
, v_src
));
3065 set_MIPS_rounding_default_MSA(env
);
3069 case Iop_FtoI32Sx4_RZ
: {
3070 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3071 HReg v_dst
= newVRegV(env
);
3073 MIPSInstr_Msa2RF(MSA_FTRUNC_S
, MSA_F_WH
, v_dst
, v_src
));
3077 case Iop_FtoI32Ux4_RZ
: {
3078 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3079 HReg v_dst
= newVRegV(env
);
3081 MIPSInstr_Msa2RF(MSA_FTRUNC_U
, MSA_F_WH
, v_dst
, v_src
));
3085 case Iop_Log2_32Fx4
: {
3086 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3087 HReg v_dst
= newVRegV(env
);
3089 MIPSInstr_Msa2RF(MSA_FLOG2
, MSA_F_WH
, v_dst
, v_src
));
3093 case Iop_Log2_64Fx2
: {
3094 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3095 HReg v_dst
= newVRegV(env
);
3097 MIPSInstr_Msa2RF(MSA_FLOG2
, MSA_F_DW
, v_dst
, v_src
));
3100 case Iop_CmpNEZ8x16
: {
3101 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3102 HReg v_dst
= newVRegV(env
);
3103 HReg zero
= Zero(mode64
);
3104 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, zero
, v_dst
));
3106 MIPSInstr_Msa3R(MSA_CEQ
, MSA_B
, v_dst
, v_src
, v_dst
));
3107 addInstr(env
, MIPSInstr_MsaVec(MSA_NORV
, v_dst
, v_dst
, v_dst
));
3110 case Iop_CmpNEZ16x8
: {
3111 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3112 HReg v_dst
= newVRegV(env
);
3113 HReg zero
= Zero(mode64
);
3114 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, zero
, v_dst
));
3116 MIPSInstr_Msa3R(MSA_CEQ
, MSA_H
, v_dst
, v_src
, v_dst
));
3117 addInstr(env
, MIPSInstr_MsaVec(MSA_NORV
, v_dst
, v_dst
, v_dst
));
3120 case Iop_CmpNEZ32x4
: {
3121 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3122 HReg v_dst
= newVRegV(env
);
3123 HReg zero
= Zero(mode64
);
3124 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, zero
, v_dst
));
3126 MIPSInstr_Msa3R(MSA_CEQ
, MSA_W
, v_dst
, v_src
, v_dst
));
3127 addInstr(env
, MIPSInstr_MsaVec(MSA_NORV
, v_dst
, v_dst
, v_dst
));
3130 case Iop_CmpNEZ64x2
: {
3131 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
3132 HReg v_dst
= newVRegV(env
);
3133 HReg zero
= Zero(mode64
);
3134 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, zero
, v_dst
));
3136 MIPSInstr_Msa3R(MSA_CEQ
, MSA_D
, v_dst
, v_src
, v_dst
));
3137 addInstr(env
, MIPSInstr_MsaVec(MSA_NORV
, v_dst
, v_dst
, v_dst
));
3141 vex_printf("iselV128Expr_wrk: Unsupported unop: %u\n", op_unop
);
3145 if (e
->tag
== Iex_Binop
) {
3146 IROp op_binop
= e
->Iex
.Binop
.op
;
3150 HReg v_dst
= newVRegV(env
);
3151 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3152 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3154 MIPSInstr_Msa3R(MSA_ADDV
, MSA_B
,
3155 v_dst
, v_src1
, v_src2
));
3160 HReg v_dst
= newVRegV(env
);
3161 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3162 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3164 MIPSInstr_Msa3R(MSA_ADDV
, MSA_H
,
3165 v_dst
, v_src1
, v_src2
));
3170 HReg v_dst
= newVRegV(env
);
3171 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3172 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3174 MIPSInstr_Msa3R(MSA_ADDV
, MSA_W
,
3175 v_dst
, v_src1
, v_src2
));
3180 HReg v_dst
= newVRegV(env
);
3181 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3182 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3184 MIPSInstr_Msa3R(MSA_ADDV
, MSA_D
,
3185 v_dst
, v_src1
, v_src2
));
3190 HReg v_dst
= newVRegV(env
);
3191 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3192 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3194 MIPSInstr_Msa3R(MSA_SUBV
, MSA_B
,
3195 v_dst
, v_src1
, v_src2
));
3200 HReg v_dst
= newVRegV(env
);
3201 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3202 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3204 MIPSInstr_Msa3R(MSA_SUBV
, MSA_H
,
3205 v_dst
, v_src1
, v_src2
));
3210 HReg v_dst
= newVRegV(env
);
3211 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3212 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3214 MIPSInstr_Msa3R(MSA_SUBV
, MSA_W
,
3215 v_dst
, v_src1
, v_src2
));
3220 HReg v_dst
= newVRegV(env
);
3221 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3222 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3224 MIPSInstr_Msa3R(MSA_SUBV
, MSA_D
,
3225 v_dst
, v_src1
, v_src2
));
3229 case Iop_QAdd8Sx16
: {
3230 HReg v_dst
= newVRegV(env
);
3231 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3232 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3234 MIPSInstr_Msa3R(MSA_ADDS_S
, MSA_B
,
3235 v_dst
, v_src1
, v_src2
));
3239 case Iop_QAdd16Sx8
: {
3240 HReg v_dst
= newVRegV(env
);
3241 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3242 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3244 MIPSInstr_Msa3R(MSA_ADDS_S
, MSA_H
,
3245 v_dst
, v_src1
, v_src2
));
3249 case Iop_QAdd32Sx4
: {
3250 HReg v_dst
= newVRegV(env
);
3251 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3252 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3254 MIPSInstr_Msa3R(MSA_ADDS_S
, MSA_W
,
3255 v_dst
, v_src1
, v_src2
));
3259 case Iop_QAdd64Sx2
: {
3260 HReg v_dst
= newVRegV(env
);
3261 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3262 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3264 MIPSInstr_Msa3R(MSA_ADDS_S
, MSA_D
,
3265 v_dst
, v_src1
, v_src2
));
3269 case Iop_QAdd8Ux16
: {
3270 HReg v_dst
= newVRegV(env
);
3271 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3272 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3274 MIPSInstr_Msa3R(MSA_ADDS_U
, MSA_B
,
3275 v_dst
, v_src1
, v_src2
));
3279 case Iop_QAdd16Ux8
: {
3280 HReg v_dst
= newVRegV(env
);
3281 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3282 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3284 MIPSInstr_Msa3R(MSA_ADDS_U
, MSA_H
,
3285 v_dst
, v_src1
, v_src2
));
3289 case Iop_QAdd32Ux4
: {
3290 HReg v_dst
= newVRegV(env
);
3291 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3292 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3294 MIPSInstr_Msa3R(MSA_ADDS_U
, MSA_W
,
3295 v_dst
, v_src1
, v_src2
));
3299 case Iop_QAdd64Ux2
: {
3300 HReg v_dst
= newVRegV(env
);
3301 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3302 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3304 MIPSInstr_Msa3R(MSA_ADDS_U
, MSA_D
,
3305 v_dst
, v_src1
, v_src2
));
3309 case Iop_QSub8Sx16
: {
3310 HReg v_dst
= newVRegV(env
);
3311 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3312 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3314 MIPSInstr_Msa3R(MSA_SUBS_S
, MSA_B
,
3315 v_dst
, v_src1
, v_src2
));
3319 case Iop_QSub16Sx8
: {
3320 HReg v_dst
= newVRegV(env
);
3321 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3322 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3324 MIPSInstr_Msa3R(MSA_SUBS_S
, MSA_H
,
3325 v_dst
, v_src1
, v_src2
));
3329 case Iop_QSub32Sx4
: {
3330 HReg v_dst
= newVRegV(env
);
3331 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3332 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3334 MIPSInstr_Msa3R(MSA_SUBS_S
, MSA_W
,
3335 v_dst
, v_src1
, v_src2
));
3339 case Iop_QSub64Sx2
: {
3340 HReg v_dst
= newVRegV(env
);
3341 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3342 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3344 MIPSInstr_Msa3R(MSA_SUBS_S
, MSA_D
,
3345 v_dst
, v_src1
, v_src2
));
3349 case Iop_QSub8Ux16
: {
3350 HReg v_dst
= newVRegV(env
);
3351 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3352 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3354 MIPSInstr_Msa3R(MSA_SUBS_U
, MSA_B
,
3355 v_dst
, v_src1
, v_src2
));
3359 case Iop_QSub16Ux8
: {
3360 HReg v_dst
= newVRegV(env
);
3361 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3362 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3364 MIPSInstr_Msa3R(MSA_SUBS_U
, MSA_H
,
3365 v_dst
, v_src1
, v_src2
));
3369 case Iop_QSub32Ux4
: {
3370 HReg v_dst
= newVRegV(env
);
3371 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3372 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3374 MIPSInstr_Msa3R(MSA_SUBS_U
, MSA_W
,
3375 v_dst
, v_src1
, v_src2
));
3379 case Iop_QSub64Ux2
: {
3380 HReg v_dst
= newVRegV(env
);
3381 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3382 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3384 MIPSInstr_Msa3R(MSA_SUBS_U
, MSA_D
,
3385 v_dst
, v_src1
, v_src2
));
3389 case Iop_QDMulHi32Sx4
: {
3390 HReg v_dst
= newVRegV(env
);
3391 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3392 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3394 MIPSInstr_Msa3RF(MSA_MUL_Q
, MSA_F_DW
,
3395 v_dst
, v_src1
, v_src2
));
3399 case Iop_QDMulHi16Sx8
: {
3400 HReg v_dst
= newVRegV(env
);
3401 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3402 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3404 MIPSInstr_Msa3RF(MSA_MUL_Q
, MSA_F_WH
,
3405 v_dst
, v_src1
, v_src2
));
3409 case Iop_QRDMulHi32Sx4
: {
3410 HReg v_dst
= newVRegV(env
);
3411 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3412 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3414 MIPSInstr_Msa3RF(MSA_MULR_Q
, MSA_F_DW
,
3415 v_dst
, v_src1
, v_src2
));
3419 case Iop_QRDMulHi16Sx8
: {
3420 HReg v_dst
= newVRegV(env
);
3421 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3422 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3424 MIPSInstr_Msa3RF(MSA_MULR_Q
, MSA_F_WH
,
3425 v_dst
, v_src1
, v_src2
));
3429 case Iop_Max8Sx16
: {
3430 HReg v_dst
= newVRegV(env
);
3431 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3432 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3434 MIPSInstr_Msa3R(MSA_MAX_S
, MSA_B
,
3435 v_dst
, v_src1
, v_src2
));
3439 case Iop_Max16Sx8
: {
3440 HReg v_dst
= newVRegV(env
);
3441 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3442 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3444 MIPSInstr_Msa3R(MSA_MAX_S
, MSA_H
,
3445 v_dst
, v_src1
, v_src2
));
3449 case Iop_Max32Sx4
: {
3450 HReg v_dst
= newVRegV(env
);
3451 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3452 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3454 MIPSInstr_Msa3R(MSA_MAX_S
, MSA_W
,
3455 v_dst
, v_src1
, v_src2
));
3459 case Iop_Max64Sx2
: {
3460 HReg v_dst
= newVRegV(env
);
3461 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3462 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3464 MIPSInstr_Msa3R(MSA_MAX_S
, MSA_D
,
3465 v_dst
, v_src1
, v_src2
));
3469 case Iop_Max8Ux16
: {
3470 HReg v_dst
= newVRegV(env
);
3471 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3472 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3474 MIPSInstr_Msa3R(MSA_MAX_U
, MSA_B
,
3475 v_dst
, v_src1
, v_src2
));
3479 case Iop_Max16Ux8
: {
3480 HReg v_dst
= newVRegV(env
);
3481 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3482 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3484 MIPSInstr_Msa3R(MSA_MAX_U
, MSA_H
,
3485 v_dst
, v_src1
, v_src2
));
3489 case Iop_Max32Ux4
: {
3490 HReg v_dst
= newVRegV(env
);
3491 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3492 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3494 MIPSInstr_Msa3R(MSA_MAX_U
, MSA_W
,
3495 v_dst
, v_src1
, v_src2
));
3499 case Iop_Max64Ux2
: {
3500 HReg v_dst
= newVRegV(env
);
3501 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3502 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3504 MIPSInstr_Msa3R(MSA_MAX_U
, MSA_D
,
3505 v_dst
, v_src1
, v_src2
));
3509 case Iop_Min8Sx16
: {
3510 HReg v_dst
= newVRegV(env
);
3511 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3512 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3514 MIPSInstr_Msa3R(MSA_MIN_S
, MSA_B
,
3515 v_dst
, v_src1
, v_src2
));
3519 case Iop_Min16Sx8
: {
3520 HReg v_dst
= newVRegV(env
);
3521 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3522 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3524 MIPSInstr_Msa3R(MSA_MIN_S
, MSA_H
,
3525 v_dst
, v_src1
, v_src2
));
3529 case Iop_Min32Sx4
: {
3530 HReg v_dst
= newVRegV(env
);
3531 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3532 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3534 MIPSInstr_Msa3R(MSA_MIN_S
, MSA_W
,
3535 v_dst
, v_src1
, v_src2
));
3539 case Iop_Min64Sx2
: {
3540 HReg v_dst
= newVRegV(env
);
3541 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3542 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3544 MIPSInstr_Msa3R(MSA_MIN_S
, MSA_D
,
3545 v_dst
, v_src1
, v_src2
));
3549 case Iop_Min8Ux16
: {
3550 HReg v_dst
= newVRegV(env
);
3551 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3552 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3554 MIPSInstr_Msa3R(MSA_MIN_U
, MSA_B
,
3555 v_dst
, v_src1
, v_src2
));
3559 case Iop_Min16Ux8
: {
3560 HReg v_dst
= newVRegV(env
);
3561 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3562 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3564 MIPSInstr_Msa3R(MSA_MIN_U
, MSA_H
,
3565 v_dst
, v_src1
, v_src2
));
3569 case Iop_Min32Ux4
: {
3570 HReg v_dst
= newVRegV(env
);
3571 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3572 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3574 MIPSInstr_Msa3R(MSA_MIN_U
, MSA_W
,
3575 v_dst
, v_src1
, v_src2
));
3579 case Iop_Min64Ux2
: {
3580 HReg v_dst
= newVRegV(env
);
3581 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3582 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3584 MIPSInstr_Msa3R(MSA_MIN_U
, MSA_D
,
3585 v_dst
, v_src1
, v_src2
));
3590 HReg v_dst
= newVRegV(env
);
3591 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3592 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3594 MIPSInstr_Msa3R(MSA_SLL
, MSA_B
, v_dst
, v_src1
, v_src2
));
3599 HReg v_dst
= newVRegV(env
);
3600 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3601 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3603 MIPSInstr_Msa3R(MSA_SLL
, MSA_H
, v_dst
, v_src1
, v_src2
));
3608 HReg v_dst
= newVRegV(env
);
3609 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3610 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3612 MIPSInstr_Msa3R(MSA_SLL
, MSA_W
, v_dst
, v_src1
, v_src2
));
3617 HReg v_dst
= newVRegV(env
);
3618 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3619 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3621 MIPSInstr_Msa3R(MSA_SLL
, MSA_D
, v_dst
, v_src1
, v_src2
));
3626 HReg v_dst
= newVRegV(env
);
3627 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3628 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3630 MIPSInstr_Msa3R(MSA_SRL
, MSA_B
, v_dst
, v_src1
, v_src2
));
3635 HReg v_dst
= newVRegV(env
);
3636 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3637 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3639 MIPSInstr_Msa3R(MSA_SRL
, MSA_H
, v_dst
, v_src1
, v_src2
));
3644 HReg v_dst
= newVRegV(env
);
3645 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3646 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3648 MIPSInstr_Msa3R(MSA_SRL
, MSA_W
, v_dst
, v_src1
, v_src2
));
3653 HReg v_dst
= newVRegV(env
);
3654 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3655 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3657 MIPSInstr_Msa3R(MSA_SRL
, MSA_D
, v_dst
, v_src1
, v_src2
));
3662 HReg v_dst
= newVRegV(env
);
3663 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3664 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3666 MIPSInstr_Msa3R(MSA_SRA
, MSA_B
, v_dst
, v_src1
, v_src2
));
3671 HReg v_dst
= newVRegV(env
);
3672 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3673 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3675 MIPSInstr_Msa3R(MSA_SRA
, MSA_H
, v_dst
, v_src1
, v_src2
));
3680 HReg v_dst
= newVRegV(env
);
3681 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3682 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3684 MIPSInstr_Msa3R(MSA_SRA
, MSA_W
, v_dst
, v_src1
, v_src2
));
3689 HReg v_dst
= newVRegV(env
);
3690 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3691 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3693 MIPSInstr_Msa3R(MSA_SRA
, MSA_D
, v_dst
, v_src1
, v_src2
));
3697 case Iop_InterleaveHI8x16
: {
3698 HReg v_dst
= newVRegV(env
);
3699 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3700 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3702 MIPSInstr_Msa3R(MSA_ILVL
, MSA_B
, v_dst
, v_src1
, v_src2
));
3706 case Iop_InterleaveHI16x8
: {
3707 HReg v_dst
= newVRegV(env
);
3708 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3709 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3711 MIPSInstr_Msa3R(MSA_ILVL
, MSA_H
,
3712 v_dst
, v_src1
, v_src2
));
3716 case Iop_InterleaveHI32x4
: {
3717 HReg v_dst
= newVRegV(env
);
3718 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3719 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3721 MIPSInstr_Msa3R(MSA_ILVL
, MSA_W
,
3722 v_dst
, v_src1
, v_src2
));
3726 case Iop_InterleaveHI64x2
: {
3727 HReg v_dst
= newVRegV(env
);
3728 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3729 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3731 MIPSInstr_Msa3R(MSA_ILVL
, MSA_D
,
3732 v_dst
, v_src1
, v_src2
));
3736 case Iop_InterleaveLO8x16
: {
3737 HReg v_dst
= newVRegV(env
);
3738 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3739 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3741 MIPSInstr_Msa3R(MSA_ILVR
, MSA_B
,
3742 v_dst
, v_src1
, v_src2
));
3746 case Iop_InterleaveLO16x8
: {
3747 HReg v_dst
= newVRegV(env
);
3748 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3749 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3751 MIPSInstr_Msa3R(MSA_ILVR
, MSA_H
,
3752 v_dst
, v_src1
, v_src2
));
3756 case Iop_InterleaveLO32x4
: {
3757 HReg v_dst
= newVRegV(env
);
3758 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3759 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3761 MIPSInstr_Msa3R(MSA_ILVR
, MSA_W
,
3762 v_dst
, v_src1
, v_src2
));
3766 case Iop_InterleaveLO64x2
: {
3767 HReg v_dst
= newVRegV(env
);
3768 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3769 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3771 MIPSInstr_Msa3R(MSA_ILVR
, MSA_D
,
3772 v_dst
, v_src1
, v_src2
));
3776 case Iop_InterleaveEvenLanes8x16
: {
3777 HReg v_dst
= newVRegV(env
);
3778 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3779 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3781 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_B
,
3782 v_dst
, v_src1
, v_src2
));
3786 case Iop_InterleaveEvenLanes16x8
: {
3787 HReg v_dst
= newVRegV(env
);
3788 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3789 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3791 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_H
,
3792 v_dst
, v_src1
, v_src2
));
3796 case Iop_InterleaveEvenLanes32x4
: {
3797 HReg v_dst
= newVRegV(env
);
3798 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3799 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3801 MIPSInstr_Msa3R(MSA_ILVEV
, MSA_W
,
3802 v_dst
, v_src1
, v_src2
));
3806 case Iop_InterleaveOddLanes8x16
: {
3807 HReg v_dst
= newVRegV(env
);
3808 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3809 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3811 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_B
,
3812 v_dst
, v_src1
, v_src2
));
3816 case Iop_InterleaveOddLanes16x8
: {
3817 HReg v_dst
= newVRegV(env
);
3818 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3819 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3821 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_H
,
3822 v_dst
, v_src1
, v_src2
));
3826 case Iop_InterleaveOddLanes32x4
: {
3827 HReg v_dst
= newVRegV(env
);
3828 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3829 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3831 MIPSInstr_Msa3R(MSA_ILVOD
, MSA_W
,
3832 v_dst
, v_src1
, v_src2
));
3836 case Iop_PackEvenLanes8x16
: {
3837 HReg v_dst
= newVRegV(env
);
3838 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3839 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3841 MIPSInstr_Msa3R(MSA_PCKEV
, MSA_B
,
3842 v_dst
, v_src1
, v_src2
));
3846 case Iop_PackEvenLanes16x8
: {
3847 HReg v_dst
= newVRegV(env
);
3848 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3849 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3851 MIPSInstr_Msa3R(MSA_PCKEV
, MSA_H
,
3852 v_dst
, v_src1
, v_src2
));
3856 case Iop_PackEvenLanes32x4
: {
3857 HReg v_dst
= newVRegV(env
);
3858 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3859 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3861 MIPSInstr_Msa3R(MSA_PCKEV
, MSA_W
,
3862 v_dst
, v_src1
, v_src2
));
3866 case Iop_PackOddLanes8x16
: {
3867 HReg v_dst
= newVRegV(env
);
3868 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3869 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3871 MIPSInstr_Msa3R(MSA_PCKOD
, MSA_B
,
3872 v_dst
, v_src1
, v_src2
));
3876 case Iop_PackOddLanes16x8
: {
3877 HReg v_dst
= newVRegV(env
);
3878 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3879 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3881 MIPSInstr_Msa3R(MSA_PCKOD
, MSA_H
,
3882 v_dst
, v_src1
, v_src2
));
3886 case Iop_PackOddLanes32x4
: {
3887 HReg v_dst
= newVRegV(env
);
3888 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3889 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3891 MIPSInstr_Msa3R(MSA_PCKOD
, MSA_W
,
3892 v_dst
, v_src1
, v_src2
));
3896 case Iop_CmpEQ8x16
: {
3897 HReg v_dst
= newVRegV(env
);
3898 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3899 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3901 MIPSInstr_Msa3R(MSA_CEQ
, MSA_B
, v_dst
, v_src1
, v_src2
));
3905 case Iop_CmpEQ16x8
: {
3906 HReg v_dst
= newVRegV(env
);
3907 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3908 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3910 MIPSInstr_Msa3R(MSA_CEQ
, MSA_H
, v_dst
, v_src1
, v_src2
));
3914 case Iop_CmpEQ32x4
: {
3915 HReg v_dst
= newVRegV(env
);
3916 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3917 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3919 MIPSInstr_Msa3R(MSA_CEQ
, MSA_W
, v_dst
, v_src1
, v_src2
));
3923 case Iop_CmpEQ64x2
: {
3924 HReg v_dst
= newVRegV(env
);
3925 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3926 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3928 MIPSInstr_Msa3R(MSA_CEQ
, MSA_D
, v_dst
, v_src1
, v_src2
));
3932 case Iop_CmpGT8Sx16
: {
3933 HReg v_dst
= newVRegV(env
);
3934 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3935 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3937 MIPSInstr_Msa3R(MSA_CLT_S
, MSA_B
,
3938 v_dst
, v_src2
, v_src1
));
3942 case Iop_CmpGT16Sx8
: {
3943 HReg v_dst
= newVRegV(env
);
3944 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3945 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3947 MIPSInstr_Msa3R(MSA_CLT_S
, MSA_H
,
3948 v_dst
, v_src2
, v_src1
));
3952 case Iop_CmpGT32Sx4
: {
3953 HReg v_dst
= newVRegV(env
);
3954 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3955 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3957 MIPSInstr_Msa3R(MSA_CLT_S
, MSA_W
,
3958 v_dst
, v_src2
, v_src1
));
3962 case Iop_CmpGT64Sx2
: {
3963 HReg v_dst
= newVRegV(env
);
3964 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3965 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3967 MIPSInstr_Msa3R(MSA_CLT_S
, MSA_D
,
3968 v_dst
, v_src2
, v_src1
));
3972 case Iop_CmpGT8Ux16
: {
3973 HReg v_dst
= newVRegV(env
);
3974 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3975 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3977 MIPSInstr_Msa3R(MSA_CLT_U
, MSA_B
,
3978 v_dst
, v_src2
, v_src1
));
3982 case Iop_CmpGT16Ux8
: {
3983 HReg v_dst
= newVRegV(env
);
3984 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3985 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3987 MIPSInstr_Msa3R(MSA_CLT_U
, MSA_H
,
3988 v_dst
, v_src2
, v_src1
));
3992 case Iop_CmpGT32Ux4
: {
3993 HReg v_dst
= newVRegV(env
);
3994 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
3995 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
3997 MIPSInstr_Msa3R(MSA_CLT_U
, MSA_W
,
3998 v_dst
, v_src2
, v_src1
));
4002 case Iop_CmpGT64Ux2
: {
4003 HReg v_dst
= newVRegV(env
);
4004 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4005 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4007 MIPSInstr_Msa3R(MSA_CLT_U
, MSA_D
,
4008 v_dst
, v_src2
, v_src1
));
4012 case Iop_Avg8Sx16
: {
4013 HReg v_dst
= newVRegV(env
);
4014 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4015 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4017 MIPSInstr_Msa3R(MSA_AVER_S
, MSA_B
,
4018 v_dst
, v_src1
, v_src2
));
4022 case Iop_Avg16Sx8
: {
4023 HReg v_dst
= newVRegV(env
);
4024 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4025 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4027 MIPSInstr_Msa3R(MSA_AVER_S
, MSA_H
,
4028 v_dst
, v_src1
, v_src2
));
4032 case Iop_Avg32Sx4
: {
4033 HReg v_dst
= newVRegV(env
);
4034 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4035 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4037 MIPSInstr_Msa3R(MSA_AVER_S
, MSA_W
,
4038 v_dst
, v_src1
, v_src2
));
4042 case Iop_Avg8Ux16
: {
4043 HReg v_dst
= newVRegV(env
);
4044 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4045 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4047 MIPSInstr_Msa3R(MSA_AVER_U
, MSA_B
,
4048 v_dst
, v_src1
, v_src2
));
4052 case Iop_Avg16Ux8
: {
4053 HReg v_dst
= newVRegV(env
);
4054 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4055 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4057 MIPSInstr_Msa3R(MSA_AVER_U
, MSA_H
,
4058 v_dst
, v_src1
, v_src2
));
4062 case Iop_Avg32Ux4
: {
4063 HReg v_dst
= newVRegV(env
);
4064 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4065 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4067 MIPSInstr_Msa3R(MSA_AVER_U
, MSA_W
,
4068 v_dst
, v_src1
, v_src2
));
4073 HReg v_dst
= newVRegV(env
);
4074 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4075 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4077 MIPSInstr_Msa3R(MSA_MULV
, MSA_B
,
4078 v_dst
, v_src1
, v_src2
));
4083 HReg v_dst
= newVRegV(env
);
4084 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4085 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4087 MIPSInstr_Msa3R(MSA_MULV
, MSA_H
,
4088 v_dst
, v_src1
, v_src2
));
4093 HReg v_dst
= newVRegV(env
);
4094 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4095 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4097 MIPSInstr_Msa3R(MSA_MULV
, MSA_W
,
4098 v_dst
, v_src1
, v_src2
));
4103 HReg v_dst
= newVRegV(env
);
4104 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4105 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4106 addInstr(env
, MIPSInstr_MsaVec(MSA_ANDV
, v_dst
, v_src1
, v_src2
));
4111 HReg v_dst
= newVRegV(env
);
4112 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4113 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4114 addInstr(env
, MIPSInstr_MsaVec(MSA_ORV
, v_dst
, v_src1
, v_src2
));
4119 HReg v_dst
= newVRegV(env
);
4120 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4121 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4122 addInstr(env
, MIPSInstr_MsaVec(MSA_XORV
, v_dst
, v_src1
, v_src2
));
4127 HReg v_dst
= newVRegV(env
);
4128 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4130 sm
= iselWordExpr_RH7u(env
, e
->Iex
.Binop
.arg2
);
4132 MIPSInstr_Msa3R(MSA_SUBV
, MSA_B
,
4133 v_dst
, v_src1
, v_src1
));
4135 if (sm
->tag
== Mrh_Imm
) {
4136 int n
= (sm
->Mrh
.Imm
.imm16
) >> 3;
4138 MIPSInstr_MsaElm(MSA_SLDI
, v_src1
, v_dst
,
4141 HReg v_src2
= sm
->Mrh
.Reg
.reg
;
4142 MIPSRH
*ri
= MIPSRH_Imm(False
, 3);
4143 HReg r_dst
= newVRegI(env
);
4144 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/*32bit shift */,
4145 r_dst
, v_src2
, ri
));
4147 MIPSInstr_Msa3R(MSA_SLD
, MSA_B
,
4148 v_dst
, v_src1
, r_dst
));
4155 HReg v_dst
= newVRegV(env
);
4156 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4158 sm
= iselWordExpr_RH7u(env
, e
->Iex
.Binop
.arg2
);
4160 MIPSInstr_Msa3R(MSA_SUBV
, MSA_B
,
4161 v_dst
, v_src1
, v_src1
));
4163 if (sm
->tag
== Mrh_Imm
) {
4164 int n
= 16 - ((sm
->Mrh
.Imm
.imm16
) >> 3);
4169 MIPSInstr_MsaElm(MSA_SLDI
, v_dst
, v_src1
,
4172 HReg v_src2
= sm
->Mrh
.Reg
.reg
;
4173 MIPSRH
*ri
= MIPSRH_Imm(False
, 3);
4174 HReg r_dst
= newVRegI(env
);
4175 HReg help
= newVRegI(env
);
4176 addInstr(env
, MIPSInstr_Alu(Malu_XOR
, help
, v_src2
, sm
));
4177 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, help
, help
, sm
));
4178 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/*32bit shift */,
4181 MIPSInstr_Msa3R(MSA_SLD
, MSA_B
,
4182 v_src1
, v_dst
, r_dst
));
4188 case Iop_ShlN8x16
: {
4189 HReg v_dst
= newVRegV(env
);
4190 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4191 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4192 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4193 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4195 MIPSInstr_MsaBit(MSA_SLLI
, MSA_B
,
4196 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4201 case Iop_ShlN16x8
: {
4202 HReg v_dst
= newVRegV(env
);
4203 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4204 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4205 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4206 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4208 MIPSInstr_MsaBit(MSA_SLLI
, MSA_H
,
4209 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4214 case Iop_ShlN32x4
: {
4215 HReg v_dst
= newVRegV(env
);
4216 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4217 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4218 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4219 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4221 MIPSInstr_MsaBit(MSA_SLLI
, MSA_W
,
4222 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4227 case Iop_ShlN64x2
: {
4228 HReg v_dst
= newVRegV(env
);
4229 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4230 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4231 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4232 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4234 MIPSInstr_MsaBit(MSA_SLLI
, MSA_D
,
4235 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4240 case Iop_SarN8x16
: {
4241 HReg v_dst
= newVRegV(env
);
4242 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4243 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4244 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4245 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4247 MIPSInstr_MsaBit(MSA_SRAI
, MSA_B
,
4248 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4253 case Iop_SarN16x8
: {
4254 HReg v_dst
= newVRegV(env
);
4255 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4256 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4257 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4258 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4260 MIPSInstr_MsaBit(MSA_SRAI
, MSA_H
,
4261 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4266 case Iop_SarN32x4
: {
4267 HReg v_dst
= newVRegV(env
);
4268 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4269 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4270 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4271 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4273 MIPSInstr_MsaBit(MSA_SRAI
, MSA_W
,
4274 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4279 case Iop_SarN64x2
: {
4280 HReg v_dst
= newVRegV(env
);
4281 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4282 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4283 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4284 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4286 MIPSInstr_MsaBit(MSA_SRAI
, MSA_D
,
4287 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4292 case Iop_ShrN8x16
: {
4293 HReg v_dst
= newVRegV(env
);
4294 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4295 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4296 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4297 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4299 MIPSInstr_MsaBit(MSA_SRLI
, MSA_B
,
4300 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4305 case Iop_ShrN16x8
: {
4306 HReg v_dst
= newVRegV(env
);
4307 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4308 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4309 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4310 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4312 MIPSInstr_MsaBit(MSA_SRLI
, MSA_H
,
4313 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4318 case Iop_ShrN32x4
: {
4319 HReg v_dst
= newVRegV(env
);
4320 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4321 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4322 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4323 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4325 MIPSInstr_MsaBit(MSA_SRLI
, MSA_W
,
4326 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4331 case Iop_ShrN64x2
: {
4332 HReg v_dst
= newVRegV(env
);
4333 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4334 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4335 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4336 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4338 MIPSInstr_MsaBit(MSA_SRLI
, MSA_D
,
4339 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4344 case Iop_QandQSarNnarrow64Sto32Sx2
: {
4345 HReg v_dst
= newVRegV(env
);
4346 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4347 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4348 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4349 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4351 MIPSInstr_MsaBit(MSA_SRAI
, MSA_D
,
4352 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4354 addInstr(env
, MIPSInstr_MsaBit(MSA_SAT_S
, MSA_D
, 31, v_dst
, v_dst
));
4358 case Iop_QandQSarNnarrow32Sto16Sx4
: {
4359 HReg v_dst
= newVRegV(env
);
4360 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4361 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4362 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4363 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4365 MIPSInstr_MsaBit(MSA_SRAI
, MSA_W
,
4366 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4369 MIPSInstr_MsaBit(MSA_SAT_S
, MSA_W
, 15, v_dst
, v_dst
));
4373 case Iop_QandQRSarNnarrow64Sto32Sx2
: {
4374 HReg v_dst
= newVRegV(env
);
4375 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4376 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4377 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4378 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4380 MIPSInstr_MsaBit(MSA_SRARI
, MSA_D
,
4381 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4384 MIPSInstr_MsaBit(MSA_SAT_S
, MSA_D
, 31, v_dst
, v_dst
));
4388 case Iop_QandQRSarNnarrow32Sto16Sx4
: {
4389 HReg v_dst
= newVRegV(env
);
4390 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4391 vassert(e
->Iex
.Binop
.arg2
->tag
== Iex_Const
);
4392 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->tag
== Ico_U8
);
4393 vassert(e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
<= 63);
4395 MIPSInstr_MsaBit(MSA_SRARI
, MSA_W
,
4396 e
->Iex
.Binop
.arg2
->Iex
.Const
.con
->Ico
.U8
,
4399 MIPSInstr_MsaBit(MSA_SAT_S
, MSA_W
, 15, v_dst
, v_dst
));
4403 case Iop_CmpEQ32Fx4
: {
4404 HReg v_dst
= newVRegV(env
);
4405 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4406 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4408 MIPSInstr_Msa3RF(MSA_FCEQ
, MSA_F_WH
,
4409 v_dst
, v_src1
, v_src2
));
4413 case Iop_CmpEQ64Fx2
: {
4414 HReg v_dst
= newVRegV(env
);
4415 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4416 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4418 MIPSInstr_Msa3RF(MSA_FCEQ
, MSA_F_DW
,
4419 v_dst
, v_src1
, v_src2
));
4423 case Iop_CmpLT32Fx4
: {
4424 HReg v_dst
= newVRegV(env
);
4425 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4426 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4428 MIPSInstr_Msa3RF(MSA_FCLT
, MSA_F_WH
,
4429 v_dst
, v_src1
, v_src2
));
4433 case Iop_CmpLT64Fx2
: {
4434 HReg v_dst
= newVRegV(env
);
4435 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4436 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4438 MIPSInstr_Msa3RF(MSA_FCLT
, MSA_F_DW
,
4439 v_dst
, v_src1
, v_src2
));
4443 case Iop_CmpLE32Fx4
: {
4444 HReg v_dst
= newVRegV(env
);
4445 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4446 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4448 MIPSInstr_Msa3RF(MSA_FCLE
, MSA_F_WH
,
4449 v_dst
, v_src1
, v_src2
));
4453 case Iop_CmpLE64Fx2
: {
4454 HReg v_dst
= newVRegV(env
);
4455 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4456 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4458 MIPSInstr_Msa3RF(MSA_FCLE
, MSA_F_DW
,
4459 v_dst
, v_src1
, v_src2
));
4463 case Iop_CmpUN32Fx4
: {
4464 HReg v_dst
= newVRegV(env
);
4465 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4466 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4468 MIPSInstr_Msa3RF(MSA_FCUN
, MSA_F_WH
,
4469 v_dst
, v_src1
, v_src2
));
4473 case Iop_CmpUN64Fx2
: {
4474 HReg v_dst
= newVRegV(env
);
4475 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4476 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4478 MIPSInstr_Msa3RF(MSA_FCUN
, MSA_F_DW
,
4479 v_dst
, v_src1
, v_src2
));
4483 case Iop_64HLtoV128
: {
4484 HReg v_dst
= newVRegV(env
);
4489 r_src1
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
4490 r_src2
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
4492 MIPSInstr_Msa2R(MSA_FILL
, MSA_D
, r_src2
, v_dst
));
4494 MIPSInstr_MsaElm(MSA_INSERT
, r_src1
, v_dst
,
4497 HReg r_src1h
, r_src1l
;
4498 HReg r_src2h
, r_src2l
;
4499 iselInt64Expr(&r_src1h
, &r_src1l
, env
, e
->Iex
.Binop
.arg1
);
4500 iselInt64Expr(&r_src2h
, &r_src2l
, env
, e
->Iex
.Binop
.arg2
);
4502 MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, r_src2l
, v_dst
));
4504 MIPSInstr_MsaElm(MSA_INSERT
, r_src2h
, v_dst
,
4507 MIPSInstr_MsaElm(MSA_INSERT
, r_src1l
, v_dst
,
4510 MIPSInstr_MsaElm(MSA_INSERT
, r_src1h
, v_dst
,
4517 case Iop_Min32Fx4
: {
4518 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4519 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4520 HReg v_dst
= newVRegV(env
);
4522 MIPSInstr_Msa3RF(MSA_FMIN
, MSA_F_WH
,
4523 v_dst
, v_src1
, v_src2
));
4527 case Iop_Min64Fx2
: {
4528 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4529 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4530 HReg v_dst
= newVRegV(env
);
4532 MIPSInstr_Msa3RF(MSA_FMIN
, MSA_F_DW
,
4533 v_dst
, v_src1
, v_src2
));
4537 case Iop_Max32Fx4
: {
4538 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4539 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4540 HReg v_dst
= newVRegV(env
);
4542 MIPSInstr_Msa3RF(MSA_FMAX
, MSA_F_WH
,
4543 v_dst
, v_src1
, v_src2
));
4547 case Iop_Max64Fx2
: {
4548 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
4549 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4550 HReg v_dst
= newVRegV(env
);
4552 MIPSInstr_Msa3RF(MSA_FMAX
, MSA_F_DW
,
4553 v_dst
, v_src1
, v_src2
));
4557 case Iop_Sqrt32Fx4
: {
4558 HReg v_src
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4559 HReg v_dst
= newVRegV(env
);
4560 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Binop
.arg1
);
4562 MIPSInstr_Msa2RF(MSA_FSQRT
, MSA_F_WH
, v_dst
, v_src
));
4563 set_MIPS_rounding_default_MSA(env
);
4567 case Iop_Sqrt64Fx2
: {
4568 HReg v_src
= iselV128Expr(env
, e
->Iex
.Binop
.arg2
);
4569 HReg v_dst
= newVRegV(env
);
4570 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Binop
.arg1
);
4572 MIPSInstr_Msa2RF(MSA_FSQRT
, MSA_F_DW
, v_dst
, v_src
));
4573 set_MIPS_rounding_default_MSA(env
);
4578 vex_printf("iselV128Expr_wrk: unsupported binop: %x\n", op_binop
);
4582 if (e
->tag
== Iex_Triop
) {
4583 IROp op_triop
= e
->Iex
.Triop
.details
->op
;
4586 case Iop_Add32Fx4
: {
4587 HReg v_dst
= newVRegV(env
);
4588 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4589 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4590 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4592 MIPSInstr_Msa3RF(MSA_FADD
, MSA_F_WH
,
4593 v_dst
, v_src1
, v_src2
));
4594 set_MIPS_rounding_default_MSA(env
);
4598 case Iop_Add64Fx2
: {
4599 HReg v_dst
= newVRegV(env
);
4600 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4601 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4602 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4604 MIPSInstr_Msa3RF(MSA_FADD
, MSA_F_DW
,
4605 v_dst
, v_src1
, v_src2
));
4606 set_MIPS_rounding_default_MSA(env
);
4610 case Iop_Sub32Fx4
: {
4611 HReg v_dst
= newVRegV(env
);
4612 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4613 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4614 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4616 MIPSInstr_Msa3RF(MSA_FSUB
, MSA_F_WH
,
4617 v_dst
, v_src1
, v_src2
));
4618 set_MIPS_rounding_default_MSA(env
);
4622 case Iop_Sub64Fx2
: {
4623 HReg v_dst
= newVRegV(env
);
4624 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4625 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4626 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4628 MIPSInstr_Msa3RF(MSA_FSUB
, MSA_F_DW
,
4629 v_dst
, v_src1
, v_src2
));
4630 set_MIPS_rounding_default_MSA(env
);
4634 case Iop_Mul32Fx4
: {
4635 HReg v_dst
= newVRegV(env
);
4636 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4637 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4638 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4640 MIPSInstr_Msa3RF(MSA_FMUL
, MSA_F_WH
,
4641 v_dst
, v_src1
, v_src2
));
4642 set_MIPS_rounding_default_MSA(env
);
4646 case Iop_Mul64Fx2
: {
4647 HReg v_dst
= newVRegV(env
);
4648 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4649 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4650 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4652 MIPSInstr_Msa3RF(MSA_FMUL
, MSA_F_DW
,
4653 v_dst
, v_src1
, v_src2
));
4654 set_MIPS_rounding_default_MSA(env
);
4658 case Iop_Div32Fx4
: {
4659 HReg v_dst
= newVRegV(env
);
4660 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4661 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4662 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4664 MIPSInstr_Msa3RF(MSA_FDIV
, MSA_F_WH
,
4665 v_dst
, v_src1
, v_src2
));
4666 set_MIPS_rounding_default_MSA(env
);
4670 case Iop_Div64Fx2
: {
4671 HReg v_dst
= newVRegV(env
);
4672 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4673 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4674 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4676 MIPSInstr_Msa3RF(MSA_FDIV
, MSA_F_DW
,
4677 v_dst
, v_src1
, v_src2
));
4678 set_MIPS_rounding_default_MSA(env
);
4682 case Iop_F32x4_2toQ16x8
: {
4683 HReg v_dst
= newVRegV(env
);
4684 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4685 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4686 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4688 MIPSInstr_Msa3RF(MSA_FTQ
, MSA_F_WH
,
4689 v_dst
, v_src1
, v_src2
));
4690 set_MIPS_rounding_default_MSA(env
);
4694 case Iop_F64x2_2toQ32x4
: {
4695 HReg v_dst
= newVRegV(env
);
4696 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4697 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4698 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4700 MIPSInstr_Msa3RF(MSA_FTQ
, MSA_F_DW
,
4701 v_dst
, v_src1
, v_src2
));
4702 set_MIPS_rounding_default_MSA(env
);
4706 case Iop_Scale2_32Fx4
: {
4707 HReg v_dst
= newVRegV(env
);
4708 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4709 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4710 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4712 MIPSInstr_Msa3RF(MSA_FEXP2
, MSA_F_WH
,
4713 v_dst
, v_src1
, v_src2
));
4714 set_MIPS_rounding_default_MSA(env
);
4718 case Iop_Scale2_64Fx2
: {
4719 HReg v_dst
= newVRegV(env
);
4720 HReg v_src1
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg2
);
4721 HReg v_src2
= iselV128Expr(env
, e
->Iex
.Triop
.details
->arg3
);
4722 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
4724 MIPSInstr_Msa3RF(MSA_FEXP2
, MSA_F_DW
,
4725 v_dst
, v_src1
, v_src2
));
4726 set_MIPS_rounding_default_MSA(env
);
4731 vex_printf("iselV128Expr_wrk: unsupported triop: %x\n", op_triop
);
4735 if (e
->tag
== Iex_Const
) {
4736 IRConst
*con
= e
->Iex
.Const
.con
;
4738 if (con
->tag
!= Ico_V128
) {
4739 vpanic("iselV128Expr.const(mips)");
4741 HReg v_dst
= newVRegV(env
);
4742 UShort val
= con
->Ico
.V128
;
4743 HReg zero
= Zero(mode64
);
4746 case 0: /* likely */
4747 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, zero
, v_dst
));
4751 HReg r_tmp
= newVRegI(env
);
4753 addInstr(env
, MIPSInstr_LI(r_tmp
, 0xfful
));
4757 MIPSInstr_Msa2R(MSA_FILL
, MSA_B
, r_tmp
, v_dst
));
4760 MIPSInstr_Msa2R(MSA_FILL
, MSA_B
, zero
, v_dst
));
4763 for (i
= 1; i
< 16; i
++) {
4768 MIPSInstr_MsaElm(MSA_INSERT
, r_tmp
, v_dst
,
4772 MIPSInstr_MsaElm(MSA_INSERT
, zero
, v_dst
,
4785 if (e
->tag
== Iex_ITE
) {
4786 HReg v_dst
= newVRegV(env
);
4787 HReg iff
= iselV128Expr(env
, e
->Iex
.ITE
.iffalse
);
4788 HReg ift
= iselV128Expr(env
, e
->Iex
.ITE
.iftrue
);
4789 HReg r_cond
= iselWordExpr_R(env
, e
->Iex
.ITE
.cond
);
4790 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, r_cond
, r_cond
,
4791 MIPSRH_Imm(False
, 1)));
4792 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, r_cond
, v_dst
));
4794 MIPSInstr_Alu(Malu_ADD
, r_cond
, r_cond
, MIPSRH_Imm(True
, 1)));
4795 addInstr(env
, MIPSInstr_MsaElm(MSA_INSERT
, r_cond
, v_dst
, MSA_DFN_W
| 2));
4796 addInstr(env
, MIPSInstr_Msa3R(MSA_VSHF
, MSA_D
, v_dst
, ift
, iff
));
4800 vex_printf("iselV128Expr_wrk: Unsupported tag: %x\n", e
->tag
);
4802 vpanic("iselV128Expr(mips)");
4805 /*---------------------------------------------------------*/
4806 /*--- ISEL: Integer expressions (128 bit) ---*/
4807 /*---------------------------------------------------------*/
4809 /* 64-bit mode ONLY: compute a 128-bit value into a register pair,
4810 which is returned as the first two parameters. As with
4811 iselWordExpr_R, these may be either real or virtual regs; in any
4812 case they must not be changed by subsequent code emitted by the
4815 static void iselInt128Expr(HReg
* rHi
, HReg
* rLo
, ISelEnv
* env
, IRExpr
* e
)
4817 vassert(env
->mode64
);
4818 iselInt128Expr_wrk(rHi
, rLo
, env
, e
);
4819 vassert(hregClass(*rHi
) == HRcGPR(env
->mode64
));
4820 vassert(hregIsVirtual(*rHi
));
4821 vassert(hregClass(*rLo
) == HRcGPR(env
->mode64
));
4822 vassert(hregIsVirtual(*rLo
));
4825 /* DO NOT CALL THIS DIRECTLY ! */
4826 static void iselInt128Expr_wrk(HReg
* rHi
, HReg
* rLo
, ISelEnv
* env
,
4830 vassert(typeOfIRExpr(env
->type_env
, e
) == Ity_I128
);
4832 /* read 128-bit IRTemp */
4833 if (e
->tag
== Iex_RdTmp
) {
4834 lookupIRTempPair(rHi
, rLo
, env
, e
->Iex
.RdTmp
.tmp
);
4838 /* --------- BINARY ops --------- */
4839 if (e
->tag
== Iex_Binop
) {
4840 switch (e
->Iex
.Binop
.op
) {
4841 /* 64 x 64 -> 128 multiply */
4844 HReg tLo
= newVRegI(env
);
4845 HReg tHi
= newVRegI(env
);
4846 Bool syned
= toBool(e
->Iex
.Binop
.op
== Iop_MullS64
);
4847 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
4848 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
4849 #if (__mips_isa_rev >= 6)
4850 addInstr(env
, MIPSInstr_Mulr6(syned
, False
, True
,
4851 tLo
, r_srcL
, r_srcR
));
4852 addInstr(env
, MIPSInstr_Mulr6(syned
, False
, False
,
4853 tHi
, r_srcL
, r_srcR
));
4855 addInstr(env
, MIPSInstr_Mult(syned
, r_srcL
, r_srcR
));
4856 addInstr(env
, MIPSInstr_Mfhi(tHi
));
4857 addInstr(env
, MIPSInstr_Mflo(tLo
));
4864 /* 64HLto128(e1,e2) */
4866 *rHi
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
4867 *rLo
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
4870 case Iop_DivModU64to64
:
4871 case Iop_DivModS64to64
: {
4872 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
4873 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
4874 HReg tLo
= newVRegI(env
);
4875 HReg tHi
= newVRegI(env
);
4876 Bool syned
= toBool(e
->Iex
.Binop
.op
== Iop_DivModS64to64
);
4877 #if (__mips_isa_rev >= 6)
4878 addInstr(env
, MIPSInstr_Divr6(syned
/*Unsigned or Signed */ ,
4879 False
/*32bit or 64bit div */ ,
4881 tLo
, r_srcL
, r_srcR
));
4882 addInstr(env
, MIPSInstr_Divr6(syned
/*Unsigned or Signed */ ,
4883 False
/*32bit or 64bit div */ ,
4885 tHi
, r_srcL
, r_srcR
));
4887 addInstr(env
, MIPSInstr_Div(syned
, False
, r_srcL
, r_srcR
));
4888 addInstr(env
, MIPSInstr_Mfhi(tHi
));
4889 addInstr(env
, MIPSInstr_Mflo(tLo
));
4900 vex_printf("iselInt128Expr(mips64): No such tag(%u)\n", e
->tag
);
4902 vpanic("iselInt128Expr(mips64)");
4905 /*---------------------------------------------------------*/
4906 /*--- ISEL: Integer expressions (64 bit) ---*/
4907 /*---------------------------------------------------------*/
4909 /* 32-bit mode ONLY. Compute a 64-bit value into the register
4910 * pair HI, LO. HI and LO must not be changed by subsequent
4911 * code emitted by the caller. */
4913 static void iselInt64Expr(HReg
* rHi
, HReg
* rLo
, ISelEnv
* env
, IRExpr
* e
)
4915 vassert(!env
->mode64
);
4916 iselInt64Expr_wrk(rHi
, rLo
, env
, e
);
4917 vassert(hregClass(*rHi
) == HRcInt32
);
4918 vassert(hregIsVirtual(*rHi
));
4919 vassert(hregClass(*rLo
) == HRcInt32
);
4920 vassert(hregIsVirtual(*rLo
));
4923 /* DO NOT CALL THIS DIRECTLY ! */
4924 static void iselInt64Expr_wrk(HReg
* rHi
, HReg
* rLo
, ISelEnv
* env
, IRExpr
* e
)
4927 vassert(typeOfIRExpr(env
->type_env
, e
) == Ity_I64
);
4929 /* read 64-bit IRTemp */
4930 if (e
->tag
== Iex_RdTmp
) {
4931 lookupIRTemp64(rHi
, rLo
, env
, e
->Iex
.RdTmp
.tmp
);
4935 if (e
->tag
== Iex_Load
) {
4936 HReg tLo
= newVRegI(env
);
4937 HReg tHi
= newVRegI(env
);
4938 HReg r_addr
= iselWordExpr_R(env
, e
->Iex
.Load
.addr
);
4939 addInstr(env
, MIPSInstr_Load(4, tHi
, MIPSAMode_IR(0, r_addr
), mode64
));
4940 addInstr(env
, MIPSInstr_Load(4, tLo
, MIPSAMode_IR(4, r_addr
), mode64
));
4946 /* 64-bit literal */
4947 if (e
->tag
== Iex_Const
) {
4948 ULong w64
= e
->Iex
.Const
.con
->Ico
.U64
;
4949 UInt wHi
= toUInt(w64
>> 32);
4950 UInt wLo
= toUInt(w64
);
4951 HReg tLo
= newVRegI(env
);
4952 HReg tHi
= newVRegI(env
);
4953 vassert(e
->Iex
.Const
.con
->tag
== Ico_U64
);
4956 /* Save a precious Int register in this special case. */
4957 addInstr(env
, MIPSInstr_LI(tLo
, (ULong
) wLo
));
4961 addInstr(env
, MIPSInstr_LI(tHi
, (ULong
) wHi
));
4962 addInstr(env
, MIPSInstr_LI(tLo
, (ULong
) wLo
));
4971 if (e
->tag
== Iex_Get
) {
4972 HReg tLo
= newVRegI(env
);
4973 HReg tHi
= newVRegI(env
);
4975 MIPSAMode
*am_addr
= MIPSAMode_IR(e
->Iex
.Get
.offset
,
4976 GuestStatePointer(mode64
));
4977 addInstr(env
, MIPSInstr_Load(4, tLo
, am_addr
, mode64
));
4978 addInstr(env
, MIPSInstr_Load(4, tHi
, nextMIPSAModeInt(am_addr
), mode64
));
4985 if (e
->tag
== Iex_ITE
) {
4986 vassert(typeOfIRExpr(env
->type_env
, e
->Iex
.ITE
.cond
) == Ity_I1
);
4987 HReg expr0Lo
, expr0Hi
;
4988 HReg expr1Lo
, expr1Hi
;
4989 HReg desLo
= newVRegI(env
);
4990 HReg desHi
= newVRegI(env
);
4991 HReg cond
= iselWordExpr_R(env
, e
->Iex
.ITE
.cond
);
4993 /* expr0Hi:expr0Lo = iffalse */
4994 /* expr1Hi:expr1Lo = iftrue */
4995 iselInt64Expr(&expr0Hi
, &expr0Lo
, env
, e
->Iex
.ITE
.iffalse
);
4996 iselInt64Expr(&expr1Hi
, &expr1Lo
, env
, e
->Iex
.ITE
.iftrue
);
4998 /* move desLo, expr0Lo
4999 * move desHi, expr0Hi
5000 * movn desLo, expr1Lo, cond
5001 * movn desHi, expr1Hi, cond */
5002 #if (__mips_isa_rev >= 6)
5004 HReg r_temp
= newVRegI(env
);
5005 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, desLo
, expr0Lo
, cond
));
5006 addInstr(env
, MIPSInstr_MoveCond(MSelnez
, r_temp
, expr1Lo
, cond
));
5007 addInstr(env
, MIPSInstr_Alu(Malu_OR
, desLo
, desLo
, MIPSRH_Reg(r_temp
)));
5009 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, desHi
, expr0Hi
, cond
));
5010 addInstr(env
, MIPSInstr_MoveCond(MSelnez
, r_temp
, expr1Hi
, cond
));
5011 addInstr(env
, MIPSInstr_Alu(Malu_OR
, desHi
, desHi
, MIPSRH_Reg(r_temp
)));
5014 addInstr(env
, mk_iMOVds_RR(desLo
, expr0Lo
));
5015 addInstr(env
, mk_iMOVds_RR(desHi
, expr0Hi
));
5016 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, desLo
, expr1Lo
, cond
));
5017 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, desHi
, expr1Hi
, cond
));
5025 if (e
->tag
== Iex_CCall
) {
5026 HReg r_dstH
= newVRegI(env
);
5027 HReg r_dstL
= newVRegI(env
);
5028 vassert(e
->Iex
.CCall
.retty
== Ity_I64
);
5030 /* Marshal args, do the call, clear stack. */
5032 RetLoc rloc
= mk_RetLoc_INVALID();
5033 doHelperCall(&addToSp
, &rloc
, env
, NULL
/*guard*/, e
->Iex
.CCall
.cee
,
5034 e
->Iex
.CCall
.retty
, e
->Iex
.CCall
.args
);
5036 vassert(is_sane_RetLoc(rloc
));
5037 vassert(rloc
.pri
== RLPri_2Int
);
5038 vassert(addToSp
== 0);
5039 addInstr(env
, mk_iMOVds_RR(r_dstL
, hregMIPS_GPR2(False
)));
5040 addInstr(env
, mk_iMOVds_RR(r_dstH
, hregMIPS_GPR3(False
)));
5046 /* --------- BINARY ops --------- */
5047 if (e
->tag
== Iex_Binop
) {
5048 IROp op_binop
= e
->Iex
.Binop
.op
;
5050 /* 32 x 32 -> 64 multiply */
5053 HReg xLo
, xHi
, yLo
, yHi
, carryBit
;
5055 HReg tHi
= newVRegI(env
);
5056 HReg tHi1
= newVRegI(env
);
5057 HReg tLo
= newVRegI(env
);
5059 carryBit
= newVRegI(env
);
5062 MIPSCondCode cc
= MIPScc_LO
;
5064 iselInt64Expr(&xHi
, &xLo
, env
, e
->Iex
.Binop
.arg1
);
5065 iselInt64Expr(&yHi
, &yLo
, env
, e
->Iex
.Binop
.arg2
);
5066 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, tLo
, xLo
, MIPSRH_Reg(yLo
)));
5069 addInstr(env
, MIPSInstr_Cmp(False
, size32
, carryBit
, tLo
, xLo
, cc
));
5071 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, tHi1
, xHi
, MIPSRH_Reg(yHi
)));
5072 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, tHi
, tHi1
,
5073 MIPSRH_Reg(carryBit
)));
5080 HReg xLo
, xHi
, yLo
, yHi
, borrow
;
5082 MIPSCondCode cc
= MIPScc_LO
;
5084 HReg tHi
= newVRegI(env
);
5085 HReg tLo
= newVRegI(env
);
5087 borrow
= newVRegI(env
);
5089 iselInt64Expr(&xHi
, &xLo
, env
, e
->Iex
.Binop
.arg1
);
5090 iselInt64Expr(&yHi
, &yLo
, env
, e
->Iex
.Binop
.arg2
);
5092 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, tLo
, xLo
, MIPSRH_Reg(yLo
)));
5094 /* Check if borrow is nedded. */
5095 addInstr(env
, MIPSInstr_Cmp(False
, size32
, borrow
, xLo
, yLo
, cc
));
5097 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, yHi
, yHi
,
5098 MIPSRH_Reg(borrow
)));
5099 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, tHi
, xHi
, MIPSRH_Reg(yHi
)));
5107 HReg tLo
= newVRegI(env
);
5108 HReg tHi
= newVRegI(env
);
5109 Bool syned
= toBool(op_binop
== Iop_MullS32
);
5110 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
5111 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
5112 #if (__mips_isa_rev >= 6)
5113 addInstr(env
, MIPSInstr_Mulr6(syned
, True
, True
,
5114 tLo
, r_srcL
, r_srcR
));
5115 addInstr(env
, MIPSInstr_Mulr6(syned
, True
, False
,
5116 tHi
, r_srcL
, r_srcR
));
5118 addInstr(env
, MIPSInstr_Mult(syned
, r_srcL
, r_srcR
));
5119 addInstr(env
, MIPSInstr_Mfhi(tHi
));
5120 addInstr(env
, MIPSInstr_Mflo(tLo
));
5128 case Iop_DivModU32to32
:
5129 case Iop_DivModS32to32
: {
5130 HReg r_srcL
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
5131 HReg r_srcR
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
5132 HReg tLo
= newVRegI(env
);
5133 HReg tHi
= newVRegI(env
);
5134 Bool syned
= toBool(e
->Iex
.Binop
.op
== Iop_DivModS32to32
);
5136 #if (__mips_isa_rev >= 6)
5137 addInstr(env
, MIPSInstr_Divr6(syned
/*Unsigned or Signed */ ,
5138 True
/*32bit or 64bit div */ ,
5140 tLo
, r_srcL
, r_srcR
));
5141 addInstr(env
, MIPSInstr_Divr6(syned
/*Unsigned or Signed */ ,
5142 True
/*32bit or 64bit div */ ,
5144 tHi
, r_srcL
, r_srcR
));
5146 addInstr(env
, MIPSInstr_Div(syned
, True
, r_srcL
, r_srcR
));
5147 addInstr(env
, MIPSInstr_Mfhi(tHi
));
5148 addInstr(env
, MIPSInstr_Mflo(tLo
));
5155 /* 32HLto64(e1,e2) */
5157 *rHi
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg1
);
5158 *rLo
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
5161 /* Or64/And64/Xor64 */
5165 HReg xLo
, xHi
, yLo
, yHi
;
5166 HReg tLo
= newVRegI(env
);
5167 HReg tHi
= newVRegI(env
);
5168 MIPSAluOp op
= (op_binop
== Iop_Or64
) ? Malu_OR
:
5169 (op_binop
== Iop_And64
) ? Malu_AND
: Malu_XOR
;
5170 iselInt64Expr(&xHi
, &xLo
, env
, e
->Iex
.Binop
.arg1
);
5171 iselInt64Expr(&yHi
, &yLo
, env
, e
->Iex
.Binop
.arg2
);
5172 addInstr(env
, MIPSInstr_Alu(op
, tHi
, xHi
, MIPSRH_Reg(yHi
)));
5173 addInstr(env
, MIPSInstr_Alu(op
, tLo
, xLo
, MIPSRH_Reg(yLo
)));
5180 /* 64-bit logical shift right based on what gcc generates:
5193 HReg r_srcLo
, r_srcHi
;
5194 HReg r_srcLotmp
= newVRegI(env
);
5195 HReg shift
= newVRegI(env
);
5196 HReg a3
= newVRegI(env
);
5197 HReg r_dstLo
= newVRegI(env
);
5198 HReg r_dstHi
= newVRegI(env
);
5199 HReg zero
= hregMIPS_GPR0(env
->mode64
);
5202 iselInt64Expr(&r_srcHi
, &r_srcLo
, env
, e
->Iex
.Binop
.arg1
);
5203 sa
= iselWordExpr_RH6u(env
, e
->Iex
.Binop
.arg2
);
5205 if (sa
->tag
== Mrh_Imm
) {
5206 addInstr(env
, MIPSInstr_LI(shift
, sa
->Mrh
.Imm
.imm16
));
5209 addInstr(env
, MIPSInstr_Alu(Malu_AND
, shift
, sa
->Mrh
.Reg
.reg
,
5210 MIPSRH_Imm(False
, 0x3f)));
5212 /* nor r_dstLo, zero, shift */
5213 addInstr(env
, MIPSInstr_Alu(Malu_NOR
, r_dstLo
, zero
, MIPSRH_Reg(shift
)));
5214 /* sll a3, r_srcHi, 0x1 */
5215 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
/* 32bit shift */,
5216 a3
, r_srcHi
, MIPSRH_Imm(False
, 0x1)));
5217 /* sllv a3, a3, r_dstLo */
5218 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
/* 32bit shift */,
5219 a3
, a3
, MIPSRH_Reg(r_dstLo
)));
5220 /* srlv r_dstLo, r_srcLo, shift */
5221 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/* 32bit shift */,
5222 r_dstLo
, r_srcLo
, MIPSRH_Reg(shift
)));
5223 /* srlv r_dstHi, r_srcHi, shift */
5224 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/* 32bit shift */,
5225 r_dstHi
, r_srcHi
, MIPSRH_Reg(shift
)));
5226 /* andi r_srcLo, shift, 0x20 */
5227 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_srcLotmp
, shift
,
5228 MIPSRH_Imm(False
, 0x20)));
5229 /* or r_dstLo, a3, r_dstLo */
5230 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dstLo
, a3
, MIPSRH_Reg(r_dstLo
)));
5231 #if (__mips_isa_rev >= 6)
5232 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, r_dstLo
, r_dstLo
, r_srcLotmp
));
5233 addInstr(env
, MIPSInstr_MoveCond(MSelnez
, a3
, r_dstHi
, r_srcLotmp
));
5234 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dstLo
, r_dstLo
, MIPSRH_Reg(a3
)));
5236 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, r_dstHi
, r_dstHi
, r_srcLotmp
));
5238 /* movn r_dstLo, r_dstHi, r_srcLo */
5239 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, r_dstLo
, r_dstHi
, r_srcLotmp
));
5240 /* movn r_dstHi, zero, r_srcLo */
5241 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, r_dstHi
, zero
, r_srcLotmp
));
5249 /* 64-bit shift left based on what gcc generates:
5263 HReg r_srcLo
, r_srcHi
;
5264 HReg r_shift
= newVRegI(env
);
5265 HReg a3
= newVRegI(env
);
5266 HReg r_dstLo
= newVRegI(env
);
5267 HReg r_dstHi
= newVRegI(env
);
5268 HReg zero
= hregMIPS_GPR0(env
->mode64
);
5271 iselInt64Expr(&r_srcHi
, &r_srcLo
, env
, e
->Iex
.Binop
.arg1
);
5272 sa
= iselWordExpr_RH6u(env
, e
->Iex
.Binop
.arg2
);
5274 if (sa
->tag
== Mrh_Imm
) {
5275 addInstr(env
, MIPSInstr_LI(r_shift
, sa
->Mrh
.Imm
.imm16
));
5278 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_shift
, sa
->Mrh
.Reg
.reg
,
5279 MIPSRH_Imm(False
, 0x3f)));
5281 /* nor r_dstLo, zero, r_shift */
5282 addInstr(env
, MIPSInstr_Alu(Malu_NOR
, r_dstLo
, zero
, MIPSRH_Reg(r_shift
)));
5283 /* srl a3, r_srcLo, 0x1 */
5284 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/* 32bit shift */,
5285 a3
, r_srcLo
, MIPSRH_Imm(False
, 0x1)));
5286 /* srlv a3, a3, r_dstLo */
5287 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/* 32bit shift */,
5288 a3
, a3
, MIPSRH_Reg(r_dstLo
)));
5289 /* sllv r_dstHi, r_srcHi, r_shift */
5290 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
/* 32bit shift */,
5291 r_dstHi
, r_srcHi
, MIPSRH_Reg(r_shift
)));
5292 /* or r_dstHi, a3, r_dstHi */
5293 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dstHi
, a3
, MIPSRH_Reg(r_dstHi
)));
5294 /* andi a3, r_shift, 0x20 */
5295 addInstr(env
, MIPSInstr_Alu(Malu_AND
, a3
, r_shift
,
5296 MIPSRH_Imm(False
, 0x20)));
5297 /* sllv r_dstLo, r_srcLo, r_shift */
5298 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
/* 32bit shift */,
5299 r_dstLo
, r_srcLo
, MIPSRH_Reg(r_shift
)));
5300 #if (__mips_isa_rev >= 6)
5301 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, r_dstHi
, r_dstHi
, a3
));
5302 addInstr(env
, MIPSInstr_MoveCond(MSelnez
, r_shift
, r_dstLo
, a3
));
5303 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dstHi
, r_dstHi
, MIPSRH_Reg(r_shift
)));
5305 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, r_dstLo
, r_dstLo
, a3
));
5307 /* movn r_dstHi, r_dstLo, a3 */
5308 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, r_dstHi
, r_dstLo
, a3
));
5309 /* movn r_dstLo, zero, a3 */
5310 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, r_dstLo
, zero
, a3
));
5318 /* 64-bit arithmetic shift right based on what gcc generates:
5332 HReg r_srcHi
, r_srcLo
;
5333 HReg r_srcHitmp
= newVRegI(env
);
5334 HReg r_srcLotmp
= newVRegI(env
);
5335 HReg r_shift
= newVRegI(env
);
5336 HReg a3
= newVRegI(env
);
5337 HReg r_dstLo
= newVRegI(env
);
5338 HReg r_dstHi
= newVRegI(env
);
5339 HReg zero
= hregMIPS_GPR0(env
->mode64
);
5342 iselInt64Expr(&r_srcLo
, &r_srcHi
, env
, e
->Iex
.Binop
.arg1
);
5343 sa
= iselWordExpr_RH6u(env
, e
->Iex
.Binop
.arg2
);
5345 if (sa
->tag
== Mrh_Imm
) {
5346 addInstr(env
, MIPSInstr_LI(r_shift
, sa
->Mrh
.Imm
.imm16
));
5349 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_shift
, sa
->Mrh
.Reg
.reg
,
5350 MIPSRH_Imm(False
, 0x3f)));
5352 /* nor r_dstLo, zero, r_shift */
5353 addInstr(env
, MIPSInstr_Alu(Malu_NOR
, r_dstLo
, zero
, MIPSRH_Reg(r_shift
)));
5354 /* sll a3, r_srcLo, 0x1 */
5355 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
/* 32bit shift */,
5356 a3
, r_srcLo
, MIPSRH_Imm(False
, 0x1)));
5357 /* sllv a3, a3, r_dstLo */
5358 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
/* 32bit shift */,
5359 a3
, a3
, MIPSRH_Reg(r_dstLo
)));
5360 /* srlv r_dstLo, r_srcHi, r_shift */
5361 addInstr(env
, MIPSInstr_Shft(Mshft_SRL
, True
/* 32bit shift */,
5362 r_dstLo
, r_srcHi
, MIPSRH_Reg(r_shift
)));
5363 /* srav r_dstHi, r_srcLo, r_shift */
5364 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
/* 32bit shift */,
5365 r_dstHi
, r_srcLo
, MIPSRH_Reg(r_shift
)));
5366 /* andi r_srcHi, r_shift, 0x20 */
5367 addInstr(env
, MIPSInstr_Alu(Malu_AND
, r_srcHitmp
, r_shift
,
5368 MIPSRH_Imm(False
, 0x20)));
5369 /* sra r_srcLo, r_srcLo, 0x1f */
5370 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
/* 32bit shift */,
5371 r_srcLotmp
, r_srcLo
, MIPSRH_Imm(False
, 0x1f)));
5372 /* or r_dstLo, a3, r_dstLo */
5373 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dstLo
, a3
, MIPSRH_Reg(r_dstLo
)));
5374 #if (__mips_isa_rev >= 6)
5375 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, r_dstLo
, r_dstLo
, r_srcHitmp
));
5376 addInstr(env
, MIPSInstr_MoveCond(MSelnez
, a3
, r_dstHi
, r_srcHitmp
));
5377 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dstLo
, r_dstLo
, MIPSRH_Reg(a3
)));
5379 addInstr(env
, MIPSInstr_MoveCond(MSeleqz
, r_dstHi
, r_dstHi
, r_srcHitmp
));
5380 addInstr(env
, MIPSInstr_MoveCond(MSelnez
, a3
, r_srcLotmp
, r_srcHitmp
));
5381 addInstr(env
, MIPSInstr_Alu(Malu_OR
, r_dstHi
, r_dstHi
, MIPSRH_Reg(a3
)));
5383 /* movn r_dstLo, r_dstHi, r_srcHi */
5384 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, r_dstLo
, r_dstHi
, r_srcHitmp
));
5385 /* movn r_dstHi, r_srcLo, r_srcHi */
5386 addInstr(env
, MIPSInstr_MoveCond(MMoveCond_movn
, r_dstHi
, r_srcLotmp
, r_srcHitmp
));
5393 case Iop_F32toI64S
: {
5394 HReg tmpD
= newVRegD(env
);
5395 HReg valF
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
5396 HReg tLo
= newVRegI(env
);
5397 HReg tHi
= newVRegI(env
);
5400 /* CVTLS tmpD, valF */
5401 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
5402 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTLS
, tmpD
, valF
));
5403 set_MIPS_rounding_default(env
);
5405 sub_from_sp(env
, 16); /* Move SP down 16 bytes */
5406 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
5409 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 8, tmpD
,
5412 #if defined (_MIPSEL)
5413 addInstr(env
, MIPSInstr_Load(4, tLo
, am_addr
, mode64
));
5414 addInstr(env
, MIPSInstr_Load(4, tHi
, nextMIPSAModeFloat(am_addr
),
5416 #elif defined (_MIPSEB)
5417 addInstr(env
, MIPSInstr_Load(4, tHi
, am_addr
, mode64
));
5418 addInstr(env
, MIPSInstr_Load(4, tLo
, nextMIPSAModeFloat(am_addr
),
5430 case Iop_F64toI64U
: {
5432 HReg tmp
= newVRegV(env
);
5434 r_src
= iselDblExpr( env
, e
->Iex
.Binop
.arg2
);
5435 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Binop
.arg1
);
5436 addInstr(env
, MIPSInstr_Msa2RF(MSA_FTINT_U
, MSA_F_DW
, tmp
, r_src
));
5437 HReg r_dsth
= newVRegI(env
);
5438 HReg r_dstl
= newVRegI(env
);
5440 MIPSInstr_MsaElm(MSA_COPY_S
, tmp
, r_dstl
, MSA_DFN_W
| 0));
5442 MIPSInstr_MsaElm(MSA_COPY_S
, tmp
, r_dsth
, MSA_DFN_W
| 1));
5445 set_MIPS_rounding_default_MSA(env
);
5449 case Iop_GetElem64x2
: {
5451 HReg v_src
= iselV128Expr(env
, e
->Iex
.Binop
.arg1
);
5452 HReg r_dstHI
= newVRegI(env
);
5453 HReg r_dstLO
= newVRegI(env
);
5454 MIPSRH
*tmp
= iselWordExpr_RH(env
, False
, e
->Iex
.Binop
.arg2
);
5459 MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, r_dstHI
,
5461 (((tmp
->Mrh
.Imm
.imm16
& 0x01) << 1)
5464 MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, r_dstLO
,
5466 ((tmp
->Mrh
.Imm
.imm16
& 0x01) << 1)));
5470 HReg v_tmp
= newVRegV(env
);
5472 MIPSInstr_Msa3R(MSA_SPLAT
, MSA_D
, v_tmp
, v_src
,
5475 MIPSInstr_MsaElm(MSA_COPY_S
, v_tmp
, r_dstHI
,
5478 MIPSInstr_MsaElm(MSA_COPY_S
, v_tmp
, r_dstLO
,
5490 HReg a_L
, a_H
, b_L
, b_H
;
5491 HReg dst_L
= newVRegI(env
);
5492 HReg dst_H
= newVRegI(env
);
5494 iselInt64Expr(&a_H
, &a_L
, env
, e
->Iex
.Binop
.arg1
);
5495 iselInt64Expr(&b_H
, &b_L
, env
, e
->Iex
.Binop
.arg2
);
5496 #if (__mips_isa_rev >= 6)
5497 addInstr(env
, MIPSInstr_Mulr6(True
, True
, True
,
5499 addInstr(env
, MIPSInstr_Mulr6(True
, True
, True
,
5501 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, dst_H
, dst_H
,
5502 MIPSRH_Reg(dst_L
)));
5503 addInstr(env
, MIPSInstr_Mulr6(False
, True
, False
,
5506 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, dst_H
, dst_H
,
5507 MIPSRH_Reg(dst_L
)));
5508 addInstr(env
, MIPSInstr_Mulr6(False
, True
, True
,
5511 addInstr(env
, MIPSInstr_Mul(dst_H
, a_H
, b_L
));
5512 addInstr(env
, MIPSInstr_Mult(True
, b_H
, a_L
));
5513 addInstr(env
, MIPSInstr_Mflo(dst_L
));
5514 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, dst_H
, dst_H
,
5515 MIPSRH_Reg(dst_L
)));
5516 addInstr(env
, MIPSInstr_Mult(False
, a_L
, b_L
));
5517 addInstr(env
, MIPSInstr_Mfhi(dst_L
));
5519 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, dst_H
, dst_H
,
5520 MIPSRH_Reg(dst_L
)));
5521 addInstr(env
, MIPSInstr_Mflo(dst_L
));
5529 HReg src1_L
, src1_H
, src2_L
, src2_H
;
5530 HReg dst_L
= newVRegI(env
);
5531 HReg dst_H
= newVRegI(env
);
5532 HReg tmp1
= newVRegV(env
);
5533 HReg tmp2
= newVRegV(env
);
5535 iselInt64Expr(&src1_H
, &src1_L
, env
, e
->Iex
.Binop
.arg1
);
5536 iselInt64Expr(&src2_H
, &src2_L
, env
, e
->Iex
.Binop
.arg2
);
5537 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, src1_L
, tmp1
));
5538 addInstr(env
, MIPSInstr_MsaElm(MSA_INSERT
, src1_H
, tmp1
, MSA_DFN_W
| 1));
5539 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, src2_L
, tmp2
));
5540 addInstr(env
, MIPSInstr_MsaElm(MSA_INSERT
, src2_H
, tmp2
, MSA_DFN_W
| 1));
5541 addInstr(env
, MIPSInstr_Msa3R(MSA_DIVS
, MSA_D
, tmp1
, tmp1
, tmp2
));
5542 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, tmp1
, dst_H
, MSA_DFN_W
| 1));
5543 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, tmp1
, dst_L
, MSA_DFN_W
| 0));
5550 HReg src1_L
, src1_H
, src2_L
, src2_H
;
5551 HReg dst_L
= newVRegI(env
);
5552 HReg dst_H
= newVRegI(env
);
5553 HReg tmp1
= newVRegV(env
);
5554 HReg tmp2
= newVRegV(env
);
5556 iselInt64Expr(&src1_H
, &src1_L
, env
, e
->Iex
.Binop
.arg1
);
5557 iselInt64Expr(&src2_H
, &src2_L
, env
, e
->Iex
.Binop
.arg2
);
5558 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, src1_L
, tmp1
));
5559 addInstr(env
, MIPSInstr_MsaElm(MSA_INSERT
, src1_H
, tmp1
, MSA_DFN_W
| 1));
5560 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, src2_L
, tmp2
));
5561 addInstr(env
, MIPSInstr_MsaElm(MSA_INSERT
, src2_H
, tmp2
, MSA_DFN_W
| 1));
5562 addInstr(env
, MIPSInstr_Msa3R(MSA_DIVU
, MSA_D
, tmp1
, tmp1
, tmp2
));
5563 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, tmp1
, dst_H
, MSA_DFN_W
| 1));
5564 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, tmp1
, dst_L
, MSA_DFN_W
| 0));
5570 case Iop_F64toI64S
: {
5571 HReg tmpD
= newVRegD(env
);
5573 HReg tLo
= newVRegI(env
);
5574 HReg tHi
= newVRegI(env
);
5578 valF
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
5580 valF
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
5583 /* CVTLS tmpD, valF */
5584 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
5585 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTLD
, tmpD
, valF
));
5586 set_MIPS_rounding_default(env
);
5588 sub_from_sp(env
, 16); /* Move SP down 16 bytes */
5589 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
5592 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 8, tmpD
,
5595 #if defined (_MIPSEL)
5596 addInstr(env
, MIPSInstr_Load(4, tLo
, am_addr
, mode64
));
5597 addInstr(env
, MIPSInstr_Load(4, tHi
, nextMIPSAModeFloat(am_addr
),
5599 #elif defined (_MIPSEB)
5600 addInstr(env
, MIPSInstr_Load(4, tHi
, am_addr
, mode64
));
5601 addInstr(env
, MIPSInstr_Load(4, tLo
, nextMIPSAModeFloat(am_addr
),
5619 /* --------- UNARY ops --------- */
5620 if (e
->tag
== Iex_Unop
) {
5621 switch (e
->Iex
.Unop
.op
) {
5623 HReg tLo
= newVRegI(env
);
5624 HReg tHi
= newVRegI(env
);
5625 HReg src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
5626 HReg tmp
= newVRegI(env
);
5628 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, tmp
, src
,
5629 MIPSRH_Imm(False
, 31)));
5630 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
, tmp
, tmp
,
5631 MIPSRH_Imm(False
, 31)));
5633 addInstr(env
, mk_iMOVds_RR(tHi
, tmp
));
5634 addInstr(env
, mk_iMOVds_RR(tLo
, tmp
));
5643 HReg tLo
= newVRegI(env
);
5644 HReg tHi
= newVRegI(env
);
5645 HReg src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
5646 UInt no_bits
= (e
->Iex
.Unop
.op
== Iop_8Sto64
) ? 24 : 16;
5647 addInstr(env
, mk_iMOVds_RR(tLo
, src
));
5648 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, tLo
, tLo
,
5649 MIPSRH_Imm(False
, no_bits
)));
5650 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
, tHi
, tLo
,
5651 MIPSRH_Imm(False
, 31)));
5652 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
, tLo
, tLo
,
5653 MIPSRH_Imm(False
, no_bits
)));
5654 addInstr(env
, mk_iMOVds_RR(tHi
, tLo
));
5662 HReg tLo
= newVRegI(env
);
5663 HReg tHi
= newVRegI(env
);
5664 HReg src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
5665 addInstr(env
, mk_iMOVds_RR(tHi
, src
));
5666 addInstr(env
, mk_iMOVds_RR(tLo
, src
));
5667 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
, tHi
, tHi
,
5668 MIPSRH_Imm(False
, 31)));
5676 HReg tLo
= newVRegI(env
);
5677 HReg tHi
= newVRegI(env
);
5678 HReg src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
5679 UInt mask
= (e
->Iex
.Unop
.op
== Iop_8Sto64
) ? 0xFF : 0xFFFF;
5680 addInstr(env
, MIPSInstr_Alu(Malu_AND
, tLo
, src
,
5681 MIPSRH_Imm(False
, mask
)));
5682 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, tHi
, hregMIPS_GPR0(mode64
),
5683 MIPSRH_Reg(hregMIPS_GPR0(mode64
))));
5691 HReg tLo
= newVRegI(env
);
5692 HReg tHi
= newVRegI(env
);
5693 HReg src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
5694 addInstr(env
, mk_iMOVds_RR(tLo
, src
));
5695 addInstr(env
, MIPSInstr_Alu(Malu_ADD
, tHi
, hregMIPS_GPR0(mode64
),
5696 MIPSRH_Reg(hregMIPS_GPR0(mode64
))));
5704 HReg tHi
= newVRegI(env
);
5705 HReg tLo
= newVRegI(env
);
5706 HReg tmp
= newVRegI(env
);
5707 HReg tmp1
= newVRegI(env
);
5708 HReg tmp2
= newVRegI(env
);
5709 HReg zero
= newVRegI(env
);
5710 MIPSCondCode cc
= MIPScc_LO
;
5713 iselInt64Expr(&yHi
, &yLo
, env
, e
->Iex
.Unop
.arg
);
5715 addInstr(env
, MIPSInstr_LI(zero
, 0x00000000));
5717 /* tmp2:tmp1 = 0 - (yHi:yLo)*/
5718 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, tmp2
, zero
, MIPSRH_Reg(yLo
)));
5719 addInstr(env
, MIPSInstr_Cmp(False
, True
, tmp1
, zero
, tmp2
, cc
));
5720 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, tmp
, zero
, MIPSRH_Reg(yHi
)));
5721 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, tmp1
, tmp
, MIPSRH_Reg(tmp1
)));
5723 /* So now we have tmp2:tmp1 = -arg. To finish off, or 'arg'
5724 back in, so as to give the final result
5725 tHi:tLo = arg | -arg. */
5726 addInstr(env
, MIPSInstr_Alu(Malu_OR
, tHi
, yHi
, MIPSRH_Reg(tmp1
)));
5727 addInstr(env
, MIPSInstr_Alu(Malu_OR
, tLo
, yLo
, MIPSRH_Reg(tmp2
)));
5733 case Iop_CmpwNEZ64
: {
5735 HReg tmp1
= newVRegI(env
);
5736 HReg tmp2
= newVRegI(env
);
5737 /* srcHi:srcLo = arg */
5738 iselInt64Expr(&srcHi
, &srcLo
, env
, e
->Iex
.Unop
.arg
);
5739 /* tmp1 = srcHi | srcLo */
5740 addInstr(env
, MIPSInstr_Alu(Malu_OR
, tmp1
, srcLo
,
5741 MIPSRH_Reg(srcHi
)));
5742 /* tmp2 = (tmp1 | -tmp1) >>s 31 */
5744 addInstr(env
, MIPSInstr_Alu(Malu_SUB
, tmp2
, hregMIPS_GPR0(mode64
),
5747 addInstr(env
, MIPSInstr_Alu(Malu_OR
, tmp2
, tmp2
, MIPSRH_Reg(tmp1
)));
5748 addInstr(env
, MIPSInstr_Shft(Mshft_SRA
, True
, tmp2
, tmp2
,
5749 MIPSRH_Imm(False
, 31)));
5755 case Iop_ReinterpF64asI64
: {
5756 HReg tLo
= newVRegI(env
);
5757 HReg tHi
= newVRegI(env
);
5759 HReg fr_src
= iselDblExpr(env
, e
->Iex
.Unop
.arg
);
5761 sub_from_sp(env
, 16); /* Move SP down 16 bytes */
5762 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
5765 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 8, fr_src
,
5768 #if defined (_MIPSEL)
5769 addInstr(env
, MIPSInstr_Load(4, tLo
, am_addr
, mode64
));
5770 addInstr(env
, MIPSInstr_Load(4, tHi
, nextMIPSAModeFloat(am_addr
),
5772 #elif defined (_MIPSEB)
5773 addInstr(env
, MIPSInstr_Load(4, tHi
, am_addr
, mode64
));
5774 addInstr(env
, MIPSInstr_Load(4, tLo
, nextMIPSAModeFloat(am_addr
),
5787 HReg tLo
= newVRegI(env
);
5788 HReg tHi
= newVRegI(env
);
5789 iselInt64Expr(&tHi
, &tLo
, env
, e
->Iex
.Unop
.arg
);
5790 addInstr(env
, MIPSInstr_Alu(Malu_NOR
, tLo
, tLo
, MIPSRH_Reg(tLo
)));
5791 addInstr(env
, MIPSInstr_Alu(Malu_NOR
, tHi
, tHi
, MIPSRH_Reg(tHi
)));
5798 case Iop_V128HIto64
: {
5800 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
5801 HReg tLo
= newVRegI(env
);
5802 HReg tHi
= newVRegI(env
);
5803 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, tLo
, MSA_DFN_W
| 2));
5804 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, tHi
, MSA_DFN_W
| 3));
5810 case Iop_V128to64
: {
5812 HReg v_src
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
5813 HReg tLo
= newVRegI(env
);
5814 HReg tHi
= newVRegI(env
);
5815 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, tLo
, MSA_DFN_W
| 0));
5816 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, tHi
, MSA_DFN_W
| 1));
5822 case Iop_F32toF16x4
: {
5824 HReg v_arg
= iselV128Expr(env
, e
->Iex
.Unop
.arg
);
5825 HReg v_src
= newVRegV(env
);
5826 set_guest_MIPS_rounding_mode_MSA(env
);
5827 addInstr(env
, MIPSInstr_Msa3RF(MSA_FEXDO
, MSA_F_WH
, v_src
, v_arg
, v_arg
));
5828 set_MIPS_rounding_default_MSA(env
);
5829 HReg tLo
= newVRegI(env
);
5830 HReg tHi
= newVRegI(env
);
5831 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, tLo
, MSA_DFN_W
| 0));
5832 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, v_src
, tHi
, MSA_DFN_W
| 1));
5839 vex_printf("UNARY: No such op: ");
5840 ppIROp(e
->Iex
.Unop
.op
);
5846 vex_printf("iselInt64Expr(mips): No such tag(%u)\n", e
->tag
);
5848 vpanic("iselInt64Expr(mips)");
5851 /*---------------------------------------------------------*/
5852 /*--- ISEL: Floating point expressions (32 bit) ---*/
5853 /*---------------------------------------------------------*/
5855 /* Nothing interesting here; really just wrappers for
5857 static HReg
iselFltExpr(ISelEnv
* env
, IRExpr
* e
)
5860 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
5861 if (ty
== Ity_F32
|| (ty
== Ity_F64
&& fp_mode64
)) {
5862 r
= iselFltExpr_wrk(env
, e
);
5864 r
= iselDblExpr_wrk(env
, e
);
5865 vassert(hregClass(r
) == HRcFlt64
);
5870 /* DO NOT CALL THIS DIRECTLY */
5871 static HReg
iselFltExpr_wrk(ISelEnv
* env
, IRExpr
* e
)
5873 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
5874 vassert(ty
== Ity_F32
|| (ty
== Ity_F64
&& fp_mode64
));
5876 if (e
->tag
== Iex_RdTmp
) {
5877 return lookupIRTemp(env
, e
->Iex
.RdTmp
.tmp
);
5880 if (e
->tag
== Iex_Load
) {
5881 vassert(e
->Iex
.Load
.ty
== Ity_F32
5882 || (e
->Iex
.Load
.ty
== Ity_F64
&& fp_mode64
));
5884 MIPSAMode
*am_addr
= iselWordExpr_AMode(env
, e
->Iex
.Load
.addr
, ty
);
5885 if (e
->Iex
.Load
.ty
== Ity_F64
) {
5886 r_dst
= newVRegD(env
);
5887 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 8, r_dst
, am_addr
));
5889 r_dst
= newVRegF(env
);
5890 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 4, r_dst
, am_addr
));
5895 if (e
->tag
== Iex_Get
) {
5896 MIPSAMode
*am_addr
= MIPSAMode_IR(e
->Iex
.Get
.offset
,
5897 GuestStatePointer(mode64
));
5899 if (e
->Iex
.Load
.ty
== Ity_F64
) {
5900 r_dst
= newVRegD(env
);
5901 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 8, r_dst
, am_addr
));
5903 r_dst
= newVRegF(env
);
5904 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 4, r_dst
, am_addr
));
5909 if (e
->tag
== Iex_Unop
) {
5910 switch (e
->Iex
.Unop
.op
) {
5911 case Iop_ReinterpI32asF32
: {
5912 HReg fr_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
5913 HReg r_dst
= newVRegF(env
);
5915 /* Move Word to Floating Point
5917 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mtc1
, r_dst
, fr_src
));
5921 case Iop_F32toF64
: {
5923 HReg src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
5924 HReg dst
= newVRegD(env
);
5926 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDS
, dst
, src
));
5929 case Iop_ReinterpI64asF64
: {
5932 HReg fr_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
5933 r_dst
= newVRegF(env
);
5934 /* Move Doubleword to Floating Point
5935 dmtc1 r_dst, fr_src */
5936 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_dmtc1
, r_dst
, fr_src
));
5939 r_dst
= newVRegD(env
);
5940 iselInt64Expr(&Hi
, &Lo
, env
, e
->Iex
.Unop
.arg
);
5941 r_dst
= mk_LoadRR32toFPR(env
, Hi
, Lo
); /* 2*I32 -> F64 */
5945 case Iop_I32StoF64
: {
5947 HReg dst
= newVRegF(env
);
5948 HReg tmp
= newVRegF(env
);
5949 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
5951 /* Move Word to Floating Point
5953 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mtc1
, tmp
, r_src
));
5955 /* and do convert */
5956 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDW
, dst
, tmp
));
5962 Bool sz32
= e
->Iex
.Unop
.op
== Iop_AbsF32
;
5963 HReg src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
5964 HReg dst
= newVRegF(env
);
5965 addInstr(env
, MIPSInstr_FpUnary(sz32
? Mfp_ABSS
: Mfp_ABSD
, dst
, src
));
5970 Bool sz32
= e
->Iex
.Unop
.op
== Iop_NegF32
;
5971 HReg src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
5972 HReg dst
= newVRegF(env
);
5973 addInstr(env
, MIPSInstr_FpUnary(sz32
? Mfp_NEGS
: Mfp_NEGD
, dst
, src
));
5976 case Iop_RoundF64toF64_ZERO
: {
5978 HReg src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
5979 HReg dst
= newVRegF(env
);
5980 addInstr(env
, MIPSInstr_FpConvert(Mfp_TRULD
, dst
, src
));
5983 case Iop_RoundF64toF64_NEAREST
: {
5985 HReg src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
5986 HReg dst
= newVRegF(env
);
5987 addInstr(env
, MIPSInstr_FpConvert(Mfp_ROUNDLD
, dst
, src
));
5990 case Iop_RoundF64toF64_NegINF
: {
5992 HReg src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
5993 HReg dst
= newVRegF(env
);
5994 addInstr(env
, MIPSInstr_FpConvert(Mfp_FLOORLD
, dst
, src
));
5997 case Iop_RoundF64toF64_PosINF
: {
5999 HReg src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
6000 HReg dst
= newVRegF(env
);
6001 addInstr(env
, MIPSInstr_FpConvert(Mfp_CEILLD
, dst
, src
));
6010 if (e
->tag
== Iex_Triop
) {
6011 switch (e
->Iex
.Triop
.details
->op
) {
6021 HReg argL
= iselFltExpr(env
, e
->Iex
.Triop
.details
->arg2
);
6022 HReg argR
= iselFltExpr(env
, e
->Iex
.Triop
.details
->arg3
);
6023 HReg dst
= newVRegF(env
);
6024 switch (e
->Iex
.Triop
.details
->op
) {
6056 set_MIPS_rounding_mode(env
, e
->Iex
.Triop
.details
->arg1
);
6057 addInstr(env
, MIPSInstr_FpBinary(op
, dst
, argL
, argR
));
6058 set_MIPS_rounding_default(env
);
6061 case Iop_ScaleF64
: {
6062 HReg src1
= iselFltExpr(env
, e
->Iex
.Triop
.details
->arg2
);
6063 HReg src2
= iselFltExpr(env
, e
->Iex
.Triop
.details
->arg3
);
6064 HReg v_help
= newVRegV(env
);
6065 HReg dst
= newVRegF(env
);
6067 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
6068 addInstr(env
, MIPSInstr_Msa2RF(MSA_FTINT_S
, MSA_F_DW
, v_help
, src2
));
6069 addInstr(env
, MIPSInstr_Msa3RF(MSA_FEXP2
, MSA_F_DW
, dst
, src1
, v_help
));
6070 set_MIPS_rounding_default_MSA(env
);
6079 if (e
->tag
== Iex_Binop
) {
6080 switch (e
->Iex
.Binop
.op
) {
6081 case Iop_F64toF32
: {
6084 valD
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
6086 valD
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
6087 HReg valS
= newVRegF(env
);
6089 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6090 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTSD
, valS
, valD
));
6091 set_MIPS_rounding_default(env
);
6095 case Iop_RoundF32toInt
: {
6096 HReg valS
= newVRegF(env
);
6097 HReg valF
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
6099 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6100 #if (__mips_isa_rev >= 6)
6101 addInstr(env
, MIPSInstr_FpConvert(Mfp_RINTS
, valS
, valF
));
6103 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTWS
, valS
, valF
));
6104 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTSW
, valS
, valS
));
6106 set_MIPS_rounding_default(env
);
6110 case Iop_RoundF64toInt
: {
6111 HReg valS
= newVRegF(env
);
6112 HReg valF
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
6114 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6115 #if (__mips_isa_rev >= 6)
6116 addInstr(env
, MIPSInstr_FpConvert(Mfp_RINTD
, valS
, valF
));
6118 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTLD
, valS
, valF
));
6119 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDL
, valS
, valS
));
6122 set_MIPS_rounding_default(env
);
6126 case Iop_I32StoF32
: {
6127 HReg r_dst
= newVRegF(env
);
6128 HReg fr_src
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
6129 HReg tmp
= newVRegF(env
);
6131 /* Move Word to Floating Point
6133 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mtc1
, tmp
, fr_src
));
6135 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6136 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTSW
, r_dst
, tmp
));
6137 set_MIPS_rounding_default(env
);
6142 case Iop_I64StoF64
: {
6143 HReg r_dst
= newVRegF(env
);
6147 tmp
= newVRegF(env
);
6148 fr_src
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
6149 /* Move SP down 8 bytes */
6150 sub_from_sp(env
, 8);
6151 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
6154 addInstr(env
, MIPSInstr_Store(8, am_addr
, fr_src
, mode64
));
6156 /* load as Ity_F64 */
6157 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 8, tmp
, am_addr
));
6163 tmp
= newVRegD(env
);
6164 iselInt64Expr(&Hi
, &Lo
, env
, e
->Iex
.Binop
.arg2
);
6165 tmp
= mk_LoadRR32toFPR(env
, Hi
, Lo
); /* 2*I32 -> F64 */
6168 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6169 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDL
, r_dst
, tmp
));
6170 set_MIPS_rounding_default(env
);
6175 case Iop_I64StoF32
: {
6176 HReg r_dst
= newVRegF(env
);
6180 tmp
= newVRegF(env
);
6181 fr_src
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
6182 /* Move SP down 8 bytes */
6183 sub_from_sp(env
, 8);
6184 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
6187 addInstr(env
, MIPSInstr_Store(8, am_addr
, fr_src
, mode64
));
6189 /* load as Ity_F64 */
6190 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 8, tmp
, am_addr
));
6196 tmp
= newVRegD(env
);
6197 iselInt64Expr(&Hi
, &Lo
, env
, e
->Iex
.Binop
.arg2
);
6198 tmp
= mk_LoadRR32toFPR(env
, Hi
, Lo
); /* 2*I32 -> F64 */
6201 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6202 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTSL
, r_dst
, tmp
));
6203 set_MIPS_rounding_default(env
);
6210 Bool sz32
= e
->Iex
.Binop
.op
== Iop_SqrtF32
;
6211 HReg src
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
6212 HReg dst
= newVRegF(env
);
6213 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6214 addInstr(env
, MIPSInstr_FpUnary(sz32
? Mfp_SQRTS
: Mfp_SQRTD
, dst
,
6216 set_MIPS_rounding_default(env
);
6220 case Iop_I64UtoF64
: {
6222 HReg r_dst
= newVRegF(env
);
6223 HReg tmp
= newVRegV(env
);
6226 r_src
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
6227 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Binop
.arg1
);
6228 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_D
, r_src
, tmp
));
6229 HReg r_srch
= newVRegI(env
);
6230 addInstr(env
, MIPSInstr_Msa2RF(MSA_FFINT_U
, MSA_F_DW
, tmp
, tmp
));
6231 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, tmp
, r_srch
, MSA_DFN_D
| 0));
6232 sub_from_sp(env
, 8);
6233 MIPSAMode
*am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
6236 addInstr(env
, MIPSInstr_Store(8, am_addr
, r_srch
, mode64
));
6238 /* load as Ity_F64 */
6239 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 8, r_dst
, am_addr
));
6243 set_MIPS_rounding_default_MSA(env
);
6247 #if (__mips_isa_rev >= 6)
6248 case Iop_MaxNumF32
: {
6249 HReg src1
= iselFltExpr(env
, e
->Iex
.Binop
.arg1
);
6250 HReg src2
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
6251 HReg dst
= newVRegF(env
);
6252 addInstr(env
, MIPSInstr_FpMinMax(Mfp_MAXS
, dst
,
6257 case Iop_MaxNumF64
: {
6258 HReg src1
= iselFltExpr(env
, e
->Iex
.Binop
.arg1
);
6259 HReg src2
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
6260 HReg dst
= newVRegF(env
);
6261 addInstr(env
, MIPSInstr_FpMinMax(Mfp_MAXD
, dst
,
6266 case Iop_MinNumF32
: {
6267 HReg src1
= iselFltExpr(env
, e
->Iex
.Binop
.arg1
);
6268 HReg src2
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
6269 HReg dst
= newVRegF(env
);
6270 addInstr(env
, MIPSInstr_FpMinMax(Mfp_MINS
, dst
,
6275 case Iop_MinNumF64
: {
6276 HReg src1
= iselFltExpr(env
, e
->Iex
.Binop
.arg1
);
6277 HReg src2
= iselFltExpr(env
, e
->Iex
.Binop
.arg2
);
6278 HReg dst
= newVRegF(env
);
6279 addInstr(env
, MIPSInstr_FpMinMax(Mfp_MIND
, dst
,
6289 if (e
->tag
== Iex_Qop
) {
6290 switch (e
->Iex
.Qop
.details
->op
) {
6296 #if (__mips_isa_rev < 6)
6299 switch (e
->Iex
.Qop
.details
->op
) {
6300 #if (__mips_isa_rev >= 6)
6315 op
= has_msa
? MSA_FMADD
: Mfp_MADDS
;
6319 op
= has_msa
? MSA_FMADD
: Mfp_MADDD
;
6323 op
= has_msa
? MSA_FMSUB
: Mfp_MSUBS
;
6327 op
= has_msa
? MSA_FMSUB
: Mfp_MSUBD
;
6335 HReg dst
= newVRegF(env
);
6336 HReg src1
= iselFltExpr(env
, e
->Iex
.Qop
.details
->arg2
);
6337 HReg src2
= iselFltExpr(env
, e
->Iex
.Qop
.details
->arg3
);
6338 HReg src3
= iselFltExpr(env
, e
->Iex
.Qop
.details
->arg4
);
6339 #if (__mips_isa_rev >= 6)
6340 set_MIPS_rounding_mode(env
, e
->Iex
.Qop
.details
->arg1
);
6341 addInstr(env
, MIPSInstr_FpTernary(op
, dst
,
6343 set_MIPS_rounding_default(env
);
6346 addInstr(env
, MIPSInstr_MsaElm(MSA_MOVE
, src3
, dst
, 0));
6347 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Qop
.details
->arg1
);
6348 addInstr(env
, MIPSInstr_Msa3RF(op
, type
, dst
, src1
, src2
));
6349 set_MIPS_rounding_default_MSA(env
);
6351 set_MIPS_rounding_mode(env
, e
->Iex
.Qop
.details
->arg1
);
6352 addInstr(env
, MIPSInstr_FpTernary(op
, dst
,
6354 set_MIPS_rounding_default(env
);
6365 if (e
->tag
== Iex_Unop
&& e
->Iex
.Unop
.op
== Iop_TruncF64asF32
) {
6366 /* This is quite subtle. The only way to do the relevant
6367 truncation is to do a single-precision store and then a
6368 double precision load to get it back into a register. The
6369 problem is, if the data is then written to memory a second
6372 STbe(...) = TruncF64asF32(...)
6374 then will the second truncation further alter the value? The
6375 answer is no: flds (as generated here) followed by fsts
6376 (generated for the STbe) is the identity function on 32-bit
6377 floats, so we are safe.
6379 Another upshot of this is that if iselStmt can see the
6382 STbe(...) = TruncF64asF32(arg)
6384 then it can short circuit having to deal with TruncF64asF32
6385 individually; instead just compute arg into a 64-bit FP
6386 register and do 'fsts' (since that itself does the
6389 We generate pretty poor code here (should be ok both for
6390 32-bit and 64-bit mode); but it is expected that for the most
6391 part the latter optimisation will apply and hence this code
6392 will not often be used.
6394 HReg fsrc
= iselDblExpr(env
, e
->Iex
.Unop
.arg
);
6395 HReg fdst
= newVRegF(env
);
6396 MIPSAMode
*zero_r1
= MIPSAMode_IR(0, StackPointer(mode64
));
6398 sub_from_sp(env
, 16);
6399 /* store as F32, hence truncating */
6400 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 4, fsrc
, zero_r1
));
6401 /* and reload. Good huh?! (sigh) */
6402 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */ , 4, fdst
, zero_r1
));
6407 /* --------- ITE --------- */
6408 if (e
->tag
== Iex_ITE
) {
6409 vassert(typeOfIRExpr(env
->type_env
, e
->Iex
.ITE
.cond
) == Ity_I1
);
6410 HReg r0
= iselFltExpr(env
, e
->Iex
.ITE
.iffalse
);
6411 HReg r1
= iselFltExpr(env
, e
->Iex
.ITE
.iftrue
);
6412 HReg r_cond
= iselWordExpr_R(env
, e
->Iex
.ITE
.cond
);
6413 HReg r_dst
= newVRegF(env
);
6414 #if (__mips_isa_rev >= 6)
6415 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mtc1
, r_dst
, r_cond
));
6416 addInstr(env
, MIPSInstr_MoveCond(MFpSeld
, r_dst
, r0
, r1
));
6418 addInstr(env
, MIPSInstr_FpUnary((ty
== Ity_F64
) ? Mfp_MOVD
: Mfp_MOVS
,
6420 addInstr(env
, MIPSInstr_MoveCond((ty
== Ity_F64
) ? MFpMoveCond_movnd
:
6422 r_dst
, r1
, r_cond
));
6427 vex_printf("iselFltExpr(mips): No such tag(0x%x)\n", e
->tag
);
6429 vpanic("iselFltExpr_wrk(mips)");
6432 static HReg
iselDblExpr(ISelEnv
* env
, IRExpr
* e
)
6434 HReg r
= iselDblExpr_wrk(env
, e
);
6435 vassert(hregClass(r
) == HRcFlt64
);
6436 vassert(hregIsVirtual(r
));
6440 /* DO NOT CALL THIS DIRECTLY */
6441 static HReg
iselDblExpr_wrk(ISelEnv
* env
, IRExpr
* e
)
6443 IRType ty
= typeOfIRExpr(env
->type_env
, e
);
6445 vassert(ty
== Ity_F64
);
6447 if (e
->tag
== Iex_RdTmp
) {
6448 return lookupIRTemp(env
, e
->Iex
.RdTmp
.tmp
);
6451 /* --------- LOAD --------- */
6452 if (e
->tag
== Iex_Load
) {
6453 HReg r_dst
= newVRegD(env
);
6455 vassert(e
->Iex
.Load
.ty
== Ity_F64
);
6456 am_addr
= iselWordExpr_AMode(env
, e
->Iex
.Load
.addr
, ty
);
6457 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */ , 8, r_dst
, am_addr
));
6461 /* --------- GET --------- */
6462 if (e
->tag
== Iex_Get
) {
6464 HReg r_dst
= newVRegD(env
);
6465 MIPSAMode
*am_addr
= MIPSAMode_IR(e
->Iex
.Get
.offset
,
6466 GuestStatePointer(mode64
));
6467 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */ , 8, r_dst
, am_addr
));
6471 if (e
->tag
== Iex_Unop
) {
6472 MIPSFpOp fpop
= Mfp_INVALID
;
6473 switch (e
->Iex
.Unop
.op
) {
6480 case Iop_F32toF64
: {
6482 HReg src
= iselFltExpr(env
, e
->Iex
.Unop
.arg
);
6483 HReg dst
= newVRegD(env
);
6485 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDS
, dst
, src
));
6488 case Iop_ReinterpI64asF64
: {
6490 HReg dst
= newVRegD(env
);
6492 iselInt64Expr(&Hi
, &Lo
, env
, e
->Iex
.Unop
.arg
);
6494 dst
= mk_LoadRR32toFPR(env
, Hi
, Lo
); /* 2*I32 -> F64 */
6497 case Iop_I32StoF64
: {
6499 HReg dst
= newVRegD(env
);
6500 HReg tmp
= newVRegF(env
);
6501 HReg r_src
= iselWordExpr_R(env
, e
->Iex
.Unop
.arg
);
6503 /* Move Word to Floating Point
6505 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mtc1
, tmp
, r_src
));
6507 /* and do convert */
6508 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDW
, dst
, tmp
));
6516 if (fpop
!= Mfp_INVALID
) {
6517 HReg src
= iselDblExpr(env
, e
->Iex
.Unop
.arg
);
6518 HReg dst
= newVRegD(env
);
6519 addInstr(env
, MIPSInstr_FpUnary(fpop
, dst
, src
));
6524 if (e
->tag
== Iex_Binop
) {
6525 switch (e
->Iex
.Binop
.op
) {
6526 case Iop_RoundF64toInt
: {
6527 HReg src
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
6528 HReg dst
= newVRegD(env
);
6530 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6531 #if (__mips_isa_rev >= 6)
6532 addInstr(env
, MIPSInstr_FpConvert(Mfp_RINTD
, dst
, src
));
6534 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTLD
, dst
, src
));
6535 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDL
, dst
, dst
));
6538 set_MIPS_rounding_default(env
);
6544 HReg src
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
6545 HReg dst
= newVRegD(env
);
6546 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6547 addInstr(env
, MIPSInstr_FpUnary(Mfp_SQRTD
, dst
, src
));
6548 set_MIPS_rounding_default(env
);
6552 case Iop_I64StoF64
: {
6553 HReg r_dst
= newVRegD(env
);
6557 tmp
= newVRegD(env
);
6558 fr_src
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
6559 /* Move SP down 8 bytes */
6560 sub_from_sp(env
, 8);
6561 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
6564 addInstr(env
, MIPSInstr_Store(8, am_addr
, fr_src
, mode64
));
6566 /* load as Ity_F64 */
6567 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 8, tmp
, am_addr
));
6573 tmp
= newVRegD(env
);
6574 iselInt64Expr(&Hi
, &Lo
, env
, e
->Iex
.Binop
.arg2
);
6575 tmp
= mk_LoadRR32toFPR(env
, Hi
, Lo
); /* 2*I32 -> F64 */
6578 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6579 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDL
, r_dst
, tmp
));
6580 set_MIPS_rounding_default(env
);
6585 case Iop_I64UtoF64
: {
6587 HReg tmp
= newVRegV(env
);
6588 HReg r_src2h
, r_src2l
;
6590 iselInt64Expr(&r_src2h
, &r_src2l
, env
, e
->Iex
.Binop
.arg2
);
6591 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Binop
.arg1
);
6592 addInstr(env
, MIPSInstr_Msa2R(MSA_FILL
, MSA_W
, r_src2l
, tmp
));
6593 addInstr(env
, MIPSInstr_MsaElm(MSA_INSERT
, r_src2h
, tmp
, MSA_DFN_W
| 1));
6594 addInstr(env
, MIPSInstr_MsaElm(MSA_INSERT
, r_src2l
, tmp
, MSA_DFN_W
| 2));
6595 addInstr(env
, MIPSInstr_MsaElm(MSA_INSERT
, r_src2h
, tmp
, MSA_DFN_W
| 3));
6596 HReg r_srchh
= newVRegI(env
);
6597 HReg r_srchl
= newVRegI(env
);
6598 addInstr(env
, MIPSInstr_Msa2RF(MSA_FFINT_U
, MSA_F_DW
, tmp
, tmp
));
6599 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, tmp
, r_srchl
, MSA_DFN_W
| 0));
6600 addInstr(env
, MIPSInstr_MsaElm(MSA_COPY_S
, tmp
, r_srchh
, MSA_DFN_W
| 1));
6601 r_dst
= mk_LoadRR32toFPR(env
, r_srchh
, r_srchl
);
6602 set_MIPS_rounding_default_MSA(env
);
6605 #if (__mips_isa_rev >= 6)
6606 case Iop_MaxNumF64
: {
6607 HReg src1
= iselDblExpr(env
, e
->Iex
.Binop
.arg1
);
6608 HReg src2
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
6609 HReg dst
= newVRegD(env
);
6610 addInstr(env
, MIPSInstr_FpMinMax(Mfp_MAXD
, dst
,
6615 case Iop_MinNumF64
: {
6616 HReg src1
= iselDblExpr(env
, e
->Iex
.Binop
.arg1
);
6617 HReg src2
= iselDblExpr(env
, e
->Iex
.Binop
.arg2
);
6618 HReg dst
= newVRegD(env
);
6619 addInstr(env
, MIPSInstr_FpMinMax(Mfp_MIND
, dst
,
6631 if (e
->tag
== Iex_Triop
) {
6632 switch (e
->Iex
.Triop
.details
->op
) {
6639 HReg argL
= iselDblExpr(env
, e
->Iex
.Triop
.details
->arg2
);
6640 HReg argR
= iselDblExpr(env
, e
->Iex
.Triop
.details
->arg3
);
6641 HReg dst
= newVRegD(env
);
6642 switch (e
->Iex
.Triop
.details
->op
) {
6661 set_MIPS_rounding_mode(env
, e
->Iex
.Triop
.details
->arg1
);
6662 addInstr(env
, MIPSInstr_FpBinary(op
, dst
, argL
, argR
));
6663 set_MIPS_rounding_default(env
);
6667 case Iop_ScaleF64
: {
6668 HReg src1
= iselDblExpr(env
, e
->Iex
.Triop
.details
->arg2
);
6669 HReg src2
= iselDblExpr(env
, e
->Iex
.Triop
.details
->arg3
);
6670 HReg v_help
= newVRegV(env
);
6671 HReg dst
= newVRegD(env
);
6673 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Triop
.details
->arg1
);
6674 addInstr(env
, MIPSInstr_Msa2RF(MSA_FTINT_S
, MSA_F_DW
, v_help
, src2
));
6675 addInstr(env
, MIPSInstr_Msa3RF(MSA_FEXP2
, MSA_F_DW
, dst
, src1
, v_help
));
6676 set_MIPS_rounding_default_MSA(env
);
6684 if (e
->tag
== Iex_Qop
) {
6685 switch (e
->Iex
.Qop
.details
->op
) {
6689 switch (e
->Iex
.Qop
.details
->op
) {
6690 #if (__mips_isa_rev >= 6)
6708 HReg dst
= newVRegD(env
);
6709 HReg src1
= iselDblExpr(env
, e
->Iex
.Qop
.details
->arg2
);
6710 HReg src2
= iselDblExpr(env
, e
->Iex
.Qop
.details
->arg3
);
6711 HReg src3
= iselDblExpr(env
, e
->Iex
.Qop
.details
->arg4
);
6712 #if (__mips_isa_rev >= 6)
6713 set_MIPS_rounding_mode(env
, e
->Iex
.Qop
.details
->arg1
);
6714 addInstr(env
, MIPSInstr_FpTernary(op
, dst
,
6716 set_MIPS_rounding_default(env
);
6719 addInstr(env
, MIPSInstr_MsaElm(MSA_MOVE
, src3
, dst
, 0));
6720 set_MIPS_rounding_mode_MSA(env
, e
->Iex
.Qop
.details
->arg1
);
6721 addInstr(env
, MIPSInstr_Msa3RF(op
, MSA_F_DW
, dst
, src1
, src2
));
6722 set_MIPS_rounding_default_MSA(env
);
6726 case Iop_I64StoF64
: {
6727 HReg r_dst
= newVRegD(env
);
6731 tmp
= newVRegF(env
);
6732 fr_src
= iselWordExpr_R(env
, e
->Iex
.Binop
.arg2
);
6733 /* Move SP down 8 bytes */
6734 sub_from_sp(env
, 8);
6735 am_addr
= MIPSAMode_IR(0, StackPointer(mode64
));
6738 addInstr(env
, MIPSInstr_Store(8, am_addr
, fr_src
, mode64
));
6740 /* load as Ity_F64 */
6741 addInstr(env
, MIPSInstr_FpLdSt(True
/*load */, 8, tmp
, am_addr
));
6747 tmp
= newVRegD(env
);
6748 iselInt64Expr(&Hi
, &Lo
, env
, e
->Iex
.Binop
.arg2
);
6749 tmp
= mk_LoadRR32toFPR(env
, Hi
, Lo
); /* 2*I32 -> F64 */
6752 set_MIPS_rounding_mode(env
, e
->Iex
.Binop
.arg1
);
6753 addInstr(env
, MIPSInstr_FpConvert(Mfp_CVTDL
, r_dst
, tmp
));
6754 set_MIPS_rounding_default(env
);
6764 /* --------- ITE --------- */
6765 if (e
->tag
== Iex_ITE
) {
6767 && typeOfIRExpr(env
->type_env
, e
->Iex
.ITE
.cond
) == Ity_I1
) {
6768 HReg r0
= iselDblExpr(env
, e
->Iex
.ITE
.iffalse
);
6769 HReg r1
= iselDblExpr(env
, e
->Iex
.ITE
.iftrue
);
6770 HReg r_cond
= iselWordExpr_R(env
, e
->Iex
.ITE
.cond
);
6771 HReg r_dst
= newVRegD(env
);
6772 #if (__mips_isa_rev >= 6)
6773 addInstr(env
, MIPSInstr_FpGpMove(MFpGpMove_mtc1
, r_dst
, r_cond
));
6774 addInstr(env
, MIPSInstr_MoveCond(MFpSeld
, r_dst
, r0
, r1
));
6776 addInstr(env
, MIPSInstr_FpUnary(Mfp_MOVD
, r_dst
, r0
));
6777 addInstr(env
, MIPSInstr_MoveCond(MFpMoveCond_movnd
, r_dst
, r1
,
6784 vex_printf("iselDblExpr(mips): No such tag(%u)\n", e
->tag
);
6786 vpanic("iselDblExpr_wrk(mips)");
6789 /*---------------------------------------------------------*/
6790 /*--- ISEL: Statements ---*/
6791 /*---------------------------------------------------------*/
6793 static void iselStmt(ISelEnv
* env
, IRStmt
* stmt
)
6795 if (vex_traceflags
& VEX_TRACE_VCODE
) {
6796 vex_printf("\n-- ");
6802 switch (stmt
->tag
) {
6803 /* --------- STORE --------- */
6806 IRType tyd
= typeOfIRExpr(env
->type_env
, stmt
->Ist
.Store
.data
);
6808 if (tyd
== Ity_V128
) {
6810 HReg res
= iselV128Expr(env
, stmt
->Ist
.Store
.data
);
6811 HReg addr
= iselWordExpr_R(env
, stmt
->Ist
.Store
.addr
);
6812 addInstr(env
, MIPSInstr_MsaMi10(MSA_ST
, 0, addr
, res
, MSA_B
));
6816 /*constructs addressing mode from address provided */
6817 am_addr
= iselWordExpr_AMode(env
, stmt
->Ist
.Store
.addr
, tyd
);
6819 if (tyd
== Ity_I8
|| tyd
== Ity_I16
|| tyd
== Ity_I32
||
6820 (mode64
&& (tyd
== Ity_I64
))) {
6821 HReg r_src
= iselWordExpr_R(env
, stmt
->Ist
.Store
.data
);
6822 addInstr(env
, MIPSInstr_Store(toUChar(sizeofIRType(tyd
)),
6823 am_addr
, r_src
, mode64
));
6826 if (!mode64
&& (tyd
== Ity_I64
)) {
6828 HReg r_addr
= iselWordExpr_R(env
, stmt
->Ist
.Store
.addr
);
6830 iselInt64Expr(&vHi
, &vLo
, env
, stmt
->Ist
.Store
.data
);
6832 addInstr(env
, MIPSInstr_Store(toUChar(sizeofIRType(Ity_I32
)),
6833 MIPSAMode_IR(0, r_addr
), vHi
, mode64
));
6834 addInstr(env
, MIPSInstr_Store(toUChar(sizeofIRType(Ity_I32
)),
6835 MIPSAMode_IR(4, r_addr
), vLo
, mode64
));
6838 if (tyd
== Ity_F32
) {
6839 HReg fr_src
= iselFltExpr(env
, stmt
->Ist
.Store
.data
);
6840 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 4, fr_src
,
6844 if (tyd
== Ity_F64
&& mode64
) {
6845 HReg fr_src
= iselFltExpr(env
, stmt
->Ist
.Store
.data
);
6846 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 8, fr_src
,
6850 if (!mode64
&& (tyd
== Ity_F64
)) {
6851 HReg fr_src
= iselDblExpr(env
, stmt
->Ist
.Store
.data
);
6852 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 8, fr_src
,
6860 /* --------- PUT --------- */
6862 IRType ty
= typeOfIRExpr(env
->type_env
, stmt
->Ist
.Put
.data
);
6864 if (ty
== Ity_I8
|| ty
== Ity_I16
|| ty
== Ity_I32
||
6865 (ty
== Ity_I64
&& mode64
)) {
6866 HReg r_src
= iselWordExpr_R(env
, stmt
->Ist
.Put
.data
);
6867 MIPSAMode
*am_addr
= MIPSAMode_IR(stmt
->Ist
.Put
.offset
,
6868 GuestStatePointer(mode64
));
6869 addInstr(env
, MIPSInstr_Store(toUChar(sizeofIRType(ty
)),
6870 am_addr
, r_src
, mode64
));
6874 if (ty
== Ity_I64
&& !mode64
) {
6876 MIPSAMode
*am_addr
= MIPSAMode_IR(stmt
->Ist
.Put
.offset
,
6877 GuestStatePointer(mode64
));
6878 MIPSAMode
*am_addr4
= MIPSAMode_IR(stmt
->Ist
.Put
.offset
+ 4,
6879 GuestStatePointer(mode64
));
6880 iselInt64Expr(&vHi
, &vLo
, env
, stmt
->Ist
.Put
.data
);
6881 addInstr(env
, MIPSInstr_Store(toUChar(sizeofIRType(Ity_I32
)),
6882 am_addr
, vLo
, mode64
));
6883 addInstr(env
, MIPSInstr_Store(toUChar(sizeofIRType(Ity_I32
)),
6884 am_addr4
, vHi
, mode64
));
6889 if (ty
== Ity_F32
) {
6890 HReg fr_src
= iselFltExpr(env
, stmt
->Ist
.Put
.data
);
6891 MIPSAMode
*am_addr
= MIPSAMode_IR(stmt
->Ist
.Put
.offset
,
6892 GuestStatePointer(mode64
));
6893 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 4, fr_src
,
6898 if (ty
== Ity_F64
) {
6900 HReg fr_src
= iselFltExpr(env
, stmt
->Ist
.Put
.data
);
6901 MIPSAMode
*am_addr
= MIPSAMode_IR(stmt
->Ist
.Put
.offset
,
6902 GuestStatePointer(mode64
));
6903 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 8, fr_src
,
6906 HReg fr_src
= iselDblExpr(env
, stmt
->Ist
.Put
.data
);
6907 MIPSAMode
*am_addr
= MIPSAMode_IR(stmt
->Ist
.Put
.offset
,
6908 GuestStatePointer(mode64
));
6909 addInstr(env
, MIPSInstr_FpLdSt(False
/*store */ , 8, fr_src
,
6914 if (ty
== Ity_V128
) {
6916 HReg v_src
= iselV128Expr(env
, stmt
->Ist
.Put
.data
);
6917 #if defined(_MIPSEB)
6918 HReg r_addr
= newVRegI(env
);
6919 addInstr(env
, MIPSInstr_Alu(mode64
? Malu_DADD
: Malu_ADD
, r_addr
, GuestStatePointer(mode64
),
6920 MIPSRH_Imm(False
, stmt
->Ist
.Put
.offset
)));
6921 addInstr(env
, MIPSInstr_MsaMi10(MSA_ST
, 0, r_addr
, v_src
, MSA_B
));
6923 vassert(!(stmt
->Ist
.Put
.offset
& 7));
6924 addInstr(env
, MIPSInstr_MsaMi10(MSA_ST
, stmt
->Ist
.Put
.offset
>> 3,
6925 GuestStatePointer(mode64
), v_src
, MSA_D
));
6932 /* --------- TMP --------- */
6934 IRTemp tmp
= stmt
->Ist
.WrTmp
.tmp
;
6935 IRType ty
= typeOfIRTemp(env
->type_env
, tmp
);
6937 if (ty
== Ity_I8
|| ty
== Ity_I16
|| ty
== Ity_I32
|| ty
== Ity_I1
) {
6938 HReg r_dst
= lookupIRTemp(env
, tmp
);
6939 HReg r_src
= iselWordExpr_R(env
, stmt
->Ist
.WrTmp
.data
);
6940 addInstr(env
, mk_iMOVds_RR(r_dst
, r_src
));
6944 if (ty
== Ity_I64
) {
6946 HReg r_dst
= lookupIRTemp(env
, tmp
);
6947 HReg r_src
= iselWordExpr_R(env
, stmt
->Ist
.WrTmp
.data
);
6948 addInstr(env
, mk_iMOVds_RR(r_dst
, r_src
));
6951 HReg rHi
, rLo
, dstHi
, dstLo
;
6952 iselInt64Expr(&rHi
, &rLo
, env
, stmt
->Ist
.WrTmp
.data
);
6953 lookupIRTemp64(&dstHi
, &dstLo
, env
, tmp
);
6954 addInstr(env
, mk_iMOVds_RR(dstHi
, rHi
));
6955 addInstr(env
, mk_iMOVds_RR(dstLo
, rLo
));
6960 if (mode64
&& ty
== Ity_I128
) {
6961 HReg rHi
, rLo
, dstHi
, dstLo
;
6962 iselInt128Expr(&rHi
, &rLo
, env
, stmt
->Ist
.WrTmp
.data
);
6963 lookupIRTempPair(&dstHi
, &dstLo
, env
, tmp
);
6964 addInstr(env
, mk_iMOVds_RR(dstHi
, rHi
));
6965 addInstr(env
, mk_iMOVds_RR(dstLo
, rLo
));
6969 if (ty
== Ity_F32
) {
6970 HReg fr_dst
= lookupIRTemp(env
, tmp
);
6971 HReg fr_src
= iselFltExpr(env
, stmt
->Ist
.WrTmp
.data
);
6972 addInstr(env
, MIPSInstr_FpUnary(Mfp_MOVS
, fr_dst
, fr_src
));
6976 if (ty
== Ity_F64
) {
6978 HReg src
= iselFltExpr(env
, stmt
->Ist
.WrTmp
.data
);
6979 HReg dst
= lookupIRTemp(env
, tmp
);
6980 addInstr(env
, MIPSInstr_FpUnary(Mfp_MOVD
, dst
, src
));
6983 HReg src
= iselDblExpr(env
, stmt
->Ist
.WrTmp
.data
);
6984 HReg dst
= lookupIRTemp(env
, tmp
);
6985 addInstr(env
, MIPSInstr_FpUnary(Mfp_MOVD
, dst
, src
));
6990 if (ty
== Ity_V128
) {
6992 HReg v_dst
= lookupIRTemp(env
, tmp
);
6993 HReg v_src
= iselV128Expr(env
, stmt
->Ist
.WrTmp
.data
);
6994 addInstr(env
, MIPSInstr_MsaElm(MSA_MOVE
, v_src
, v_dst
, 0));
7000 /* --------- Call to DIRTY helper --------- */
7002 IRDirty
*d
= stmt
->Ist
.Dirty
.details
;
7004 /* Figure out the return type, if any. */
7005 IRType retty
= Ity_INVALID
;
7006 if (d
->tmp
!= IRTemp_INVALID
)
7007 retty
= typeOfIRTemp(env
->type_env
, d
->tmp
);
7009 /* Throw out any return types we don't know about. */
7010 Bool retty_ok
= False
;
7012 case Ity_INVALID
: /* Function doesn't return anything. */
7014 case Ity_I64
: case Ity_I32
: case Ity_I16
: case Ity_I8
:
7015 retty_ok
= True
; break;
7021 break; /* will go to stmt_fail: */
7023 /* Marshal args, do the call, clear stack, set the return value
7024 to 0x555..555 if this is a conditional call that returns a
7025 value and the call is skipped. */
7027 RetLoc rloc
= mk_RetLoc_INVALID();
7028 doHelperCall( &addToSp
, &rloc
, env
, d
->guard
, d
->cee
, retty
, d
->args
);
7029 vassert(is_sane_RetLoc(rloc
));
7031 /* Now figure out what to do with the returned value, if any. */
7034 /* No return value. Nothing to do. */
7035 vassert(d
->tmp
== IRTemp_INVALID
);
7036 vassert(rloc
.pri
== RLPri_None
);
7037 vassert(addToSp
== 0);
7040 case Ity_I32
: case Ity_I16
: case Ity_I8
: {
7041 /* The returned value is in $v0. Park it in the register
7042 associated with tmp. */
7043 HReg r_dst
= lookupIRTemp(env
, d
->tmp
);
7044 addInstr(env
, MIPSInstr_Shft(Mshft_SLL
, True
, r_dst
,
7045 hregMIPS_GPR2(mode64
),
7046 MIPSRH_Imm(False
, 0)));
7047 vassert(rloc
.pri
== RLPri_Int
);
7048 vassert(addToSp
== 0);
7053 /* The returned value is in $v0. Park it in the register
7054 associated with tmp. */
7055 HReg r_dst
= lookupIRTemp(env
, d
->tmp
);
7056 addInstr(env
, mk_iMOVds_RR(r_dst
, hregMIPS_GPR2(mode64
)));
7057 vassert(rloc
.pri
== RLPri_Int
);
7058 vassert(addToSp
== 0);
7061 HReg rHi
= newVRegI(env
);
7062 HReg rLo
= newVRegI(env
);
7064 addInstr(env
, mk_iMOVds_RR(rLo
, hregMIPS_GPR2(mode64
)));
7065 addInstr(env
, mk_iMOVds_RR(rHi
, hregMIPS_GPR3(mode64
)));
7066 lookupIRTemp64(&dstHi
, &dstLo
, env
, d
->tmp
);
7067 addInstr(env
, mk_iMOVds_RR(dstHi
, rHi
));
7068 addInstr(env
, mk_iMOVds_RR(dstLo
, rLo
));
7074 vassert(rloc
.pri
== RLPri_V128SpRel
);
7075 vassert((rloc
.spOff
< 512) && (rloc
.spOff
> -512));
7076 vassert(addToSp
>= 16);
7077 HReg dst
= lookupIRTemp(env
, d
->tmp
);
7078 addInstr(env
, MIPSInstr_MsaMi10(MSA_LD
, rloc
.spOff
, StackPointer(mode64
), dst
, MSA_B
));
7079 add_to_sp(env
, addToSp
);
7089 /* --------- Load Linked or Store Conditional --------- */
7091 /* Temporary solution; this need to be rewritten again for MIPS.
7092 On MIPS you can not read from address that is locked with LL
7093 before SC. If you read from address that is locked than SC will
7095 IRTemp res
= stmt
->Ist
.LLSC
.result
;
7096 IRType tyRes
= typeOfIRTemp(env
->type_env
, res
);
7097 IRType tyAddr
= typeOfIRExpr(env
->type_env
, stmt
->Ist
.LLSC
.addr
);
7099 if (!mode64
&& (tyAddr
!= Ity_I32
))
7102 if (stmt
->Ist
.LLSC
.storedata
== NULL
) {
7105 /* constructs addressing mode from address provided */
7106 r_addr
= iselWordExpr_AMode(env
, stmt
->Ist
.LLSC
.addr
, tyAddr
);
7108 HReg r_dst
= lookupIRTemp(env
, res
);
7109 if (tyRes
== Ity_I32
) {
7110 addInstr(env
, MIPSInstr_LoadL(4, r_dst
, r_addr
, mode64
));
7112 } else if (tyRes
== Ity_I64
&& mode64
) {
7113 addInstr(env
, MIPSInstr_LoadL(8, r_dst
, r_addr
, mode64
));
7119 r_addr
= iselWordExpr_AMode(env
, stmt
->Ist
.LLSC
.addr
, tyAddr
);
7120 HReg r_src
= iselWordExpr_R(env
, stmt
->Ist
.LLSC
.storedata
);
7121 HReg r_dst
= lookupIRTemp(env
, res
);
7122 IRType tyData
= typeOfIRExpr(env
->type_env
,
7123 stmt
->Ist
.LLSC
.storedata
);
7125 if (tyData
== Ity_I32
) {
7126 addInstr(env
, mk_iMOVds_RR(r_dst
, r_src
));
7127 addInstr(env
, MIPSInstr_StoreC(4, r_addr
, r_dst
, mode64
));
7129 } else if (tyData
== Ity_I64
&& mode64
) {
7130 addInstr(env
, mk_iMOVds_RR(r_dst
, r_src
));
7131 addInstr(env
, MIPSInstr_StoreC(8, r_addr
, r_dst
, mode64
));
7139 if (stmt
->Ist
.CAS
.details
->oldHi
== IRTemp_INVALID
) {
7140 IRCAS
*cas
= stmt
->Ist
.CAS
.details
;
7141 HReg old
= lookupIRTemp(env
, cas
->oldLo
);
7142 HReg addr
= iselWordExpr_R(env
, cas
->addr
);
7143 HReg expd
= iselWordExpr_R(env
, cas
->expdLo
);
7144 HReg data
= iselWordExpr_R(env
, cas
->dataLo
);
7145 if (typeOfIRTemp(env
->type_env
, cas
->oldLo
) == Ity_I64
) {
7146 addInstr(env
, MIPSInstr_Cas(8, old
, addr
, expd
, data
, mode64
));
7147 } else if (typeOfIRTemp(env
->type_env
, cas
->oldLo
) == Ity_I32
) {
7148 addInstr(env
, MIPSInstr_Cas(4, old
, addr
, expd
, data
, mode64
));
7153 /* --------- INSTR MARK --------- */
7154 /* Doesn't generate any executable code ... */
7158 /* --------- ABI HINT --------- */
7159 /* These have no meaning (denotation in the IR) and so we ignore
7160 them ... if any actually made it this far. */
7164 /* --------- NO-OP --------- */
7165 /* Fairly self-explanatory, wouldn't you say? */
7169 /* --------- EXIT --------- */
7171 IRConst
* dst
= stmt
->Ist
.Exit
.dst
;
7172 if (!mode64
&& dst
->tag
!= Ico_U32
)
7173 vpanic("iselStmt(mips32): Ist_Exit: dst is not a 32-bit value");
7174 if (mode64
&& dst
->tag
!= Ico_U64
)
7175 vpanic("iselStmt(mips64): Ist_Exit: dst is not a 64-bit value");
7177 MIPSCondCode cc
= iselCondCode(env
, stmt
->Ist
.Exit
.guard
);
7178 MIPSAMode
* amPC
= MIPSAMode_IR(stmt
->Ist
.Exit
.offsIP
,
7179 GuestStatePointer(mode64
));
7181 /* Case: boring transfer to known address */
7182 if (stmt
->Ist
.Exit
.jk
== Ijk_Boring
7183 || stmt
->Ist
.Exit
.jk
== Ijk_Call
7184 /* || stmt->Ist.Exit.jk == Ijk_Ret */) {
7185 if (env
->chainingAllowed
) {
7186 /* .. almost always true .. */
7187 /* Skip the event check at the dst if this is a forwards
7191 ? (((Addr64
)stmt
->Ist
.Exit
.dst
->Ico
.U64
) > (Addr64
)env
->max_ga
)
7192 : (((Addr32
)stmt
->Ist
.Exit
.dst
->Ico
.U32
) > (Addr32
)env
->max_ga
);
7193 if (0) vex_printf("%s", toFastEP
? "Y" : ",");
7194 addInstr(env
, MIPSInstr_XDirect(
7195 mode64
? (Addr64
)stmt
->Ist
.Exit
.dst
->Ico
.U64
7196 : (Addr64
)stmt
->Ist
.Exit
.dst
->Ico
.U32
,
7197 amPC
, cc
, toFastEP
));
7199 /* .. very occasionally .. */
7200 /* We can't use chaining, so ask for an assisted transfer,
7201 as that's the only alternative that is allowable. */
7202 HReg r
= iselWordExpr_R(env
, IRExpr_Const(stmt
->Ist
.Exit
.dst
));
7203 addInstr(env
, MIPSInstr_XAssisted(r
, amPC
, cc
, Ijk_Boring
));
7208 /* Case: assisted transfer to arbitrary address */
7209 switch (stmt
->Ist
.Exit
.jk
) {
7210 /* Keep this list in sync with that in iselNext below */
7219 case Ijk_SigFPE_IntDiv
:
7220 case Ijk_SigFPE_IntOvf
:
7221 case Ijk_Sys_syscall
:
7222 case Ijk_InvalICache
:
7224 HReg r
= iselWordExpr_R(env
, IRExpr_Const(stmt
->Ist
.Exit
.dst
));
7225 addInstr(env
, MIPSInstr_XAssisted(r
, amPC
, cc
,
7226 stmt
->Ist
.Exit
.jk
));
7233 /* Do we ever expect to see any other kind? */
7242 vex_printf("stmt_fail tag: 0x%x\n", stmt
->tag
);
7244 vpanic("iselStmt:\n");
7247 /*---------------------------------------------------------*/
7248 /*--- ISEL: Basic block terminators (Nexts) ---*/
7249 /*---------------------------------------------------------*/
7251 static void iselNext ( ISelEnv
* env
,
7252 IRExpr
* next
, IRJumpKind jk
, Int offsIP
)
7254 if (vex_traceflags
& VEX_TRACE_VCODE
) {
7255 vex_printf( "\n-- PUT(%d) = ", offsIP
);
7257 vex_printf( "; exit-");
7262 /* Case: boring transfer to known address */
7263 if (next
->tag
== Iex_Const
) {
7264 IRConst
* cdst
= next
->Iex
.Const
.con
;
7265 vassert(cdst
->tag
== (env
->mode64
? Ico_U64
:Ico_U32
));
7266 if (jk
== Ijk_Boring
|| jk
== Ijk_Call
) {
7267 /* Boring transfer to known address */
7268 MIPSAMode
* amPC
= MIPSAMode_IR(offsIP
, GuestStatePointer(env
->mode64
));
7269 if (env
->chainingAllowed
) {
7270 /* .. almost always true .. */
7271 /* Skip the event check at the dst if this is a forwards
7275 ? (((Addr64
)cdst
->Ico
.U64
) > (Addr64
)env
->max_ga
)
7276 : (((Addr32
)cdst
->Ico
.U32
) > (Addr32
)env
->max_ga
);
7277 if (0) vex_printf("%s", toFastEP
? "X" : ".");
7278 addInstr(env
, MIPSInstr_XDirect(
7279 env
->mode64
? (Addr64
)cdst
->Ico
.U64
7280 : (Addr64
)cdst
->Ico
.U32
,
7281 amPC
, MIPScc_AL
, toFastEP
));
7283 /* .. very occasionally .. */
7284 /* We can't use chaining, so ask for an assisted transfer,
7285 as that's the only alternative that is allowable. */
7286 HReg r
= iselWordExpr_R(env
, next
);
7287 addInstr(env
, MIPSInstr_XAssisted(r
, amPC
, MIPScc_AL
,
7294 /* Case: call/return (==boring) transfer to any address */
7296 case Ijk_Boring
: case Ijk_Ret
: case Ijk_Call
: {
7297 HReg r
= iselWordExpr_R(env
, next
);
7298 MIPSAMode
* amPC
= MIPSAMode_IR(offsIP
,
7299 GuestStatePointer(env
->mode64
));
7300 if (env
->chainingAllowed
) {
7301 addInstr(env
, MIPSInstr_XIndir(r
, amPC
, MIPScc_AL
));
7303 addInstr(env
, MIPSInstr_XAssisted(r
, amPC
, MIPScc_AL
,
7312 /* Case: assisted transfer to arbitrary address */
7314 /* Keep this list in sync with that for Ist_Exit above */
7323 case Ijk_SigFPE_IntDiv
:
7324 case Ijk_SigFPE_IntOvf
:
7325 case Ijk_Sys_syscall
:
7326 case Ijk_InvalICache
: {
7327 HReg r
= iselWordExpr_R(env
, next
);
7328 MIPSAMode
* amPC
= MIPSAMode_IR(offsIP
, GuestStatePointer(env
->mode64
));
7329 addInstr(env
, MIPSInstr_XAssisted(r
, amPC
, MIPScc_AL
, jk
));
7336 vex_printf("\n-- PUT(%d) = ", offsIP
);
7338 vex_printf("; exit-");
7341 vassert(0); /* are we expecting any other kind? */
7344 /*---------------------------------------------------------*/
7345 /*--- Insn selector top-level ---*/
7346 /*---------------------------------------------------------*/
7348 /* Translate an entire BB to mips code. */
7349 HInstrArray
*iselSB_MIPS ( const IRSB
* bb
,
7351 const VexArchInfo
* archinfo_host
,
7352 const VexAbiInfo
* vbi
,
7353 Int offs_Host_EvC_Counter
,
7354 Int offs_Host_EvC_FailAddr
,
7355 Bool chainingAllowed
,
7362 MIPSAMode
*amCounter
, *amFailAddr
;
7364 hwcaps_host
= archinfo_host
->hwcaps
;
7367 vassert(arch_host
== VexArchMIPS32
|| arch_host
== VexArchMIPS64
);
7368 vassert(VEX_PRID_COMP_MIPS
== VEX_MIPS_COMP_ID(hwcaps_host
)
7369 || VEX_PRID_COMP_CAVIUM
== VEX_MIPS_COMP_ID(hwcaps_host
)
7370 || VEX_PRID_COMP_BROADCOM
== VEX_MIPS_COMP_ID(hwcaps_host
)
7371 || VEX_PRID_COMP_NETLOGIC
== VEX_MIPS_COMP_ID(hwcaps_host
)
7372 || VEX_PRID_COMP_INGENIC_E1
== VEX_MIPS_COMP_ID(hwcaps_host
)
7373 || VEX_PRID_COMP_LEGACY
== VEX_MIPS_COMP_ID(hwcaps_host
));
7375 /* Check that the host's endianness is as expected. */
7376 vassert(archinfo_host
->endness
== VexEndnessLE
7377 || archinfo_host
->endness
== VexEndnessBE
);
7379 mode64
= arch_host
!= VexArchMIPS32
;
7380 fp_mode64
= VEX_MIPS_HOST_FP_MODE(hwcaps_host
);
7381 has_msa
= VEX_MIPS_PROC_MSA(archinfo_host
->hwcaps
);
7383 /* Make up an initial environment to use. */
7384 env
= LibVEX_Alloc_inline(sizeof(ISelEnv
));
7386 env
->mode64
= mode64
;
7387 env
->fp_mode64
= fp_mode64
;
7389 /* Set up output code array. */
7390 env
->code
= newHInstrArray();
7392 /* Copy BB's type env. */
7393 env
->type_env
= bb
->tyenv
;
7395 /* Make up an IRTemp -> virtual HReg mapping. This doesn't
7396 change as we go along. */
7397 env
->n_vregmap
= bb
->tyenv
->types_used
;
7398 env
->vregmap
= LibVEX_Alloc_inline(env
->n_vregmap
* sizeof(HReg
));
7399 env
->vregmapHI
= LibVEX_Alloc_inline(env
->n_vregmap
* sizeof(HReg
));
7401 /* and finally ... */
7402 env
->hwcaps
= hwcaps_host
;
7403 env
->chainingAllowed
= chainingAllowed
;
7404 env
->hwcaps
= hwcaps_host
;
7405 env
->max_ga
= max_ga
;
7407 /* For each IR temporary, allocate a suitably-kinded virtual
7410 for (i
= 0; i
< env
->n_vregmap
; i
++) {
7411 hregHI
= hreg
= INVALID_HREG
;
7412 switch (bb
->tyenv
->types
[i
]) {
7418 hreg
= mkHReg(True
, HRcInt64
, 0, j
++);
7421 hreg
= mkHReg(True
, HRcInt32
, 0, j
++);
7426 hreg
= mkHReg(True
, HRcInt64
, 0, j
++);
7429 hreg
= mkHReg(True
, HRcInt32
, 0, j
++);
7430 hregHI
= mkHReg(True
, HRcInt32
, 0, j
++);
7435 hreg
= mkHReg(True
, HRcInt64
, 0, j
++);
7436 hregHI
= mkHReg(True
, HRcInt64
, 0, j
++);
7440 hreg
= mkHReg(True
, HRcFlt64
, 0, j
++);
7443 hreg
= mkHReg(True
, HRcFlt32
, 0, j
++);
7447 hreg
= mkHReg(True
, HRcFlt64
, 0, j
++);
7450 hreg
= mkHReg(True
, HRcVec128
, 0, j
++);
7453 ppIRType(bb
->tyenv
->types
[i
]);
7454 vpanic("iselBB(mips): IRTemp type");
7457 env
->vregmap
[i
] = hreg
;
7458 env
->vregmapHI
[i
] = hregHI
;
7462 /* The very first instruction must be an event check. */
7463 amCounter
= MIPSAMode_IR(offs_Host_EvC_Counter
, GuestStatePointer(mode64
));
7464 amFailAddr
= MIPSAMode_IR(offs_Host_EvC_FailAddr
, GuestStatePointer(mode64
));
7465 addInstr(env
, MIPSInstr_EvCheck(amCounter
, amFailAddr
));
7467 /* Possibly a block counter increment (for profiling). At this
7468 point we don't know the address of the counter, so just pretend
7469 it is zero. It will have to be patched later, but before this
7470 translation is used, by a call to LibVEX_patchProfCtr. */
7472 addInstr(env
, MIPSInstr_ProfInc());
7475 /* Ok, finally we can iterate over the statements. */
7476 for (i
= 0; i
< bb
->stmts_used
; i
++)
7477 iselStmt(env
, bb
->stmts
[i
]);
7479 iselNext(env
, bb
->next
, bb
->jumpkind
, bb
->offsIP
);
7481 /* record the number of vregs we used. */
7482 env
->code
->n_vregs
= env
->vreg_ctr
;
7487 /*---------------------------------------------------------------*/
7488 /*--- end host_mips_isel.c ---*/
7489 /*---------------------------------------------------------------*/