Home | History | Annotate | Download | only in priv
      1 /* -*- mode: C; c-basic-offset: 3; -*- */
      2 
      3 /*---------------------------------------------------------------*/
      4 /*--- begin                                 guest_s390_toIR.c ---*/
      5 /*---------------------------------------------------------------*/
      6 
      7 /*
      8    This file is part of Valgrind, a dynamic binary instrumentation
      9    framework.
     10 
     11    Copyright IBM Corp. 2010-2012
     12 
     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.
     17 
     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.
     22 
     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
     26    02110-1301, USA.
     27 
     28    The GNU General Public License is contained in the file COPYING.
     29 */
     30 
     31 /* Contributed by Florian Krohm and Christian Borntraeger */
     32 
     33 /* Translates s390 code to IR. */
     34 
     35 #include "libvex_basictypes.h"
     36 #include "libvex_ir.h"
     37 #include "libvex.h"                  /* needed for bb_to_IR.h */
     38 #include "libvex_s390x_common.h"
     39 #include "main_util.h"               /* vassert */
     40 #include "main_globals.h"            /* vex_traceflags */
     41 #include "guest_generic_bb_to_IR.h"  /* DisResult */
     42 #include "guest_s390_defs.h"         /* prototypes for this file's functions */
     43 #include "host_s390_disasm.h"
     44 #include "host_s390_defs.h"          /* S390_ROUND_xyzzy */
     45 
     46 
     47 /*------------------------------------------------------------*/
     48 /*--- Forward declarations                                 ---*/
     49 /*------------------------------------------------------------*/
     50 static UInt s390_decode_and_irgen(UChar *, UInt, DisResult *);
     51 static void s390_irgen_xonc(IROp, IRTemp, IRTemp, IRTemp);
     52 static void s390_irgen_CLC_EX(IRTemp, IRTemp, IRTemp);
     53 
     54 
     55 /*------------------------------------------------------------*/
     56 /*--- Globals                                              ---*/
     57 /*------------------------------------------------------------*/
     58 
     59 /* The IRSB* into which we're generating code. */
     60 static IRSB *irsb;
     61 
     62 /* The guest address for the instruction currently being
     63    translated. */
     64 static Addr64 guest_IA_curr_instr;
     65 
     66 /* The guest address for the instruction following the current instruction. */
     67 static Addr64 guest_IA_next_instr;
     68 
     69 /* Result of disassembly step. */
     70 static DisResult *dis_res;
     71 
     72 /* Resteer function and callback data */
     73 static Bool (*resteer_fn)(void *, Addr64);
     74 static void *resteer_data;
     75 
     76 /* The last seen execute target instruction */
     77 ULong last_execute_target;
     78 
     79 /* The possible outcomes of a decoding operation */
     80 typedef enum {
     81    S390_DECODE_OK,
     82    S390_DECODE_UNKNOWN_INSN,
     83    S390_DECODE_UNIMPLEMENTED_INSN,
     84    S390_DECODE_UNKNOWN_SPECIAL_INSN,
     85    S390_DECODE_ERROR
     86 } s390_decode_t;
     87 
     88 
     89 /*------------------------------------------------------------*/
     90 /*--- Helpers for constructing IR.                         ---*/
     91 /*------------------------------------------------------------*/
     92 
     93 /* Sign extend a value with the given number of bits. This is a
     94    macro because it allows us to overload the type of the value.
     95    Note that VALUE must have a signed type! */
     96 #undef sign_extend
     97 #define sign_extend(value,num_bits) \
     98 (((value) << (sizeof(__typeof__(value)) * 8 - (num_bits))) >> \
     99  (sizeof(__typeof__(value)) * 8 - (num_bits)))
    100 
    101 
    102 /* Add a statement to the current irsb. */
    103 static __inline__ void
    104 stmt(IRStmt *st)
    105 {
    106    addStmtToIRSB(irsb, st);
    107 }
    108 
    109 /* Allocate a new temporary of the given type. */
    110 static __inline__ IRTemp
    111 newTemp(IRType type)
    112 {
    113    vassert(isPlausibleIRType(type));
    114 
    115    return newIRTemp(irsb->tyenv, type);
    116 }
    117 
    118 /* Create an expression node for a temporary */
    119 static __inline__ IRExpr *
    120 mkexpr(IRTemp tmp)
    121 {
    122    return IRExpr_RdTmp(tmp);
    123 }
    124 
    125 /* Generate an expression node for an address. */
    126 static __inline__ IRExpr *
    127 mkaddr_expr(Addr64 addr)
    128 {
    129    return IRExpr_Const(IRConst_U64(addr));
    130 }
    131 
    132 /* Add a statement that assigns to a temporary */
    133 static __inline__ void
    134 assign(IRTemp dst, IRExpr *expr)
    135 {
    136    stmt(IRStmt_WrTmp(dst, expr));
    137 }
    138 
    139 /* Write an address into the guest_IA */
    140 static __inline__ void
    141 put_IA(IRExpr *address)
    142 {
    143    stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_IA), address));
    144 }
    145 
    146 /* Create a temporary of the given type and assign the expression to it */
    147 static __inline__ IRTemp
    148 mktemp(IRType type, IRExpr *expr)
    149 {
    150    IRTemp temp = newTemp(type);
    151 
    152    assign(temp, expr);
    153 
    154    return temp;
    155 }
    156 
    157 /* Create a unary expression */
    158 static __inline__ IRExpr *
    159 unop(IROp kind, IRExpr *op)
    160 {
    161    return IRExpr_Unop(kind, op);
    162 }
    163 
    164 /* Create a binary expression */
    165 static __inline__ IRExpr *
    166 binop(IROp kind, IRExpr *op1, IRExpr *op2)
    167 {
    168    return IRExpr_Binop(kind, op1, op2);
    169 }
    170 
    171 /* Create a ternary expression */
    172 static __inline__ IRExpr *
    173 triop(IROp kind, IRExpr *op1, IRExpr *op2, IRExpr *op3)
    174 {
    175    return IRExpr_Triop(kind, op1, op2, op3);
    176 }
    177 
    178 /* Create a quaternary expression */
    179 static __inline__  IRExpr *
    180 qop(IROp kind, IRExpr *op1, IRExpr *op2, IRExpr *op3, IRExpr *op4)
    181 {
    182    return IRExpr_Qop(kind, op1, op2, op3, op4);
    183 }
    184 
    185 /* Create an expression node for an 8-bit integer constant */
    186 static __inline__ IRExpr *
    187 mkU8(UInt value)
    188 {
    189    vassert(value < 256);
    190 
    191    return IRExpr_Const(IRConst_U8((UChar)value));
    192 }
    193 
    194 /* Create an expression node for a 16-bit integer constant */
    195 static __inline__ IRExpr *
    196 mkU16(UInt value)
    197 {
    198    vassert(value < 65536);
    199 
    200    return IRExpr_Const(IRConst_U16((UShort)value));
    201 }
    202 
    203 /* Create an expression node for a 32-bit integer constant */
    204 static __inline__ IRExpr *
    205 mkU32(UInt value)
    206 {
    207    return IRExpr_Const(IRConst_U32(value));
    208 }
    209 
    210 /* Create an expression node for a 64-bit integer constant */
    211 static __inline__ IRExpr *
    212 mkU64(ULong value)
    213 {
    214    return IRExpr_Const(IRConst_U64(value));
    215 }
    216 
    217 /* Create an expression node for a 32-bit floating point constant
    218    whose value is given by a bit pattern. */
    219 static __inline__ IRExpr *
    220 mkF32i(UInt value)
    221 {
    222    return IRExpr_Const(IRConst_F32i(value));
    223 }
    224 
    225 /* Create an expression node for a 32-bit floating point constant
    226    whose value is given by a bit pattern. */
    227 static __inline__ IRExpr *
    228 mkF64i(ULong value)
    229 {
    230    return IRExpr_Const(IRConst_F64i(value));
    231 }
    232 
    233 /* Little helper function for my sanity. ITE = if-then-else */
    234 static IRExpr *
    235 mkite(IRExpr *condition, IRExpr *iftrue, IRExpr *iffalse)
    236 {
    237    vassert(typeOfIRExpr(irsb->tyenv, condition) == Ity_I1);
    238 
    239    return IRExpr_Mux0X(unop(Iop_1Uto8, condition), iffalse, iftrue);
    240 }
    241 
    242 /* Add a statement that stores DATA at ADDR. This is a big-endian machine. */
    243 static void __inline__
    244 store(IRExpr *addr, IRExpr *data)
    245 {
    246    stmt(IRStmt_Store(Iend_BE, addr, data));
    247 }
    248 
    249 /* Create an expression that loads a TYPE sized value from ADDR.
    250    This is a big-endian machine. */
    251 static __inline__ IRExpr *
    252 load(IRType type, IRExpr *addr)
    253 {
    254    return IRExpr_Load(Iend_BE, type, addr);
    255 }
    256 
    257 /* Function call */
    258 static void
    259 call_function(IRExpr *callee_address)
    260 {
    261    put_IA(callee_address);
    262 
    263    dis_res->whatNext    = Dis_StopHere;
    264    dis_res->jk_StopHere = Ijk_Call;
    265 }
    266 
    267 /* Function call with known target. */
    268 static void
    269 call_function_and_chase(Addr64 callee_address)
    270 {
    271    if (resteer_fn(resteer_data, callee_address)) {
    272       dis_res->whatNext   = Dis_ResteerU;
    273       dis_res->continueAt = callee_address;
    274    } else {
    275       put_IA(mkaddr_expr(callee_address));
    276 
    277       dis_res->whatNext = Dis_StopHere;
    278       dis_res->jk_StopHere = Ijk_Call;
    279    }
    280 }
    281 
    282 /* Function return sequence */
    283 static void
    284 return_from_function(IRExpr *return_address)
    285 {
    286    put_IA(return_address);
    287 
    288    dis_res->whatNext    = Dis_StopHere;
    289    dis_res->jk_StopHere = Ijk_Ret;
    290 }
    291 
    292 /* A conditional branch whose target is not known at instrumentation time.
    293 
    294    if (condition) goto computed_target;
    295 
    296    Needs to be represented as:
    297 
    298    if (! condition) goto next_instruction;
    299    goto computed_target;
    300 */
    301 static void
    302 if_condition_goto_computed(IRExpr *condition, IRExpr *target)
    303 {
    304    vassert(typeOfIRExpr(irsb->tyenv, condition) == Ity_I1);
    305 
    306    condition = unop(Iop_Not1, condition);
    307 
    308    stmt(IRStmt_Exit(condition, Ijk_Boring, IRConst_U64(guest_IA_next_instr),
    309                     S390X_GUEST_OFFSET(guest_IA)));
    310 
    311    put_IA(target);
    312 
    313    dis_res->whatNext    = Dis_StopHere;
    314    dis_res->jk_StopHere = Ijk_Boring;
    315 }
    316 
    317 /* A conditional branch whose target is known at instrumentation time. */
    318 static void
    319 if_condition_goto(IRExpr *condition, Addr64 target)
    320 {
    321    vassert(typeOfIRExpr(irsb->tyenv, condition) == Ity_I1);
    322 
    323    stmt(IRStmt_Exit(condition, Ijk_Boring, IRConst_U64(target),
    324                     S390X_GUEST_OFFSET(guest_IA)));
    325 
    326    put_IA(mkaddr_expr(guest_IA_next_instr));
    327 
    328    dis_res->whatNext    = Dis_StopHere;
    329    dis_res->jk_StopHere = Ijk_Boring;
    330 }
    331 
    332 /* An unconditional branch. Target may or may not be known at instrumentation
    333    time. */
    334 static void
    335 always_goto(IRExpr *target)
    336 {
    337    put_IA(target);
    338 
    339    dis_res->whatNext    = Dis_StopHere;
    340    dis_res->jk_StopHere = Ijk_Boring;
    341 }
    342 
    343 
    344 /* An unconditional branch to a known target. */
    345 static void
    346 always_goto_and_chase(Addr64 target)
    347 {
    348    if (resteer_fn(resteer_data, target)) {
    349       /* Follow into the target */
    350       dis_res->whatNext   = Dis_ResteerU;
    351       dis_res->continueAt = target;
    352    } else {
    353       put_IA(mkaddr_expr(target));
    354 
    355       dis_res->whatNext    = Dis_StopHere;
    356       dis_res->jk_StopHere = Ijk_Boring;
    357    }
    358 }
    359 
    360 /* A system call */
    361 static void
    362 system_call(IRExpr *sysno)
    363 {
    364    /* Store the system call number in the pseudo register. */
    365    stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_SYSNO), sysno));
    366 
    367    /* Store the current IA into guest_IP_AT_SYSCALL. libvex_ir.h says so. */
    368    stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_IP_AT_SYSCALL),
    369                    mkU64(guest_IA_curr_instr)));
    370 
    371    put_IA(mkaddr_expr(guest_IA_next_instr));
    372 
    373    /* It's important that all ArchRegs carry their up-to-date value
    374       at this point.  So we declare an end-of-block here, which
    375       forces any TempRegs caching ArchRegs to be flushed. */
    376    dis_res->whatNext    = Dis_StopHere;
    377    dis_res->jk_StopHere = Ijk_Sys_syscall;
    378 }
    379 
    380 /* A side exit that branches back to the current insn if CONDITION is
    381    true. Does not set DisResult. */
    382 static void
    383 iterate_if(IRExpr *condition)
    384 {
    385    vassert(typeOfIRExpr(irsb->tyenv, condition) == Ity_I1);
    386 
    387    stmt(IRStmt_Exit(condition, Ijk_Boring, IRConst_U64(guest_IA_curr_instr),
    388                     S390X_GUEST_OFFSET(guest_IA)));
    389 }
    390 
    391 /* A side exit that branches back to the current insn.
    392    Does not set DisResult. */
    393 static __inline__ void
    394 iterate(void)
    395 {
    396    iterate_if(IRExpr_Const(IRConst_U1(True)));
    397 }
    398 
    399 /* A side exit that branches back to the insn immediately following the
    400    current insn if CONDITION is true. Does not set DisResult. */
    401 static void
    402 next_insn_if(IRExpr *condition)
    403 {
    404    vassert(typeOfIRExpr(irsb->tyenv, condition) == Ity_I1);
    405 
    406    stmt(IRStmt_Exit(condition, Ijk_Boring, IRConst_U64(guest_IA_next_instr),
    407                     S390X_GUEST_OFFSET(guest_IA)));
    408 }
    409 
    410 /* Convenience function to restart the current insn */
    411 static void
    412 restart_if(IRExpr *condition)
    413 {
    414    vassert(typeOfIRExpr(irsb->tyenv, condition) == Ity_I1);
    415 
    416    stmt(IRStmt_Exit(condition, Ijk_TInval, IRConst_U64(guest_IA_curr_instr),
    417                     S390X_GUEST_OFFSET(guest_IA)));
    418 }
    419 
    420 /* Convenience function to yield to thread scheduler */
    421 static void
    422 yield_if(IRExpr *condition)
    423 {
    424    stmt(IRStmt_Exit(condition, Ijk_Yield, IRConst_U64(guest_IA_next_instr),
    425                     S390X_GUEST_OFFSET(guest_IA)));
    426 }
    427 
    428 /* Encode the s390 rounding mode as it appears in the m3/m4 fields of certain
    429    instructions to VEX's IRRoundingMode. */
    430 static IRRoundingMode
    431 encode_rounding_mode(UChar mode)
    432 {
    433    switch (mode) {
    434    case S390_ROUND_NEAREST_EVEN:  return Irrm_NEAREST;
    435    case S390_ROUND_ZERO:          return Irrm_ZERO;
    436    case S390_ROUND_POSINF:        return Irrm_PosINF;
    437    case S390_ROUND_NEGINF:        return Irrm_NegINF;
    438    }
    439    vpanic("encode_rounding_mode");
    440 }
    441 
    442 static __inline__ IRExpr *get_fpr_dw0(UInt);
    443 static __inline__ void    put_fpr_dw0(UInt, IRExpr *);
    444 
    445 /* Read a floating point register pair and combine their contents into a
    446    128-bit value */
    447 static IRExpr *
    448 get_fpr_pair(UInt archreg)
    449 {
    450    IRExpr *high = get_fpr_dw0(archreg);
    451    IRExpr *low  = get_fpr_dw0(archreg + 2);
    452 
    453    return binop(Iop_F64HLtoF128, high, low);
    454 }
    455 
    456 /* Write a 128-bit floating point value into a register pair. */
    457 static void
    458 put_fpr_pair(UInt archreg, IRExpr *expr)
    459 {
    460    IRExpr *high = unop(Iop_F128HItoF64, expr);
    461    IRExpr *low  = unop(Iop_F128LOtoF64, expr);
    462 
    463    put_fpr_dw0(archreg,     high);
    464    put_fpr_dw0(archreg + 2, low);
    465 }
    466 
    467 
    468 /*------------------------------------------------------------*/
    469 /*--- IR Debugging aids.                                   ---*/
    470 /*------------------------------------------------------------*/
    471 #if 0
    472 
    473 static ULong
    474 s390_do_print(HChar *text, ULong value)
    475 {
    476    vex_printf("%s %llu\n", text, value);
    477    return 0;
    478 }
    479 
    480 static void
    481 s390_print(HChar *text, IRExpr *value)
    482 {
    483    IRDirty *d;
    484 
    485    d = unsafeIRDirty_0_N(0 /* regparms */, "s390_do_print", &s390_do_print,
    486                          mkIRExprVec_2(mkU64((ULong)text), value));
    487    stmt(IRStmt_Dirty(d));
    488 }
    489 #endif
    490 
    491 
    492 /*------------------------------------------------------------*/
    493 /*--- Build the flags thunk.                               ---*/
    494 /*------------------------------------------------------------*/
    495 
    496 /* Completely fill the flags thunk. We're always filling all fields.
    497    Apparently, that is better for redundant PUT elimination. */
    498 static void
    499 s390_cc_thunk_fill(IRExpr *op, IRExpr *dep1, IRExpr *dep2, IRExpr *ndep)
    500 {
    501    UInt op_off, dep1_off, dep2_off, ndep_off;
    502 
    503    op_off   = S390X_GUEST_OFFSET(guest_CC_OP);
    504    dep1_off = S390X_GUEST_OFFSET(guest_CC_DEP1);
    505    dep2_off = S390X_GUEST_OFFSET(guest_CC_DEP2);
    506    ndep_off = S390X_GUEST_OFFSET(guest_CC_NDEP);
    507 
    508    stmt(IRStmt_Put(op_off,   op));
    509    stmt(IRStmt_Put(dep1_off, dep1));
    510    stmt(IRStmt_Put(dep2_off, dep2));
    511    stmt(IRStmt_Put(ndep_off, ndep));
    512 }
    513 
    514 
    515 /* Create an expression for V and widen the result to 64 bit. */
    516 static IRExpr *
    517 s390_cc_widen(IRTemp v, Bool sign_extend)
    518 {
    519    IRExpr *expr;
    520 
    521    expr = mkexpr(v);
    522 
    523    switch (typeOfIRTemp(irsb->tyenv, v)) {
    524    case Ity_I64:
    525       break;
    526    case Ity_I32:
    527       expr = unop(sign_extend ? Iop_32Sto64 : Iop_32Uto64, expr);
    528       break;
    529    case Ity_I16:
    530       expr = unop(sign_extend ? Iop_16Sto64 : Iop_16Uto64, expr);
    531       break;
    532    case Ity_I8:
    533       expr = unop(sign_extend ? Iop_8Sto64 : Iop_8Uto64, expr);
    534       break;
    535    default:
    536       vpanic("s390_cc_widen");
    537    }
    538 
    539    return expr;
    540 }
    541 
    542 static void
    543 s390_cc_thunk_put1(UInt opc, IRTemp d1, Bool sign_extend)
    544 {
    545    IRExpr *op, *dep1, *dep2, *ndep;
    546 
    547    op   = mkU64(opc);
    548    dep1 = s390_cc_widen(d1, sign_extend);
    549    dep2 = mkU64(0);
    550    ndep = mkU64(0);
    551 
    552    s390_cc_thunk_fill(op, dep1, dep2, ndep);
    553 }
    554 
    555 
    556 static void
    557 s390_cc_thunk_put2(UInt opc, IRTemp d1, IRTemp d2, Bool sign_extend)
    558 {
    559    IRExpr *op, *dep1, *dep2, *ndep;
    560 
    561    op   = mkU64(opc);
    562    dep1 = s390_cc_widen(d1, sign_extend);
    563    dep2 = s390_cc_widen(d2, sign_extend);
    564    ndep = mkU64(0);
    565 
    566    s390_cc_thunk_fill(op, dep1, dep2, ndep);
    567 }
    568 
    569 
    570 /* memcheck believes that the NDEP field in the flags thunk is always
    571    defined. But for some flag computations (e.g. add with carry) that is
    572    just not true. We therefore need to convey to memcheck that the value
    573    of the ndep field does matter and therefore we make the DEP2 field
    574    depend on it:
    575 
    576    DEP2 = original_DEP2 ^ NDEP
    577 
    578    In s390_calculate_cc we exploit that  (a^b)^b == a
    579    I.e. we xor the DEP2 value with the NDEP value to recover the
    580    original_DEP2 value. */
    581 static void
    582 s390_cc_thunk_put3(UInt opc, IRTemp d1, IRTemp d2, IRTemp nd, Bool sign_extend)
    583 {
    584    IRExpr *op, *dep1, *dep2, *ndep, *dep2x;
    585 
    586    op   = mkU64(opc);
    587    dep1 = s390_cc_widen(d1, sign_extend);
    588    dep2 = s390_cc_widen(d2, sign_extend);
    589    ndep = s390_cc_widen(nd, sign_extend);
    590 
    591    dep2x = binop(Iop_Xor64, dep2, ndep);
    592 
    593    s390_cc_thunk_fill(op, dep1, dep2x, ndep);
    594 }
    595 
    596 
    597 /* Write one floating point value into the flags thunk */
    598 static void
    599 s390_cc_thunk_put1f(UInt opc, IRTemp d1)
    600 {
    601    IRExpr *op, *dep1, *dep2, *ndep;
    602 
    603    op   = mkU64(opc);
    604    dep1 = mkexpr(d1);
    605    dep2 = mkU64(0);
    606    ndep = mkU64(0);
    607 
    608    s390_cc_thunk_fill(op, dep1, dep2, ndep);
    609 }
    610 
    611 
    612 /* Write a floating point value and an integer into the flags thunk. The
    613    integer value is zero-extended first. */
    614 static void
    615 s390_cc_thunk_putFZ(UInt opc, IRTemp d1, IRTemp d2)
    616 {
    617    IRExpr *op, *dep1, *dep2, *ndep;
    618 
    619    op   = mkU64(opc);
    620    dep1 = mkexpr(d1);
    621    dep2 = s390_cc_widen(d2, False);
    622    ndep = mkU64(0);
    623 
    624    s390_cc_thunk_fill(op, dep1, dep2, ndep);
    625 }
    626 
    627 
    628 /* Write a 128-bit floating point value into the flags thunk. This is
    629    done by splitting the value into two 64-bits values. */
    630 static void
    631 s390_cc_thunk_put1f128(UInt opc, IRTemp d1)
    632 {
    633    IRExpr *op, *hi, *lo, *ndep;
    634 
    635    op   = mkU64(opc);
    636    hi   = unop(Iop_F128HItoF64, mkexpr(d1));
    637    lo   = unop(Iop_F128LOtoF64, mkexpr(d1));
    638    ndep = mkU64(0);
    639 
    640    s390_cc_thunk_fill(op, hi, lo, ndep);
    641 }
    642 
    643 
    644 /* Write a 128-bit floating point value and an integer into the flags thunk.
    645    The integer value is zero-extended first. */
    646 static void
    647 s390_cc_thunk_put1f128Z(UInt opc, IRTemp d1, IRTemp nd)
    648 {
    649    IRExpr *op, *hi, *lo, *lox, *ndep;
    650 
    651    op   = mkU64(opc);
    652    hi   = unop(Iop_F128HItoF64, mkexpr(d1));
    653    lo   = unop(Iop_ReinterpF64asI64, unop(Iop_F128LOtoF64, mkexpr(d1)));
    654    ndep = s390_cc_widen(nd, False);
    655 
    656    lox = binop(Iop_Xor64, lo, ndep);  /* convey dependency */
    657 
    658    s390_cc_thunk_fill(op, hi, lox, ndep);
    659 }
    660 
    661 
    662 static void
    663 s390_cc_set(UInt val)
    664 {
    665    s390_cc_thunk_fill(mkU64(S390_CC_OP_SET),
    666                       mkU64(val), mkU64(0), mkU64(0));
    667 }
    668 
    669 /* Build IR to calculate the condition code from flags thunk.
    670    Returns an expression of type Ity_I32 */
    671 static IRExpr *
    672 s390_call_calculate_cc(void)
    673 {
    674    IRExpr **args, *call, *op, *dep1, *dep2, *ndep;
    675 
    676    op   = IRExpr_Get(S390X_GUEST_OFFSET(guest_CC_OP),   Ity_I64);
    677    dep1 = IRExpr_Get(S390X_GUEST_OFFSET(guest_CC_DEP1), Ity_I64);
    678    dep2 = IRExpr_Get(S390X_GUEST_OFFSET(guest_CC_DEP2), Ity_I64);
    679    ndep = IRExpr_Get(S390X_GUEST_OFFSET(guest_CC_NDEP), Ity_I64);
    680 
    681    args = mkIRExprVec_4(op, dep1, dep2, ndep);
    682    call = mkIRExprCCall(Ity_I32, 0 /*regparm*/,
    683                         "s390_calculate_cc", &s390_calculate_cc, args);
    684 
    685    /* Exclude OP and NDEP from definedness checking.  We're only
    686       interested in DEP1 and DEP2. */
    687    call->Iex.CCall.cee->mcx_mask = (1<<0) | (1<<3);
    688 
    689    return call;
    690 }
    691 
    692 /* Build IR to calculate the internal condition code for a "compare and branch"
    693    insn. Returns an expression of type Ity_I32 */
    694 static IRExpr *
    695 s390_call_calculate_icc(UInt m, UInt opc, IRTemp op1, IRTemp op2)
    696 {
    697    IRExpr **args, *call, *op, *dep1, *dep2, *mask;
    698 
    699    switch (opc) {
    700    case S390_CC_OP_SIGNED_COMPARE:
    701       dep1 = s390_cc_widen(op1, True);
    702       dep2 = s390_cc_widen(op2, True);
    703       break;
    704 
    705    case S390_CC_OP_UNSIGNED_COMPARE:
    706       dep1 = s390_cc_widen(op1, False);
    707       dep2 = s390_cc_widen(op2, False);
    708       break;
    709 
    710    default:
    711       vpanic("s390_call_calculate_icc");
    712    }
    713 
    714    mask = mkU64(m);
    715    op   = mkU64(opc);
    716 
    717    args = mkIRExprVec_5(mask, op, dep1, dep2, mkU64(0) /* unused */);
    718    call = mkIRExprCCall(Ity_I32, 0 /*regparm*/,
    719                         "s390_calculate_cond", &s390_calculate_cond, args);
    720 
    721    /* Exclude the requested condition, OP and NDEP from definedness
    722       checking.  We're only interested in DEP1 and DEP2. */
    723    call->Iex.CCall.cee->mcx_mask = (1<<0) | (1<<1) | (1<<4);
    724 
    725    return call;
    726 }
    727 
    728 /* Build IR to calculate the condition code from flags thunk.
    729    Returns an expression of type Ity_I32 */
    730 static IRExpr *
    731 s390_call_calculate_cond(UInt m)
    732 {
    733    IRExpr **args, *call, *op, *dep1, *dep2, *ndep, *mask;
    734 
    735    mask = mkU64(m);
    736    op   = IRExpr_Get(S390X_GUEST_OFFSET(guest_CC_OP),   Ity_I64);
    737    dep1 = IRExpr_Get(S390X_GUEST_OFFSET(guest_CC_DEP1), Ity_I64);
    738    dep2 = IRExpr_Get(S390X_GUEST_OFFSET(guest_CC_DEP2), Ity_I64);
    739    ndep = IRExpr_Get(S390X_GUEST_OFFSET(guest_CC_NDEP), Ity_I64);
    740 
    741    args = mkIRExprVec_5(mask, op, dep1, dep2, ndep);
    742    call = mkIRExprCCall(Ity_I32, 0 /*regparm*/,
    743                         "s390_calculate_cond", &s390_calculate_cond, args);
    744 
    745    /* Exclude the requested condition, OP and NDEP from definedness
    746       checking.  We're only interested in DEP1 and DEP2. */
    747    call->Iex.CCall.cee->mcx_mask = (1<<0) | (1<<1) | (1<<4);
    748 
    749    return call;
    750 }
    751 
    752 #define s390_cc_thunk_putZ(op,dep1)  s390_cc_thunk_put1(op,dep1,False)
    753 #define s390_cc_thunk_putS(op,dep1)  s390_cc_thunk_put1(op,dep1,True)
    754 #define s390_cc_thunk_putF(op,dep1)  s390_cc_thunk_put1f(op,dep1)
    755 #define s390_cc_thunk_putZZ(op,dep1,dep2) s390_cc_thunk_put2(op,dep1,dep2,False)
    756 #define s390_cc_thunk_putSS(op,dep1,dep2) s390_cc_thunk_put2(op,dep1,dep2,True)
    757 #define s390_cc_thunk_putFF(op,dep1,dep2) s390_cc_thunk_put2f(op,dep1,dep2)
    758 #define s390_cc_thunk_putZZZ(op,dep1,dep2,ndep) \
    759         s390_cc_thunk_put3(op,dep1,dep2,ndep,False)
    760 #define s390_cc_thunk_putSSS(op,dep1,dep2,ndep) \
    761         s390_cc_thunk_put3(op,dep1,dep2,ndep,True)
    762 
    763 
    764 
    765 
    766 /*------------------------------------------------------------*/
    767 /*--- Guest register access                                ---*/
    768 /*------------------------------------------------------------*/
    769 
    770 
    771 /*------------------------------------------------------------*/
    772 /*--- ar registers                                         ---*/
    773 /*------------------------------------------------------------*/
    774 
    775 /* Return the guest state offset of a ar register. */
    776 static UInt
    777 ar_offset(UInt archreg)
    778 {
    779    static const UInt offset[16] = {
    780       S390X_GUEST_OFFSET(guest_a0),
    781       S390X_GUEST_OFFSET(guest_a1),
    782       S390X_GUEST_OFFSET(guest_a2),
    783       S390X_GUEST_OFFSET(guest_a3),
    784       S390X_GUEST_OFFSET(guest_a4),
    785       S390X_GUEST_OFFSET(guest_a5),
    786       S390X_GUEST_OFFSET(guest_a6),
    787       S390X_GUEST_OFFSET(guest_a7),
    788       S390X_GUEST_OFFSET(guest_a8),
    789       S390X_GUEST_OFFSET(guest_a9),
    790       S390X_GUEST_OFFSET(guest_a10),
    791       S390X_GUEST_OFFSET(guest_a11),
    792       S390X_GUEST_OFFSET(guest_a12),
    793       S390X_GUEST_OFFSET(guest_a13),
    794       S390X_GUEST_OFFSET(guest_a14),
    795       S390X_GUEST_OFFSET(guest_a15),
    796    };
    797 
    798    vassert(archreg < 16);
    799 
    800    return offset[archreg];
    801 }
    802 
    803 
    804 /* Return the guest state offset of word #0 of a ar register. */
    805 static __inline__ UInt
    806 ar_w0_offset(UInt archreg)
    807 {
    808    return ar_offset(archreg) + 0;
    809 }
    810 
    811 /* Write word #0 of a ar to the guest state. */
    812 static __inline__ void
    813 put_ar_w0(UInt archreg, IRExpr *expr)
    814 {
    815    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I32);
    816 
    817    stmt(IRStmt_Put(ar_w0_offset(archreg), expr));
    818 }
    819 
    820 /* Read word #0 of a ar register. */
    821 static __inline__ IRExpr *
    822 get_ar_w0(UInt archreg)
    823 {
    824    return IRExpr_Get(ar_w0_offset(archreg), Ity_I32);
    825 }
    826 
    827 
    828 /*------------------------------------------------------------*/
    829 /*--- fpr registers                                        ---*/
    830 /*------------------------------------------------------------*/
    831 
    832 /* Return the guest state offset of a fpr register. */
    833 static UInt
    834 fpr_offset(UInt archreg)
    835 {
    836    static const UInt offset[16] = {
    837       S390X_GUEST_OFFSET(guest_f0),
    838       S390X_GUEST_OFFSET(guest_f1),
    839       S390X_GUEST_OFFSET(guest_f2),
    840       S390X_GUEST_OFFSET(guest_f3),
    841       S390X_GUEST_OFFSET(guest_f4),
    842       S390X_GUEST_OFFSET(guest_f5),
    843       S390X_GUEST_OFFSET(guest_f6),
    844       S390X_GUEST_OFFSET(guest_f7),
    845       S390X_GUEST_OFFSET(guest_f8),
    846       S390X_GUEST_OFFSET(guest_f9),
    847       S390X_GUEST_OFFSET(guest_f10),
    848       S390X_GUEST_OFFSET(guest_f11),
    849       S390X_GUEST_OFFSET(guest_f12),
    850       S390X_GUEST_OFFSET(guest_f13),
    851       S390X_GUEST_OFFSET(guest_f14),
    852       S390X_GUEST_OFFSET(guest_f15),
    853    };
    854 
    855    vassert(archreg < 16);
    856 
    857    return offset[archreg];
    858 }
    859 
    860 
    861 /* Return the guest state offset of word #0 of a fpr register. */
    862 static __inline__ UInt
    863 fpr_w0_offset(UInt archreg)
    864 {
    865    return fpr_offset(archreg) + 0;
    866 }
    867 
    868 /* Write word #0 of a fpr to the guest state. */
    869 static __inline__ void
    870 put_fpr_w0(UInt archreg, IRExpr *expr)
    871 {
    872    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_F32);
    873 
    874    stmt(IRStmt_Put(fpr_w0_offset(archreg), expr));
    875 }
    876 
    877 /* Read word #0 of a fpr register. */
    878 static __inline__ IRExpr *
    879 get_fpr_w0(UInt archreg)
    880 {
    881    return IRExpr_Get(fpr_w0_offset(archreg), Ity_F32);
    882 }
    883 
    884 /* Return the guest state offset of double word #0 of a fpr register. */
    885 static __inline__ UInt
    886 fpr_dw0_offset(UInt archreg)
    887 {
    888    return fpr_offset(archreg) + 0;
    889 }
    890 
    891 /* Write double word #0 of a fpr to the guest state. */
    892 static __inline__ void
    893 put_fpr_dw0(UInt archreg, IRExpr *expr)
    894 {
    895    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_F64);
    896 
    897    stmt(IRStmt_Put(fpr_dw0_offset(archreg), expr));
    898 }
    899 
    900 /* Read double word #0 of a fpr register. */
    901 static __inline__ IRExpr *
    902 get_fpr_dw0(UInt archreg)
    903 {
    904    return IRExpr_Get(fpr_dw0_offset(archreg), Ity_F64);
    905 }
    906 
    907 
    908 /*------------------------------------------------------------*/
    909 /*--- gpr registers                                        ---*/
    910 /*------------------------------------------------------------*/
    911 
    912 /* Return the guest state offset of a gpr register. */
    913 static UInt
    914 gpr_offset(UInt archreg)
    915 {
    916    static const UInt offset[16] = {
    917       S390X_GUEST_OFFSET(guest_r0),
    918       S390X_GUEST_OFFSET(guest_r1),
    919       S390X_GUEST_OFFSET(guest_r2),
    920       S390X_GUEST_OFFSET(guest_r3),
    921       S390X_GUEST_OFFSET(guest_r4),
    922       S390X_GUEST_OFFSET(guest_r5),
    923       S390X_GUEST_OFFSET(guest_r6),
    924       S390X_GUEST_OFFSET(guest_r7),
    925       S390X_GUEST_OFFSET(guest_r8),
    926       S390X_GUEST_OFFSET(guest_r9),
    927       S390X_GUEST_OFFSET(guest_r10),
    928       S390X_GUEST_OFFSET(guest_r11),
    929       S390X_GUEST_OFFSET(guest_r12),
    930       S390X_GUEST_OFFSET(guest_r13),
    931       S390X_GUEST_OFFSET(guest_r14),
    932       S390X_GUEST_OFFSET(guest_r15),
    933    };
    934 
    935    vassert(archreg < 16);
    936 
    937    return offset[archreg];
    938 }
    939 
    940 
    941 /* Return the guest state offset of word #0 of a gpr register. */
    942 static __inline__ UInt
    943 gpr_w0_offset(UInt archreg)
    944 {
    945    return gpr_offset(archreg) + 0;
    946 }
    947 
    948 /* Write word #0 of a gpr to the guest state. */
    949 static __inline__ void
    950 put_gpr_w0(UInt archreg, IRExpr *expr)
    951 {
    952    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I32);
    953 
    954    stmt(IRStmt_Put(gpr_w0_offset(archreg), expr));
    955 }
    956 
    957 /* Read word #0 of a gpr register. */
    958 static __inline__ IRExpr *
    959 get_gpr_w0(UInt archreg)
    960 {
    961    return IRExpr_Get(gpr_w0_offset(archreg), Ity_I32);
    962 }
    963 
    964 /* Return the guest state offset of double word #0 of a gpr register. */
    965 static __inline__ UInt
    966 gpr_dw0_offset(UInt archreg)
    967 {
    968    return gpr_offset(archreg) + 0;
    969 }
    970 
    971 /* Write double word #0 of a gpr to the guest state. */
    972 static __inline__ void
    973 put_gpr_dw0(UInt archreg, IRExpr *expr)
    974 {
    975    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I64);
    976 
    977    stmt(IRStmt_Put(gpr_dw0_offset(archreg), expr));
    978 }
    979 
    980 /* Read double word #0 of a gpr register. */
    981 static __inline__ IRExpr *
    982 get_gpr_dw0(UInt archreg)
    983 {
    984    return IRExpr_Get(gpr_dw0_offset(archreg), Ity_I64);
    985 }
    986 
    987 /* Return the guest state offset of half word #1 of a gpr register. */
    988 static __inline__ UInt
    989 gpr_hw1_offset(UInt archreg)
    990 {
    991    return gpr_offset(archreg) + 2;
    992 }
    993 
    994 /* Write half word #1 of a gpr to the guest state. */
    995 static __inline__ void
    996 put_gpr_hw1(UInt archreg, IRExpr *expr)
    997 {
    998    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I16);
    999 
   1000    stmt(IRStmt_Put(gpr_hw1_offset(archreg), expr));
   1001 }
   1002 
   1003 /* Read half word #1 of a gpr register. */
   1004 static __inline__ IRExpr *
   1005 get_gpr_hw1(UInt archreg)
   1006 {
   1007    return IRExpr_Get(gpr_hw1_offset(archreg), Ity_I16);
   1008 }
   1009 
   1010 /* Return the guest state offset of byte #6 of a gpr register. */
   1011 static __inline__ UInt
   1012 gpr_b6_offset(UInt archreg)
   1013 {
   1014    return gpr_offset(archreg) + 6;
   1015 }
   1016 
   1017 /* Write byte #6 of a gpr to the guest state. */
   1018 static __inline__ void
   1019 put_gpr_b6(UInt archreg, IRExpr *expr)
   1020 {
   1021    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I8);
   1022 
   1023    stmt(IRStmt_Put(gpr_b6_offset(archreg), expr));
   1024 }
   1025 
   1026 /* Read byte #6 of a gpr register. */
   1027 static __inline__ IRExpr *
   1028 get_gpr_b6(UInt archreg)
   1029 {
   1030    return IRExpr_Get(gpr_b6_offset(archreg), Ity_I8);
   1031 }
   1032 
   1033 /* Return the guest state offset of byte #3 of a gpr register. */
   1034 static __inline__ UInt
   1035 gpr_b3_offset(UInt archreg)
   1036 {
   1037    return gpr_offset(archreg) + 3;
   1038 }
   1039 
   1040 /* Write byte #3 of a gpr to the guest state. */
   1041 static __inline__ void
   1042 put_gpr_b3(UInt archreg, IRExpr *expr)
   1043 {
   1044    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I8);
   1045 
   1046    stmt(IRStmt_Put(gpr_b3_offset(archreg), expr));
   1047 }
   1048 
   1049 /* Read byte #3 of a gpr register. */
   1050 static __inline__ IRExpr *
   1051 get_gpr_b3(UInt archreg)
   1052 {
   1053    return IRExpr_Get(gpr_b3_offset(archreg), Ity_I8);
   1054 }
   1055 
   1056 /* Return the guest state offset of byte #0 of a gpr register. */
   1057 static __inline__ UInt
   1058 gpr_b0_offset(UInt archreg)
   1059 {
   1060    return gpr_offset(archreg) + 0;
   1061 }
   1062 
   1063 /* Write byte #0 of a gpr to the guest state. */
   1064 static __inline__ void
   1065 put_gpr_b0(UInt archreg, IRExpr *expr)
   1066 {
   1067    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I8);
   1068 
   1069    stmt(IRStmt_Put(gpr_b0_offset(archreg), expr));
   1070 }
   1071 
   1072 /* Read byte #0 of a gpr register. */
   1073 static __inline__ IRExpr *
   1074 get_gpr_b0(UInt archreg)
   1075 {
   1076    return IRExpr_Get(gpr_b0_offset(archreg), Ity_I8);
   1077 }
   1078 
   1079 /* Return the guest state offset of word #1 of a gpr register. */
   1080 static __inline__ UInt
   1081 gpr_w1_offset(UInt archreg)
   1082 {
   1083    return gpr_offset(archreg) + 4;
   1084 }
   1085 
   1086 /* Write word #1 of a gpr to the guest state. */
   1087 static __inline__ void
   1088 put_gpr_w1(UInt archreg, IRExpr *expr)
   1089 {
   1090    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I32);
   1091 
   1092    stmt(IRStmt_Put(gpr_w1_offset(archreg), expr));
   1093 }
   1094 
   1095 /* Read word #1 of a gpr register. */
   1096 static __inline__ IRExpr *
   1097 get_gpr_w1(UInt archreg)
   1098 {
   1099    return IRExpr_Get(gpr_w1_offset(archreg), Ity_I32);
   1100 }
   1101 
   1102 /* Return the guest state offset of half word #3 of a gpr register. */
   1103 static __inline__ UInt
   1104 gpr_hw3_offset(UInt archreg)
   1105 {
   1106    return gpr_offset(archreg) + 6;
   1107 }
   1108 
   1109 /* Write half word #3 of a gpr to the guest state. */
   1110 static __inline__ void
   1111 put_gpr_hw3(UInt archreg, IRExpr *expr)
   1112 {
   1113    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I16);
   1114 
   1115    stmt(IRStmt_Put(gpr_hw3_offset(archreg), expr));
   1116 }
   1117 
   1118 /* Read half word #3 of a gpr register. */
   1119 static __inline__ IRExpr *
   1120 get_gpr_hw3(UInt archreg)
   1121 {
   1122    return IRExpr_Get(gpr_hw3_offset(archreg), Ity_I16);
   1123 }
   1124 
   1125 /* Return the guest state offset of byte #7 of a gpr register. */
   1126 static __inline__ UInt
   1127 gpr_b7_offset(UInt archreg)
   1128 {
   1129    return gpr_offset(archreg) + 7;
   1130 }
   1131 
   1132 /* Write byte #7 of a gpr to the guest state. */
   1133 static __inline__ void
   1134 put_gpr_b7(UInt archreg, IRExpr *expr)
   1135 {
   1136    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I8);
   1137 
   1138    stmt(IRStmt_Put(gpr_b7_offset(archreg), expr));
   1139 }
   1140 
   1141 /* Read byte #7 of a gpr register. */
   1142 static __inline__ IRExpr *
   1143 get_gpr_b7(UInt archreg)
   1144 {
   1145    return IRExpr_Get(gpr_b7_offset(archreg), Ity_I8);
   1146 }
   1147 
   1148 /* Return the guest state offset of half word #0 of a gpr register. */
   1149 static __inline__ UInt
   1150 gpr_hw0_offset(UInt archreg)
   1151 {
   1152    return gpr_offset(archreg) + 0;
   1153 }
   1154 
   1155 /* Write half word #0 of a gpr to the guest state. */
   1156 static __inline__ void
   1157 put_gpr_hw0(UInt archreg, IRExpr *expr)
   1158 {
   1159    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I16);
   1160 
   1161    stmt(IRStmt_Put(gpr_hw0_offset(archreg), expr));
   1162 }
   1163 
   1164 /* Read half word #0 of a gpr register. */
   1165 static __inline__ IRExpr *
   1166 get_gpr_hw0(UInt archreg)
   1167 {
   1168    return IRExpr_Get(gpr_hw0_offset(archreg), Ity_I16);
   1169 }
   1170 
   1171 /* Return the guest state offset of byte #4 of a gpr register. */
   1172 static __inline__ UInt
   1173 gpr_b4_offset(UInt archreg)
   1174 {
   1175    return gpr_offset(archreg) + 4;
   1176 }
   1177 
   1178 /* Write byte #4 of a gpr to the guest state. */
   1179 static __inline__ void
   1180 put_gpr_b4(UInt archreg, IRExpr *expr)
   1181 {
   1182    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I8);
   1183 
   1184    stmt(IRStmt_Put(gpr_b4_offset(archreg), expr));
   1185 }
   1186 
   1187 /* Read byte #4 of a gpr register. */
   1188 static __inline__ IRExpr *
   1189 get_gpr_b4(UInt archreg)
   1190 {
   1191    return IRExpr_Get(gpr_b4_offset(archreg), Ity_I8);
   1192 }
   1193 
   1194 /* Return the guest state offset of byte #1 of a gpr register. */
   1195 static __inline__ UInt
   1196 gpr_b1_offset(UInt archreg)
   1197 {
   1198    return gpr_offset(archreg) + 1;
   1199 }
   1200 
   1201 /* Write byte #1 of a gpr to the guest state. */
   1202 static __inline__ void
   1203 put_gpr_b1(UInt archreg, IRExpr *expr)
   1204 {
   1205    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I8);
   1206 
   1207    stmt(IRStmt_Put(gpr_b1_offset(archreg), expr));
   1208 }
   1209 
   1210 /* Read byte #1 of a gpr register. */
   1211 static __inline__ IRExpr *
   1212 get_gpr_b1(UInt archreg)
   1213 {
   1214    return IRExpr_Get(gpr_b1_offset(archreg), Ity_I8);
   1215 }
   1216 
   1217 /* Return the guest state offset of half word #2 of a gpr register. */
   1218 static __inline__ UInt
   1219 gpr_hw2_offset(UInt archreg)
   1220 {
   1221    return gpr_offset(archreg) + 4;
   1222 }
   1223 
   1224 /* Write half word #2 of a gpr to the guest state. */
   1225 static __inline__ void
   1226 put_gpr_hw2(UInt archreg, IRExpr *expr)
   1227 {
   1228    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I16);
   1229 
   1230    stmt(IRStmt_Put(gpr_hw2_offset(archreg), expr));
   1231 }
   1232 
   1233 /* Read half word #2 of a gpr register. */
   1234 static __inline__ IRExpr *
   1235 get_gpr_hw2(UInt archreg)
   1236 {
   1237    return IRExpr_Get(gpr_hw2_offset(archreg), Ity_I16);
   1238 }
   1239 
   1240 /* Return the guest state offset of byte #5 of a gpr register. */
   1241 static __inline__ UInt
   1242 gpr_b5_offset(UInt archreg)
   1243 {
   1244    return gpr_offset(archreg) + 5;
   1245 }
   1246 
   1247 /* Write byte #5 of a gpr to the guest state. */
   1248 static __inline__ void
   1249 put_gpr_b5(UInt archreg, IRExpr *expr)
   1250 {
   1251    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I8);
   1252 
   1253    stmt(IRStmt_Put(gpr_b5_offset(archreg), expr));
   1254 }
   1255 
   1256 /* Read byte #5 of a gpr register. */
   1257 static __inline__ IRExpr *
   1258 get_gpr_b5(UInt archreg)
   1259 {
   1260    return IRExpr_Get(gpr_b5_offset(archreg), Ity_I8);
   1261 }
   1262 
   1263 /* Return the guest state offset of byte #2 of a gpr register. */
   1264 static __inline__ UInt
   1265 gpr_b2_offset(UInt archreg)
   1266 {
   1267    return gpr_offset(archreg) + 2;
   1268 }
   1269 
   1270 /* Write byte #2 of a gpr to the guest state. */
   1271 static __inline__ void
   1272 put_gpr_b2(UInt archreg, IRExpr *expr)
   1273 {
   1274    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I8);
   1275 
   1276    stmt(IRStmt_Put(gpr_b2_offset(archreg), expr));
   1277 }
   1278 
   1279 /* Read byte #2 of a gpr register. */
   1280 static __inline__ IRExpr *
   1281 get_gpr_b2(UInt archreg)
   1282 {
   1283    return IRExpr_Get(gpr_b2_offset(archreg), Ity_I8);
   1284 }
   1285 
   1286 /* Return the guest state offset of the counter register. */
   1287 static UInt
   1288 counter_offset(void)
   1289 {
   1290    return S390X_GUEST_OFFSET(guest_counter);
   1291 }
   1292 
   1293 /* Return the guest state offset of double word #0 of the counter register. */
   1294 static __inline__ UInt
   1295 counter_dw0_offset(void)
   1296 {
   1297    return counter_offset() + 0;
   1298 }
   1299 
   1300 /* Write double word #0 of the counter to the guest state. */
   1301 static __inline__ void
   1302 put_counter_dw0(IRExpr *expr)
   1303 {
   1304    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I64);
   1305 
   1306    stmt(IRStmt_Put(counter_dw0_offset(), expr));
   1307 }
   1308 
   1309 /* Read double word #0 of the counter register. */
   1310 static __inline__ IRExpr *
   1311 get_counter_dw0(void)
   1312 {
   1313    return IRExpr_Get(counter_dw0_offset(), Ity_I64);
   1314 }
   1315 
   1316 /* Return the guest state offset of word #0 of the counter register. */
   1317 static __inline__ UInt
   1318 counter_w0_offset(void)
   1319 {
   1320    return counter_offset() + 0;
   1321 }
   1322 
   1323 /* Return the guest state offset of word #1 of the counter register. */
   1324 static __inline__ UInt
   1325 counter_w1_offset(void)
   1326 {
   1327    return counter_offset() + 4;
   1328 }
   1329 
   1330 /* Write word #0 of the counter to the guest state. */
   1331 static __inline__ void
   1332 put_counter_w0(IRExpr *expr)
   1333 {
   1334    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I32);
   1335 
   1336    stmt(IRStmt_Put(counter_w0_offset(), expr));
   1337 }
   1338 
   1339 /* Read word #0 of the counter register. */
   1340 static __inline__ IRExpr *
   1341 get_counter_w0(void)
   1342 {
   1343    return IRExpr_Get(counter_w0_offset(), Ity_I32);
   1344 }
   1345 
   1346 /* Write word #1 of the counter to the guest state. */
   1347 static __inline__ void
   1348 put_counter_w1(IRExpr *expr)
   1349 {
   1350    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I32);
   1351 
   1352    stmt(IRStmt_Put(counter_w1_offset(), expr));
   1353 }
   1354 
   1355 /* Read word #1 of the counter register. */
   1356 static __inline__ IRExpr *
   1357 get_counter_w1(void)
   1358 {
   1359    return IRExpr_Get(counter_w1_offset(), Ity_I32);
   1360 }
   1361 
   1362 /* Return the guest state offset of the fpc register. */
   1363 static UInt
   1364 fpc_offset(void)
   1365 {
   1366    return S390X_GUEST_OFFSET(guest_fpc);
   1367 }
   1368 
   1369 /* Return the guest state offset of word #0 of the fpc register. */
   1370 static __inline__ UInt
   1371 fpc_w0_offset(void)
   1372 {
   1373    return fpc_offset() + 0;
   1374 }
   1375 
   1376 /* Write word #0 of the fpc to the guest state. */
   1377 static __inline__ void
   1378 put_fpc_w0(IRExpr *expr)
   1379 {
   1380    vassert(typeOfIRExpr(irsb->tyenv, expr) == Ity_I32);
   1381 
   1382    stmt(IRStmt_Put(fpc_w0_offset(), expr));
   1383 }
   1384 
   1385 /* Read word #0 of the fpc register. */
   1386 static __inline__ IRExpr *
   1387 get_fpc_w0(void)
   1388 {
   1389    return IRExpr_Get(fpc_w0_offset(), Ity_I32);
   1390 }
   1391 
   1392 
   1393 /*------------------------------------------------------------*/
   1394 /*--- Build IR for formats                                 ---*/
   1395 /*------------------------------------------------------------*/
   1396 static void
   1397 s390_format_I(HChar *(*irgen)(UChar i),
   1398               UChar i)
   1399 {
   1400    HChar *mnm = irgen(i);
   1401 
   1402    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1403       s390_disasm(ENC2(MNM, UINT), mnm, i);
   1404 }
   1405 
   1406 static void
   1407 s390_format_RI(HChar *(*irgen)(UChar r1, UShort i2),
   1408                UChar r1, UShort i2)
   1409 {
   1410    irgen(r1, i2);
   1411 }
   1412 
   1413 static void
   1414 s390_format_RI_RU(HChar *(*irgen)(UChar r1, UShort i2),
   1415                   UChar r1, UShort i2)
   1416 {
   1417    HChar *mnm = irgen(r1, i2);
   1418 
   1419    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1420       s390_disasm(ENC3(MNM, GPR, UINT), mnm, r1, i2);
   1421 }
   1422 
   1423 static void
   1424 s390_format_RI_RI(HChar *(*irgen)(UChar r1, UShort i2),
   1425                   UChar r1, UShort i2)
   1426 {
   1427    HChar *mnm = irgen(r1, i2);
   1428 
   1429    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1430       s390_disasm(ENC3(MNM, GPR, INT), mnm, r1, (Int)(Short)i2);
   1431 }
   1432 
   1433 static void
   1434 s390_format_RI_RP(HChar *(*irgen)(UChar r1, UShort i2),
   1435                   UChar r1, UShort i2)
   1436 {
   1437    HChar *mnm = irgen(r1, i2);
   1438 
   1439    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1440       s390_disasm(ENC3(MNM, GPR, PCREL), mnm, r1, (Int)(Short)i2);
   1441 }
   1442 
   1443 static void
   1444 s390_format_RIE_RRP(HChar *(*irgen)(UChar r1, UChar r3, UShort i2),
   1445                     UChar r1, UChar r3, UShort i2)
   1446 {
   1447    HChar *mnm = irgen(r1, r3, i2);
   1448 
   1449    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1450       s390_disasm(ENC4(MNM, GPR, GPR, PCREL), mnm, r1, r3, (Int)(Short)i2);
   1451 }
   1452 
   1453 static void
   1454 s390_format_RIE_RRI0(HChar *(*irgen)(UChar r1, UChar r3, UShort i2),
   1455                      UChar r1, UChar r3, UShort i2)
   1456 {
   1457    HChar *mnm = irgen(r1, r3, i2);
   1458 
   1459    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1460       s390_disasm(ENC4(MNM, GPR, GPR, INT), mnm, r1, r3, (Int)(Short)i2);
   1461 }
   1462 
   1463 static void
   1464 s390_format_RIE_RRUUU(HChar *(*irgen)(UChar r1, UChar r2, UChar i3, UChar i4,
   1465                       UChar i5),
   1466                       UChar r1, UChar r2, UChar i3, UChar i4, UChar i5)
   1467 {
   1468    HChar *mnm = irgen(r1, r2, i3, i4, i5);
   1469 
   1470    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1471       s390_disasm(ENC6(MNM, GPR, GPR, UINT, UINT, UINT), mnm, r1, r2, i3, i4,
   1472                   i5);
   1473 }
   1474 
   1475 static void
   1476 s390_format_RIE_RRPU(HChar *(*irgen)(UChar r1, UChar r2, UShort i4, UChar m3),
   1477                      UChar r1, UChar r2, UShort i4, UChar m3)
   1478 {
   1479    HChar *mnm = irgen(r1, r2, i4, m3);
   1480 
   1481    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1482       s390_disasm(ENC5(XMNM, GPR, GPR, CABM, PCREL), S390_XMNM_CAB, mnm, m3, r1,
   1483                   r2, m3, (Int)(Short)i4);
   1484 }
   1485 
   1486 static void
   1487 s390_format_RIE_RUPU(HChar *(*irgen)(UChar r1, UChar m3, UShort i4, UChar i2),
   1488                      UChar r1, UChar m3, UShort i4, UChar i2)
   1489 {
   1490    HChar *mnm = irgen(r1, m3, i4, i2);
   1491 
   1492    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1493       s390_disasm(ENC5(XMNM, GPR, UINT, CABM, PCREL), S390_XMNM_CAB, mnm, m3,
   1494                   r1, i2, m3, (Int)(Short)i4);
   1495 }
   1496 
   1497 static void
   1498 s390_format_RIE_RUPI(HChar *(*irgen)(UChar r1, UChar m3, UShort i4, UChar i2),
   1499                      UChar r1, UChar m3, UShort i4, UChar i2)
   1500 {
   1501    HChar *mnm = irgen(r1, m3, i4, i2);
   1502 
   1503    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1504       s390_disasm(ENC5(XMNM, GPR, INT, CABM, PCREL), S390_XMNM_CAB, mnm, m3, r1,
   1505                   (Int)(Char)i2, m3, (Int)(Short)i4);
   1506 }
   1507 
   1508 static void
   1509 s390_format_RIL(HChar *(*irgen)(UChar r1, UInt i2),
   1510                 UChar r1, UInt i2)
   1511 {
   1512    irgen(r1, i2);
   1513 }
   1514 
   1515 static void
   1516 s390_format_RIL_RU(HChar *(*irgen)(UChar r1, UInt i2),
   1517                    UChar r1, UInt i2)
   1518 {
   1519    HChar *mnm = irgen(r1, i2);
   1520 
   1521    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1522       s390_disasm(ENC3(MNM, GPR, UINT), mnm, r1, i2);
   1523 }
   1524 
   1525 static void
   1526 s390_format_RIL_RI(HChar *(*irgen)(UChar r1, UInt i2),
   1527                    UChar r1, UInt i2)
   1528 {
   1529    HChar *mnm = irgen(r1, i2);
   1530 
   1531    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1532       s390_disasm(ENC3(MNM, GPR, INT), mnm, r1, i2);
   1533 }
   1534 
   1535 static void
   1536 s390_format_RIL_RP(HChar *(*irgen)(UChar r1, UInt i2),
   1537                    UChar r1, UInt i2)
   1538 {
   1539    HChar *mnm = irgen(r1, i2);
   1540 
   1541    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1542       s390_disasm(ENC3(MNM, GPR, PCREL), mnm, r1, i2);
   1543 }
   1544 
   1545 static void
   1546 s390_format_RIL_UP(HChar *(*irgen)(void),
   1547                    UChar r1, UInt i2)
   1548 {
   1549    HChar *mnm = irgen();
   1550 
   1551    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1552       s390_disasm(ENC3(MNM, UINT, PCREL), mnm, r1, i2);
   1553 }
   1554 
   1555 static void
   1556 s390_format_RIS_RURDI(HChar *(*irgen)(UChar r1, UChar m3, UChar i2,
   1557                       IRTemp op4addr),
   1558                       UChar r1, UChar m3, UChar b4, UShort d4, UChar i2)
   1559 {
   1560    HChar *mnm;
   1561    IRTemp op4addr = newTemp(Ity_I64);
   1562 
   1563    assign(op4addr, binop(Iop_Add64, mkU64(d4), b4 != 0 ? get_gpr_dw0(b4) :
   1564           mkU64(0)));
   1565 
   1566    mnm = irgen(r1, m3, i2, op4addr);
   1567 
   1568    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1569       s390_disasm(ENC5(XMNM, GPR, INT, CABM, UDXB), S390_XMNM_CAB, mnm, m3, r1,
   1570                   (Int)(Char)i2, m3, d4, 0, b4);
   1571 }
   1572 
   1573 static void
   1574 s390_format_RIS_RURDU(HChar *(*irgen)(UChar r1, UChar m3, UChar i2,
   1575                       IRTemp op4addr),
   1576                       UChar r1, UChar m3, UChar b4, UShort d4, UChar i2)
   1577 {
   1578    HChar *mnm;
   1579    IRTemp op4addr = newTemp(Ity_I64);
   1580 
   1581    assign(op4addr, binop(Iop_Add64, mkU64(d4), b4 != 0 ? get_gpr_dw0(b4) :
   1582           mkU64(0)));
   1583 
   1584    mnm = irgen(r1, m3, i2, op4addr);
   1585 
   1586    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1587       s390_disasm(ENC5(XMNM, GPR, UINT, CABM, UDXB), S390_XMNM_CAB, mnm, m3, r1,
   1588                   i2, m3, d4, 0, b4);
   1589 }
   1590 
   1591 static void
   1592 s390_format_RR(HChar *(*irgen)(UChar r1, UChar r2),
   1593                UChar r1, UChar r2)
   1594 {
   1595    irgen(r1, r2);
   1596 }
   1597 
   1598 static void
   1599 s390_format_RR_RR(HChar *(*irgen)(UChar r1, UChar r2),
   1600                   UChar r1, UChar r2)
   1601 {
   1602    HChar *mnm = irgen(r1, r2);
   1603 
   1604    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1605       s390_disasm(ENC3(MNM, GPR, GPR), mnm, r1, r2);
   1606 }
   1607 
   1608 static void
   1609 s390_format_RR_FF(HChar *(*irgen)(UChar r1, UChar r2),
   1610                   UChar r1, UChar r2)
   1611 {
   1612    HChar *mnm = irgen(r1, r2);
   1613 
   1614    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1615       s390_disasm(ENC3(MNM, FPR, FPR), mnm, r1, r2);
   1616 }
   1617 
   1618 static void
   1619 s390_format_RRE(HChar *(*irgen)(UChar r1, UChar r2),
   1620                 UChar r1, UChar r2)
   1621 {
   1622    irgen(r1, r2);
   1623 }
   1624 
   1625 static void
   1626 s390_format_RRE_RR(HChar *(*irgen)(UChar r1, UChar r2),
   1627                    UChar r1, UChar r2)
   1628 {
   1629    HChar *mnm = irgen(r1, r2);
   1630 
   1631    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1632       s390_disasm(ENC3(MNM, GPR, GPR), mnm, r1, r2);
   1633 }
   1634 
   1635 static void
   1636 s390_format_RRE_FF(HChar *(*irgen)(UChar r1, UChar r2),
   1637                    UChar r1, UChar r2)
   1638 {
   1639    HChar *mnm = irgen(r1, r2);
   1640 
   1641    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1642       s390_disasm(ENC3(MNM, FPR, FPR), mnm, r1, r2);
   1643 }
   1644 
   1645 static void
   1646 s390_format_RRE_RF(HChar *(*irgen)(UChar, UChar),
   1647                    UChar r1, UChar r2)
   1648 {
   1649    HChar *mnm = irgen(r1, r2);
   1650 
   1651    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1652       s390_disasm(ENC3(MNM, GPR, FPR), mnm, r1, r2);
   1653 }
   1654 
   1655 static void
   1656 s390_format_RRE_FR(HChar *(*irgen)(UChar r1, UChar r2),
   1657                    UChar r1, UChar r2)
   1658 {
   1659    HChar *mnm = irgen(r1, r2);
   1660 
   1661    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1662       s390_disasm(ENC3(MNM, FPR, GPR), mnm, r1, r2);
   1663 }
   1664 
   1665 static void
   1666 s390_format_RRE_R0(HChar *(*irgen)(UChar r1),
   1667                    UChar r1)
   1668 {
   1669    HChar *mnm = irgen(r1);
   1670 
   1671    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1672       s390_disasm(ENC2(MNM, GPR), mnm, r1);
   1673 }
   1674 
   1675 static void
   1676 s390_format_RRE_F0(HChar *(*irgen)(UChar r1),
   1677                    UChar r1)
   1678 {
   1679    HChar *mnm = irgen(r1);
   1680 
   1681    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1682       s390_disasm(ENC2(MNM, FPR), mnm, r1);
   1683 }
   1684 
   1685 static void
   1686 s390_format_RRF_M0RERE(HChar *(*irgen)(UChar m3, UChar r1, UChar r2),
   1687                        UChar m3, UChar r1, UChar r2)
   1688 {
   1689    HChar *mnm = irgen(m3, r1, r2);
   1690 
   1691    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1692       s390_disasm(ENC4(MNM, GPR, GPR, UINT), mnm, r1, r2, m3);
   1693 }
   1694 
   1695 static void
   1696 s390_format_RRF_F0FF(HChar *(*irgen)(UChar, UChar, UChar),
   1697                      UChar r1, UChar r3, UChar r2)
   1698 {
   1699    HChar *mnm = irgen(r1, r3, r2);
   1700 
   1701    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1702       s390_disasm(ENC4(MNM, FPR, FPR, FPR), mnm, r1, r3, r2);
   1703 }
   1704 
   1705 static void
   1706 s390_format_RRF_U0RR(HChar *(*irgen)(UChar m3, UChar r1, UChar r2),
   1707                      UChar m3, UChar r1, UChar r2, Int xmnm_kind)
   1708 {
   1709    irgen(m3, r1, r2);
   1710 
   1711    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1712       s390_disasm(ENC3(XMNM, GPR, GPR), xmnm_kind, m3, r1, r2);
   1713 }
   1714 
   1715 static void
   1716 s390_format_RRF_U0RF(HChar *(*irgen)(UChar r3, UChar r1, UChar r2),
   1717                      UChar r3, UChar r1, UChar r2)
   1718 {
   1719    HChar *mnm = irgen(r3, r1, r2);
   1720 
   1721    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1722       s390_disasm(ENC4(MNM, GPR, UINT, FPR), mnm, r1, r3, r2);
   1723 }
   1724 
   1725 static void
   1726 s390_format_RRF_F0FF2(HChar *(*irgen)(UChar, UChar, UChar),
   1727                       UChar r3, UChar r1, UChar r2)
   1728 {
   1729    HChar *mnm = irgen(r3, r1, r2);
   1730 
   1731    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1732       s390_disasm(ENC4(MNM, FPR, FPR, FPR), mnm, r1, r3, r2);
   1733 }
   1734 
   1735 static void
   1736 s390_format_RRF_R0RR2(HChar *(*irgen)(UChar r3, UChar r1, UChar r2),
   1737                       UChar r3, UChar r1, UChar r2)
   1738 {
   1739    HChar *mnm = irgen(r3, r1, r2);
   1740 
   1741    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1742       s390_disasm(ENC4(MNM, GPR, GPR, GPR), mnm, r1, r2, r3);
   1743 }
   1744 
   1745 static void
   1746 s390_format_RRS(HChar *(*irgen)(UChar r1, UChar r2, UChar m3, IRTemp op4addr),
   1747                 UChar r1, UChar r2, UChar b4, UShort d4, UChar m3)
   1748 {
   1749    HChar *mnm;
   1750    IRTemp op4addr = newTemp(Ity_I64);
   1751 
   1752    assign(op4addr, binop(Iop_Add64, mkU64(d4), b4 != 0 ? get_gpr_dw0(b4) :
   1753           mkU64(0)));
   1754 
   1755    mnm = irgen(r1, r2, m3, op4addr);
   1756 
   1757    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1758       s390_disasm(ENC5(XMNM, GPR, GPR, CABM, UDXB), S390_XMNM_CAB, mnm, m3, r1,
   1759                   r2, m3, d4, 0, b4);
   1760 }
   1761 
   1762 static void
   1763 s390_format_RS_R0RD(HChar *(*irgen)(UChar r1, IRTemp op2addr),
   1764                     UChar r1, UChar b2, UShort d2)
   1765 {
   1766    HChar *mnm;
   1767    IRTemp op2addr = newTemp(Ity_I64);
   1768 
   1769    assign(op2addr, binop(Iop_Add64, mkU64(d2), b2 != 0 ? get_gpr_dw0(b2) :
   1770           mkU64(0)));
   1771 
   1772    mnm = irgen(r1, op2addr);
   1773 
   1774    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1775       s390_disasm(ENC3(MNM, GPR, UDXB), mnm, r1, d2, 0, b2);
   1776 }
   1777 
   1778 static void
   1779 s390_format_RS_RRRD(HChar *(*irgen)(UChar r1, UChar r3, IRTemp op2addr),
   1780                     UChar r1, UChar r3, UChar b2, UShort d2)
   1781 {
   1782    HChar *mnm;
   1783    IRTemp op2addr = newTemp(Ity_I64);
   1784 
   1785    assign(op2addr, binop(Iop_Add64, mkU64(d2), b2 != 0 ? get_gpr_dw0(b2) :
   1786           mkU64(0)));
   1787 
   1788    mnm = irgen(r1, r3, op2addr);
   1789 
   1790    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1791       s390_disasm(ENC4(MNM, GPR, GPR, UDXB), mnm, r1, r3, d2, 0, b2);
   1792 }
   1793 
   1794 static void
   1795 s390_format_RS_RURD(HChar *(*irgen)(UChar r1, UChar r3, IRTemp op2addr),
   1796                     UChar r1, UChar r3, UChar b2, UShort d2)
   1797 {
   1798    HChar *mnm;
   1799    IRTemp op2addr = newTemp(Ity_I64);
   1800 
   1801    assign(op2addr, binop(Iop_Add64, mkU64(d2), b2 != 0 ? get_gpr_dw0(b2) :
   1802           mkU64(0)));
   1803 
   1804    mnm = irgen(r1, r3, op2addr);
   1805 
   1806    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1807       s390_disasm(ENC4(MNM, GPR, UINT, UDXB), mnm, r1, r3, d2, 0, b2);
   1808 }
   1809 
   1810 static void
   1811 s390_format_RS_AARD(HChar *(*irgen)(UChar, UChar, IRTemp),
   1812                     UChar r1, UChar r3, UChar b2, UShort d2)
   1813 {
   1814    HChar *mnm;
   1815    IRTemp op2addr = newTemp(Ity_I64);
   1816 
   1817    assign(op2addr, binop(Iop_Add64, mkU64(d2), b2 != 0 ? get_gpr_dw0(b2) :
   1818           mkU64(0)));
   1819 
   1820    mnm = irgen(r1, r3, op2addr);
   1821 
   1822    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1823       s390_disasm(ENC4(MNM, AR, AR, UDXB), mnm, r1, r3, d2, 0, b2);
   1824 }
   1825 
   1826 static void
   1827 s390_format_RSI_RRP(HChar *(*irgen)(UChar r1, UChar r3, UShort i2),
   1828                     UChar r1, UChar r3, UShort i2)
   1829 {
   1830    HChar *mnm = irgen(r1, r3, i2);
   1831 
   1832    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1833       s390_disasm(ENC4(MNM, GPR, GPR, PCREL), mnm, r1, r3, (Int)(Short)i2);
   1834 }
   1835 
   1836 static void
   1837 s390_format_RSY_RRRD(HChar *(*irgen)(UChar r1, UChar r3, IRTemp op2addr),
   1838                      UChar r1, UChar r3, UChar b2, UShort dl2, UChar dh2)
   1839 {
   1840    HChar *mnm;
   1841    IRTemp op2addr = newTemp(Ity_I64);
   1842    IRTemp d2 = newTemp(Ity_I64);
   1843 
   1844    assign(d2, mkU64(((ULong)(Long)(Char)dh2 << 12) | ((ULong)dl2)));
   1845    assign(op2addr, binop(Iop_Add64, mkexpr(d2), b2 != 0 ? get_gpr_dw0(b2) :
   1846           mkU64(0)));
   1847 
   1848    mnm = irgen(r1, r3, op2addr);
   1849 
   1850    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1851       s390_disasm(ENC4(MNM, GPR, GPR, SDXB), mnm, r1, r3, dh2, dl2, 0, b2);
   1852 }
   1853 
   1854 static void
   1855 s390_format_RSY_AARD(HChar *(*irgen)(UChar, UChar, IRTemp),
   1856                      UChar r1, UChar r3, UChar b2, UShort dl2, UChar dh2)
   1857 {
   1858    HChar *mnm;
   1859    IRTemp op2addr = newTemp(Ity_I64);
   1860    IRTemp d2 = newTemp(Ity_I64);
   1861 
   1862    assign(d2, mkU64(((ULong)(Long)(Char)dh2 << 12) | ((ULong)dl2)));
   1863    assign(op2addr, binop(Iop_Add64, mkexpr(d2), b2 != 0 ? get_gpr_dw0(b2) :
   1864           mkU64(0)));
   1865 
   1866    mnm = irgen(r1, r3, op2addr);
   1867 
   1868    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1869       s390_disasm(ENC4(MNM, AR, AR, SDXB), mnm, r1, r3, dh2, dl2, 0, b2);
   1870 }
   1871 
   1872 static void
   1873 s390_format_RSY_RURD(HChar *(*irgen)(UChar r1, UChar r3, IRTemp op2addr),
   1874                      UChar r1, UChar r3, UChar b2, UShort dl2, UChar dh2)
   1875 {
   1876    HChar *mnm;
   1877    IRTemp op2addr = newTemp(Ity_I64);
   1878    IRTemp d2 = newTemp(Ity_I64);
   1879 
   1880    assign(d2, mkU64(((ULong)(Long)(Char)dh2 << 12) | ((ULong)dl2)));
   1881    assign(op2addr, binop(Iop_Add64, mkexpr(d2), b2 != 0 ? get_gpr_dw0(b2) :
   1882           mkU64(0)));
   1883 
   1884    mnm = irgen(r1, r3, op2addr);
   1885 
   1886    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1887       s390_disasm(ENC4(MNM, GPR, UINT, SDXB), mnm, r1, r3, dh2, dl2, 0, b2);
   1888 }
   1889 
   1890 static void
   1891 s390_format_RSY_RDRM(HChar *(*irgen)(UChar r1, IRTemp op2addr),
   1892                      UChar r1, UChar m3, UChar b2, UShort dl2, UChar dh2,
   1893                      Int xmnm_kind)
   1894 {
   1895    IRTemp op2addr = newTemp(Ity_I64);
   1896    IRTemp d2 = newTemp(Ity_I64);
   1897 
   1898    next_insn_if(binop(Iop_CmpEQ32, s390_call_calculate_cond(m3), mkU32(0)));
   1899 
   1900    assign(d2, mkU64(((ULong)(Long)(Char)dh2 << 12) | ((ULong)dl2)));
   1901    assign(op2addr, binop(Iop_Add64, mkexpr(d2), b2 != 0 ? get_gpr_dw0(b2) :
   1902           mkU64(0)));
   1903 
   1904    irgen(r1, op2addr);
   1905 
   1906    vassert(dis_res->whatNext == Dis_Continue);
   1907 
   1908    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1909       s390_disasm(ENC3(XMNM, GPR, SDXB), xmnm_kind, m3, r1, dh2, dl2, 0, b2);
   1910 }
   1911 
   1912 static void
   1913 s390_format_RX(HChar *(*irgen)(UChar r1, UChar x2, UChar b2, UShort d2,
   1914                IRTemp op2addr),
   1915                UChar r1, UChar x2, UChar b2, UShort d2)
   1916 {
   1917    IRTemp op2addr = newTemp(Ity_I64);
   1918 
   1919    assign(op2addr, binop(Iop_Add64, binop(Iop_Add64, mkU64(d2),
   1920           b2 != 0 ? get_gpr_dw0(b2) : mkU64(0)), x2 != 0 ? get_gpr_dw0(x2) :
   1921           mkU64(0)));
   1922 
   1923    irgen(r1, x2, b2, d2, op2addr);
   1924 }
   1925 
   1926 static void
   1927 s390_format_RX_RRRD(HChar *(*irgen)(UChar r1, IRTemp op2addr),
   1928                     UChar r1, UChar x2, UChar b2, UShort d2)
   1929 {
   1930    HChar *mnm;
   1931    IRTemp op2addr = newTemp(Ity_I64);
   1932 
   1933    assign(op2addr, binop(Iop_Add64, binop(Iop_Add64, mkU64(d2),
   1934           b2 != 0 ? get_gpr_dw0(b2) : mkU64(0)), x2 != 0 ? get_gpr_dw0(x2) :
   1935           mkU64(0)));
   1936 
   1937    mnm = irgen(r1, op2addr);
   1938 
   1939    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1940       s390_disasm(ENC3(MNM, GPR, UDXB), mnm, r1, d2, x2, b2);
   1941 }
   1942 
   1943 static void
   1944 s390_format_RX_FRRD(HChar *(*irgen)(UChar r1, IRTemp op2addr),
   1945                     UChar r1, UChar x2, UChar b2, UShort d2)
   1946 {
   1947    HChar *mnm;
   1948    IRTemp op2addr = newTemp(Ity_I64);
   1949 
   1950    assign(op2addr, binop(Iop_Add64, binop(Iop_Add64, mkU64(d2),
   1951           b2 != 0 ? get_gpr_dw0(b2) : mkU64(0)), x2 != 0 ? get_gpr_dw0(x2) :
   1952           mkU64(0)));
   1953 
   1954    mnm = irgen(r1, op2addr);
   1955 
   1956    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1957       s390_disasm(ENC3(MNM, FPR, UDXB), mnm, r1, d2, x2, b2);
   1958 }
   1959 
   1960 static void
   1961 s390_format_RXE_FRRD(HChar *(*irgen)(UChar r1, IRTemp op2addr),
   1962                      UChar r1, UChar x2, UChar b2, UShort d2)
   1963 {
   1964    HChar *mnm;
   1965    IRTemp op2addr = newTemp(Ity_I64);
   1966 
   1967    assign(op2addr, binop(Iop_Add64, binop(Iop_Add64, mkU64(d2),
   1968           b2 != 0 ? get_gpr_dw0(b2) : mkU64(0)), x2 != 0 ? get_gpr_dw0(x2) :
   1969           mkU64(0)));
   1970 
   1971    mnm = irgen(r1, op2addr);
   1972 
   1973    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1974       s390_disasm(ENC3(MNM, FPR, UDXB), mnm, r1, d2, x2, b2);
   1975 }
   1976 
   1977 static void
   1978 s390_format_RXF_FRRDF(HChar *(*irgen)(UChar, IRTemp, UChar),
   1979                       UChar r3, UChar x2, UChar b2, UShort d2, UChar r1)
   1980 {
   1981    HChar *mnm;
   1982    IRTemp op2addr = newTemp(Ity_I64);
   1983 
   1984    assign(op2addr, binop(Iop_Add64, binop(Iop_Add64, mkU64(d2),
   1985           b2 != 0 ? get_gpr_dw0(b2) : mkU64(0)), x2 != 0 ? get_gpr_dw0(x2) :
   1986           mkU64(0)));
   1987 
   1988    mnm = irgen(r3, op2addr, r1);
   1989 
   1990    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   1991       s390_disasm(ENC4(MNM, FPR, FPR, UDXB), mnm, r1, r3, d2, x2, b2);
   1992 }
   1993 
   1994 static void
   1995 s390_format_RXY_RRRD(HChar *(*irgen)(UChar r1, IRTemp op2addr),
   1996                      UChar r1, UChar x2, UChar b2, UShort dl2, UChar dh2)
   1997 {
   1998    HChar *mnm;
   1999    IRTemp op2addr = newTemp(Ity_I64);
   2000    IRTemp d2 = newTemp(Ity_I64);
   2001 
   2002    assign(d2, mkU64(((ULong)(Long)(Char)dh2 << 12) | ((ULong)dl2)));
   2003    assign(op2addr, binop(Iop_Add64, binop(Iop_Add64, mkexpr(d2),
   2004           b2 != 0 ? get_gpr_dw0(b2) : mkU64(0)), x2 != 0 ? get_gpr_dw0(x2) :
   2005           mkU64(0)));
   2006 
   2007    mnm = irgen(r1, op2addr);
   2008 
   2009    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2010       s390_disasm(ENC3(MNM, GPR, SDXB), mnm, r1, dh2, dl2, x2, b2);
   2011 }
   2012 
   2013 static void
   2014 s390_format_RXY_FRRD(HChar *(*irgen)(UChar r1, IRTemp op2addr),
   2015                      UChar r1, UChar x2, UChar b2, UShort dl2, UChar dh2)
   2016 {
   2017    HChar *mnm;
   2018    IRTemp op2addr = newTemp(Ity_I64);
   2019    IRTemp d2 = newTemp(Ity_I64);
   2020 
   2021    assign(d2, mkU64(((ULong)(Long)(Char)dh2 << 12) | ((ULong)dl2)));
   2022    assign(op2addr, binop(Iop_Add64, binop(Iop_Add64, mkexpr(d2),
   2023           b2 != 0 ? get_gpr_dw0(b2) : mkU64(0)), x2 != 0 ? get_gpr_dw0(x2) :
   2024           mkU64(0)));
   2025 
   2026    mnm = irgen(r1, op2addr);
   2027 
   2028    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2029       s390_disasm(ENC3(MNM, FPR, SDXB), mnm, r1, dh2, dl2, x2, b2);
   2030 }
   2031 
   2032 static void
   2033 s390_format_RXY_URRD(HChar *(*irgen)(void),
   2034                      UChar r1, UChar x2, UChar b2, UShort dl2, UChar dh2)
   2035 {
   2036    HChar *mnm;
   2037    IRTemp op2addr = newTemp(Ity_I64);
   2038    IRTemp d2 = newTemp(Ity_I64);
   2039 
   2040    assign(d2, mkU64(((ULong)(Long)(Char)dh2 << 12) | ((ULong)dl2)));
   2041    assign(op2addr, binop(Iop_Add64, binop(Iop_Add64, mkexpr(d2),
   2042           b2 != 0 ? get_gpr_dw0(b2) : mkU64(0)), x2 != 0 ? get_gpr_dw0(x2) :
   2043           mkU64(0)));
   2044 
   2045    mnm = irgen();
   2046 
   2047    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2048       s390_disasm(ENC3(MNM, UINT, SDXB), mnm, r1, dh2, dl2, x2, b2);
   2049 }
   2050 
   2051 static void
   2052 s390_format_S_RD(HChar *(*irgen)(IRTemp op2addr),
   2053                  UChar b2, UShort d2)
   2054 {
   2055    HChar *mnm;
   2056    IRTemp op2addr = newTemp(Ity_I64);
   2057 
   2058    assign(op2addr, binop(Iop_Add64, mkU64(d2), b2 != 0 ? get_gpr_dw0(b2) :
   2059           mkU64(0)));
   2060 
   2061    mnm = irgen(op2addr);
   2062 
   2063    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2064       s390_disasm(ENC2(MNM, UDXB), mnm, d2, 0, b2);
   2065 }
   2066 
   2067 static void
   2068 s390_format_SI_URD(HChar *(*irgen)(UChar i2, IRTemp op1addr),
   2069                    UChar i2, UChar b1, UShort d1)
   2070 {
   2071    HChar *mnm;
   2072    IRTemp op1addr = newTemp(Ity_I64);
   2073 
   2074    assign(op1addr, binop(Iop_Add64, mkU64(d1), b1 != 0 ? get_gpr_dw0(b1) :
   2075           mkU64(0)));
   2076 
   2077    mnm = irgen(i2, op1addr);
   2078 
   2079    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2080       s390_disasm(ENC3(MNM, UDXB, UINT), mnm, d1, 0, b1, i2);
   2081 }
   2082 
   2083 static void
   2084 s390_format_SIY_URD(HChar *(*irgen)(UChar i2, IRTemp op1addr),
   2085                     UChar i2, UChar b1, UShort dl1, UChar dh1)
   2086 {
   2087    HChar *mnm;
   2088    IRTemp op1addr = newTemp(Ity_I64);
   2089    IRTemp d1 = newTemp(Ity_I64);
   2090 
   2091    assign(d1, mkU64(((ULong)(Long)(Char)dh1 << 12) | ((ULong)dl1)));
   2092    assign(op1addr, binop(Iop_Add64, mkexpr(d1), b1 != 0 ? get_gpr_dw0(b1) :
   2093           mkU64(0)));
   2094 
   2095    mnm = irgen(i2, op1addr);
   2096 
   2097    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2098       s390_disasm(ENC3(MNM, SDXB, UINT), mnm, dh1, dl1, 0, b1, i2);
   2099 }
   2100 
   2101 static void
   2102 s390_format_SIY_IRD(HChar *(*irgen)(UChar i2, IRTemp op1addr),
   2103                     UChar i2, UChar b1, UShort dl1, UChar dh1)
   2104 {
   2105    HChar *mnm;
   2106    IRTemp op1addr = newTemp(Ity_I64);
   2107    IRTemp d1 = newTemp(Ity_I64);
   2108 
   2109    assign(d1, mkU64(((ULong)(Long)(Char)dh1 << 12) | ((ULong)dl1)));
   2110    assign(op1addr, binop(Iop_Add64, mkexpr(d1), b1 != 0 ? get_gpr_dw0(b1) :
   2111           mkU64(0)));
   2112 
   2113    mnm = irgen(i2, op1addr);
   2114 
   2115    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2116       s390_disasm(ENC3(MNM, SDXB, INT), mnm, dh1, dl1, 0, b1, (Int)(Char)i2);
   2117 }
   2118 
   2119 static void
   2120 s390_format_SS_L0RDRD(HChar *(*irgen)(UChar, IRTemp, IRTemp),
   2121                       UChar l, UChar b1, UShort d1, UChar b2, UShort d2)
   2122 {
   2123    HChar *mnm;
   2124    IRTemp op1addr = newTemp(Ity_I64);
   2125    IRTemp op2addr = newTemp(Ity_I64);
   2126 
   2127    assign(op1addr, binop(Iop_Add64, mkU64(d1), b1 != 0 ? get_gpr_dw0(b1) :
   2128           mkU64(0)));
   2129    assign(op2addr, binop(Iop_Add64, mkU64(d2), b2 != 0 ? get_gpr_dw0(b2) :
   2130           mkU64(0)));
   2131 
   2132    mnm = irgen(l, op1addr, op2addr);
   2133 
   2134    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2135       s390_disasm(ENC3(MNM, UDLB, UDXB), mnm, d1, l, b1, d2, 0, b2);
   2136 }
   2137 
   2138 static void
   2139 s390_format_SIL_RDI(HChar *(*irgen)(UShort i2, IRTemp op1addr),
   2140                     UChar b1, UShort d1, UShort i2)
   2141 {
   2142    HChar *mnm;
   2143    IRTemp op1addr = newTemp(Ity_I64);
   2144 
   2145    assign(op1addr, binop(Iop_Add64, mkU64(d1), b1 != 0 ? get_gpr_dw0(b1) :
   2146           mkU64(0)));
   2147 
   2148    mnm = irgen(i2, op1addr);
   2149 
   2150    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2151       s390_disasm(ENC3(MNM, UDXB, INT), mnm, d1, 0, b1, (Int)(Short)i2);
   2152 }
   2153 
   2154 static void
   2155 s390_format_SIL_RDU(HChar *(*irgen)(UShort i2, IRTemp op1addr),
   2156                     UChar b1, UShort d1, UShort i2)
   2157 {
   2158    HChar *mnm;
   2159    IRTemp op1addr = newTemp(Ity_I64);
   2160 
   2161    assign(op1addr, binop(Iop_Add64, mkU64(d1), b1 != 0 ? get_gpr_dw0(b1) :
   2162           mkU64(0)));
   2163 
   2164    mnm = irgen(i2, op1addr);
   2165 
   2166    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   2167       s390_disasm(ENC3(MNM, UDXB, UINT), mnm, d1, 0, b1, i2);
   2168 }
   2169 
   2170 
   2171 
   2172 /*------------------------------------------------------------*/
   2173 /*--- Build IR for opcodes                                 ---*/
   2174 /*------------------------------------------------------------*/
   2175 
   2176 static HChar *
   2177 s390_irgen_AR(UChar r1, UChar r2)
   2178 {
   2179    IRTemp op1 = newTemp(Ity_I32);
   2180    IRTemp op2 = newTemp(Ity_I32);
   2181    IRTemp result = newTemp(Ity_I32);
   2182 
   2183    assign(op1, get_gpr_w1(r1));
   2184    assign(op2, get_gpr_w1(r2));
   2185    assign(result, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)));
   2186    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, op2);
   2187    put_gpr_w1(r1, mkexpr(result));
   2188 
   2189    return "ar";
   2190 }
   2191 
   2192 static HChar *
   2193 s390_irgen_AGR(UChar r1, UChar r2)
   2194 {
   2195    IRTemp op1 = newTemp(Ity_I64);
   2196    IRTemp op2 = newTemp(Ity_I64);
   2197    IRTemp result = newTemp(Ity_I64);
   2198 
   2199    assign(op1, get_gpr_dw0(r1));
   2200    assign(op2, get_gpr_dw0(r2));
   2201    assign(result, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)));
   2202    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op1, op2);
   2203    put_gpr_dw0(r1, mkexpr(result));
   2204 
   2205    return "agr";
   2206 }
   2207 
   2208 static HChar *
   2209 s390_irgen_AGFR(UChar r1, UChar r2)
   2210 {
   2211    IRTemp op1 = newTemp(Ity_I64);
   2212    IRTemp op2 = newTemp(Ity_I64);
   2213    IRTemp result = newTemp(Ity_I64);
   2214 
   2215    assign(op1, get_gpr_dw0(r1));
   2216    assign(op2, unop(Iop_32Sto64, get_gpr_w1(r2)));
   2217    assign(result, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)));
   2218    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op1, op2);
   2219    put_gpr_dw0(r1, mkexpr(result));
   2220 
   2221    return "agfr";
   2222 }
   2223 
   2224 static HChar *
   2225 s390_irgen_ARK(UChar r3, UChar r1, UChar r2)
   2226 {
   2227    IRTemp op2 = newTemp(Ity_I32);
   2228    IRTemp op3 = newTemp(Ity_I32);
   2229    IRTemp result = newTemp(Ity_I32);
   2230 
   2231    assign(op2, get_gpr_w1(r2));
   2232    assign(op3, get_gpr_w1(r3));
   2233    assign(result, binop(Iop_Add32, mkexpr(op2), mkexpr(op3)));
   2234    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op2, op3);
   2235    put_gpr_w1(r1, mkexpr(result));
   2236 
   2237    return "ark";
   2238 }
   2239 
   2240 static HChar *
   2241 s390_irgen_AGRK(UChar r3, UChar r1, UChar r2)
   2242 {
   2243    IRTemp op2 = newTemp(Ity_I64);
   2244    IRTemp op3 = newTemp(Ity_I64);
   2245    IRTemp result = newTemp(Ity_I64);
   2246 
   2247    assign(op2, get_gpr_dw0(r2));
   2248    assign(op3, get_gpr_dw0(r3));
   2249    assign(result, binop(Iop_Add64, mkexpr(op2), mkexpr(op3)));
   2250    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op2, op3);
   2251    put_gpr_dw0(r1, mkexpr(result));
   2252 
   2253    return "agrk";
   2254 }
   2255 
   2256 static HChar *
   2257 s390_irgen_A(UChar r1, IRTemp op2addr)
   2258 {
   2259    IRTemp op1 = newTemp(Ity_I32);
   2260    IRTemp op2 = newTemp(Ity_I32);
   2261    IRTemp result = newTemp(Ity_I32);
   2262 
   2263    assign(op1, get_gpr_w1(r1));
   2264    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   2265    assign(result, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)));
   2266    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, op2);
   2267    put_gpr_w1(r1, mkexpr(result));
   2268 
   2269    return "a";
   2270 }
   2271 
   2272 static HChar *
   2273 s390_irgen_AY(UChar r1, IRTemp op2addr)
   2274 {
   2275    IRTemp op1 = newTemp(Ity_I32);
   2276    IRTemp op2 = newTemp(Ity_I32);
   2277    IRTemp result = newTemp(Ity_I32);
   2278 
   2279    assign(op1, get_gpr_w1(r1));
   2280    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   2281    assign(result, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)));
   2282    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, op2);
   2283    put_gpr_w1(r1, mkexpr(result));
   2284 
   2285    return "ay";
   2286 }
   2287 
   2288 static HChar *
   2289 s390_irgen_AG(UChar r1, IRTemp op2addr)
   2290 {
   2291    IRTemp op1 = newTemp(Ity_I64);
   2292    IRTemp op2 = newTemp(Ity_I64);
   2293    IRTemp result = newTemp(Ity_I64);
   2294 
   2295    assign(op1, get_gpr_dw0(r1));
   2296    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   2297    assign(result, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)));
   2298    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op1, op2);
   2299    put_gpr_dw0(r1, mkexpr(result));
   2300 
   2301    return "ag";
   2302 }
   2303 
   2304 static HChar *
   2305 s390_irgen_AGF(UChar r1, IRTemp op2addr)
   2306 {
   2307    IRTemp op1 = newTemp(Ity_I64);
   2308    IRTemp op2 = newTemp(Ity_I64);
   2309    IRTemp result = newTemp(Ity_I64);
   2310 
   2311    assign(op1, get_gpr_dw0(r1));
   2312    assign(op2, unop(Iop_32Sto64, load(Ity_I32, mkexpr(op2addr))));
   2313    assign(result, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)));
   2314    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op1, op2);
   2315    put_gpr_dw0(r1, mkexpr(result));
   2316 
   2317    return "agf";
   2318 }
   2319 
   2320 static HChar *
   2321 s390_irgen_AFI(UChar r1, UInt i2)
   2322 {
   2323    IRTemp op1 = newTemp(Ity_I32);
   2324    Int op2;
   2325    IRTemp result = newTemp(Ity_I32);
   2326 
   2327    assign(op1, get_gpr_w1(r1));
   2328    op2 = (Int)i2;
   2329    assign(result, binop(Iop_Add32, mkexpr(op1), mkU32((UInt)op2)));
   2330    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, mktemp(Ity_I32,
   2331                        mkU32((UInt)op2)));
   2332    put_gpr_w1(r1, mkexpr(result));
   2333 
   2334    return "afi";
   2335 }
   2336 
   2337 static HChar *
   2338 s390_irgen_AGFI(UChar r1, UInt i2)
   2339 {
   2340    IRTemp op1 = newTemp(Ity_I64);
   2341    Long op2;
   2342    IRTemp result = newTemp(Ity_I64);
   2343 
   2344    assign(op1, get_gpr_dw0(r1));
   2345    op2 = (Long)(Int)i2;
   2346    assign(result, binop(Iop_Add64, mkexpr(op1), mkU64((ULong)op2)));
   2347    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op1, mktemp(Ity_I64,
   2348                        mkU64((ULong)op2)));
   2349    put_gpr_dw0(r1, mkexpr(result));
   2350 
   2351    return "agfi";
   2352 }
   2353 
   2354 static HChar *
   2355 s390_irgen_AHIK(UChar r1, UChar r3, UShort i2)
   2356 {
   2357    Int op2;
   2358    IRTemp op3 = newTemp(Ity_I32);
   2359    IRTemp result = newTemp(Ity_I32);
   2360 
   2361    op2 = (Int)(Short)i2;
   2362    assign(op3, get_gpr_w1(r3));
   2363    assign(result, binop(Iop_Add32, mkU32((UInt)op2), mkexpr(op3)));
   2364    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, mktemp(Ity_I32, mkU32((UInt)
   2365                        op2)), op3);
   2366    put_gpr_w1(r1, mkexpr(result));
   2367 
   2368    return "ahik";
   2369 }
   2370 
   2371 static HChar *
   2372 s390_irgen_AGHIK(UChar r1, UChar r3, UShort i2)
   2373 {
   2374    Long op2;
   2375    IRTemp op3 = newTemp(Ity_I64);
   2376    IRTemp result = newTemp(Ity_I64);
   2377 
   2378    op2 = (Long)(Short)i2;
   2379    assign(op3, get_gpr_dw0(r3));
   2380    assign(result, binop(Iop_Add64, mkU64((ULong)op2), mkexpr(op3)));
   2381    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, mktemp(Ity_I64, mkU64((ULong)
   2382                        op2)), op3);
   2383    put_gpr_dw0(r1, mkexpr(result));
   2384 
   2385    return "aghik";
   2386 }
   2387 
   2388 static HChar *
   2389 s390_irgen_ASI(UChar i2, IRTemp op1addr)
   2390 {
   2391    IRTemp op1 = newTemp(Ity_I32);
   2392    Int op2;
   2393    IRTemp result = newTemp(Ity_I32);
   2394 
   2395    assign(op1, load(Ity_I32, mkexpr(op1addr)));
   2396    op2 = (Int)(Char)i2;
   2397    assign(result, binop(Iop_Add32, mkexpr(op1), mkU32((UInt)op2)));
   2398    store(mkexpr(op1addr), mkexpr(result));
   2399    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, mktemp(Ity_I32,
   2400                        mkU32((UInt)op2)));
   2401 
   2402    return "asi";
   2403 }
   2404 
   2405 static HChar *
   2406 s390_irgen_AGSI(UChar i2, IRTemp op1addr)
   2407 {
   2408    IRTemp op1 = newTemp(Ity_I64);
   2409    Long op2;
   2410    IRTemp result = newTemp(Ity_I64);
   2411 
   2412    assign(op1, load(Ity_I64, mkexpr(op1addr)));
   2413    op2 = (Long)(Char)i2;
   2414    assign(result, binop(Iop_Add64, mkexpr(op1), mkU64((ULong)op2)));
   2415    store(mkexpr(op1addr), mkexpr(result));
   2416    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op1, mktemp(Ity_I64,
   2417                        mkU64((ULong)op2)));
   2418 
   2419    return "agsi";
   2420 }
   2421 
   2422 static HChar *
   2423 s390_irgen_AH(UChar r1, IRTemp op2addr)
   2424 {
   2425    IRTemp op1 = newTemp(Ity_I32);
   2426    IRTemp op2 = newTemp(Ity_I32);
   2427    IRTemp result = newTemp(Ity_I32);
   2428 
   2429    assign(op1, get_gpr_w1(r1));
   2430    assign(op2, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   2431    assign(result, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)));
   2432    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, op2);
   2433    put_gpr_w1(r1, mkexpr(result));
   2434 
   2435    return "ah";
   2436 }
   2437 
   2438 static HChar *
   2439 s390_irgen_AHY(UChar r1, IRTemp op2addr)
   2440 {
   2441    IRTemp op1 = newTemp(Ity_I32);
   2442    IRTemp op2 = newTemp(Ity_I32);
   2443    IRTemp result = newTemp(Ity_I32);
   2444 
   2445    assign(op1, get_gpr_w1(r1));
   2446    assign(op2, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   2447    assign(result, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)));
   2448    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, op2);
   2449    put_gpr_w1(r1, mkexpr(result));
   2450 
   2451    return "ahy";
   2452 }
   2453 
   2454 static HChar *
   2455 s390_irgen_AHI(UChar r1, UShort i2)
   2456 {
   2457    IRTemp op1 = newTemp(Ity_I32);
   2458    Int op2;
   2459    IRTemp result = newTemp(Ity_I32);
   2460 
   2461    assign(op1, get_gpr_w1(r1));
   2462    op2 = (Int)(Short)i2;
   2463    assign(result, binop(Iop_Add32, mkexpr(op1), mkU32((UInt)op2)));
   2464    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, mktemp(Ity_I32,
   2465                        mkU32((UInt)op2)));
   2466    put_gpr_w1(r1, mkexpr(result));
   2467 
   2468    return "ahi";
   2469 }
   2470 
   2471 static HChar *
   2472 s390_irgen_AGHI(UChar r1, UShort i2)
   2473 {
   2474    IRTemp op1 = newTemp(Ity_I64);
   2475    Long op2;
   2476    IRTemp result = newTemp(Ity_I64);
   2477 
   2478    assign(op1, get_gpr_dw0(r1));
   2479    op2 = (Long)(Short)i2;
   2480    assign(result, binop(Iop_Add64, mkexpr(op1), mkU64((ULong)op2)));
   2481    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op1, mktemp(Ity_I64,
   2482                        mkU64((ULong)op2)));
   2483    put_gpr_dw0(r1, mkexpr(result));
   2484 
   2485    return "aghi";
   2486 }
   2487 
   2488 static HChar *
   2489 s390_irgen_AHHHR(UChar r3, UChar r1, UChar r2)
   2490 {
   2491    IRTemp op2 = newTemp(Ity_I32);
   2492    IRTemp op3 = newTemp(Ity_I32);
   2493    IRTemp result = newTemp(Ity_I32);
   2494 
   2495    assign(op2, get_gpr_w0(r2));
   2496    assign(op3, get_gpr_w0(r3));
   2497    assign(result, binop(Iop_Add32, mkexpr(op2), mkexpr(op3)));
   2498    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op2, op3);
   2499    put_gpr_w0(r1, mkexpr(result));
   2500 
   2501    return "ahhhr";
   2502 }
   2503 
   2504 static HChar *
   2505 s390_irgen_AHHLR(UChar r3, UChar r1, UChar r2)
   2506 {
   2507    IRTemp op2 = newTemp(Ity_I32);
   2508    IRTemp op3 = newTemp(Ity_I32);
   2509    IRTemp result = newTemp(Ity_I32);
   2510 
   2511    assign(op2, get_gpr_w0(r2));
   2512    assign(op3, get_gpr_w1(r3));
   2513    assign(result, binop(Iop_Add32, mkexpr(op2), mkexpr(op3)));
   2514    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op2, op3);
   2515    put_gpr_w0(r1, mkexpr(result));
   2516 
   2517    return "ahhlr";
   2518 }
   2519 
   2520 static HChar *
   2521 s390_irgen_AIH(UChar r1, UInt i2)
   2522 {
   2523    IRTemp op1 = newTemp(Ity_I32);
   2524    Int op2;
   2525    IRTemp result = newTemp(Ity_I32);
   2526 
   2527    assign(op1, get_gpr_w0(r1));
   2528    op2 = (Int)i2;
   2529    assign(result, binop(Iop_Add32, mkexpr(op1), mkU32((UInt)op2)));
   2530    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op1, mktemp(Ity_I32,
   2531                        mkU32((UInt)op2)));
   2532    put_gpr_w0(r1, mkexpr(result));
   2533 
   2534    return "aih";
   2535 }
   2536 
   2537 static HChar *
   2538 s390_irgen_ALR(UChar r1, UChar r2)
   2539 {
   2540    IRTemp op1 = newTemp(Ity_I32);
   2541    IRTemp op2 = newTemp(Ity_I32);
   2542    IRTemp result = newTemp(Ity_I32);
   2543 
   2544    assign(op1, get_gpr_w1(r1));
   2545    assign(op2, get_gpr_w1(r2));
   2546    assign(result, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)));
   2547    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op1, op2);
   2548    put_gpr_w1(r1, mkexpr(result));
   2549 
   2550    return "alr";
   2551 }
   2552 
   2553 static HChar *
   2554 s390_irgen_ALGR(UChar r1, UChar r2)
   2555 {
   2556    IRTemp op1 = newTemp(Ity_I64);
   2557    IRTemp op2 = newTemp(Ity_I64);
   2558    IRTemp result = newTemp(Ity_I64);
   2559 
   2560    assign(op1, get_gpr_dw0(r1));
   2561    assign(op2, get_gpr_dw0(r2));
   2562    assign(result, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)));
   2563    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, op1, op2);
   2564    put_gpr_dw0(r1, mkexpr(result));
   2565 
   2566    return "algr";
   2567 }
   2568 
   2569 static HChar *
   2570 s390_irgen_ALGFR(UChar r1, UChar r2)
   2571 {
   2572    IRTemp op1 = newTemp(Ity_I64);
   2573    IRTemp op2 = newTemp(Ity_I64);
   2574    IRTemp result = newTemp(Ity_I64);
   2575 
   2576    assign(op1, get_gpr_dw0(r1));
   2577    assign(op2, unop(Iop_32Uto64, get_gpr_w1(r2)));
   2578    assign(result, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)));
   2579    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, op1, op2);
   2580    put_gpr_dw0(r1, mkexpr(result));
   2581 
   2582    return "algfr";
   2583 }
   2584 
   2585 static HChar *
   2586 s390_irgen_ALRK(UChar r3, UChar r1, UChar r2)
   2587 {
   2588    IRTemp op2 = newTemp(Ity_I32);
   2589    IRTemp op3 = newTemp(Ity_I32);
   2590    IRTemp result = newTemp(Ity_I32);
   2591 
   2592    assign(op2, get_gpr_w1(r2));
   2593    assign(op3, get_gpr_w1(r3));
   2594    assign(result, binop(Iop_Add32, mkexpr(op2), mkexpr(op3)));
   2595    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op2, op3);
   2596    put_gpr_w1(r1, mkexpr(result));
   2597 
   2598    return "alrk";
   2599 }
   2600 
   2601 static HChar *
   2602 s390_irgen_ALGRK(UChar r3, UChar r1, UChar r2)
   2603 {
   2604    IRTemp op2 = newTemp(Ity_I64);
   2605    IRTemp op3 = newTemp(Ity_I64);
   2606    IRTemp result = newTemp(Ity_I64);
   2607 
   2608    assign(op2, get_gpr_dw0(r2));
   2609    assign(op3, get_gpr_dw0(r3));
   2610    assign(result, binop(Iop_Add64, mkexpr(op2), mkexpr(op3)));
   2611    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, op2, op3);
   2612    put_gpr_dw0(r1, mkexpr(result));
   2613 
   2614    return "algrk";
   2615 }
   2616 
   2617 static HChar *
   2618 s390_irgen_AL(UChar r1, IRTemp op2addr)
   2619 {
   2620    IRTemp op1 = newTemp(Ity_I32);
   2621    IRTemp op2 = newTemp(Ity_I32);
   2622    IRTemp result = newTemp(Ity_I32);
   2623 
   2624    assign(op1, get_gpr_w1(r1));
   2625    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   2626    assign(result, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)));
   2627    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op1, op2);
   2628    put_gpr_w1(r1, mkexpr(result));
   2629 
   2630    return "al";
   2631 }
   2632 
   2633 static HChar *
   2634 s390_irgen_ALY(UChar r1, IRTemp op2addr)
   2635 {
   2636    IRTemp op1 = newTemp(Ity_I32);
   2637    IRTemp op2 = newTemp(Ity_I32);
   2638    IRTemp result = newTemp(Ity_I32);
   2639 
   2640    assign(op1, get_gpr_w1(r1));
   2641    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   2642    assign(result, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)));
   2643    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op1, op2);
   2644    put_gpr_w1(r1, mkexpr(result));
   2645 
   2646    return "aly";
   2647 }
   2648 
   2649 static HChar *
   2650 s390_irgen_ALG(UChar r1, IRTemp op2addr)
   2651 {
   2652    IRTemp op1 = newTemp(Ity_I64);
   2653    IRTemp op2 = newTemp(Ity_I64);
   2654    IRTemp result = newTemp(Ity_I64);
   2655 
   2656    assign(op1, get_gpr_dw0(r1));
   2657    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   2658    assign(result, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)));
   2659    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, op1, op2);
   2660    put_gpr_dw0(r1, mkexpr(result));
   2661 
   2662    return "alg";
   2663 }
   2664 
   2665 static HChar *
   2666 s390_irgen_ALGF(UChar r1, IRTemp op2addr)
   2667 {
   2668    IRTemp op1 = newTemp(Ity_I64);
   2669    IRTemp op2 = newTemp(Ity_I64);
   2670    IRTemp result = newTemp(Ity_I64);
   2671 
   2672    assign(op1, get_gpr_dw0(r1));
   2673    assign(op2, unop(Iop_32Uto64, load(Ity_I32, mkexpr(op2addr))));
   2674    assign(result, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)));
   2675    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, op1, op2);
   2676    put_gpr_dw0(r1, mkexpr(result));
   2677 
   2678    return "algf";
   2679 }
   2680 
   2681 static HChar *
   2682 s390_irgen_ALFI(UChar r1, UInt i2)
   2683 {
   2684    IRTemp op1 = newTemp(Ity_I32);
   2685    UInt op2;
   2686    IRTemp result = newTemp(Ity_I32);
   2687 
   2688    assign(op1, get_gpr_w1(r1));
   2689    op2 = i2;
   2690    assign(result, binop(Iop_Add32, mkexpr(op1), mkU32(op2)));
   2691    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op1, mktemp(Ity_I32,
   2692                        mkU32(op2)));
   2693    put_gpr_w1(r1, mkexpr(result));
   2694 
   2695    return "alfi";
   2696 }
   2697 
   2698 static HChar *
   2699 s390_irgen_ALGFI(UChar r1, UInt i2)
   2700 {
   2701    IRTemp op1 = newTemp(Ity_I64);
   2702    ULong op2;
   2703    IRTemp result = newTemp(Ity_I64);
   2704 
   2705    assign(op1, get_gpr_dw0(r1));
   2706    op2 = (ULong)i2;
   2707    assign(result, binop(Iop_Add64, mkexpr(op1), mkU64(op2)));
   2708    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, op1, mktemp(Ity_I64,
   2709                        mkU64(op2)));
   2710    put_gpr_dw0(r1, mkexpr(result));
   2711 
   2712    return "algfi";
   2713 }
   2714 
   2715 static HChar *
   2716 s390_irgen_ALHHHR(UChar r3, UChar r1, UChar r2)
   2717 {
   2718    IRTemp op2 = newTemp(Ity_I32);
   2719    IRTemp op3 = newTemp(Ity_I32);
   2720    IRTemp result = newTemp(Ity_I32);
   2721 
   2722    assign(op2, get_gpr_w0(r2));
   2723    assign(op3, get_gpr_w0(r3));
   2724    assign(result, binop(Iop_Add32, mkexpr(op2), mkexpr(op3)));
   2725    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op2, op3);
   2726    put_gpr_w0(r1, mkexpr(result));
   2727 
   2728    return "alhhhr";
   2729 }
   2730 
   2731 static HChar *
   2732 s390_irgen_ALHHLR(UChar r3, UChar r1, UChar r2)
   2733 {
   2734    IRTemp op2 = newTemp(Ity_I32);
   2735    IRTemp op3 = newTemp(Ity_I32);
   2736    IRTemp result = newTemp(Ity_I32);
   2737 
   2738    assign(op2, get_gpr_w0(r2));
   2739    assign(op3, get_gpr_w1(r3));
   2740    assign(result, binop(Iop_Add32, mkexpr(op2), mkexpr(op3)));
   2741    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op2, op3);
   2742    put_gpr_w0(r1, mkexpr(result));
   2743 
   2744    return "alhhlr";
   2745 }
   2746 
   2747 static HChar *
   2748 s390_irgen_ALCR(UChar r1, UChar r2)
   2749 {
   2750    IRTemp op1 = newTemp(Ity_I32);
   2751    IRTemp op2 = newTemp(Ity_I32);
   2752    IRTemp result = newTemp(Ity_I32);
   2753    IRTemp carry_in = newTemp(Ity_I32);
   2754 
   2755    assign(op1, get_gpr_w1(r1));
   2756    assign(op2, get_gpr_w1(r2));
   2757    assign(carry_in, binop(Iop_Shr32, s390_call_calculate_cc(), mkU8(1)));
   2758    assign(result, binop(Iop_Add32, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)),
   2759           mkexpr(carry_in)));
   2760    s390_cc_thunk_putZZZ(S390_CC_OP_UNSIGNED_ADDC_32, op1, op2, carry_in);
   2761    put_gpr_w1(r1, mkexpr(result));
   2762 
   2763    return "alcr";
   2764 }
   2765 
   2766 static HChar *
   2767 s390_irgen_ALCGR(UChar r1, UChar r2)
   2768 {
   2769    IRTemp op1 = newTemp(Ity_I64);
   2770    IRTemp op2 = newTemp(Ity_I64);
   2771    IRTemp result = newTemp(Ity_I64);
   2772    IRTemp carry_in = newTemp(Ity_I64);
   2773 
   2774    assign(op1, get_gpr_dw0(r1));
   2775    assign(op2, get_gpr_dw0(r2));
   2776    assign(carry_in, unop(Iop_32Uto64, binop(Iop_Shr32, s390_call_calculate_cc(),
   2777           mkU8(1))));
   2778    assign(result, binop(Iop_Add64, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)),
   2779           mkexpr(carry_in)));
   2780    s390_cc_thunk_putZZZ(S390_CC_OP_UNSIGNED_ADDC_64, op1, op2, carry_in);
   2781    put_gpr_dw0(r1, mkexpr(result));
   2782 
   2783    return "alcgr";
   2784 }
   2785 
   2786 static HChar *
   2787 s390_irgen_ALC(UChar r1, IRTemp op2addr)
   2788 {
   2789    IRTemp op1 = newTemp(Ity_I32);
   2790    IRTemp op2 = newTemp(Ity_I32);
   2791    IRTemp result = newTemp(Ity_I32);
   2792    IRTemp carry_in = newTemp(Ity_I32);
   2793 
   2794    assign(op1, get_gpr_w1(r1));
   2795    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   2796    assign(carry_in, binop(Iop_Shr32, s390_call_calculate_cc(), mkU8(1)));
   2797    assign(result, binop(Iop_Add32, binop(Iop_Add32, mkexpr(op1), mkexpr(op2)),
   2798           mkexpr(carry_in)));
   2799    s390_cc_thunk_putZZZ(S390_CC_OP_UNSIGNED_ADDC_32, op1, op2, carry_in);
   2800    put_gpr_w1(r1, mkexpr(result));
   2801 
   2802    return "alc";
   2803 }
   2804 
   2805 static HChar *
   2806 s390_irgen_ALCG(UChar r1, IRTemp op2addr)
   2807 {
   2808    IRTemp op1 = newTemp(Ity_I64);
   2809    IRTemp op2 = newTemp(Ity_I64);
   2810    IRTemp result = newTemp(Ity_I64);
   2811    IRTemp carry_in = newTemp(Ity_I64);
   2812 
   2813    assign(op1, get_gpr_dw0(r1));
   2814    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   2815    assign(carry_in, unop(Iop_32Uto64, binop(Iop_Shr32, s390_call_calculate_cc(),
   2816           mkU8(1))));
   2817    assign(result, binop(Iop_Add64, binop(Iop_Add64, mkexpr(op1), mkexpr(op2)),
   2818           mkexpr(carry_in)));
   2819    s390_cc_thunk_putZZZ(S390_CC_OP_UNSIGNED_ADDC_64, op1, op2, carry_in);
   2820    put_gpr_dw0(r1, mkexpr(result));
   2821 
   2822    return "alcg";
   2823 }
   2824 
   2825 static HChar *
   2826 s390_irgen_ALSI(UChar i2, IRTemp op1addr)
   2827 {
   2828    IRTemp op1 = newTemp(Ity_I32);
   2829    UInt op2;
   2830    IRTemp result = newTemp(Ity_I32);
   2831 
   2832    assign(op1, load(Ity_I32, mkexpr(op1addr)));
   2833    op2 = (UInt)(Int)(Char)i2;
   2834    assign(result, binop(Iop_Add32, mkexpr(op1), mkU32(op2)));
   2835    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op1, mktemp(Ity_I32,
   2836                        mkU32(op2)));
   2837    store(mkexpr(op1addr), mkexpr(result));
   2838 
   2839    return "alsi";
   2840 }
   2841 
   2842 static HChar *
   2843 s390_irgen_ALGSI(UChar i2, IRTemp op1addr)
   2844 {
   2845    IRTemp op1 = newTemp(Ity_I64);
   2846    ULong op2;
   2847    IRTemp result = newTemp(Ity_I64);
   2848 
   2849    assign(op1, load(Ity_I64, mkexpr(op1addr)));
   2850    op2 = (ULong)(Long)(Char)i2;
   2851    assign(result, binop(Iop_Add64, mkexpr(op1), mkU64(op2)));
   2852    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, op1, mktemp(Ity_I64,
   2853                        mkU64(op2)));
   2854    store(mkexpr(op1addr), mkexpr(result));
   2855 
   2856    return "algsi";
   2857 }
   2858 
   2859 static HChar *
   2860 s390_irgen_ALHSIK(UChar r1, UChar r3, UShort i2)
   2861 {
   2862    UInt op2;
   2863    IRTemp op3 = newTemp(Ity_I32);
   2864    IRTemp result = newTemp(Ity_I32);
   2865 
   2866    op2 = (UInt)(Int)(Short)i2;
   2867    assign(op3, get_gpr_w1(r3));
   2868    assign(result, binop(Iop_Add32, mkU32(op2), mkexpr(op3)));
   2869    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, mktemp(Ity_I32, mkU32(op2)),
   2870                        op3);
   2871    put_gpr_w1(r1, mkexpr(result));
   2872 
   2873    return "alhsik";
   2874 }
   2875 
   2876 static HChar *
   2877 s390_irgen_ALGHSIK(UChar r1, UChar r3, UShort i2)
   2878 {
   2879    ULong op2;
   2880    IRTemp op3 = newTemp(Ity_I64);
   2881    IRTemp result = newTemp(Ity_I64);
   2882 
   2883    op2 = (ULong)(Long)(Short)i2;
   2884    assign(op3, get_gpr_dw0(r3));
   2885    assign(result, binop(Iop_Add64, mkU64(op2), mkexpr(op3)));
   2886    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, mktemp(Ity_I64, mkU64(op2)),
   2887                        op3);
   2888    put_gpr_dw0(r1, mkexpr(result));
   2889 
   2890    return "alghsik";
   2891 }
   2892 
   2893 static HChar *
   2894 s390_irgen_ALSIH(UChar r1, UInt i2)
   2895 {
   2896    IRTemp op1 = newTemp(Ity_I32);
   2897    UInt op2;
   2898    IRTemp result = newTemp(Ity_I32);
   2899 
   2900    assign(op1, get_gpr_w0(r1));
   2901    op2 = i2;
   2902    assign(result, binop(Iop_Add32, mkexpr(op1), mkU32(op2)));
   2903    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op1, mktemp(Ity_I32,
   2904                        mkU32(op2)));
   2905    put_gpr_w0(r1, mkexpr(result));
   2906 
   2907    return "alsih";
   2908 }
   2909 
   2910 static HChar *
   2911 s390_irgen_ALSIHN(UChar r1, UInt i2)
   2912 {
   2913    IRTemp op1 = newTemp(Ity_I32);
   2914    UInt op2;
   2915    IRTemp result = newTemp(Ity_I32);
   2916 
   2917    assign(op1, get_gpr_w0(r1));
   2918    op2 = i2;
   2919    assign(result, binop(Iop_Add32, mkexpr(op1), mkU32(op2)));
   2920    put_gpr_w0(r1, mkexpr(result));
   2921 
   2922    return "alsihn";
   2923 }
   2924 
   2925 static HChar *
   2926 s390_irgen_NR(UChar r1, UChar r2)
   2927 {
   2928    IRTemp op1 = newTemp(Ity_I32);
   2929    IRTemp op2 = newTemp(Ity_I32);
   2930    IRTemp result = newTemp(Ity_I32);
   2931 
   2932    assign(op1, get_gpr_w1(r1));
   2933    assign(op2, get_gpr_w1(r2));
   2934    assign(result, binop(Iop_And32, mkexpr(op1), mkexpr(op2)));
   2935    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   2936    put_gpr_w1(r1, mkexpr(result));
   2937 
   2938    return "nr";
   2939 }
   2940 
   2941 static HChar *
   2942 s390_irgen_NGR(UChar r1, UChar r2)
   2943 {
   2944    IRTemp op1 = newTemp(Ity_I64);
   2945    IRTemp op2 = newTemp(Ity_I64);
   2946    IRTemp result = newTemp(Ity_I64);
   2947 
   2948    assign(op1, get_gpr_dw0(r1));
   2949    assign(op2, get_gpr_dw0(r2));
   2950    assign(result, binop(Iop_And64, mkexpr(op1), mkexpr(op2)));
   2951    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   2952    put_gpr_dw0(r1, mkexpr(result));
   2953 
   2954    return "ngr";
   2955 }
   2956 
   2957 static HChar *
   2958 s390_irgen_NRK(UChar r3, UChar r1, UChar r2)
   2959 {
   2960    IRTemp op2 = newTemp(Ity_I32);
   2961    IRTemp op3 = newTemp(Ity_I32);
   2962    IRTemp result = newTemp(Ity_I32);
   2963 
   2964    assign(op2, get_gpr_w1(r2));
   2965    assign(op3, get_gpr_w1(r3));
   2966    assign(result, binop(Iop_And32, mkexpr(op2), mkexpr(op3)));
   2967    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   2968    put_gpr_w1(r1, mkexpr(result));
   2969 
   2970    return "nrk";
   2971 }
   2972 
   2973 static HChar *
   2974 s390_irgen_NGRK(UChar r3, UChar r1, UChar r2)
   2975 {
   2976    IRTemp op2 = newTemp(Ity_I64);
   2977    IRTemp op3 = newTemp(Ity_I64);
   2978    IRTemp result = newTemp(Ity_I64);
   2979 
   2980    assign(op2, get_gpr_dw0(r2));
   2981    assign(op3, get_gpr_dw0(r3));
   2982    assign(result, binop(Iop_And64, mkexpr(op2), mkexpr(op3)));
   2983    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   2984    put_gpr_dw0(r1, mkexpr(result));
   2985 
   2986    return "ngrk";
   2987 }
   2988 
   2989 static HChar *
   2990 s390_irgen_N(UChar r1, IRTemp op2addr)
   2991 {
   2992    IRTemp op1 = newTemp(Ity_I32);
   2993    IRTemp op2 = newTemp(Ity_I32);
   2994    IRTemp result = newTemp(Ity_I32);
   2995 
   2996    assign(op1, get_gpr_w1(r1));
   2997    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   2998    assign(result, binop(Iop_And32, mkexpr(op1), mkexpr(op2)));
   2999    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3000    put_gpr_w1(r1, mkexpr(result));
   3001 
   3002    return "n";
   3003 }
   3004 
   3005 static HChar *
   3006 s390_irgen_NY(UChar r1, IRTemp op2addr)
   3007 {
   3008    IRTemp op1 = newTemp(Ity_I32);
   3009    IRTemp op2 = newTemp(Ity_I32);
   3010    IRTemp result = newTemp(Ity_I32);
   3011 
   3012    assign(op1, get_gpr_w1(r1));
   3013    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   3014    assign(result, binop(Iop_And32, mkexpr(op1), mkexpr(op2)));
   3015    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3016    put_gpr_w1(r1, mkexpr(result));
   3017 
   3018    return "ny";
   3019 }
   3020 
   3021 static HChar *
   3022 s390_irgen_NG(UChar r1, IRTemp op2addr)
   3023 {
   3024    IRTemp op1 = newTemp(Ity_I64);
   3025    IRTemp op2 = newTemp(Ity_I64);
   3026    IRTemp result = newTemp(Ity_I64);
   3027 
   3028    assign(op1, get_gpr_dw0(r1));
   3029    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   3030    assign(result, binop(Iop_And64, mkexpr(op1), mkexpr(op2)));
   3031    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3032    put_gpr_dw0(r1, mkexpr(result));
   3033 
   3034    return "ng";
   3035 }
   3036 
   3037 static HChar *
   3038 s390_irgen_NI(UChar i2, IRTemp op1addr)
   3039 {
   3040    IRTemp op1 = newTemp(Ity_I8);
   3041    UChar op2;
   3042    IRTemp result = newTemp(Ity_I8);
   3043 
   3044    assign(op1, load(Ity_I8, mkexpr(op1addr)));
   3045    op2 = i2;
   3046    assign(result, binop(Iop_And8, mkexpr(op1), mkU8(op2)));
   3047    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3048    store(mkexpr(op1addr), mkexpr(result));
   3049 
   3050    return "ni";
   3051 }
   3052 
   3053 static HChar *
   3054 s390_irgen_NIY(UChar i2, IRTemp op1addr)
   3055 {
   3056    IRTemp op1 = newTemp(Ity_I8);
   3057    UChar op2;
   3058    IRTemp result = newTemp(Ity_I8);
   3059 
   3060    assign(op1, load(Ity_I8, mkexpr(op1addr)));
   3061    op2 = i2;
   3062    assign(result, binop(Iop_And8, mkexpr(op1), mkU8(op2)));
   3063    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3064    store(mkexpr(op1addr), mkexpr(result));
   3065 
   3066    return "niy";
   3067 }
   3068 
   3069 static HChar *
   3070 s390_irgen_NIHF(UChar r1, UInt i2)
   3071 {
   3072    IRTemp op1 = newTemp(Ity_I32);
   3073    UInt op2;
   3074    IRTemp result = newTemp(Ity_I32);
   3075 
   3076    assign(op1, get_gpr_w0(r1));
   3077    op2 = i2;
   3078    assign(result, binop(Iop_And32, mkexpr(op1), mkU32(op2)));
   3079    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3080    put_gpr_w0(r1, mkexpr(result));
   3081 
   3082    return "nihf";
   3083 }
   3084 
   3085 static HChar *
   3086 s390_irgen_NIHH(UChar r1, UShort i2)
   3087 {
   3088    IRTemp op1 = newTemp(Ity_I16);
   3089    UShort op2;
   3090    IRTemp result = newTemp(Ity_I16);
   3091 
   3092    assign(op1, get_gpr_hw0(r1));
   3093    op2 = i2;
   3094    assign(result, binop(Iop_And16, mkexpr(op1), mkU16(op2)));
   3095    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3096    put_gpr_hw0(r1, mkexpr(result));
   3097 
   3098    return "nihh";
   3099 }
   3100 
   3101 static HChar *
   3102 s390_irgen_NIHL(UChar r1, UShort i2)
   3103 {
   3104    IRTemp op1 = newTemp(Ity_I16);
   3105    UShort op2;
   3106    IRTemp result = newTemp(Ity_I16);
   3107 
   3108    assign(op1, get_gpr_hw1(r1));
   3109    op2 = i2;
   3110    assign(result, binop(Iop_And16, mkexpr(op1), mkU16(op2)));
   3111    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3112    put_gpr_hw1(r1, mkexpr(result));
   3113 
   3114    return "nihl";
   3115 }
   3116 
   3117 static HChar *
   3118 s390_irgen_NILF(UChar r1, UInt i2)
   3119 {
   3120    IRTemp op1 = newTemp(Ity_I32);
   3121    UInt op2;
   3122    IRTemp result = newTemp(Ity_I32);
   3123 
   3124    assign(op1, get_gpr_w1(r1));
   3125    op2 = i2;
   3126    assign(result, binop(Iop_And32, mkexpr(op1), mkU32(op2)));
   3127    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3128    put_gpr_w1(r1, mkexpr(result));
   3129 
   3130    return "nilf";
   3131 }
   3132 
   3133 static HChar *
   3134 s390_irgen_NILH(UChar r1, UShort i2)
   3135 {
   3136    IRTemp op1 = newTemp(Ity_I16);
   3137    UShort op2;
   3138    IRTemp result = newTemp(Ity_I16);
   3139 
   3140    assign(op1, get_gpr_hw2(r1));
   3141    op2 = i2;
   3142    assign(result, binop(Iop_And16, mkexpr(op1), mkU16(op2)));
   3143    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3144    put_gpr_hw2(r1, mkexpr(result));
   3145 
   3146    return "nilh";
   3147 }
   3148 
   3149 static HChar *
   3150 s390_irgen_NILL(UChar r1, UShort i2)
   3151 {
   3152    IRTemp op1 = newTemp(Ity_I16);
   3153    UShort op2;
   3154    IRTemp result = newTemp(Ity_I16);
   3155 
   3156    assign(op1, get_gpr_hw3(r1));
   3157    op2 = i2;
   3158    assign(result, binop(Iop_And16, mkexpr(op1), mkU16(op2)));
   3159    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   3160    put_gpr_hw3(r1, mkexpr(result));
   3161 
   3162    return "nill";
   3163 }
   3164 
   3165 static HChar *
   3166 s390_irgen_BASR(UChar r1, UChar r2)
   3167 {
   3168    IRTemp target = newTemp(Ity_I64);
   3169 
   3170    if (r2 == 0) {
   3171       put_gpr_dw0(r1, mkU64(guest_IA_curr_instr + 2ULL));
   3172    } else {
   3173       if (r1 != r2) {
   3174          put_gpr_dw0(r1, mkU64(guest_IA_curr_instr + 2ULL));
   3175          call_function(get_gpr_dw0(r2));
   3176       } else {
   3177          assign(target, get_gpr_dw0(r2));
   3178          put_gpr_dw0(r1, mkU64(guest_IA_curr_instr + 2ULL));
   3179          call_function(mkexpr(target));
   3180       }
   3181    }
   3182 
   3183    return "basr";
   3184 }
   3185 
   3186 static HChar *
   3187 s390_irgen_BAS(UChar r1, IRTemp op2addr)
   3188 {
   3189    IRTemp target = newTemp(Ity_I64);
   3190 
   3191    put_gpr_dw0(r1, mkU64(guest_IA_curr_instr + 4ULL));
   3192    assign(target, mkexpr(op2addr));
   3193    call_function(mkexpr(target));
   3194 
   3195    return "bas";
   3196 }
   3197 
   3198 static HChar *
   3199 s390_irgen_BCR(UChar r1, UChar r2)
   3200 {
   3201    IRTemp cond = newTemp(Ity_I32);
   3202 
   3203    if (r2 == 0 && (r1 >= 14)) {    /* serialization */
   3204       stmt(IRStmt_MBE(Imbe_Fence));
   3205    }
   3206 
   3207    if ((r2 == 0) || (r1 == 0)) {
   3208    } else {
   3209       if (r1 == 15) {
   3210          return_from_function(get_gpr_dw0(r2));
   3211       } else {
   3212          assign(cond, s390_call_calculate_cond(r1));
   3213          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3214                                     get_gpr_dw0(r2));
   3215       }
   3216    }
   3217    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   3218       s390_disasm(ENC2(XMNM, GPR), S390_XMNM_BCR, r1, r2);
   3219 
   3220    return "bcr";
   3221 }
   3222 
   3223 static HChar *
   3224 s390_irgen_BC(UChar r1, UChar x2, UChar b2, UShort d2, IRTemp op2addr)
   3225 {
   3226    IRTemp cond = newTemp(Ity_I32);
   3227 
   3228    if (r1 == 0) {
   3229    } else {
   3230       if (r1 == 15) {
   3231          always_goto(mkexpr(op2addr));
   3232       } else {
   3233          assign(cond, s390_call_calculate_cond(r1));
   3234          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3235                                     mkexpr(op2addr));
   3236       }
   3237    }
   3238    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   3239       s390_disasm(ENC2(XMNM, UDXB), S390_XMNM_BC, r1, d2, x2, b2);
   3240 
   3241    return "bc";
   3242 }
   3243 
   3244 static HChar *
   3245 s390_irgen_BCTR(UChar r1, UChar r2)
   3246 {
   3247    put_gpr_w1(r1, binop(Iop_Sub32, get_gpr_w1(r1), mkU32(1)));
   3248    if (r2 != 0) {
   3249       if_condition_goto_computed(binop(Iop_CmpNE32, get_gpr_w1(r1), mkU32(0)),
   3250                                  get_gpr_dw0(r2));
   3251    }
   3252 
   3253    return "bctr";
   3254 }
   3255 
   3256 static HChar *
   3257 s390_irgen_BCTGR(UChar r1, UChar r2)
   3258 {
   3259    put_gpr_dw0(r1, binop(Iop_Sub64, get_gpr_dw0(r1), mkU64(1)));
   3260    if (r2 != 0) {
   3261       if_condition_goto_computed(binop(Iop_CmpNE64, get_gpr_dw0(r1), mkU64(0)),
   3262                                  get_gpr_dw0(r2));
   3263    }
   3264 
   3265    return "bctgr";
   3266 }
   3267 
   3268 static HChar *
   3269 s390_irgen_BCT(UChar r1, IRTemp op2addr)
   3270 {
   3271    put_gpr_w1(r1, binop(Iop_Sub32, get_gpr_w1(r1), mkU32(1)));
   3272    if_condition_goto_computed(binop(Iop_CmpNE32, get_gpr_w1(r1), mkU32(0)),
   3273                               mkexpr(op2addr));
   3274 
   3275    return "bct";
   3276 }
   3277 
   3278 static HChar *
   3279 s390_irgen_BCTG(UChar r1, IRTemp op2addr)
   3280 {
   3281    put_gpr_dw0(r1, binop(Iop_Sub64, get_gpr_dw0(r1), mkU64(1)));
   3282    if_condition_goto_computed(binop(Iop_CmpNE64, get_gpr_dw0(r1), mkU64(0)),
   3283                               mkexpr(op2addr));
   3284 
   3285    return "bctg";
   3286 }
   3287 
   3288 static HChar *
   3289 s390_irgen_BXH(UChar r1, UChar r3, IRTemp op2addr)
   3290 {
   3291    IRTemp value = newTemp(Ity_I32);
   3292 
   3293    assign(value, get_gpr_w1(r3 | 1));
   3294    put_gpr_w1(r1, binop(Iop_Add32, get_gpr_w1(r1), get_gpr_w1(r3)));
   3295    if_condition_goto_computed(binop(Iop_CmpLT32S, mkexpr(value),
   3296                                     get_gpr_w1(r1)), mkexpr(op2addr));
   3297 
   3298    return "bxh";
   3299 }
   3300 
   3301 static HChar *
   3302 s390_irgen_BXHG(UChar r1, UChar r3, IRTemp op2addr)
   3303 {
   3304    IRTemp value = newTemp(Ity_I64);
   3305 
   3306    assign(value, get_gpr_dw0(r3 | 1));
   3307    put_gpr_dw0(r1, binop(Iop_Add64, get_gpr_dw0(r1), get_gpr_dw0(r3)));
   3308    if_condition_goto_computed(binop(Iop_CmpLT64S, mkexpr(value),
   3309                                     get_gpr_dw0(r1)), mkexpr(op2addr));
   3310 
   3311    return "bxhg";
   3312 }
   3313 
   3314 static HChar *
   3315 s390_irgen_BXLE(UChar r1, UChar r3, IRTemp op2addr)
   3316 {
   3317    IRTemp value = newTemp(Ity_I32);
   3318 
   3319    assign(value, get_gpr_w1(r3 | 1));
   3320    put_gpr_w1(r1, binop(Iop_Add32, get_gpr_w1(r1), get_gpr_w1(r3)));
   3321    if_condition_goto_computed(binop(Iop_CmpLE32S, get_gpr_w1(r1),
   3322                                     mkexpr(value)), mkexpr(op2addr));
   3323 
   3324    return "bxle";
   3325 }
   3326 
   3327 static HChar *
   3328 s390_irgen_BXLEG(UChar r1, UChar r3, IRTemp op2addr)
   3329 {
   3330    IRTemp value = newTemp(Ity_I64);
   3331 
   3332    assign(value, get_gpr_dw0(r3 | 1));
   3333    put_gpr_dw0(r1, binop(Iop_Add64, get_gpr_dw0(r1), get_gpr_dw0(r3)));
   3334    if_condition_goto_computed(binop(Iop_CmpLE64S, get_gpr_dw0(r1),
   3335                                     mkexpr(value)), mkexpr(op2addr));
   3336 
   3337    return "bxleg";
   3338 }
   3339 
   3340 static HChar *
   3341 s390_irgen_BRAS(UChar r1, UShort i2)
   3342 {
   3343    put_gpr_dw0(r1, mkU64(guest_IA_curr_instr + 4ULL));
   3344    call_function_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3345 
   3346    return "bras";
   3347 }
   3348 
   3349 static HChar *
   3350 s390_irgen_BRASL(UChar r1, UInt i2)
   3351 {
   3352    put_gpr_dw0(r1, mkU64(guest_IA_curr_instr + 6ULL));
   3353    call_function_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Int)i2 << 1));
   3354 
   3355    return "brasl";
   3356 }
   3357 
   3358 static HChar *
   3359 s390_irgen_BRC(UChar r1, UShort i2)
   3360 {
   3361    IRTemp cond = newTemp(Ity_I32);
   3362 
   3363    if (r1 == 0) {
   3364    } else {
   3365       if (r1 == 15) {
   3366          always_goto_and_chase(
   3367                guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3368       } else {
   3369          assign(cond, s390_call_calculate_cond(r1));
   3370          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3371                            guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3372 
   3373       }
   3374    }
   3375    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   3376       s390_disasm(ENC2(XMNM, PCREL), S390_XMNM_BRC, r1, (Int)(Short)i2);
   3377 
   3378    return "brc";
   3379 }
   3380 
   3381 static HChar *
   3382 s390_irgen_BRCL(UChar r1, UInt i2)
   3383 {
   3384    IRTemp cond = newTemp(Ity_I32);
   3385 
   3386    if (r1 == 0) {
   3387    } else {
   3388       if (r1 == 15) {
   3389          always_goto_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Int)i2 << 1));
   3390       } else {
   3391          assign(cond, s390_call_calculate_cond(r1));
   3392          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3393                            guest_IA_curr_instr + ((ULong)(Long)(Int)i2 << 1));
   3394       }
   3395    }
   3396    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   3397       s390_disasm(ENC2(XMNM, PCREL), S390_XMNM_BRCL, r1, i2);
   3398 
   3399    return "brcl";
   3400 }
   3401 
   3402 static HChar *
   3403 s390_irgen_BRCT(UChar r1, UShort i2)
   3404 {
   3405    put_gpr_w1(r1, binop(Iop_Sub32, get_gpr_w1(r1), mkU32(1)));
   3406    if_condition_goto(binop(Iop_CmpNE32, get_gpr_w1(r1), mkU32(0)),
   3407                      guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3408 
   3409    return "brct";
   3410 }
   3411 
   3412 static HChar *
   3413 s390_irgen_BRCTG(UChar r1, UShort i2)
   3414 {
   3415    put_gpr_dw0(r1, binop(Iop_Sub64, get_gpr_dw0(r1), mkU64(1)));
   3416    if_condition_goto(binop(Iop_CmpNE64, get_gpr_dw0(r1), mkU64(0)),
   3417                      guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3418 
   3419    return "brctg";
   3420 }
   3421 
   3422 static HChar *
   3423 s390_irgen_BRXH(UChar r1, UChar r3, UShort i2)
   3424 {
   3425    IRTemp value = newTemp(Ity_I32);
   3426 
   3427    assign(value, get_gpr_w1(r3 | 1));
   3428    put_gpr_w1(r1, binop(Iop_Add32, get_gpr_w1(r1), get_gpr_w1(r3)));
   3429    if_condition_goto(binop(Iop_CmpLT32S, mkexpr(value), get_gpr_w1(r1)),
   3430                      guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3431 
   3432    return "brxh";
   3433 }
   3434 
   3435 static HChar *
   3436 s390_irgen_BRXHG(UChar r1, UChar r3, UShort i2)
   3437 {
   3438    IRTemp value = newTemp(Ity_I64);
   3439 
   3440    assign(value, get_gpr_dw0(r3 | 1));
   3441    put_gpr_dw0(r1, binop(Iop_Add64, get_gpr_dw0(r1), get_gpr_dw0(r3)));
   3442    if_condition_goto(binop(Iop_CmpLT64S, mkexpr(value), get_gpr_dw0(r1)),
   3443                      guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3444 
   3445    return "brxhg";
   3446 }
   3447 
   3448 static HChar *
   3449 s390_irgen_BRXLE(UChar r1, UChar r3, UShort i2)
   3450 {
   3451    IRTemp value = newTemp(Ity_I32);
   3452 
   3453    assign(value, get_gpr_w1(r3 | 1));
   3454    put_gpr_w1(r1, binop(Iop_Add32, get_gpr_w1(r1), get_gpr_w1(r3)));
   3455    if_condition_goto(binop(Iop_CmpLE32S, get_gpr_w1(r1), mkexpr(value)),
   3456                      guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3457 
   3458    return "brxle";
   3459 }
   3460 
   3461 static HChar *
   3462 s390_irgen_BRXLG(UChar r1, UChar r3, UShort i2)
   3463 {
   3464    IRTemp value = newTemp(Ity_I64);
   3465 
   3466    assign(value, get_gpr_dw0(r3 | 1));
   3467    put_gpr_dw0(r1, binop(Iop_Add64, get_gpr_dw0(r1), get_gpr_dw0(r3)));
   3468    if_condition_goto(binop(Iop_CmpLE64S, get_gpr_dw0(r1), mkexpr(value)),
   3469                      guest_IA_curr_instr + ((ULong)(Long)(Short)i2 << 1));
   3470 
   3471    return "brxlg";
   3472 }
   3473 
   3474 static HChar *
   3475 s390_irgen_CR(UChar r1, UChar r2)
   3476 {
   3477    IRTemp op1 = newTemp(Ity_I32);
   3478    IRTemp op2 = newTemp(Ity_I32);
   3479 
   3480    assign(op1, get_gpr_w1(r1));
   3481    assign(op2, get_gpr_w1(r2));
   3482    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3483 
   3484    return "cr";
   3485 }
   3486 
   3487 static HChar *
   3488 s390_irgen_CGR(UChar r1, UChar r2)
   3489 {
   3490    IRTemp op1 = newTemp(Ity_I64);
   3491    IRTemp op2 = newTemp(Ity_I64);
   3492 
   3493    assign(op1, get_gpr_dw0(r1));
   3494    assign(op2, get_gpr_dw0(r2));
   3495    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3496 
   3497    return "cgr";
   3498 }
   3499 
   3500 static HChar *
   3501 s390_irgen_CGFR(UChar r1, UChar r2)
   3502 {
   3503    IRTemp op1 = newTemp(Ity_I64);
   3504    IRTemp op2 = newTemp(Ity_I64);
   3505 
   3506    assign(op1, get_gpr_dw0(r1));
   3507    assign(op2, unop(Iop_32Sto64, get_gpr_w1(r2)));
   3508    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3509 
   3510    return "cgfr";
   3511 }
   3512 
   3513 static HChar *
   3514 s390_irgen_C(UChar r1, IRTemp op2addr)
   3515 {
   3516    IRTemp op1 = newTemp(Ity_I32);
   3517    IRTemp op2 = newTemp(Ity_I32);
   3518 
   3519    assign(op1, get_gpr_w1(r1));
   3520    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   3521    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3522 
   3523    return "c";
   3524 }
   3525 
   3526 static HChar *
   3527 s390_irgen_CY(UChar r1, IRTemp op2addr)
   3528 {
   3529    IRTemp op1 = newTemp(Ity_I32);
   3530    IRTemp op2 = newTemp(Ity_I32);
   3531 
   3532    assign(op1, get_gpr_w1(r1));
   3533    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   3534    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3535 
   3536    return "cy";
   3537 }
   3538 
   3539 static HChar *
   3540 s390_irgen_CG(UChar r1, IRTemp op2addr)
   3541 {
   3542    IRTemp op1 = newTemp(Ity_I64);
   3543    IRTemp op2 = newTemp(Ity_I64);
   3544 
   3545    assign(op1, get_gpr_dw0(r1));
   3546    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   3547    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3548 
   3549    return "cg";
   3550 }
   3551 
   3552 static HChar *
   3553 s390_irgen_CGF(UChar r1, IRTemp op2addr)
   3554 {
   3555    IRTemp op1 = newTemp(Ity_I64);
   3556    IRTemp op2 = newTemp(Ity_I64);
   3557 
   3558    assign(op1, get_gpr_dw0(r1));
   3559    assign(op2, unop(Iop_32Sto64, load(Ity_I32, mkexpr(op2addr))));
   3560    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3561 
   3562    return "cgf";
   3563 }
   3564 
   3565 static HChar *
   3566 s390_irgen_CFI(UChar r1, UInt i2)
   3567 {
   3568    IRTemp op1 = newTemp(Ity_I32);
   3569    Int op2;
   3570 
   3571    assign(op1, get_gpr_w1(r1));
   3572    op2 = (Int)i2;
   3573    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, mktemp(Ity_I32,
   3574                        mkU32((UInt)op2)));
   3575 
   3576    return "cfi";
   3577 }
   3578 
   3579 static HChar *
   3580 s390_irgen_CGFI(UChar r1, UInt i2)
   3581 {
   3582    IRTemp op1 = newTemp(Ity_I64);
   3583    Long op2;
   3584 
   3585    assign(op1, get_gpr_dw0(r1));
   3586    op2 = (Long)(Int)i2;
   3587    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, mktemp(Ity_I64,
   3588                        mkU64((ULong)op2)));
   3589 
   3590    return "cgfi";
   3591 }
   3592 
   3593 static HChar *
   3594 s390_irgen_CRL(UChar r1, UInt i2)
   3595 {
   3596    IRTemp op1 = newTemp(Ity_I32);
   3597    IRTemp op2 = newTemp(Ity_I32);
   3598 
   3599    assign(op1, get_gpr_w1(r1));
   3600    assign(op2, load(Ity_I32, mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)
   3601           i2 << 1))));
   3602    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3603 
   3604    return "crl";
   3605 }
   3606 
   3607 static HChar *
   3608 s390_irgen_CGRL(UChar r1, UInt i2)
   3609 {
   3610    IRTemp op1 = newTemp(Ity_I64);
   3611    IRTemp op2 = newTemp(Ity_I64);
   3612 
   3613    assign(op1, get_gpr_dw0(r1));
   3614    assign(op2, load(Ity_I64, mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)
   3615           i2 << 1))));
   3616    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3617 
   3618    return "cgrl";
   3619 }
   3620 
   3621 static HChar *
   3622 s390_irgen_CGFRL(UChar r1, UInt i2)
   3623 {
   3624    IRTemp op1 = newTemp(Ity_I64);
   3625    IRTemp op2 = newTemp(Ity_I64);
   3626 
   3627    assign(op1, get_gpr_dw0(r1));
   3628    assign(op2, unop(Iop_32Sto64, load(Ity_I32, mkU64(guest_IA_curr_instr +
   3629           ((ULong)(Long)(Int)i2 << 1)))));
   3630    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3631 
   3632    return "cgfrl";
   3633 }
   3634 
   3635 static HChar *
   3636 s390_irgen_CRB(UChar r1, UChar r2, UChar m3, IRTemp op4addr)
   3637 {
   3638    IRTemp op1 = newTemp(Ity_I32);
   3639    IRTemp op2 = newTemp(Ity_I32);
   3640    IRTemp cond = newTemp(Ity_I32);
   3641 
   3642    if (m3 == 0) {
   3643    } else {
   3644       if (m3 == 14) {
   3645          always_goto(mkexpr(op4addr));
   3646       } else {
   3647          assign(op1, get_gpr_w1(r1));
   3648          assign(op2, get_gpr_w1(r2));
   3649          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_SIGNED_COMPARE,
   3650                                               op1, op2));
   3651          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond),
   3652                                           mkU32(0)), mkexpr(op4addr));
   3653       }
   3654    }
   3655 
   3656    return "crb";
   3657 }
   3658 
   3659 static HChar *
   3660 s390_irgen_CGRB(UChar r1, UChar r2, UChar m3, IRTemp op4addr)
   3661 {
   3662    IRTemp op1 = newTemp(Ity_I64);
   3663    IRTemp op2 = newTemp(Ity_I64);
   3664    IRTemp cond = newTemp(Ity_I32);
   3665 
   3666    if (m3 == 0) {
   3667    } else {
   3668       if (m3 == 14) {
   3669          always_goto(mkexpr(op4addr));
   3670       } else {
   3671          assign(op1, get_gpr_dw0(r1));
   3672          assign(op2, get_gpr_dw0(r2));
   3673          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_SIGNED_COMPARE,
   3674                                               op1, op2));
   3675          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond),
   3676                                           mkU32(0)), mkexpr(op4addr));
   3677       }
   3678    }
   3679 
   3680    return "cgrb";
   3681 }
   3682 
   3683 static HChar *
   3684 s390_irgen_CRJ(UChar r1, UChar r2, UShort i4, UChar m3)
   3685 {
   3686    IRTemp op1 = newTemp(Ity_I32);
   3687    IRTemp op2 = newTemp(Ity_I32);
   3688    IRTemp cond = newTemp(Ity_I32);
   3689 
   3690    if (m3 == 0) {
   3691    } else {
   3692       if (m3 == 14) {
   3693          always_goto_and_chase(
   3694                 guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   3695       } else {
   3696          assign(op1, get_gpr_w1(r1));
   3697          assign(op2, get_gpr_w1(r2));
   3698          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_SIGNED_COMPARE,
   3699                                               op1, op2));
   3700          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3701                            guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   3702 
   3703       }
   3704    }
   3705 
   3706    return "crj";
   3707 }
   3708 
   3709 static HChar *
   3710 s390_irgen_CGRJ(UChar r1, UChar r2, UShort i4, UChar m3)
   3711 {
   3712    IRTemp op1 = newTemp(Ity_I64);
   3713    IRTemp op2 = newTemp(Ity_I64);
   3714    IRTemp cond = newTemp(Ity_I32);
   3715 
   3716    if (m3 == 0) {
   3717    } else {
   3718       if (m3 == 14) {
   3719          always_goto_and_chase(
   3720                 guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   3721       } else {
   3722          assign(op1, get_gpr_dw0(r1));
   3723          assign(op2, get_gpr_dw0(r2));
   3724          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_SIGNED_COMPARE,
   3725                                               op1, op2));
   3726          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3727                            guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   3728 
   3729       }
   3730    }
   3731 
   3732    return "cgrj";
   3733 }
   3734 
   3735 static HChar *
   3736 s390_irgen_CIB(UChar r1, UChar m3, UChar i2, IRTemp op4addr)
   3737 {
   3738    IRTemp op1 = newTemp(Ity_I32);
   3739    Int op2;
   3740    IRTemp cond = newTemp(Ity_I32);
   3741 
   3742    if (m3 == 0) {
   3743    } else {
   3744       if (m3 == 14) {
   3745          always_goto(mkexpr(op4addr));
   3746       } else {
   3747          assign(op1, get_gpr_w1(r1));
   3748          op2 = (Int)(Char)i2;
   3749          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_SIGNED_COMPARE, op1,
   3750                                               mktemp(Ity_I32, mkU32((UInt)op2))));
   3751          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3752                                     mkexpr(op4addr));
   3753       }
   3754    }
   3755 
   3756    return "cib";
   3757 }
   3758 
   3759 static HChar *
   3760 s390_irgen_CGIB(UChar r1, UChar m3, UChar i2, IRTemp op4addr)
   3761 {
   3762    IRTemp op1 = newTemp(Ity_I64);
   3763    Long op2;
   3764    IRTemp cond = newTemp(Ity_I32);
   3765 
   3766    if (m3 == 0) {
   3767    } else {
   3768       if (m3 == 14) {
   3769          always_goto(mkexpr(op4addr));
   3770       } else {
   3771          assign(op1, get_gpr_dw0(r1));
   3772          op2 = (Long)(Char)i2;
   3773          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_SIGNED_COMPARE, op1,
   3774                                               mktemp(Ity_I64, mkU64((ULong)op2))));
   3775          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3776                                     mkexpr(op4addr));
   3777       }
   3778    }
   3779 
   3780    return "cgib";
   3781 }
   3782 
   3783 static HChar *
   3784 s390_irgen_CIJ(UChar r1, UChar m3, UShort i4, UChar i2)
   3785 {
   3786    IRTemp op1 = newTemp(Ity_I32);
   3787    Int op2;
   3788    IRTemp cond = newTemp(Ity_I32);
   3789 
   3790    if (m3 == 0) {
   3791    } else {
   3792       if (m3 == 14) {
   3793          always_goto_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   3794       } else {
   3795          assign(op1, get_gpr_w1(r1));
   3796          op2 = (Int)(Char)i2;
   3797          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_SIGNED_COMPARE, op1,
   3798                                               mktemp(Ity_I32, mkU32((UInt)op2))));
   3799          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3800                            guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   3801 
   3802       }
   3803    }
   3804 
   3805    return "cij";
   3806 }
   3807 
   3808 static HChar *
   3809 s390_irgen_CGIJ(UChar r1, UChar m3, UShort i4, UChar i2)
   3810 {
   3811    IRTemp op1 = newTemp(Ity_I64);
   3812    Long op2;
   3813    IRTemp cond = newTemp(Ity_I32);
   3814 
   3815    if (m3 == 0) {
   3816    } else {
   3817       if (m3 == 14) {
   3818          always_goto_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   3819       } else {
   3820          assign(op1, get_gpr_dw0(r1));
   3821          op2 = (Long)(Char)i2;
   3822          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_SIGNED_COMPARE, op1,
   3823                                               mktemp(Ity_I64, mkU64((ULong)op2))));
   3824          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   3825                            guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   3826 
   3827       }
   3828    }
   3829 
   3830    return "cgij";
   3831 }
   3832 
   3833 static HChar *
   3834 s390_irgen_CH(UChar r1, IRTemp op2addr)
   3835 {
   3836    IRTemp op1 = newTemp(Ity_I32);
   3837    IRTemp op2 = newTemp(Ity_I32);
   3838 
   3839    assign(op1, get_gpr_w1(r1));
   3840    assign(op2, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   3841    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3842 
   3843    return "ch";
   3844 }
   3845 
   3846 static HChar *
   3847 s390_irgen_CHY(UChar r1, IRTemp op2addr)
   3848 {
   3849    IRTemp op1 = newTemp(Ity_I32);
   3850    IRTemp op2 = newTemp(Ity_I32);
   3851 
   3852    assign(op1, get_gpr_w1(r1));
   3853    assign(op2, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   3854    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3855 
   3856    return "chy";
   3857 }
   3858 
   3859 static HChar *
   3860 s390_irgen_CGH(UChar r1, IRTemp op2addr)
   3861 {
   3862    IRTemp op1 = newTemp(Ity_I64);
   3863    IRTemp op2 = newTemp(Ity_I64);
   3864 
   3865    assign(op1, get_gpr_dw0(r1));
   3866    assign(op2, unop(Iop_16Sto64, load(Ity_I16, mkexpr(op2addr))));
   3867    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3868 
   3869    return "cgh";
   3870 }
   3871 
   3872 static HChar *
   3873 s390_irgen_CHI(UChar r1, UShort i2)
   3874 {
   3875    IRTemp op1 = newTemp(Ity_I32);
   3876    Int op2;
   3877 
   3878    assign(op1, get_gpr_w1(r1));
   3879    op2 = (Int)(Short)i2;
   3880    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, mktemp(Ity_I32,
   3881                        mkU32((UInt)op2)));
   3882 
   3883    return "chi";
   3884 }
   3885 
   3886 static HChar *
   3887 s390_irgen_CGHI(UChar r1, UShort i2)
   3888 {
   3889    IRTemp op1 = newTemp(Ity_I64);
   3890    Long op2;
   3891 
   3892    assign(op1, get_gpr_dw0(r1));
   3893    op2 = (Long)(Short)i2;
   3894    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, mktemp(Ity_I64,
   3895                        mkU64((ULong)op2)));
   3896 
   3897    return "cghi";
   3898 }
   3899 
   3900 static HChar *
   3901 s390_irgen_CHHSI(UShort i2, IRTemp op1addr)
   3902 {
   3903    IRTemp op1 = newTemp(Ity_I16);
   3904    Short op2;
   3905 
   3906    assign(op1, load(Ity_I16, mkexpr(op1addr)));
   3907    op2 = (Short)i2;
   3908    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, mktemp(Ity_I16,
   3909                        mkU16((UShort)op2)));
   3910 
   3911    return "chhsi";
   3912 }
   3913 
   3914 static HChar *
   3915 s390_irgen_CHSI(UShort i2, IRTemp op1addr)
   3916 {
   3917    IRTemp op1 = newTemp(Ity_I32);
   3918    Int op2;
   3919 
   3920    assign(op1, load(Ity_I32, mkexpr(op1addr)));
   3921    op2 = (Int)(Short)i2;
   3922    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, mktemp(Ity_I32,
   3923                        mkU32((UInt)op2)));
   3924 
   3925    return "chsi";
   3926 }
   3927 
   3928 static HChar *
   3929 s390_irgen_CGHSI(UShort i2, IRTemp op1addr)
   3930 {
   3931    IRTemp op1 = newTemp(Ity_I64);
   3932    Long op2;
   3933 
   3934    assign(op1, load(Ity_I64, mkexpr(op1addr)));
   3935    op2 = (Long)(Short)i2;
   3936    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, mktemp(Ity_I64,
   3937                        mkU64((ULong)op2)));
   3938 
   3939    return "cghsi";
   3940 }
   3941 
   3942 static HChar *
   3943 s390_irgen_CHRL(UChar r1, UInt i2)
   3944 {
   3945    IRTemp op1 = newTemp(Ity_I32);
   3946    IRTemp op2 = newTemp(Ity_I32);
   3947 
   3948    assign(op1, get_gpr_w1(r1));
   3949    assign(op2, unop(Iop_16Sto32, load(Ity_I16, mkU64(guest_IA_curr_instr +
   3950           ((ULong)(Long)(Int)i2 << 1)))));
   3951    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3952 
   3953    return "chrl";
   3954 }
   3955 
   3956 static HChar *
   3957 s390_irgen_CGHRL(UChar r1, UInt i2)
   3958 {
   3959    IRTemp op1 = newTemp(Ity_I64);
   3960    IRTemp op2 = newTemp(Ity_I64);
   3961 
   3962    assign(op1, get_gpr_dw0(r1));
   3963    assign(op2, unop(Iop_16Sto64, load(Ity_I16, mkU64(guest_IA_curr_instr +
   3964           ((ULong)(Long)(Int)i2 << 1)))));
   3965    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3966 
   3967    return "cghrl";
   3968 }
   3969 
   3970 static HChar *
   3971 s390_irgen_CHHR(UChar r1, UChar r2)
   3972 {
   3973    IRTemp op1 = newTemp(Ity_I32);
   3974    IRTemp op2 = newTemp(Ity_I32);
   3975 
   3976    assign(op1, get_gpr_w0(r1));
   3977    assign(op2, get_gpr_w0(r2));
   3978    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3979 
   3980    return "chhr";
   3981 }
   3982 
   3983 static HChar *
   3984 s390_irgen_CHLR(UChar r1, UChar r2)
   3985 {
   3986    IRTemp op1 = newTemp(Ity_I32);
   3987    IRTemp op2 = newTemp(Ity_I32);
   3988 
   3989    assign(op1, get_gpr_w0(r1));
   3990    assign(op2, get_gpr_w1(r2));
   3991    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   3992 
   3993    return "chlr";
   3994 }
   3995 
   3996 static HChar *
   3997 s390_irgen_CHF(UChar r1, IRTemp op2addr)
   3998 {
   3999    IRTemp op1 = newTemp(Ity_I32);
   4000    IRTemp op2 = newTemp(Ity_I32);
   4001 
   4002    assign(op1, get_gpr_w0(r1));
   4003    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   4004    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, op2);
   4005 
   4006    return "chf";
   4007 }
   4008 
   4009 static HChar *
   4010 s390_irgen_CIH(UChar r1, UInt i2)
   4011 {
   4012    IRTemp op1 = newTemp(Ity_I32);
   4013    Int op2;
   4014 
   4015    assign(op1, get_gpr_w0(r1));
   4016    op2 = (Int)i2;
   4017    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_COMPARE, op1, mktemp(Ity_I32,
   4018                        mkU32((UInt)op2)));
   4019 
   4020    return "cih";
   4021 }
   4022 
   4023 static HChar *
   4024 s390_irgen_CLR(UChar r1, UChar r2)
   4025 {
   4026    IRTemp op1 = newTemp(Ity_I32);
   4027    IRTemp op2 = newTemp(Ity_I32);
   4028 
   4029    assign(op1, get_gpr_w1(r1));
   4030    assign(op2, get_gpr_w1(r2));
   4031    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4032 
   4033    return "clr";
   4034 }
   4035 
   4036 static HChar *
   4037 s390_irgen_CLGR(UChar r1, UChar r2)
   4038 {
   4039    IRTemp op1 = newTemp(Ity_I64);
   4040    IRTemp op2 = newTemp(Ity_I64);
   4041 
   4042    assign(op1, get_gpr_dw0(r1));
   4043    assign(op2, get_gpr_dw0(r2));
   4044    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4045 
   4046    return "clgr";
   4047 }
   4048 
   4049 static HChar *
   4050 s390_irgen_CLGFR(UChar r1, UChar r2)
   4051 {
   4052    IRTemp op1 = newTemp(Ity_I64);
   4053    IRTemp op2 = newTemp(Ity_I64);
   4054 
   4055    assign(op1, get_gpr_dw0(r1));
   4056    assign(op2, unop(Iop_32Uto64, get_gpr_w1(r2)));
   4057    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4058 
   4059    return "clgfr";
   4060 }
   4061 
   4062 static HChar *
   4063 s390_irgen_CL(UChar r1, IRTemp op2addr)
   4064 {
   4065    IRTemp op1 = newTemp(Ity_I32);
   4066    IRTemp op2 = newTemp(Ity_I32);
   4067 
   4068    assign(op1, get_gpr_w1(r1));
   4069    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   4070    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4071 
   4072    return "cl";
   4073 }
   4074 
   4075 static HChar *
   4076 s390_irgen_CLY(UChar r1, IRTemp op2addr)
   4077 {
   4078    IRTemp op1 = newTemp(Ity_I32);
   4079    IRTemp op2 = newTemp(Ity_I32);
   4080 
   4081    assign(op1, get_gpr_w1(r1));
   4082    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   4083    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4084 
   4085    return "cly";
   4086 }
   4087 
   4088 static HChar *
   4089 s390_irgen_CLG(UChar r1, IRTemp op2addr)
   4090 {
   4091    IRTemp op1 = newTemp(Ity_I64);
   4092    IRTemp op2 = newTemp(Ity_I64);
   4093 
   4094    assign(op1, get_gpr_dw0(r1));
   4095    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   4096    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4097 
   4098    return "clg";
   4099 }
   4100 
   4101 static HChar *
   4102 s390_irgen_CLGF(UChar r1, IRTemp op2addr)
   4103 {
   4104    IRTemp op1 = newTemp(Ity_I64);
   4105    IRTemp op2 = newTemp(Ity_I64);
   4106 
   4107    assign(op1, get_gpr_dw0(r1));
   4108    assign(op2, unop(Iop_32Uto64, load(Ity_I32, mkexpr(op2addr))));
   4109    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4110 
   4111    return "clgf";
   4112 }
   4113 
   4114 static HChar *
   4115 s390_irgen_CLFI(UChar r1, UInt i2)
   4116 {
   4117    IRTemp op1 = newTemp(Ity_I32);
   4118    UInt op2;
   4119 
   4120    assign(op1, get_gpr_w1(r1));
   4121    op2 = i2;
   4122    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, mktemp(Ity_I32,
   4123                        mkU32(op2)));
   4124 
   4125    return "clfi";
   4126 }
   4127 
   4128 static HChar *
   4129 s390_irgen_CLGFI(UChar r1, UInt i2)
   4130 {
   4131    IRTemp op1 = newTemp(Ity_I64);
   4132    ULong op2;
   4133 
   4134    assign(op1, get_gpr_dw0(r1));
   4135    op2 = (ULong)i2;
   4136    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, mktemp(Ity_I64,
   4137                        mkU64(op2)));
   4138 
   4139    return "clgfi";
   4140 }
   4141 
   4142 static HChar *
   4143 s390_irgen_CLI(UChar i2, IRTemp op1addr)
   4144 {
   4145    IRTemp op1 = newTemp(Ity_I8);
   4146    UChar op2;
   4147 
   4148    assign(op1, load(Ity_I8, mkexpr(op1addr)));
   4149    op2 = i2;
   4150    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, mktemp(Ity_I8,
   4151                        mkU8(op2)));
   4152 
   4153    return "cli";
   4154 }
   4155 
   4156 static HChar *
   4157 s390_irgen_CLIY(UChar i2, IRTemp op1addr)
   4158 {
   4159    IRTemp op1 = newTemp(Ity_I8);
   4160    UChar op2;
   4161 
   4162    assign(op1, load(Ity_I8, mkexpr(op1addr)));
   4163    op2 = i2;
   4164    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, mktemp(Ity_I8,
   4165                        mkU8(op2)));
   4166 
   4167    return "cliy";
   4168 }
   4169 
   4170 static HChar *
   4171 s390_irgen_CLFHSI(UShort i2, IRTemp op1addr)
   4172 {
   4173    IRTemp op1 = newTemp(Ity_I32);
   4174    UInt op2;
   4175 
   4176    assign(op1, load(Ity_I32, mkexpr(op1addr)));
   4177    op2 = (UInt)i2;
   4178    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, mktemp(Ity_I32,
   4179                        mkU32(op2)));
   4180 
   4181    return "clfhsi";
   4182 }
   4183 
   4184 static HChar *
   4185 s390_irgen_CLGHSI(UShort i2, IRTemp op1addr)
   4186 {
   4187    IRTemp op1 = newTemp(Ity_I64);
   4188    ULong op2;
   4189 
   4190    assign(op1, load(Ity_I64, mkexpr(op1addr)));
   4191    op2 = (ULong)i2;
   4192    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, mktemp(Ity_I64,
   4193                        mkU64(op2)));
   4194 
   4195    return "clghsi";
   4196 }
   4197 
   4198 static HChar *
   4199 s390_irgen_CLHHSI(UShort i2, IRTemp op1addr)
   4200 {
   4201    IRTemp op1 = newTemp(Ity_I16);
   4202    UShort op2;
   4203 
   4204    assign(op1, load(Ity_I16, mkexpr(op1addr)));
   4205    op2 = i2;
   4206    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, mktemp(Ity_I16,
   4207                        mkU16(op2)));
   4208 
   4209    return "clhhsi";
   4210 }
   4211 
   4212 static HChar *
   4213 s390_irgen_CLRL(UChar r1, UInt i2)
   4214 {
   4215    IRTemp op1 = newTemp(Ity_I32);
   4216    IRTemp op2 = newTemp(Ity_I32);
   4217 
   4218    assign(op1, get_gpr_w1(r1));
   4219    assign(op2, load(Ity_I32, mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)
   4220           i2 << 1))));
   4221    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4222 
   4223    return "clrl";
   4224 }
   4225 
   4226 static HChar *
   4227 s390_irgen_CLGRL(UChar r1, UInt i2)
   4228 {
   4229    IRTemp op1 = newTemp(Ity_I64);
   4230    IRTemp op2 = newTemp(Ity_I64);
   4231 
   4232    assign(op1, get_gpr_dw0(r1));
   4233    assign(op2, load(Ity_I64, mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)
   4234           i2 << 1))));
   4235    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4236 
   4237    return "clgrl";
   4238 }
   4239 
   4240 static HChar *
   4241 s390_irgen_CLGFRL(UChar r1, UInt i2)
   4242 {
   4243    IRTemp op1 = newTemp(Ity_I64);
   4244    IRTemp op2 = newTemp(Ity_I64);
   4245 
   4246    assign(op1, get_gpr_dw0(r1));
   4247    assign(op2, unop(Iop_32Uto64, load(Ity_I32, mkU64(guest_IA_curr_instr +
   4248           ((ULong)(Long)(Int)i2 << 1)))));
   4249    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4250 
   4251    return "clgfrl";
   4252 }
   4253 
   4254 static HChar *
   4255 s390_irgen_CLHRL(UChar r1, UInt i2)
   4256 {
   4257    IRTemp op1 = newTemp(Ity_I32);
   4258    IRTemp op2 = newTemp(Ity_I32);
   4259 
   4260    assign(op1, get_gpr_w1(r1));
   4261    assign(op2, unop(Iop_16Uto32, load(Ity_I16, mkU64(guest_IA_curr_instr +
   4262           ((ULong)(Long)(Int)i2 << 1)))));
   4263    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4264 
   4265    return "clhrl";
   4266 }
   4267 
   4268 static HChar *
   4269 s390_irgen_CLGHRL(UChar r1, UInt i2)
   4270 {
   4271    IRTemp op1 = newTemp(Ity_I64);
   4272    IRTemp op2 = newTemp(Ity_I64);
   4273 
   4274    assign(op1, get_gpr_dw0(r1));
   4275    assign(op2, unop(Iop_16Uto64, load(Ity_I16, mkU64(guest_IA_curr_instr +
   4276           ((ULong)(Long)(Int)i2 << 1)))));
   4277    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4278 
   4279    return "clghrl";
   4280 }
   4281 
   4282 static HChar *
   4283 s390_irgen_CLRB(UChar r1, UChar r2, UChar m3, IRTemp op4addr)
   4284 {
   4285    IRTemp op1 = newTemp(Ity_I32);
   4286    IRTemp op2 = newTemp(Ity_I32);
   4287    IRTemp cond = newTemp(Ity_I32);
   4288 
   4289    if (m3 == 0) {
   4290    } else {
   4291       if (m3 == 14) {
   4292          always_goto(mkexpr(op4addr));
   4293       } else {
   4294          assign(op1, get_gpr_w1(r1));
   4295          assign(op2, get_gpr_w1(r2));
   4296          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_UNSIGNED_COMPARE,
   4297                                               op1, op2));
   4298          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   4299                                     mkexpr(op4addr));
   4300       }
   4301    }
   4302 
   4303    return "clrb";
   4304 }
   4305 
   4306 static HChar *
   4307 s390_irgen_CLGRB(UChar r1, UChar r2, UChar m3, IRTemp op4addr)
   4308 {
   4309    IRTemp op1 = newTemp(Ity_I64);
   4310    IRTemp op2 = newTemp(Ity_I64);
   4311    IRTemp cond = newTemp(Ity_I32);
   4312 
   4313    if (m3 == 0) {
   4314    } else {
   4315       if (m3 == 14) {
   4316          always_goto(mkexpr(op4addr));
   4317       } else {
   4318          assign(op1, get_gpr_dw0(r1));
   4319          assign(op2, get_gpr_dw0(r2));
   4320          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_UNSIGNED_COMPARE,
   4321                                               op1, op2));
   4322          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   4323                                     mkexpr(op4addr));
   4324       }
   4325    }
   4326 
   4327    return "clgrb";
   4328 }
   4329 
   4330 static HChar *
   4331 s390_irgen_CLRJ(UChar r1, UChar r2, UShort i4, UChar m3)
   4332 {
   4333    IRTemp op1 = newTemp(Ity_I32);
   4334    IRTemp op2 = newTemp(Ity_I32);
   4335    IRTemp cond = newTemp(Ity_I32);
   4336 
   4337    if (m3 == 0) {
   4338    } else {
   4339       if (m3 == 14) {
   4340          always_goto_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   4341       } else {
   4342          assign(op1, get_gpr_w1(r1));
   4343          assign(op2, get_gpr_w1(r2));
   4344          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_UNSIGNED_COMPARE,
   4345                                               op1, op2));
   4346          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   4347                            guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   4348 
   4349       }
   4350    }
   4351 
   4352    return "clrj";
   4353 }
   4354 
   4355 static HChar *
   4356 s390_irgen_CLGRJ(UChar r1, UChar r2, UShort i4, UChar m3)
   4357 {
   4358    IRTemp op1 = newTemp(Ity_I64);
   4359    IRTemp op2 = newTemp(Ity_I64);
   4360    IRTemp cond = newTemp(Ity_I32);
   4361 
   4362    if (m3 == 0) {
   4363    } else {
   4364       if (m3 == 14) {
   4365          always_goto_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   4366       } else {
   4367          assign(op1, get_gpr_dw0(r1));
   4368          assign(op2, get_gpr_dw0(r2));
   4369          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_UNSIGNED_COMPARE,
   4370                                               op1, op2));
   4371          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   4372                            guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   4373 
   4374       }
   4375    }
   4376 
   4377    return "clgrj";
   4378 }
   4379 
   4380 static HChar *
   4381 s390_irgen_CLIB(UChar r1, UChar m3, UChar i2, IRTemp op4addr)
   4382 {
   4383    IRTemp op1 = newTemp(Ity_I32);
   4384    UInt op2;
   4385    IRTemp cond = newTemp(Ity_I32);
   4386 
   4387    if (m3 == 0) {
   4388    } else {
   4389       if (m3 == 14) {
   4390          always_goto(mkexpr(op4addr));
   4391       } else {
   4392          assign(op1, get_gpr_w1(r1));
   4393          op2 = (UInt)i2;
   4394          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_UNSIGNED_COMPARE, op1,
   4395                                               mktemp(Ity_I32, mkU32(op2))));
   4396          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   4397                                     mkexpr(op4addr));
   4398       }
   4399    }
   4400 
   4401    return "clib";
   4402 }
   4403 
   4404 static HChar *
   4405 s390_irgen_CLGIB(UChar r1, UChar m3, UChar i2, IRTemp op4addr)
   4406 {
   4407    IRTemp op1 = newTemp(Ity_I64);
   4408    ULong op2;
   4409    IRTemp cond = newTemp(Ity_I32);
   4410 
   4411    if (m3 == 0) {
   4412    } else {
   4413       if (m3 == 14) {
   4414          always_goto(mkexpr(op4addr));
   4415       } else {
   4416          assign(op1, get_gpr_dw0(r1));
   4417          op2 = (ULong)i2;
   4418          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_UNSIGNED_COMPARE, op1,
   4419                                               mktemp(Ity_I64, mkU64(op2))));
   4420          if_condition_goto_computed(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   4421                                     mkexpr(op4addr));
   4422       }
   4423    }
   4424 
   4425    return "clgib";
   4426 }
   4427 
   4428 static HChar *
   4429 s390_irgen_CLIJ(UChar r1, UChar m3, UShort i4, UChar i2)
   4430 {
   4431    IRTemp op1 = newTemp(Ity_I32);
   4432    UInt op2;
   4433    IRTemp cond = newTemp(Ity_I32);
   4434 
   4435    if (m3 == 0) {
   4436    } else {
   4437       if (m3 == 14) {
   4438          always_goto_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   4439       } else {
   4440          assign(op1, get_gpr_w1(r1));
   4441          op2 = (UInt)i2;
   4442          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_UNSIGNED_COMPARE, op1,
   4443                                               mktemp(Ity_I32, mkU32(op2))));
   4444          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   4445                            guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   4446 
   4447       }
   4448    }
   4449 
   4450    return "clij";
   4451 }
   4452 
   4453 static HChar *
   4454 s390_irgen_CLGIJ(UChar r1, UChar m3, UShort i4, UChar i2)
   4455 {
   4456    IRTemp op1 = newTemp(Ity_I64);
   4457    ULong op2;
   4458    IRTemp cond = newTemp(Ity_I32);
   4459 
   4460    if (m3 == 0) {
   4461    } else {
   4462       if (m3 == 14) {
   4463          always_goto_and_chase(guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   4464       } else {
   4465          assign(op1, get_gpr_dw0(r1));
   4466          op2 = (ULong)i2;
   4467          assign(cond, s390_call_calculate_icc(m3, S390_CC_OP_UNSIGNED_COMPARE, op1,
   4468                                               mktemp(Ity_I64, mkU64(op2))));
   4469          if_condition_goto(binop(Iop_CmpNE32, mkexpr(cond), mkU32(0)),
   4470                            guest_IA_curr_instr + ((ULong)(Long)(Short)i4 << 1));
   4471 
   4472       }
   4473    }
   4474 
   4475    return "clgij";
   4476 }
   4477 
   4478 static HChar *
   4479 s390_irgen_CLM(UChar r1, UChar r3, IRTemp op2addr)
   4480 {
   4481    IRTemp op1 = newTemp(Ity_I32);
   4482    IRTemp op2 = newTemp(Ity_I32);
   4483    IRTemp b0 = newTemp(Ity_I32);
   4484    IRTemp b1 = newTemp(Ity_I32);
   4485    IRTemp b2 = newTemp(Ity_I32);
   4486    IRTemp b3 = newTemp(Ity_I32);
   4487    IRTemp c0 = newTemp(Ity_I32);
   4488    IRTemp c1 = newTemp(Ity_I32);
   4489    IRTemp c2 = newTemp(Ity_I32);
   4490    IRTemp c3 = newTemp(Ity_I32);
   4491    UChar n;
   4492 
   4493    n = 0;
   4494    if ((r3 & 8) != 0) {
   4495       assign(b0, unop(Iop_8Uto32, get_gpr_b4(r1)));
   4496       assign(c0, unop(Iop_8Uto32, load(Ity_I8, mkexpr(op2addr))));
   4497       n = n + 1;
   4498    } else {
   4499       assign(b0, mkU32(0));
   4500       assign(c0, mkU32(0));
   4501    }
   4502    if ((r3 & 4) != 0) {
   4503       assign(b1, unop(Iop_8Uto32, get_gpr_b5(r1)));
   4504       assign(c1, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4505              mkU64(n)))));
   4506       n = n + 1;
   4507    } else {
   4508       assign(b1, mkU32(0));
   4509       assign(c1, mkU32(0));
   4510    }
   4511    if ((r3 & 2) != 0) {
   4512       assign(b2, unop(Iop_8Uto32, get_gpr_b6(r1)));
   4513       assign(c2, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4514              mkU64(n)))));
   4515       n = n + 1;
   4516    } else {
   4517       assign(b2, mkU32(0));
   4518       assign(c2, mkU32(0));
   4519    }
   4520    if ((r3 & 1) != 0) {
   4521       assign(b3, unop(Iop_8Uto32, get_gpr_b7(r1)));
   4522       assign(c3, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4523              mkU64(n)))));
   4524       n = n + 1;
   4525    } else {
   4526       assign(b3, mkU32(0));
   4527       assign(c3, mkU32(0));
   4528    }
   4529    assign(op1, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Shl32,
   4530           mkexpr(b0), mkU8(24)), binop(Iop_Shl32, mkexpr(b1), mkU8(16))),
   4531           binop(Iop_Shl32, mkexpr(b2), mkU8(8))), mkexpr(b3)));
   4532    assign(op2, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Shl32,
   4533           mkexpr(c0), mkU8(24)), binop(Iop_Shl32, mkexpr(c1), mkU8(16))),
   4534           binop(Iop_Shl32, mkexpr(c2), mkU8(8))), mkexpr(c3)));
   4535    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4536 
   4537    return "clm";
   4538 }
   4539 
   4540 static HChar *
   4541 s390_irgen_CLMY(UChar r1, UChar r3, IRTemp op2addr)
   4542 {
   4543    IRTemp op1 = newTemp(Ity_I32);
   4544    IRTemp op2 = newTemp(Ity_I32);
   4545    IRTemp b0 = newTemp(Ity_I32);
   4546    IRTemp b1 = newTemp(Ity_I32);
   4547    IRTemp b2 = newTemp(Ity_I32);
   4548    IRTemp b3 = newTemp(Ity_I32);
   4549    IRTemp c0 = newTemp(Ity_I32);
   4550    IRTemp c1 = newTemp(Ity_I32);
   4551    IRTemp c2 = newTemp(Ity_I32);
   4552    IRTemp c3 = newTemp(Ity_I32);
   4553    UChar n;
   4554 
   4555    n = 0;
   4556    if ((r3 & 8) != 0) {
   4557       assign(b0, unop(Iop_8Uto32, get_gpr_b4(r1)));
   4558       assign(c0, unop(Iop_8Uto32, load(Ity_I8, mkexpr(op2addr))));
   4559       n = n + 1;
   4560    } else {
   4561       assign(b0, mkU32(0));
   4562       assign(c0, mkU32(0));
   4563    }
   4564    if ((r3 & 4) != 0) {
   4565       assign(b1, unop(Iop_8Uto32, get_gpr_b5(r1)));
   4566       assign(c1, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4567              mkU64(n)))));
   4568       n = n + 1;
   4569    } else {
   4570       assign(b1, mkU32(0));
   4571       assign(c1, mkU32(0));
   4572    }
   4573    if ((r3 & 2) != 0) {
   4574       assign(b2, unop(Iop_8Uto32, get_gpr_b6(r1)));
   4575       assign(c2, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4576              mkU64(n)))));
   4577       n = n + 1;
   4578    } else {
   4579       assign(b2, mkU32(0));
   4580       assign(c2, mkU32(0));
   4581    }
   4582    if ((r3 & 1) != 0) {
   4583       assign(b3, unop(Iop_8Uto32, get_gpr_b7(r1)));
   4584       assign(c3, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4585              mkU64(n)))));
   4586       n = n + 1;
   4587    } else {
   4588       assign(b3, mkU32(0));
   4589       assign(c3, mkU32(0));
   4590    }
   4591    assign(op1, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Shl32,
   4592           mkexpr(b0), mkU8(24)), binop(Iop_Shl32, mkexpr(b1), mkU8(16))),
   4593           binop(Iop_Shl32, mkexpr(b2), mkU8(8))), mkexpr(b3)));
   4594    assign(op2, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Shl32,
   4595           mkexpr(c0), mkU8(24)), binop(Iop_Shl32, mkexpr(c1), mkU8(16))),
   4596           binop(Iop_Shl32, mkexpr(c2), mkU8(8))), mkexpr(c3)));
   4597    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4598 
   4599    return "clmy";
   4600 }
   4601 
   4602 static HChar *
   4603 s390_irgen_CLMH(UChar r1, UChar r3, IRTemp op2addr)
   4604 {
   4605    IRTemp op1 = newTemp(Ity_I32);
   4606    IRTemp op2 = newTemp(Ity_I32);
   4607    IRTemp b0 = newTemp(Ity_I32);
   4608    IRTemp b1 = newTemp(Ity_I32);
   4609    IRTemp b2 = newTemp(Ity_I32);
   4610    IRTemp b3 = newTemp(Ity_I32);
   4611    IRTemp c0 = newTemp(Ity_I32);
   4612    IRTemp c1 = newTemp(Ity_I32);
   4613    IRTemp c2 = newTemp(Ity_I32);
   4614    IRTemp c3 = newTemp(Ity_I32);
   4615    UChar n;
   4616 
   4617    n = 0;
   4618    if ((r3 & 8) != 0) {
   4619       assign(b0, unop(Iop_8Uto32, get_gpr_b0(r1)));
   4620       assign(c0, unop(Iop_8Uto32, load(Ity_I8, mkexpr(op2addr))));
   4621       n = n + 1;
   4622    } else {
   4623       assign(b0, mkU32(0));
   4624       assign(c0, mkU32(0));
   4625    }
   4626    if ((r3 & 4) != 0) {
   4627       assign(b1, unop(Iop_8Uto32, get_gpr_b1(r1)));
   4628       assign(c1, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4629              mkU64(n)))));
   4630       n = n + 1;
   4631    } else {
   4632       assign(b1, mkU32(0));
   4633       assign(c1, mkU32(0));
   4634    }
   4635    if ((r3 & 2) != 0) {
   4636       assign(b2, unop(Iop_8Uto32, get_gpr_b2(r1)));
   4637       assign(c2, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4638              mkU64(n)))));
   4639       n = n + 1;
   4640    } else {
   4641       assign(b2, mkU32(0));
   4642       assign(c2, mkU32(0));
   4643    }
   4644    if ((r3 & 1) != 0) {
   4645       assign(b3, unop(Iop_8Uto32, get_gpr_b3(r1)));
   4646       assign(c3, unop(Iop_8Uto32, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr),
   4647              mkU64(n)))));
   4648       n = n + 1;
   4649    } else {
   4650       assign(b3, mkU32(0));
   4651       assign(c3, mkU32(0));
   4652    }
   4653    assign(op1, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Shl32,
   4654           mkexpr(b0), mkU8(24)), binop(Iop_Shl32, mkexpr(b1), mkU8(16))),
   4655           binop(Iop_Shl32, mkexpr(b2), mkU8(8))), mkexpr(b3)));
   4656    assign(op2, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Or32, binop(Iop_Shl32,
   4657           mkexpr(c0), mkU8(24)), binop(Iop_Shl32, mkexpr(c1), mkU8(16))),
   4658           binop(Iop_Shl32, mkexpr(c2), mkU8(8))), mkexpr(c3)));
   4659    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4660 
   4661    return "clmh";
   4662 }
   4663 
   4664 static HChar *
   4665 s390_irgen_CLHHR(UChar r1, UChar r2)
   4666 {
   4667    IRTemp op1 = newTemp(Ity_I32);
   4668    IRTemp op2 = newTemp(Ity_I32);
   4669 
   4670    assign(op1, get_gpr_w0(r1));
   4671    assign(op2, get_gpr_w0(r2));
   4672    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4673 
   4674    return "clhhr";
   4675 }
   4676 
   4677 static HChar *
   4678 s390_irgen_CLHLR(UChar r1, UChar r2)
   4679 {
   4680    IRTemp op1 = newTemp(Ity_I32);
   4681    IRTemp op2 = newTemp(Ity_I32);
   4682 
   4683    assign(op1, get_gpr_w0(r1));
   4684    assign(op2, get_gpr_w1(r2));
   4685    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4686 
   4687    return "clhlr";
   4688 }
   4689 
   4690 static HChar *
   4691 s390_irgen_CLHF(UChar r1, IRTemp op2addr)
   4692 {
   4693    IRTemp op1 = newTemp(Ity_I32);
   4694    IRTemp op2 = newTemp(Ity_I32);
   4695 
   4696    assign(op1, get_gpr_w0(r1));
   4697    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   4698    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, op2);
   4699 
   4700    return "clhf";
   4701 }
   4702 
   4703 static HChar *
   4704 s390_irgen_CLIH(UChar r1, UInt i2)
   4705 {
   4706    IRTemp op1 = newTemp(Ity_I32);
   4707    UInt op2;
   4708 
   4709    assign(op1, get_gpr_w0(r1));
   4710    op2 = i2;
   4711    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_COMPARE, op1, mktemp(Ity_I32,
   4712                        mkU32(op2)));
   4713 
   4714    return "clih";
   4715 }
   4716 
   4717 static HChar *
   4718 s390_irgen_CPYA(UChar r1, UChar r2)
   4719 {
   4720    put_ar_w0(r1, get_ar_w0(r2));
   4721    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   4722       s390_disasm(ENC3(MNM, AR, AR), "cpya", r1, r2);
   4723 
   4724    return "cpya";
   4725 }
   4726 
   4727 static HChar *
   4728 s390_irgen_XR(UChar r1, UChar r2)
   4729 {
   4730    IRTemp op1 = newTemp(Ity_I32);
   4731    IRTemp op2 = newTemp(Ity_I32);
   4732    IRTemp result = newTemp(Ity_I32);
   4733 
   4734    if (r1 == r2) {
   4735       assign(result, mkU32(0));
   4736    } else {
   4737       assign(op1, get_gpr_w1(r1));
   4738       assign(op2, get_gpr_w1(r2));
   4739       assign(result, binop(Iop_Xor32, mkexpr(op1), mkexpr(op2)));
   4740    }
   4741    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4742    put_gpr_w1(r1, mkexpr(result));
   4743 
   4744    return "xr";
   4745 }
   4746 
   4747 static HChar *
   4748 s390_irgen_XGR(UChar r1, UChar r2)
   4749 {
   4750    IRTemp op1 = newTemp(Ity_I64);
   4751    IRTemp op2 = newTemp(Ity_I64);
   4752    IRTemp result = newTemp(Ity_I64);
   4753 
   4754    if (r1 == r2) {
   4755       assign(result, mkU64(0));
   4756    } else {
   4757       assign(op1, get_gpr_dw0(r1));
   4758       assign(op2, get_gpr_dw0(r2));
   4759       assign(result, binop(Iop_Xor64, mkexpr(op1), mkexpr(op2)));
   4760    }
   4761    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4762    put_gpr_dw0(r1, mkexpr(result));
   4763 
   4764    return "xgr";
   4765 }
   4766 
   4767 static HChar *
   4768 s390_irgen_XRK(UChar r3, UChar r1, UChar r2)
   4769 {
   4770    IRTemp op2 = newTemp(Ity_I32);
   4771    IRTemp op3 = newTemp(Ity_I32);
   4772    IRTemp result = newTemp(Ity_I32);
   4773 
   4774    assign(op2, get_gpr_w1(r2));
   4775    assign(op3, get_gpr_w1(r3));
   4776    assign(result, binop(Iop_Xor32, mkexpr(op2), mkexpr(op3)));
   4777    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4778    put_gpr_w1(r1, mkexpr(result));
   4779 
   4780    return "xrk";
   4781 }
   4782 
   4783 static HChar *
   4784 s390_irgen_XGRK(UChar r3, UChar r1, UChar r2)
   4785 {
   4786    IRTemp op2 = newTemp(Ity_I64);
   4787    IRTemp op3 = newTemp(Ity_I64);
   4788    IRTemp result = newTemp(Ity_I64);
   4789 
   4790    assign(op2, get_gpr_dw0(r2));
   4791    assign(op3, get_gpr_dw0(r3));
   4792    assign(result, binop(Iop_Xor64, mkexpr(op2), mkexpr(op3)));
   4793    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4794    put_gpr_dw0(r1, mkexpr(result));
   4795 
   4796    return "xgrk";
   4797 }
   4798 
   4799 static HChar *
   4800 s390_irgen_X(UChar r1, IRTemp op2addr)
   4801 {
   4802    IRTemp op1 = newTemp(Ity_I32);
   4803    IRTemp op2 = newTemp(Ity_I32);
   4804    IRTemp result = newTemp(Ity_I32);
   4805 
   4806    assign(op1, get_gpr_w1(r1));
   4807    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   4808    assign(result, binop(Iop_Xor32, mkexpr(op1), mkexpr(op2)));
   4809    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4810    put_gpr_w1(r1, mkexpr(result));
   4811 
   4812    return "x";
   4813 }
   4814 
   4815 static HChar *
   4816 s390_irgen_XY(UChar r1, IRTemp op2addr)
   4817 {
   4818    IRTemp op1 = newTemp(Ity_I32);
   4819    IRTemp op2 = newTemp(Ity_I32);
   4820    IRTemp result = newTemp(Ity_I32);
   4821 
   4822    assign(op1, get_gpr_w1(r1));
   4823    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   4824    assign(result, binop(Iop_Xor32, mkexpr(op1), mkexpr(op2)));
   4825    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4826    put_gpr_w1(r1, mkexpr(result));
   4827 
   4828    return "xy";
   4829 }
   4830 
   4831 static HChar *
   4832 s390_irgen_XG(UChar r1, IRTemp op2addr)
   4833 {
   4834    IRTemp op1 = newTemp(Ity_I64);
   4835    IRTemp op2 = newTemp(Ity_I64);
   4836    IRTemp result = newTemp(Ity_I64);
   4837 
   4838    assign(op1, get_gpr_dw0(r1));
   4839    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   4840    assign(result, binop(Iop_Xor64, mkexpr(op1), mkexpr(op2)));
   4841    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4842    put_gpr_dw0(r1, mkexpr(result));
   4843 
   4844    return "xg";
   4845 }
   4846 
   4847 static HChar *
   4848 s390_irgen_XI(UChar i2, IRTemp op1addr)
   4849 {
   4850    IRTemp op1 = newTemp(Ity_I8);
   4851    UChar op2;
   4852    IRTemp result = newTemp(Ity_I8);
   4853 
   4854    assign(op1, load(Ity_I8, mkexpr(op1addr)));
   4855    op2 = i2;
   4856    assign(result, binop(Iop_Xor8, mkexpr(op1), mkU8(op2)));
   4857    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4858    store(mkexpr(op1addr), mkexpr(result));
   4859 
   4860    return "xi";
   4861 }
   4862 
   4863 static HChar *
   4864 s390_irgen_XIY(UChar i2, IRTemp op1addr)
   4865 {
   4866    IRTemp op1 = newTemp(Ity_I8);
   4867    UChar op2;
   4868    IRTemp result = newTemp(Ity_I8);
   4869 
   4870    assign(op1, load(Ity_I8, mkexpr(op1addr)));
   4871    op2 = i2;
   4872    assign(result, binop(Iop_Xor8, mkexpr(op1), mkU8(op2)));
   4873    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4874    store(mkexpr(op1addr), mkexpr(result));
   4875 
   4876    return "xiy";
   4877 }
   4878 
   4879 static HChar *
   4880 s390_irgen_XIHF(UChar r1, UInt i2)
   4881 {
   4882    IRTemp op1 = newTemp(Ity_I32);
   4883    UInt op2;
   4884    IRTemp result = newTemp(Ity_I32);
   4885 
   4886    assign(op1, get_gpr_w0(r1));
   4887    op2 = i2;
   4888    assign(result, binop(Iop_Xor32, mkexpr(op1), mkU32(op2)));
   4889    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4890    put_gpr_w0(r1, mkexpr(result));
   4891 
   4892    return "xihf";
   4893 }
   4894 
   4895 static HChar *
   4896 s390_irgen_XILF(UChar r1, UInt i2)
   4897 {
   4898    IRTemp op1 = newTemp(Ity_I32);
   4899    UInt op2;
   4900    IRTemp result = newTemp(Ity_I32);
   4901 
   4902    assign(op1, get_gpr_w1(r1));
   4903    op2 = i2;
   4904    assign(result, binop(Iop_Xor32, mkexpr(op1), mkU32(op2)));
   4905    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   4906    put_gpr_w1(r1, mkexpr(result));
   4907 
   4908    return "xilf";
   4909 }
   4910 
   4911 static HChar *
   4912 s390_irgen_EAR(UChar r1, UChar r2)
   4913 {
   4914    put_gpr_w1(r1, get_ar_w0(r2));
   4915    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   4916       s390_disasm(ENC3(MNM, GPR, AR), "ear", r1, r2);
   4917 
   4918    return "ear";
   4919 }
   4920 
   4921 static HChar *
   4922 s390_irgen_IC(UChar r1, IRTemp op2addr)
   4923 {
   4924    put_gpr_b7(r1, load(Ity_I8, mkexpr(op2addr)));
   4925 
   4926    return "ic";
   4927 }
   4928 
   4929 static HChar *
   4930 s390_irgen_ICY(UChar r1, IRTemp op2addr)
   4931 {
   4932    put_gpr_b7(r1, load(Ity_I8, mkexpr(op2addr)));
   4933 
   4934    return "icy";
   4935 }
   4936 
   4937 static HChar *
   4938 s390_irgen_ICM(UChar r1, UChar r3, IRTemp op2addr)
   4939 {
   4940    UChar n;
   4941    IRTemp result = newTemp(Ity_I32);
   4942    UInt mask;
   4943 
   4944    n = 0;
   4945    mask = (UInt)r3;
   4946    if ((mask & 8) != 0) {
   4947       put_gpr_b4(r1, load(Ity_I8, mkexpr(op2addr)));
   4948       n = n + 1;
   4949    }
   4950    if ((mask & 4) != 0) {
   4951       put_gpr_b5(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   4952 
   4953       n = n + 1;
   4954    }
   4955    if ((mask & 2) != 0) {
   4956       put_gpr_b6(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   4957 
   4958       n = n + 1;
   4959    }
   4960    if ((mask & 1) != 0) {
   4961       put_gpr_b7(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   4962 
   4963       n = n + 1;
   4964    }
   4965    assign(result, get_gpr_w1(r1));
   4966    s390_cc_thunk_putZZ(S390_CC_OP_INSERT_CHAR_MASK_32, result, mktemp(Ity_I32,
   4967                        mkU32(mask)));
   4968 
   4969    return "icm";
   4970 }
   4971 
   4972 static HChar *
   4973 s390_irgen_ICMY(UChar r1, UChar r3, IRTemp op2addr)
   4974 {
   4975    UChar n;
   4976    IRTemp result = newTemp(Ity_I32);
   4977    UInt mask;
   4978 
   4979    n = 0;
   4980    mask = (UInt)r3;
   4981    if ((mask & 8) != 0) {
   4982       put_gpr_b4(r1, load(Ity_I8, mkexpr(op2addr)));
   4983       n = n + 1;
   4984    }
   4985    if ((mask & 4) != 0) {
   4986       put_gpr_b5(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   4987 
   4988       n = n + 1;
   4989    }
   4990    if ((mask & 2) != 0) {
   4991       put_gpr_b6(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   4992 
   4993       n = n + 1;
   4994    }
   4995    if ((mask & 1) != 0) {
   4996       put_gpr_b7(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   4997 
   4998       n = n + 1;
   4999    }
   5000    assign(result, get_gpr_w1(r1));
   5001    s390_cc_thunk_putZZ(S390_CC_OP_INSERT_CHAR_MASK_32, result, mktemp(Ity_I32,
   5002                        mkU32(mask)));
   5003 
   5004    return "icmy";
   5005 }
   5006 
   5007 static HChar *
   5008 s390_irgen_ICMH(UChar r1, UChar r3, IRTemp op2addr)
   5009 {
   5010    UChar n;
   5011    IRTemp result = newTemp(Ity_I32);
   5012    UInt mask;
   5013 
   5014    n = 0;
   5015    mask = (UInt)r3;
   5016    if ((mask & 8) != 0) {
   5017       put_gpr_b0(r1, load(Ity_I8, mkexpr(op2addr)));
   5018       n = n + 1;
   5019    }
   5020    if ((mask & 4) != 0) {
   5021       put_gpr_b1(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   5022 
   5023       n = n + 1;
   5024    }
   5025    if ((mask & 2) != 0) {
   5026       put_gpr_b2(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   5027 
   5028       n = n + 1;
   5029    }
   5030    if ((mask & 1) != 0) {
   5031       put_gpr_b3(r1, load(Ity_I8, binop(Iop_Add64, mkexpr(op2addr), mkU64(n))));
   5032 
   5033       n = n + 1;
   5034    }
   5035    assign(result, get_gpr_w0(r1));
   5036    s390_cc_thunk_putZZ(S390_CC_OP_INSERT_CHAR_MASK_32, result, mktemp(Ity_I32,
   5037                        mkU32(mask)));
   5038 
   5039    return "icmh";
   5040 }
   5041 
   5042 static HChar *
   5043 s390_irgen_IIHF(UChar r1, UInt i2)
   5044 {
   5045    put_gpr_w0(r1, mkU32(i2));
   5046 
   5047    return "iihf";
   5048 }
   5049 
   5050 static HChar *
   5051 s390_irgen_IIHH(UChar r1, UShort i2)
   5052 {
   5053    put_gpr_hw0(r1, mkU16(i2));
   5054 
   5055    return "iihh";
   5056 }
   5057 
   5058 static HChar *
   5059 s390_irgen_IIHL(UChar r1, UShort i2)
   5060 {
   5061    put_gpr_hw1(r1, mkU16(i2));
   5062 
   5063    return "iihl";
   5064 }
   5065 
   5066 static HChar *
   5067 s390_irgen_IILF(UChar r1, UInt i2)
   5068 {
   5069    put_gpr_w1(r1, mkU32(i2));
   5070 
   5071    return "iilf";
   5072 }
   5073 
   5074 static HChar *
   5075 s390_irgen_IILH(UChar r1, UShort i2)
   5076 {
   5077    put_gpr_hw2(r1, mkU16(i2));
   5078 
   5079    return "iilh";
   5080 }
   5081 
   5082 static HChar *
   5083 s390_irgen_IILL(UChar r1, UShort i2)
   5084 {
   5085    put_gpr_hw3(r1, mkU16(i2));
   5086 
   5087    return "iill";
   5088 }
   5089 
   5090 static HChar *
   5091 s390_irgen_LR(UChar r1, UChar r2)
   5092 {
   5093    put_gpr_w1(r1, get_gpr_w1(r2));
   5094 
   5095    return "lr";
   5096 }
   5097 
   5098 static HChar *
   5099 s390_irgen_LGR(UChar r1, UChar r2)
   5100 {
   5101    put_gpr_dw0(r1, get_gpr_dw0(r2));
   5102 
   5103    return "lgr";
   5104 }
   5105 
   5106 static HChar *
   5107 s390_irgen_LGFR(UChar r1, UChar r2)
   5108 {
   5109    put_gpr_dw0(r1, unop(Iop_32Sto64, get_gpr_w1(r2)));
   5110 
   5111    return "lgfr";
   5112 }
   5113 
   5114 static HChar *
   5115 s390_irgen_L(UChar r1, IRTemp op2addr)
   5116 {
   5117    put_gpr_w1(r1, load(Ity_I32, mkexpr(op2addr)));
   5118 
   5119    return "l";
   5120 }
   5121 
   5122 static HChar *
   5123 s390_irgen_LY(UChar r1, IRTemp op2addr)
   5124 {
   5125    put_gpr_w1(r1, load(Ity_I32, mkexpr(op2addr)));
   5126 
   5127    return "ly";
   5128 }
   5129 
   5130 static HChar *
   5131 s390_irgen_LG(UChar r1, IRTemp op2addr)
   5132 {
   5133    put_gpr_dw0(r1, load(Ity_I64, mkexpr(op2addr)));
   5134 
   5135    return "lg";
   5136 }
   5137 
   5138 static HChar *
   5139 s390_irgen_LGF(UChar r1, IRTemp op2addr)
   5140 {
   5141    put_gpr_dw0(r1, unop(Iop_32Sto64, load(Ity_I32, mkexpr(op2addr))));
   5142 
   5143    return "lgf";
   5144 }
   5145 
   5146 static HChar *
   5147 s390_irgen_LGFI(UChar r1, UInt i2)
   5148 {
   5149    put_gpr_dw0(r1, mkU64((ULong)(Long)(Int)i2));
   5150 
   5151    return "lgfi";
   5152 }
   5153 
   5154 static HChar *
   5155 s390_irgen_LRL(UChar r1, UInt i2)
   5156 {
   5157    put_gpr_w1(r1, load(Ity_I32, mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)
   5158               i2 << 1))));
   5159 
   5160    return "lrl";
   5161 }
   5162 
   5163 static HChar *
   5164 s390_irgen_LGRL(UChar r1, UInt i2)
   5165 {
   5166    put_gpr_dw0(r1, load(Ity_I64, mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)
   5167                i2 << 1))));
   5168 
   5169    return "lgrl";
   5170 }
   5171 
   5172 static HChar *
   5173 s390_irgen_LGFRL(UChar r1, UInt i2)
   5174 {
   5175    put_gpr_dw0(r1, unop(Iop_32Sto64, load(Ity_I32, mkU64(guest_IA_curr_instr +
   5176                ((ULong)(Long)(Int)i2 << 1)))));
   5177 
   5178    return "lgfrl";
   5179 }
   5180 
   5181 static HChar *
   5182 s390_irgen_LA(UChar r1, IRTemp op2addr)
   5183 {
   5184    put_gpr_dw0(r1, mkexpr(op2addr));
   5185 
   5186    return "la";
   5187 }
   5188 
   5189 static HChar *
   5190 s390_irgen_LAY(UChar r1, IRTemp op2addr)
   5191 {
   5192    put_gpr_dw0(r1, mkexpr(op2addr));
   5193 
   5194    return "lay";
   5195 }
   5196 
   5197 static HChar *
   5198 s390_irgen_LAE(UChar r1, IRTemp op2addr)
   5199 {
   5200    put_gpr_dw0(r1, mkexpr(op2addr));
   5201 
   5202    return "lae";
   5203 }
   5204 
   5205 static HChar *
   5206 s390_irgen_LAEY(UChar r1, IRTemp op2addr)
   5207 {
   5208    put_gpr_dw0(r1, mkexpr(op2addr));
   5209 
   5210    return "laey";
   5211 }
   5212 
   5213 static HChar *
   5214 s390_irgen_LARL(UChar r1, UInt i2)
   5215 {
   5216    put_gpr_dw0(r1, mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)i2 << 1)));
   5217 
   5218    return "larl";
   5219 }
   5220 
   5221 static HChar *
   5222 s390_irgen_LAA(UChar r1, UChar r3, IRTemp op2addr)
   5223 {
   5224    IRTemp op2 = newTemp(Ity_I32);
   5225    IRTemp op3 = newTemp(Ity_I32);
   5226    IRTemp result = newTemp(Ity_I32);
   5227 
   5228    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   5229    assign(op3, get_gpr_w1(r3));
   5230    assign(result, binop(Iop_Add32, mkexpr(op2), mkexpr(op3)));
   5231    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_32, op2, op3);
   5232    store(mkexpr(op2addr), mkexpr(result));
   5233    put_gpr_w1(r1, mkexpr(op2));
   5234 
   5235    return "laa";
   5236 }
   5237 
   5238 static HChar *
   5239 s390_irgen_LAAG(UChar r1, UChar r3, IRTemp op2addr)
   5240 {
   5241    IRTemp op2 = newTemp(Ity_I64);
   5242    IRTemp op3 = newTemp(Ity_I64);
   5243    IRTemp result = newTemp(Ity_I64);
   5244 
   5245    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   5246    assign(op3, get_gpr_dw0(r3));
   5247    assign(result, binop(Iop_Add64, mkexpr(op2), mkexpr(op3)));
   5248    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_ADD_64, op2, op3);
   5249    store(mkexpr(op2addr), mkexpr(result));
   5250    put_gpr_dw0(r1, mkexpr(op2));
   5251 
   5252    return "laag";
   5253 }
   5254 
   5255 static HChar *
   5256 s390_irgen_LAAL(UChar r1, UChar r3, IRTemp op2addr)
   5257 {
   5258    IRTemp op2 = newTemp(Ity_I32);
   5259    IRTemp op3 = newTemp(Ity_I32);
   5260    IRTemp result = newTemp(Ity_I32);
   5261 
   5262    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   5263    assign(op3, get_gpr_w1(r3));
   5264    assign(result, binop(Iop_Add32, mkexpr(op2), mkexpr(op3)));
   5265    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_32, op2, op3);
   5266    store(mkexpr(op2addr), mkexpr(result));
   5267    put_gpr_w1(r1, mkexpr(op2));
   5268 
   5269    return "laal";
   5270 }
   5271 
   5272 static HChar *
   5273 s390_irgen_LAALG(UChar r1, UChar r3, IRTemp op2addr)
   5274 {
   5275    IRTemp op2 = newTemp(Ity_I64);
   5276    IRTemp op3 = newTemp(Ity_I64);
   5277    IRTemp result = newTemp(Ity_I64);
   5278 
   5279    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   5280    assign(op3, get_gpr_dw0(r3));
   5281    assign(result, binop(Iop_Add64, mkexpr(op2), mkexpr(op3)));
   5282    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_ADD_64, op2, op3);
   5283    store(mkexpr(op2addr), mkexpr(result));
   5284    put_gpr_dw0(r1, mkexpr(op2));
   5285 
   5286    return "laalg";
   5287 }
   5288 
   5289 static HChar *
   5290 s390_irgen_LAN(UChar r1, UChar r3, IRTemp op2addr)
   5291 {
   5292    IRTemp op2 = newTemp(Ity_I32);
   5293    IRTemp op3 = newTemp(Ity_I32);
   5294    IRTemp result = newTemp(Ity_I32);
   5295 
   5296    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   5297    assign(op3, get_gpr_w1(r3));
   5298    assign(result, binop(Iop_And32, mkexpr(op2), mkexpr(op3)));
   5299    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   5300    store(mkexpr(op2addr), mkexpr(result));
   5301    put_gpr_w1(r1, mkexpr(op2));
   5302 
   5303    return "lan";
   5304 }
   5305 
   5306 static HChar *
   5307 s390_irgen_LANG(UChar r1, UChar r3, IRTemp op2addr)
   5308 {
   5309    IRTemp op2 = newTemp(Ity_I64);
   5310    IRTemp op3 = newTemp(Ity_I64);
   5311    IRTemp result = newTemp(Ity_I64);
   5312 
   5313    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   5314    assign(op3, get_gpr_dw0(r3));
   5315    assign(result, binop(Iop_And64, mkexpr(op2), mkexpr(op3)));
   5316    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   5317    store(mkexpr(op2addr), mkexpr(result));
   5318    put_gpr_dw0(r1, mkexpr(op2));
   5319 
   5320    return "lang";
   5321 }
   5322 
   5323 static HChar *
   5324 s390_irgen_LAX(UChar r1, UChar r3, IRTemp op2addr)
   5325 {
   5326    IRTemp op2 = newTemp(Ity_I32);
   5327    IRTemp op3 = newTemp(Ity_I32);
   5328    IRTemp result = newTemp(Ity_I32);
   5329 
   5330    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   5331    assign(op3, get_gpr_w1(r3));
   5332    assign(result, binop(Iop_Xor32, mkexpr(op2), mkexpr(op3)));
   5333    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   5334    store(mkexpr(op2addr), mkexpr(result));
   5335    put_gpr_w1(r1, mkexpr(op2));
   5336 
   5337    return "lax";
   5338 }
   5339 
   5340 static HChar *
   5341 s390_irgen_LAXG(UChar r1, UChar r3, IRTemp op2addr)
   5342 {
   5343    IRTemp op2 = newTemp(Ity_I64);
   5344    IRTemp op3 = newTemp(Ity_I64);
   5345    IRTemp result = newTemp(Ity_I64);
   5346 
   5347    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   5348    assign(op3, get_gpr_dw0(r3));
   5349    assign(result, binop(Iop_Xor64, mkexpr(op2), mkexpr(op3)));
   5350    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   5351    store(mkexpr(op2addr), mkexpr(result));
   5352    put_gpr_dw0(r1, mkexpr(op2));
   5353 
   5354    return "laxg";
   5355 }
   5356 
   5357 static HChar *
   5358 s390_irgen_LAO(UChar r1, UChar r3, IRTemp op2addr)
   5359 {
   5360    IRTemp op2 = newTemp(Ity_I32);
   5361    IRTemp op3 = newTemp(Ity_I32);
   5362    IRTemp result = newTemp(Ity_I32);
   5363 
   5364    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   5365    assign(op3, get_gpr_w1(r3));
   5366    assign(result, binop(Iop_Or32, mkexpr(op2), mkexpr(op3)));
   5367    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   5368    store(mkexpr(op2addr), mkexpr(result));
   5369    put_gpr_w1(r1, mkexpr(op2));
   5370 
   5371    return "lao";
   5372 }
   5373 
   5374 static HChar *
   5375 s390_irgen_LAOG(UChar r1, UChar r3, IRTemp op2addr)
   5376 {
   5377    IRTemp op2 = newTemp(Ity_I64);
   5378    IRTemp op3 = newTemp(Ity_I64);
   5379    IRTemp result = newTemp(Ity_I64);
   5380 
   5381    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   5382    assign(op3, get_gpr_dw0(r3));
   5383    assign(result, binop(Iop_Or64, mkexpr(op2), mkexpr(op3)));
   5384    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   5385    store(mkexpr(op2addr), mkexpr(result));
   5386    put_gpr_dw0(r1, mkexpr(op2));
   5387 
   5388    return "laog";
   5389 }
   5390 
   5391 static HChar *
   5392 s390_irgen_LTR(UChar r1, UChar r2)
   5393 {
   5394    IRTemp op2 = newTemp(Ity_I32);
   5395 
   5396    assign(op2, get_gpr_w1(r2));
   5397    put_gpr_w1(r1, mkexpr(op2));
   5398    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, op2);
   5399 
   5400    return "ltr";
   5401 }
   5402 
   5403 static HChar *
   5404 s390_irgen_LTGR(UChar r1, UChar r2)
   5405 {
   5406    IRTemp op2 = newTemp(Ity_I64);
   5407 
   5408    assign(op2, get_gpr_dw0(r2));
   5409    put_gpr_dw0(r1, mkexpr(op2));
   5410    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, op2);
   5411 
   5412    return "ltgr";
   5413 }
   5414 
   5415 static HChar *
   5416 s390_irgen_LTGFR(UChar r1, UChar r2)
   5417 {
   5418    IRTemp op2 = newTemp(Ity_I64);
   5419 
   5420    assign(op2, unop(Iop_32Sto64, get_gpr_w1(r2)));
   5421    put_gpr_dw0(r1, mkexpr(op2));
   5422    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, op2);
   5423 
   5424    return "ltgfr";
   5425 }
   5426 
   5427 static HChar *
   5428 s390_irgen_LT(UChar r1, IRTemp op2addr)
   5429 {
   5430    IRTemp op2 = newTemp(Ity_I32);
   5431 
   5432    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   5433    put_gpr_w1(r1, mkexpr(op2));
   5434    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, op2);
   5435 
   5436    return "lt";
   5437 }
   5438 
   5439 static HChar *
   5440 s390_irgen_LTG(UChar r1, IRTemp op2addr)
   5441 {
   5442    IRTemp op2 = newTemp(Ity_I64);
   5443 
   5444    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   5445    put_gpr_dw0(r1, mkexpr(op2));
   5446    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, op2);
   5447 
   5448    return "ltg";
   5449 }
   5450 
   5451 static HChar *
   5452 s390_irgen_LTGF(UChar r1, IRTemp op2addr)
   5453 {
   5454    IRTemp op2 = newTemp(Ity_I64);
   5455 
   5456    assign(op2, unop(Iop_32Sto64, load(Ity_I32, mkexpr(op2addr))));
   5457    put_gpr_dw0(r1, mkexpr(op2));
   5458    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, op2);
   5459 
   5460    return "ltgf";
   5461 }
   5462 
   5463 static HChar *
   5464 s390_irgen_LBR(UChar r1, UChar r2)
   5465 {
   5466    put_gpr_w1(r1, unop(Iop_8Sto32, get_gpr_b7(r2)));
   5467 
   5468    return "lbr";
   5469 }
   5470 
   5471 static HChar *
   5472 s390_irgen_LGBR(UChar r1, UChar r2)
   5473 {
   5474    put_gpr_dw0(r1, unop(Iop_8Sto64, get_gpr_b7(r2)));
   5475 
   5476    return "lgbr";
   5477 }
   5478 
   5479 static HChar *
   5480 s390_irgen_LB(UChar r1, IRTemp op2addr)
   5481 {
   5482    put_gpr_w1(r1, unop(Iop_8Sto32, load(Ity_I8, mkexpr(op2addr))));
   5483 
   5484    return "lb";
   5485 }
   5486 
   5487 static HChar *
   5488 s390_irgen_LGB(UChar r1, IRTemp op2addr)
   5489 {
   5490    put_gpr_dw0(r1, unop(Iop_8Sto64, load(Ity_I8, mkexpr(op2addr))));
   5491 
   5492    return "lgb";
   5493 }
   5494 
   5495 static HChar *
   5496 s390_irgen_LBH(UChar r1, IRTemp op2addr)
   5497 {
   5498    put_gpr_w0(r1, unop(Iop_8Sto32, load(Ity_I8, mkexpr(op2addr))));
   5499 
   5500    return "lbh";
   5501 }
   5502 
   5503 static HChar *
   5504 s390_irgen_LCR(UChar r1, UChar r2)
   5505 {
   5506    Int op1;
   5507    IRTemp op2 = newTemp(Ity_I32);
   5508    IRTemp result = newTemp(Ity_I32);
   5509 
   5510    op1 = 0;
   5511    assign(op2, get_gpr_w1(r2));
   5512    assign(result, binop(Iop_Sub32, mkU32((UInt)op1), mkexpr(op2)));
   5513    put_gpr_w1(r1, mkexpr(result));
   5514    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, mktemp(Ity_I32, mkU32((UInt)
   5515                        op1)), op2);
   5516 
   5517    return "lcr";
   5518 }
   5519 
   5520 static HChar *
   5521 s390_irgen_LCGR(UChar r1, UChar r2)
   5522 {
   5523    Long op1;
   5524    IRTemp op2 = newTemp(Ity_I64);
   5525    IRTemp result = newTemp(Ity_I64);
   5526 
   5527    op1 = 0ULL;
   5528    assign(op2, get_gpr_dw0(r2));
   5529    assign(result, binop(Iop_Sub64, mkU64((ULong)op1), mkexpr(op2)));
   5530    put_gpr_dw0(r1, mkexpr(result));
   5531    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_64, mktemp(Ity_I64, mkU64((ULong)
   5532                        op1)), op2);
   5533 
   5534    return "lcgr";
   5535 }
   5536 
   5537 static HChar *
   5538 s390_irgen_LCGFR(UChar r1, UChar r2)
   5539 {
   5540    Long op1;
   5541    IRTemp op2 = newTemp(Ity_I64);
   5542    IRTemp result = newTemp(Ity_I64);
   5543 
   5544    op1 = 0ULL;
   5545    assign(op2, unop(Iop_32Sto64, get_gpr_w1(r2)));
   5546    assign(result, binop(Iop_Sub64, mkU64((ULong)op1), mkexpr(op2)));
   5547    put_gpr_dw0(r1, mkexpr(result));
   5548    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_64, mktemp(Ity_I64, mkU64((ULong)
   5549                        op1)), op2);
   5550 
   5551    return "lcgfr";
   5552 }
   5553 
   5554 static HChar *
   5555 s390_irgen_LHR(UChar r1, UChar r2)
   5556 {
   5557    put_gpr_w1(r1, unop(Iop_16Sto32, get_gpr_hw3(r2)));
   5558 
   5559    return "lhr";
   5560 }
   5561 
   5562 static HChar *
   5563 s390_irgen_LGHR(UChar r1, UChar r2)
   5564 {
   5565    put_gpr_dw0(r1, unop(Iop_16Sto64, get_gpr_hw3(r2)));
   5566 
   5567    return "lghr";
   5568 }
   5569 
   5570 static HChar *
   5571 s390_irgen_LH(UChar r1, IRTemp op2addr)
   5572 {
   5573    put_gpr_w1(r1, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   5574 
   5575    return "lh";
   5576 }
   5577 
   5578 static HChar *
   5579 s390_irgen_LHY(UChar r1, IRTemp op2addr)
   5580 {
   5581    put_gpr_w1(r1, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   5582 
   5583    return "lhy";
   5584 }
   5585 
   5586 static HChar *
   5587 s390_irgen_LGH(UChar r1, IRTemp op2addr)
   5588 {
   5589    put_gpr_dw0(r1, unop(Iop_16Sto64, load(Ity_I16, mkexpr(op2addr))));
   5590 
   5591    return "lgh";
   5592 }
   5593 
   5594 static HChar *
   5595 s390_irgen_LHI(UChar r1, UShort i2)
   5596 {
   5597    put_gpr_w1(r1, mkU32((UInt)(Int)(Short)i2));
   5598 
   5599    return "lhi";
   5600 }
   5601 
   5602 static HChar *
   5603 s390_irgen_LGHI(UChar r1, UShort i2)
   5604 {
   5605    put_gpr_dw0(r1, mkU64((ULong)(Long)(Short)i2));
   5606 
   5607    return "lghi";
   5608 }
   5609 
   5610 static HChar *
   5611 s390_irgen_LHRL(UChar r1, UInt i2)
   5612 {
   5613    put_gpr_w1(r1, unop(Iop_16Sto32, load(Ity_I16, mkU64(guest_IA_curr_instr +
   5614               ((ULong)(Long)(Int)i2 << 1)))));
   5615 
   5616    return "lhrl";
   5617 }
   5618 
   5619 static HChar *
   5620 s390_irgen_LGHRL(UChar r1, UInt i2)
   5621 {
   5622    put_gpr_dw0(r1, unop(Iop_16Sto64, load(Ity_I16, mkU64(guest_IA_curr_instr +
   5623                ((ULong)(Long)(Int)i2 << 1)))));
   5624 
   5625    return "lghrl";
   5626 }
   5627 
   5628 static HChar *
   5629 s390_irgen_LHH(UChar r1, IRTemp op2addr)
   5630 {
   5631    put_gpr_w0(r1, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   5632 
   5633    return "lhh";
   5634 }
   5635 
   5636 static HChar *
   5637 s390_irgen_LFH(UChar r1, IRTemp op2addr)
   5638 {
   5639    put_gpr_w0(r1, load(Ity_I32, mkexpr(op2addr)));
   5640 
   5641    return "lfh";
   5642 }
   5643 
   5644 static HChar *
   5645 s390_irgen_LLGFR(UChar r1, UChar r2)
   5646 {
   5647    put_gpr_dw0(r1, unop(Iop_32Uto64, get_gpr_w1(r2)));
   5648 
   5649    return "llgfr";
   5650 }
   5651 
   5652 static HChar *
   5653 s390_irgen_LLGF(UChar r1, IRTemp op2addr)
   5654 {
   5655    put_gpr_dw0(r1, unop(Iop_32Uto64, load(Ity_I32, mkexpr(op2addr))));
   5656 
   5657    return "llgf";
   5658 }
   5659 
   5660 static HChar *
   5661 s390_irgen_LLGFRL(UChar r1, UInt i2)
   5662 {
   5663    put_gpr_dw0(r1, unop(Iop_32Uto64, load(Ity_I32, mkU64(guest_IA_curr_instr +
   5664                ((ULong)(Long)(Int)i2 << 1)))));
   5665 
   5666    return "llgfrl";
   5667 }
   5668 
   5669 static HChar *
   5670 s390_irgen_LLCR(UChar r1, UChar r2)
   5671 {
   5672    put_gpr_w1(r1, unop(Iop_8Uto32, get_gpr_b7(r2)));
   5673 
   5674    return "llcr";
   5675 }
   5676 
   5677 static HChar *
   5678 s390_irgen_LLGCR(UChar r1, UChar r2)
   5679 {
   5680    put_gpr_dw0(r1, unop(Iop_8Uto64, get_gpr_b7(r2)));
   5681 
   5682    return "llgcr";
   5683 }
   5684 
   5685 static HChar *
   5686 s390_irgen_LLC(UChar r1, IRTemp op2addr)
   5687 {
   5688    put_gpr_w1(r1, unop(Iop_8Uto32, load(Ity_I8, mkexpr(op2addr))));
   5689 
   5690    return "llc";
   5691 }
   5692 
   5693 static HChar *
   5694 s390_irgen_LLGC(UChar r1, IRTemp op2addr)
   5695 {
   5696    put_gpr_dw0(r1, unop(Iop_8Uto64, load(Ity_I8, mkexpr(op2addr))));
   5697 
   5698    return "llgc";
   5699 }
   5700 
   5701 static HChar *
   5702 s390_irgen_LLCH(UChar r1, IRTemp op2addr)
   5703 {
   5704    put_gpr_w0(r1, unop(Iop_8Uto32, load(Ity_I8, mkexpr(op2addr))));
   5705 
   5706    return "llch";
   5707 }
   5708 
   5709 static HChar *
   5710 s390_irgen_LLHR(UChar r1, UChar r2)
   5711 {
   5712    put_gpr_w1(r1, unop(Iop_16Uto32, get_gpr_hw3(r2)));
   5713 
   5714    return "llhr";
   5715 }
   5716 
   5717 static HChar *
   5718 s390_irgen_LLGHR(UChar r1, UChar r2)
   5719 {
   5720    put_gpr_dw0(r1, unop(Iop_16Uto64, get_gpr_hw3(r2)));
   5721 
   5722    return "llghr";
   5723 }
   5724 
   5725 static HChar *
   5726 s390_irgen_LLH(UChar r1, IRTemp op2addr)
   5727 {
   5728    put_gpr_w1(r1, unop(Iop_16Uto32, load(Ity_I16, mkexpr(op2addr))));
   5729 
   5730    return "llh";
   5731 }
   5732 
   5733 static HChar *
   5734 s390_irgen_LLGH(UChar r1, IRTemp op2addr)
   5735 {
   5736    put_gpr_dw0(r1, unop(Iop_16Uto64, load(Ity_I16, mkexpr(op2addr))));
   5737 
   5738    return "llgh";
   5739 }
   5740 
   5741 static HChar *
   5742 s390_irgen_LLHRL(UChar r1, UInt i2)
   5743 {
   5744    put_gpr_w1(r1, unop(Iop_16Uto32, load(Ity_I16, mkU64(guest_IA_curr_instr +
   5745               ((ULong)(Long)(Int)i2 << 1)))));
   5746 
   5747    return "llhrl";
   5748 }
   5749 
   5750 static HChar *
   5751 s390_irgen_LLGHRL(UChar r1, UInt i2)
   5752 {
   5753    put_gpr_dw0(r1, unop(Iop_16Uto64, load(Ity_I16, mkU64(guest_IA_curr_instr +
   5754                ((ULong)(Long)(Int)i2 << 1)))));
   5755 
   5756    return "llghrl";
   5757 }
   5758 
   5759 static HChar *
   5760 s390_irgen_LLHH(UChar r1, IRTemp op2addr)
   5761 {
   5762    put_gpr_w0(r1, unop(Iop_16Uto32, load(Ity_I16, mkexpr(op2addr))));
   5763 
   5764    return "llhh";
   5765 }
   5766 
   5767 static HChar *
   5768 s390_irgen_LLIHF(UChar r1, UInt i2)
   5769 {
   5770    put_gpr_dw0(r1, mkU64(((ULong)i2) << 32));
   5771 
   5772    return "llihf";
   5773 }
   5774 
   5775 static HChar *
   5776 s390_irgen_LLIHH(UChar r1, UShort i2)
   5777 {
   5778    put_gpr_dw0(r1, mkU64(((ULong)i2) << 48));
   5779 
   5780    return "llihh";
   5781 }
   5782 
   5783 static HChar *
   5784 s390_irgen_LLIHL(UChar r1, UShort i2)
   5785 {
   5786    put_gpr_dw0(r1, mkU64(((ULong)i2) << 32));
   5787 
   5788    return "llihl";
   5789 }
   5790 
   5791 static HChar *
   5792 s390_irgen_LLILF(UChar r1, UInt i2)
   5793 {
   5794    put_gpr_dw0(r1, mkU64(i2));
   5795 
   5796    return "llilf";
   5797 }
   5798 
   5799 static HChar *
   5800 s390_irgen_LLILH(UChar r1, UShort i2)
   5801 {
   5802    put_gpr_dw0(r1, mkU64(((ULong)i2) << 16));
   5803 
   5804    return "llilh";
   5805 }
   5806 
   5807 static HChar *
   5808 s390_irgen_LLILL(UChar r1, UShort i2)
   5809 {
   5810    put_gpr_dw0(r1, mkU64(i2));
   5811 
   5812    return "llill";
   5813 }
   5814 
   5815 static HChar *
   5816 s390_irgen_LLGTR(UChar r1, UChar r2)
   5817 {
   5818    put_gpr_dw0(r1, unop(Iop_32Uto64, binop(Iop_And32, get_gpr_w1(r2),
   5819                mkU32(2147483647))));
   5820 
   5821    return "llgtr";
   5822 }
   5823 
   5824 static HChar *
   5825 s390_irgen_LLGT(UChar r1, IRTemp op2addr)
   5826 {
   5827    put_gpr_dw0(r1, unop(Iop_32Uto64, binop(Iop_And32, load(Ity_I32,
   5828                mkexpr(op2addr)), mkU32(2147483647))));
   5829 
   5830    return "llgt";
   5831 }
   5832 
   5833 static HChar *
   5834 s390_irgen_LNR(UChar r1, UChar r2)
   5835 {
   5836    IRTemp op2 = newTemp(Ity_I32);
   5837    IRTemp result = newTemp(Ity_I32);
   5838 
   5839    assign(op2, get_gpr_w1(r2));
   5840    assign(result, mkite(binop(Iop_CmpLE32S, mkexpr(op2), mkU32(0)), mkexpr(op2),
   5841           binop(Iop_Sub32, mkU32(0), mkexpr(op2))));
   5842    put_gpr_w1(r1, mkexpr(result));
   5843    s390_cc_thunk_putS(S390_CC_OP_BITWISE, result);
   5844 
   5845    return "lnr";
   5846 }
   5847 
   5848 static HChar *
   5849 s390_irgen_LNGR(UChar r1, UChar r2)
   5850 {
   5851    IRTemp op2 = newTemp(Ity_I64);
   5852    IRTemp result = newTemp(Ity_I64);
   5853 
   5854    assign(op2, get_gpr_dw0(r2));
   5855    assign(result, mkite(binop(Iop_CmpLE64S, mkexpr(op2), mkU64(0)), mkexpr(op2),
   5856           binop(Iop_Sub64, mkU64(0), mkexpr(op2))));
   5857    put_gpr_dw0(r1, mkexpr(result));
   5858    s390_cc_thunk_putS(S390_CC_OP_BITWISE, result);
   5859 
   5860    return "lngr";
   5861 }
   5862 
   5863 static HChar *
   5864 s390_irgen_LNGFR(UChar r1, UChar r2 __attribute__((unused)))
   5865 {
   5866    IRTemp op2 = newTemp(Ity_I64);
   5867    IRTemp result = newTemp(Ity_I64);
   5868 
   5869    assign(op2, unop(Iop_32Sto64, get_gpr_w1(r1)));
   5870    assign(result, mkite(binop(Iop_CmpLE64S, mkexpr(op2), mkU64(0)), mkexpr(op2),
   5871           binop(Iop_Sub64, mkU64(0), mkexpr(op2))));
   5872    put_gpr_dw0(r1, mkexpr(result));
   5873    s390_cc_thunk_putS(S390_CC_OP_BITWISE, result);
   5874 
   5875    return "lngfr";
   5876 }
   5877 
   5878 static HChar *
   5879 s390_irgen_LOCR(UChar m3, UChar r1, UChar r2)
   5880 {
   5881    next_insn_if(binop(Iop_CmpEQ32, s390_call_calculate_cond(m3), mkU32(0)));
   5882    put_gpr_w1(r1, get_gpr_w1(r2));
   5883 
   5884    return "locr";
   5885 }
   5886 
   5887 static HChar *
   5888 s390_irgen_LOCGR(UChar m3, UChar r1, UChar r2)
   5889 {
   5890    next_insn_if(binop(Iop_CmpEQ32, s390_call_calculate_cond(m3), mkU32(0)));
   5891    put_gpr_dw0(r1, get_gpr_dw0(r2));
   5892 
   5893    return "locgr";
   5894 }
   5895 
   5896 static HChar *
   5897 s390_irgen_LOC(UChar r1, IRTemp op2addr)
   5898 {
   5899    /* condition is checked in format handler */
   5900    put_gpr_w1(r1, load(Ity_I32, mkexpr(op2addr)));
   5901 
   5902    return "loc";
   5903 }
   5904 
   5905 static HChar *
   5906 s390_irgen_LOCG(UChar r1, IRTemp op2addr)
   5907 {
   5908    /* condition is checked in format handler */
   5909    put_gpr_dw0(r1, load(Ity_I64, mkexpr(op2addr)));
   5910 
   5911    return "locg";
   5912 }
   5913 
   5914 static HChar *
   5915 s390_irgen_LPQ(UChar r1, IRTemp op2addr)
   5916 {
   5917    put_gpr_dw0(r1, load(Ity_I64, mkexpr(op2addr)));
   5918    put_gpr_dw0(r1 + 1, load(Ity_I64, binop(Iop_Add64, mkexpr(op2addr), mkU64(8))
   5919                ));
   5920 
   5921    return "lpq";
   5922 }
   5923 
   5924 static HChar *
   5925 s390_irgen_LPR(UChar r1, UChar r2)
   5926 {
   5927    IRTemp op2 = newTemp(Ity_I32);
   5928    IRTemp result = newTemp(Ity_I32);
   5929 
   5930    assign(op2, get_gpr_w1(r2));
   5931    assign(result, mkite(binop(Iop_CmpLT32S, mkexpr(op2), mkU32(0)),
   5932           binop(Iop_Sub32, mkU32(0), mkexpr(op2)), mkexpr(op2)));
   5933    put_gpr_w1(r1, mkexpr(result));
   5934    s390_cc_thunk_putS(S390_CC_OP_LOAD_POSITIVE_32, op2);
   5935 
   5936    return "lpr";
   5937 }
   5938 
   5939 static HChar *
   5940 s390_irgen_LPGR(UChar r1, UChar r2)
   5941 {
   5942    IRTemp op2 = newTemp(Ity_I64);
   5943    IRTemp result = newTemp(Ity_I64);
   5944 
   5945    assign(op2, get_gpr_dw0(r2));
   5946    assign(result, mkite(binop(Iop_CmpLT64S, mkexpr(op2), mkU64(0)),
   5947           binop(Iop_Sub64, mkU64(0), mkexpr(op2)), mkexpr(op2)));
   5948    put_gpr_dw0(r1, mkexpr(result));
   5949    s390_cc_thunk_putS(S390_CC_OP_LOAD_POSITIVE_64, op2);
   5950 
   5951    return "lpgr";
   5952 }
   5953 
   5954 static HChar *
   5955 s390_irgen_LPGFR(UChar r1, UChar r2)
   5956 {
   5957    IRTemp op2 = newTemp(Ity_I64);
   5958    IRTemp result = newTemp(Ity_I64);
   5959 
   5960    assign(op2, unop(Iop_32Sto64, get_gpr_w1(r2)));
   5961    assign(result, mkite(binop(Iop_CmpLT64S, mkexpr(op2), mkU64(0)),
   5962           binop(Iop_Sub64, mkU64(0), mkexpr(op2)), mkexpr(op2)));
   5963    put_gpr_dw0(r1, mkexpr(result));
   5964    s390_cc_thunk_putS(S390_CC_OP_LOAD_POSITIVE_64, op2);
   5965 
   5966    return "lpgfr";
   5967 }
   5968 
   5969 static HChar *
   5970 s390_irgen_LRVR(UChar r1, UChar r2)
   5971 {
   5972    IRTemp b0 = newTemp(Ity_I8);
   5973    IRTemp b1 = newTemp(Ity_I8);
   5974    IRTemp b2 = newTemp(Ity_I8);
   5975    IRTemp b3 = newTemp(Ity_I8);
   5976 
   5977    assign(b3, get_gpr_b7(r2));
   5978    assign(b2, get_gpr_b6(r2));
   5979    assign(b1, get_gpr_b5(r2));
   5980    assign(b0, get_gpr_b4(r2));
   5981    put_gpr_b4(r1, mkexpr(b3));
   5982    put_gpr_b5(r1, mkexpr(b2));
   5983    put_gpr_b6(r1, mkexpr(b1));
   5984    put_gpr_b7(r1, mkexpr(b0));
   5985 
   5986    return "lrvr";
   5987 }
   5988 
   5989 static HChar *
   5990 s390_irgen_LRVGR(UChar r1, UChar r2)
   5991 {
   5992    IRTemp b0 = newTemp(Ity_I8);
   5993    IRTemp b1 = newTemp(Ity_I8);
   5994    IRTemp b2 = newTemp(Ity_I8);
   5995    IRTemp b3 = newTemp(Ity_I8);
   5996    IRTemp b4 = newTemp(Ity_I8);
   5997    IRTemp b5 = newTemp(Ity_I8);
   5998    IRTemp b6 = newTemp(Ity_I8);
   5999    IRTemp b7 = newTemp(Ity_I8);
   6000 
   6001    assign(b7, get_gpr_b7(r2));
   6002    assign(b6, get_gpr_b6(r2));
   6003    assign(b5, get_gpr_b5(r2));
   6004    assign(b4, get_gpr_b4(r2));
   6005    assign(b3, get_gpr_b3(r2));
   6006    assign(b2, get_gpr_b2(r2));
   6007    assign(b1, get_gpr_b1(r2));
   6008    assign(b0, get_gpr_b0(r2));
   6009    put_gpr_b0(r1, mkexpr(b7));
   6010    put_gpr_b1(r1, mkexpr(b6));
   6011    put_gpr_b2(r1, mkexpr(b5));
   6012    put_gpr_b3(r1, mkexpr(b4));
   6013    put_gpr_b4(r1, mkexpr(b3));
   6014    put_gpr_b5(r1, mkexpr(b2));
   6015    put_gpr_b6(r1, mkexpr(b1));
   6016    put_gpr_b7(r1, mkexpr(b0));
   6017 
   6018    return "lrvgr";
   6019 }
   6020 
   6021 static HChar *
   6022 s390_irgen_LRVH(UChar r1, IRTemp op2addr)
   6023 {
   6024    IRTemp op2 = newTemp(Ity_I16);
   6025 
   6026    assign(op2, load(Ity_I16, mkexpr(op2addr)));
   6027    put_gpr_b6(r1, unop(Iop_16to8, mkexpr(op2)));
   6028    put_gpr_b7(r1, unop(Iop_16HIto8, mkexpr(op2)));
   6029 
   6030    return "lrvh";
   6031 }
   6032 
   6033 static HChar *
   6034 s390_irgen_LRV(UChar r1, IRTemp op2addr)
   6035 {
   6036    IRTemp op2 = newTemp(Ity_I32);
   6037 
   6038    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6039    put_gpr_b4(r1, unop(Iop_32to8, binop(Iop_And32, mkexpr(op2), mkU32(255))));
   6040    put_gpr_b5(r1, unop(Iop_32to8, binop(Iop_And32, binop(Iop_Shr32, mkexpr(op2),
   6041               mkU8(8)), mkU32(255))));
   6042    put_gpr_b6(r1, unop(Iop_32to8, binop(Iop_And32, binop(Iop_Shr32, mkexpr(op2),
   6043               mkU8(16)), mkU32(255))));
   6044    put_gpr_b7(r1, unop(Iop_32to8, binop(Iop_And32, binop(Iop_Shr32, mkexpr(op2),
   6045               mkU8(24)), mkU32(255))));
   6046 
   6047    return "lrv";
   6048 }
   6049 
   6050 static HChar *
   6051 s390_irgen_LRVG(UChar r1, IRTemp op2addr)
   6052 {
   6053    IRTemp op2 = newTemp(Ity_I64);
   6054 
   6055    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   6056    put_gpr_b0(r1, unop(Iop_64to8, binop(Iop_And64, mkexpr(op2), mkU64(255))));
   6057    put_gpr_b1(r1, unop(Iop_64to8, binop(Iop_And64, binop(Iop_Shr64, mkexpr(op2),
   6058               mkU8(8)), mkU64(255))));
   6059    put_gpr_b2(r1, unop(Iop_64to8, binop(Iop_And64, binop(Iop_Shr64, mkexpr(op2),
   6060               mkU8(16)), mkU64(255))));
   6061    put_gpr_b3(r1, unop(Iop_64to8, binop(Iop_And64, binop(Iop_Shr64, mkexpr(op2),
   6062               mkU8(24)), mkU64(255))));
   6063    put_gpr_b4(r1, unop(Iop_64to8, binop(Iop_And64, binop(Iop_Shr64, mkexpr(op2),
   6064               mkU8(32)), mkU64(255))));
   6065    put_gpr_b5(r1, unop(Iop_64to8, binop(Iop_And64, binop(Iop_Shr64, mkexpr(op2),
   6066               mkU8(40)), mkU64(255))));
   6067    put_gpr_b6(r1, unop(Iop_64to8, binop(Iop_And64, binop(Iop_Shr64, mkexpr(op2),
   6068               mkU8(48)), mkU64(255))));
   6069    put_gpr_b7(r1, unop(Iop_64to8, binop(Iop_And64, binop(Iop_Shr64, mkexpr(op2),
   6070               mkU8(56)), mkU64(255))));
   6071 
   6072    return "lrvg";
   6073 }
   6074 
   6075 static HChar *
   6076 s390_irgen_MVHHI(UShort i2, IRTemp op1addr)
   6077 {
   6078    store(mkexpr(op1addr), mkU16(i2));
   6079 
   6080    return "mvhhi";
   6081 }
   6082 
   6083 static HChar *
   6084 s390_irgen_MVHI(UShort i2, IRTemp op1addr)
   6085 {
   6086    store(mkexpr(op1addr), mkU32((UInt)(Int)(Short)i2));
   6087 
   6088    return "mvhi";
   6089 }
   6090 
   6091 static HChar *
   6092 s390_irgen_MVGHI(UShort i2, IRTemp op1addr)
   6093 {
   6094    store(mkexpr(op1addr), mkU64((ULong)(Long)(Short)i2));
   6095 
   6096    return "mvghi";
   6097 }
   6098 
   6099 static HChar *
   6100 s390_irgen_MVI(UChar i2, IRTemp op1addr)
   6101 {
   6102    store(mkexpr(op1addr), mkU8(i2));
   6103 
   6104    return "mvi";
   6105 }
   6106 
   6107 static HChar *
   6108 s390_irgen_MVIY(UChar i2, IRTemp op1addr)
   6109 {
   6110    store(mkexpr(op1addr), mkU8(i2));
   6111 
   6112    return "mviy";
   6113 }
   6114 
   6115 static HChar *
   6116 s390_irgen_MR(UChar r1, UChar r2)
   6117 {
   6118    IRTemp op1 = newTemp(Ity_I32);
   6119    IRTemp op2 = newTemp(Ity_I32);
   6120    IRTemp result = newTemp(Ity_I64);
   6121 
   6122    assign(op1, get_gpr_w1(r1 + 1));
   6123    assign(op2, get_gpr_w1(r2));
   6124    assign(result, binop(Iop_MullS32, mkexpr(op1), mkexpr(op2)));
   6125    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   6126    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   6127 
   6128    return "mr";
   6129 }
   6130 
   6131 static HChar *
   6132 s390_irgen_M(UChar r1, IRTemp op2addr)
   6133 {
   6134    IRTemp op1 = newTemp(Ity_I32);
   6135    IRTemp op2 = newTemp(Ity_I32);
   6136    IRTemp result = newTemp(Ity_I64);
   6137 
   6138    assign(op1, get_gpr_w1(r1 + 1));
   6139    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6140    assign(result, binop(Iop_MullS32, mkexpr(op1), mkexpr(op2)));
   6141    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   6142    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   6143 
   6144    return "m";
   6145 }
   6146 
   6147 static HChar *
   6148 s390_irgen_MFY(UChar r1, IRTemp op2addr)
   6149 {
   6150    IRTemp op1 = newTemp(Ity_I32);
   6151    IRTemp op2 = newTemp(Ity_I32);
   6152    IRTemp result = newTemp(Ity_I64);
   6153 
   6154    assign(op1, get_gpr_w1(r1 + 1));
   6155    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6156    assign(result, binop(Iop_MullS32, mkexpr(op1), mkexpr(op2)));
   6157    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   6158    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   6159 
   6160    return "mfy";
   6161 }
   6162 
   6163 static HChar *
   6164 s390_irgen_MH(UChar r1, IRTemp op2addr)
   6165 {
   6166    IRTemp op1 = newTemp(Ity_I32);
   6167    IRTemp op2 = newTemp(Ity_I16);
   6168    IRTemp result = newTemp(Ity_I64);
   6169 
   6170    assign(op1, get_gpr_w1(r1));
   6171    assign(op2, load(Ity_I16, mkexpr(op2addr)));
   6172    assign(result, binop(Iop_MullS32, mkexpr(op1), unop(Iop_16Sto32, mkexpr(op2))
   6173           ));
   6174    put_gpr_w1(r1, unop(Iop_64to32, mkexpr(result)));
   6175 
   6176    return "mh";
   6177 }
   6178 
   6179 static HChar *
   6180 s390_irgen_MHY(UChar r1, IRTemp op2addr)
   6181 {
   6182    IRTemp op1 = newTemp(Ity_I32);
   6183    IRTemp op2 = newTemp(Ity_I16);
   6184    IRTemp result = newTemp(Ity_I64);
   6185 
   6186    assign(op1, get_gpr_w1(r1));
   6187    assign(op2, load(Ity_I16, mkexpr(op2addr)));
   6188    assign(result, binop(Iop_MullS32, mkexpr(op1), unop(Iop_16Sto32, mkexpr(op2))
   6189           ));
   6190    put_gpr_w1(r1, unop(Iop_64to32, mkexpr(result)));
   6191 
   6192    return "mhy";
   6193 }
   6194 
   6195 static HChar *
   6196 s390_irgen_MHI(UChar r1, UShort i2)
   6197 {
   6198    IRTemp op1 = newTemp(Ity_I32);
   6199    Short op2;
   6200    IRTemp result = newTemp(Ity_I64);
   6201 
   6202    assign(op1, get_gpr_w1(r1));
   6203    op2 = (Short)i2;
   6204    assign(result, binop(Iop_MullS32, mkexpr(op1), unop(Iop_16Sto32,
   6205           mkU16((UShort)op2))));
   6206    put_gpr_w1(r1, unop(Iop_64to32, mkexpr(result)));
   6207 
   6208    return "mhi";
   6209 }
   6210 
   6211 static HChar *
   6212 s390_irgen_MGHI(UChar r1, UShort i2)
   6213 {
   6214    IRTemp op1 = newTemp(Ity_I64);
   6215    Short op2;
   6216    IRTemp result = newTemp(Ity_I128);
   6217 
   6218    assign(op1, get_gpr_dw0(r1));
   6219    op2 = (Short)i2;
   6220    assign(result, binop(Iop_MullS64, mkexpr(op1), unop(Iop_16Sto64,
   6221           mkU16((UShort)op2))));
   6222    put_gpr_dw0(r1, unop(Iop_128to64, mkexpr(result)));
   6223 
   6224    return "mghi";
   6225 }
   6226 
   6227 static HChar *
   6228 s390_irgen_MLR(UChar r1, UChar r2)
   6229 {
   6230    IRTemp op1 = newTemp(Ity_I32);
   6231    IRTemp op2 = newTemp(Ity_I32);
   6232    IRTemp result = newTemp(Ity_I64);
   6233 
   6234    assign(op1, get_gpr_w1(r1 + 1));
   6235    assign(op2, get_gpr_w1(r2));
   6236    assign(result, binop(Iop_MullU32, mkexpr(op1), mkexpr(op2)));
   6237    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   6238    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   6239 
   6240    return "mlr";
   6241 }
   6242 
   6243 static HChar *
   6244 s390_irgen_MLGR(UChar r1, UChar r2)
   6245 {
   6246    IRTemp op1 = newTemp(Ity_I64);
   6247    IRTemp op2 = newTemp(Ity_I64);
   6248    IRTemp result = newTemp(Ity_I128);
   6249 
   6250    assign(op1, get_gpr_dw0(r1 + 1));
   6251    assign(op2, get_gpr_dw0(r2));
   6252    assign(result, binop(Iop_MullU64, mkexpr(op1), mkexpr(op2)));
   6253    put_gpr_dw0(r1, unop(Iop_128HIto64, mkexpr(result)));
   6254    put_gpr_dw0(r1 + 1, unop(Iop_128to64, mkexpr(result)));
   6255 
   6256    return "mlgr";
   6257 }
   6258 
   6259 static HChar *
   6260 s390_irgen_ML(UChar r1, IRTemp op2addr)
   6261 {
   6262    IRTemp op1 = newTemp(Ity_I32);
   6263    IRTemp op2 = newTemp(Ity_I32);
   6264    IRTemp result = newTemp(Ity_I64);
   6265 
   6266    assign(op1, get_gpr_w1(r1 + 1));
   6267    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6268    assign(result, binop(Iop_MullU32, mkexpr(op1), mkexpr(op2)));
   6269    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   6270    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   6271 
   6272    return "ml";
   6273 }
   6274 
   6275 static HChar *
   6276 s390_irgen_MLG(UChar r1, IRTemp op2addr)
   6277 {
   6278    IRTemp op1 = newTemp(Ity_I64);
   6279    IRTemp op2 = newTemp(Ity_I64);
   6280    IRTemp result = newTemp(Ity_I128);
   6281 
   6282    assign(op1, get_gpr_dw0(r1 + 1));
   6283    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   6284    assign(result, binop(Iop_MullU64, mkexpr(op1), mkexpr(op2)));
   6285    put_gpr_dw0(r1, unop(Iop_128HIto64, mkexpr(result)));
   6286    put_gpr_dw0(r1 + 1, unop(Iop_128to64, mkexpr(result)));
   6287 
   6288    return "mlg";
   6289 }
   6290 
   6291 static HChar *
   6292 s390_irgen_MSR(UChar r1, UChar r2)
   6293 {
   6294    IRTemp op1 = newTemp(Ity_I32);
   6295    IRTemp op2 = newTemp(Ity_I32);
   6296    IRTemp result = newTemp(Ity_I64);
   6297 
   6298    assign(op1, get_gpr_w1(r1));
   6299    assign(op2, get_gpr_w1(r2));
   6300    assign(result, binop(Iop_MullS32, mkexpr(op1), mkexpr(op2)));
   6301    put_gpr_w1(r1, unop(Iop_64to32, mkexpr(result)));
   6302 
   6303    return "msr";
   6304 }
   6305 
   6306 static HChar *
   6307 s390_irgen_MSGR(UChar r1, UChar r2)
   6308 {
   6309    IRTemp op1 = newTemp(Ity_I64);
   6310    IRTemp op2 = newTemp(Ity_I64);
   6311    IRTemp result = newTemp(Ity_I128);
   6312 
   6313    assign(op1, get_gpr_dw0(r1));
   6314    assign(op2, get_gpr_dw0(r2));
   6315    assign(result, binop(Iop_MullS64, mkexpr(op1), mkexpr(op2)));
   6316    put_gpr_dw0(r1, unop(Iop_128to64, mkexpr(result)));
   6317 
   6318    return "msgr";
   6319 }
   6320 
   6321 static HChar *
   6322 s390_irgen_MSGFR(UChar r1, UChar r2)
   6323 {
   6324    IRTemp op1 = newTemp(Ity_I64);
   6325    IRTemp op2 = newTemp(Ity_I32);
   6326    IRTemp result = newTemp(Ity_I128);
   6327 
   6328    assign(op1, get_gpr_dw0(r1));
   6329    assign(op2, get_gpr_w1(r2));
   6330    assign(result, binop(Iop_MullS64, mkexpr(op1), unop(Iop_32Sto64, mkexpr(op2))
   6331           ));
   6332    put_gpr_dw0(r1, unop(Iop_128to64, mkexpr(result)));
   6333 
   6334    return "msgfr";
   6335 }
   6336 
   6337 static HChar *
   6338 s390_irgen_MS(UChar r1, IRTemp op2addr)
   6339 {
   6340    IRTemp op1 = newTemp(Ity_I32);
   6341    IRTemp op2 = newTemp(Ity_I32);
   6342    IRTemp result = newTemp(Ity_I64);
   6343 
   6344    assign(op1, get_gpr_w1(r1));
   6345    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6346    assign(result, binop(Iop_MullS32, mkexpr(op1), mkexpr(op2)));
   6347    put_gpr_w1(r1, unop(Iop_64to32, mkexpr(result)));
   6348 
   6349    return "ms";
   6350 }
   6351 
   6352 static HChar *
   6353 s390_irgen_MSY(UChar r1, IRTemp op2addr)
   6354 {
   6355    IRTemp op1 = newTemp(Ity_I32);
   6356    IRTemp op2 = newTemp(Ity_I32);
   6357    IRTemp result = newTemp(Ity_I64);
   6358 
   6359    assign(op1, get_gpr_w1(r1));
   6360    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6361    assign(result, binop(Iop_MullS32, mkexpr(op1), mkexpr(op2)));
   6362    put_gpr_w1(r1, unop(Iop_64to32, mkexpr(result)));
   6363 
   6364    return "msy";
   6365 }
   6366 
   6367 static HChar *
   6368 s390_irgen_MSG(UChar r1, IRTemp op2addr)
   6369 {
   6370    IRTemp op1 = newTemp(Ity_I64);
   6371    IRTemp op2 = newTemp(Ity_I64);
   6372    IRTemp result = newTemp(Ity_I128);
   6373 
   6374    assign(op1, get_gpr_dw0(r1));
   6375    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   6376    assign(result, binop(Iop_MullS64, mkexpr(op1), mkexpr(op2)));
   6377    put_gpr_dw0(r1, unop(Iop_128to64, mkexpr(result)));
   6378 
   6379    return "msg";
   6380 }
   6381 
   6382 static HChar *
   6383 s390_irgen_MSGF(UChar r1, IRTemp op2addr)
   6384 {
   6385    IRTemp op1 = newTemp(Ity_I64);
   6386    IRTemp op2 = newTemp(Ity_I32);
   6387    IRTemp result = newTemp(Ity_I128);
   6388 
   6389    assign(op1, get_gpr_dw0(r1));
   6390    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6391    assign(result, binop(Iop_MullS64, mkexpr(op1), unop(Iop_32Sto64, mkexpr(op2))
   6392           ));
   6393    put_gpr_dw0(r1, unop(Iop_128to64, mkexpr(result)));
   6394 
   6395    return "msgf";
   6396 }
   6397 
   6398 static HChar *
   6399 s390_irgen_MSFI(UChar r1, UInt i2)
   6400 {
   6401    IRTemp op1 = newTemp(Ity_I32);
   6402    Int op2;
   6403    IRTemp result = newTemp(Ity_I64);
   6404 
   6405    assign(op1, get_gpr_w1(r1));
   6406    op2 = (Int)i2;
   6407    assign(result, binop(Iop_MullS32, mkexpr(op1), mkU32((UInt)op2)));
   6408    put_gpr_w1(r1, unop(Iop_64to32, mkexpr(result)));
   6409 
   6410    return "msfi";
   6411 }
   6412 
   6413 static HChar *
   6414 s390_irgen_MSGFI(UChar r1, UInt i2)
   6415 {
   6416    IRTemp op1 = newTemp(Ity_I64);
   6417    Int op2;
   6418    IRTemp result = newTemp(Ity_I128);
   6419 
   6420    assign(op1, get_gpr_dw0(r1));
   6421    op2 = (Int)i2;
   6422    assign(result, binop(Iop_MullS64, mkexpr(op1), unop(Iop_32Sto64, mkU32((UInt)
   6423           op2))));
   6424    put_gpr_dw0(r1, unop(Iop_128to64, mkexpr(result)));
   6425 
   6426    return "msgfi";
   6427 }
   6428 
   6429 static HChar *
   6430 s390_irgen_OR(UChar r1, UChar r2)
   6431 {
   6432    IRTemp op1 = newTemp(Ity_I32);
   6433    IRTemp op2 = newTemp(Ity_I32);
   6434    IRTemp result = newTemp(Ity_I32);
   6435 
   6436    assign(op1, get_gpr_w1(r1));
   6437    assign(op2, get_gpr_w1(r2));
   6438    assign(result, binop(Iop_Or32, mkexpr(op1), mkexpr(op2)));
   6439    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6440    put_gpr_w1(r1, mkexpr(result));
   6441 
   6442    return "or";
   6443 }
   6444 
   6445 static HChar *
   6446 s390_irgen_OGR(UChar r1, UChar r2)
   6447 {
   6448    IRTemp op1 = newTemp(Ity_I64);
   6449    IRTemp op2 = newTemp(Ity_I64);
   6450    IRTemp result = newTemp(Ity_I64);
   6451 
   6452    assign(op1, get_gpr_dw0(r1));
   6453    assign(op2, get_gpr_dw0(r2));
   6454    assign(result, binop(Iop_Or64, mkexpr(op1), mkexpr(op2)));
   6455    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6456    put_gpr_dw0(r1, mkexpr(result));
   6457 
   6458    return "ogr";
   6459 }
   6460 
   6461 static HChar *
   6462 s390_irgen_ORK(UChar r3, UChar r1, UChar r2)
   6463 {
   6464    IRTemp op2 = newTemp(Ity_I32);
   6465    IRTemp op3 = newTemp(Ity_I32);
   6466    IRTemp result = newTemp(Ity_I32);
   6467 
   6468    assign(op2, get_gpr_w1(r2));
   6469    assign(op3, get_gpr_w1(r3));
   6470    assign(result, binop(Iop_Or32, mkexpr(op2), mkexpr(op3)));
   6471    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6472    put_gpr_w1(r1, mkexpr(result));
   6473 
   6474    return "ork";
   6475 }
   6476 
   6477 static HChar *
   6478 s390_irgen_OGRK(UChar r3, UChar r1, UChar r2)
   6479 {
   6480    IRTemp op2 = newTemp(Ity_I64);
   6481    IRTemp op3 = newTemp(Ity_I64);
   6482    IRTemp result = newTemp(Ity_I64);
   6483 
   6484    assign(op2, get_gpr_dw0(r2));
   6485    assign(op3, get_gpr_dw0(r3));
   6486    assign(result, binop(Iop_Or64, mkexpr(op2), mkexpr(op3)));
   6487    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6488    put_gpr_dw0(r1, mkexpr(result));
   6489 
   6490    return "ogrk";
   6491 }
   6492 
   6493 static HChar *
   6494 s390_irgen_O(UChar r1, IRTemp op2addr)
   6495 {
   6496    IRTemp op1 = newTemp(Ity_I32);
   6497    IRTemp op2 = newTemp(Ity_I32);
   6498    IRTemp result = newTemp(Ity_I32);
   6499 
   6500    assign(op1, get_gpr_w1(r1));
   6501    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6502    assign(result, binop(Iop_Or32, mkexpr(op1), mkexpr(op2)));
   6503    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6504    put_gpr_w1(r1, mkexpr(result));
   6505 
   6506    return "o";
   6507 }
   6508 
   6509 static HChar *
   6510 s390_irgen_OY(UChar r1, IRTemp op2addr)
   6511 {
   6512    IRTemp op1 = newTemp(Ity_I32);
   6513    IRTemp op2 = newTemp(Ity_I32);
   6514    IRTemp result = newTemp(Ity_I32);
   6515 
   6516    assign(op1, get_gpr_w1(r1));
   6517    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   6518    assign(result, binop(Iop_Or32, mkexpr(op1), mkexpr(op2)));
   6519    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6520    put_gpr_w1(r1, mkexpr(result));
   6521 
   6522    return "oy";
   6523 }
   6524 
   6525 static HChar *
   6526 s390_irgen_OG(UChar r1, IRTemp op2addr)
   6527 {
   6528    IRTemp op1 = newTemp(Ity_I64);
   6529    IRTemp op2 = newTemp(Ity_I64);
   6530    IRTemp result = newTemp(Ity_I64);
   6531 
   6532    assign(op1, get_gpr_dw0(r1));
   6533    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   6534    assign(result, binop(Iop_Or64, mkexpr(op1), mkexpr(op2)));
   6535    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6536    put_gpr_dw0(r1, mkexpr(result));
   6537 
   6538    return "og";
   6539 }
   6540 
   6541 static HChar *
   6542 s390_irgen_OI(UChar i2, IRTemp op1addr)
   6543 {
   6544    IRTemp op1 = newTemp(Ity_I8);
   6545    UChar op2;
   6546    IRTemp result = newTemp(Ity_I8);
   6547 
   6548    assign(op1, load(Ity_I8, mkexpr(op1addr)));
   6549    op2 = i2;
   6550    assign(result, binop(Iop_Or8, mkexpr(op1), mkU8(op2)));
   6551    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6552    store(mkexpr(op1addr), mkexpr(result));
   6553 
   6554    return "oi";
   6555 }
   6556 
   6557 static HChar *
   6558 s390_irgen_OIY(UChar i2, IRTemp op1addr)
   6559 {
   6560    IRTemp op1 = newTemp(Ity_I8);
   6561    UChar op2;
   6562    IRTemp result = newTemp(Ity_I8);
   6563 
   6564    assign(op1, load(Ity_I8, mkexpr(op1addr)));
   6565    op2 = i2;
   6566    assign(result, binop(Iop_Or8, mkexpr(op1), mkU8(op2)));
   6567    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6568    store(mkexpr(op1addr), mkexpr(result));
   6569 
   6570    return "oiy";
   6571 }
   6572 
   6573 static HChar *
   6574 s390_irgen_OIHF(UChar r1, UInt i2)
   6575 {
   6576    IRTemp op1 = newTemp(Ity_I32);
   6577    UInt op2;
   6578    IRTemp result = newTemp(Ity_I32);
   6579 
   6580    assign(op1, get_gpr_w0(r1));
   6581    op2 = i2;
   6582    assign(result, binop(Iop_Or32, mkexpr(op1), mkU32(op2)));
   6583    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6584    put_gpr_w0(r1, mkexpr(result));
   6585 
   6586    return "oihf";
   6587 }
   6588 
   6589 static HChar *
   6590 s390_irgen_OIHH(UChar r1, UShort i2)
   6591 {
   6592    IRTemp op1 = newTemp(Ity_I16);
   6593    UShort op2;
   6594    IRTemp result = newTemp(Ity_I16);
   6595 
   6596    assign(op1, get_gpr_hw0(r1));
   6597    op2 = i2;
   6598    assign(result, binop(Iop_Or16, mkexpr(op1), mkU16(op2)));
   6599    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6600    put_gpr_hw0(r1, mkexpr(result));
   6601 
   6602    return "oihh";
   6603 }
   6604 
   6605 static HChar *
   6606 s390_irgen_OIHL(UChar r1, UShort i2)
   6607 {
   6608    IRTemp op1 = newTemp(Ity_I16);
   6609    UShort op2;
   6610    IRTemp result = newTemp(Ity_I16);
   6611 
   6612    assign(op1, get_gpr_hw1(r1));
   6613    op2 = i2;
   6614    assign(result, binop(Iop_Or16, mkexpr(op1), mkU16(op2)));
   6615    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6616    put_gpr_hw1(r1, mkexpr(result));
   6617 
   6618    return "oihl";
   6619 }
   6620 
   6621 static HChar *
   6622 s390_irgen_OILF(UChar r1, UInt i2)
   6623 {
   6624    IRTemp op1 = newTemp(Ity_I32);
   6625    UInt op2;
   6626    IRTemp result = newTemp(Ity_I32);
   6627 
   6628    assign(op1, get_gpr_w1(r1));
   6629    op2 = i2;
   6630    assign(result, binop(Iop_Or32, mkexpr(op1), mkU32(op2)));
   6631    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6632    put_gpr_w1(r1, mkexpr(result));
   6633 
   6634    return "oilf";
   6635 }
   6636 
   6637 static HChar *
   6638 s390_irgen_OILH(UChar r1, UShort i2)
   6639 {
   6640    IRTemp op1 = newTemp(Ity_I16);
   6641    UShort op2;
   6642    IRTemp result = newTemp(Ity_I16);
   6643 
   6644    assign(op1, get_gpr_hw2(r1));
   6645    op2 = i2;
   6646    assign(result, binop(Iop_Or16, mkexpr(op1), mkU16(op2)));
   6647    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6648    put_gpr_hw2(r1, mkexpr(result));
   6649 
   6650    return "oilh";
   6651 }
   6652 
   6653 static HChar *
   6654 s390_irgen_OILL(UChar r1, UShort i2)
   6655 {
   6656    IRTemp op1 = newTemp(Ity_I16);
   6657    UShort op2;
   6658    IRTemp result = newTemp(Ity_I16);
   6659 
   6660    assign(op1, get_gpr_hw3(r1));
   6661    op2 = i2;
   6662    assign(result, binop(Iop_Or16, mkexpr(op1), mkU16(op2)));
   6663    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6664    put_gpr_hw3(r1, mkexpr(result));
   6665 
   6666    return "oill";
   6667 }
   6668 
   6669 static HChar *
   6670 s390_irgen_PFD(void)
   6671 {
   6672 
   6673    return "pfd";
   6674 }
   6675 
   6676 static HChar *
   6677 s390_irgen_PFDRL(void)
   6678 {
   6679 
   6680    return "pfdrl";
   6681 }
   6682 
   6683 static HChar *
   6684 s390_irgen_RLL(UChar r1, UChar r3, IRTemp op2addr)
   6685 {
   6686    IRTemp amount = newTemp(Ity_I64);
   6687    IRTemp op = newTemp(Ity_I32);
   6688 
   6689    assign(amount, binop(Iop_And64, mkexpr(op2addr), mkU64(31)));
   6690    assign(op, get_gpr_w1(r3));
   6691    put_gpr_w1(r1, binop(Iop_Or32, binop(Iop_Shl32, mkexpr(op), unop(Iop_64to8,
   6692               mkexpr(amount))), binop(Iop_Shr32, mkexpr(op), unop(Iop_64to8,
   6693               binop(Iop_Sub64, mkU64(32), mkexpr(amount))))));
   6694 
   6695    return "rll";
   6696 }
   6697 
   6698 static HChar *
   6699 s390_irgen_RLLG(UChar r1, UChar r3, IRTemp op2addr)
   6700 {
   6701    IRTemp amount = newTemp(Ity_I64);
   6702    IRTemp op = newTemp(Ity_I64);
   6703 
   6704    assign(amount, binop(Iop_And64, mkexpr(op2addr), mkU64(63)));
   6705    assign(op, get_gpr_dw0(r3));
   6706    put_gpr_dw0(r1, binop(Iop_Or64, binop(Iop_Shl64, mkexpr(op), unop(Iop_64to8,
   6707                mkexpr(amount))), binop(Iop_Shr64, mkexpr(op), unop(Iop_64to8,
   6708                binop(Iop_Sub64, mkU64(64), mkexpr(amount))))));
   6709 
   6710    return "rllg";
   6711 }
   6712 
   6713 static HChar *
   6714 s390_irgen_RNSBG(UChar r1, UChar r2, UChar i3, UChar i4, UChar i5)
   6715 {
   6716    UChar from;
   6717    UChar to;
   6718    UChar rot;
   6719    UChar t_bit;
   6720    ULong mask;
   6721    ULong maskc;
   6722    IRTemp result = newTemp(Ity_I64);
   6723    IRTemp op2 = newTemp(Ity_I64);
   6724 
   6725    from = i3 & 63;
   6726    to = i4 & 63;
   6727    rot = i5 & 63;
   6728    t_bit = i3 & 128;
   6729    assign(op2, rot == 0 ? get_gpr_dw0(r2) : binop(Iop_Or64, binop(Iop_Shl64,
   6730           get_gpr_dw0(r2), mkU8(rot)), binop(Iop_Shr64, get_gpr_dw0(r2),
   6731           mkU8(64 - rot))));
   6732    if (from <= to) {
   6733       mask = ~0ULL;
   6734       mask = (mask >> from) & (mask << (63 - to));
   6735       maskc = ~mask;
   6736    } else {
   6737       maskc = ~0ULL;
   6738       maskc = (maskc >> (to + 1)) & (maskc << (64 - from));
   6739       mask = ~maskc;
   6740    }
   6741    assign(result, binop(Iop_And64, binop(Iop_And64, get_gpr_dw0(r1), mkexpr(op2)
   6742           ), mkU64(mask)));
   6743    if (t_bit == 0) {
   6744       put_gpr_dw0(r1, binop(Iop_Or64, binop(Iop_And64, get_gpr_dw0(r1),
   6745                   mkU64(maskc)), mkexpr(result)));
   6746    }
   6747    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6748 
   6749    return "rnsbg";
   6750 }
   6751 
   6752 static HChar *
   6753 s390_irgen_RXSBG(UChar r1, UChar r2, UChar i3, UChar i4, UChar i5)
   6754 {
   6755    UChar from;
   6756    UChar to;
   6757    UChar rot;
   6758    UChar t_bit;
   6759    ULong mask;
   6760    ULong maskc;
   6761    IRTemp result = newTemp(Ity_I64);
   6762    IRTemp op2 = newTemp(Ity_I64);
   6763 
   6764    from = i3 & 63;
   6765    to = i4 & 63;
   6766    rot = i5 & 63;
   6767    t_bit = i3 & 128;
   6768    assign(op2, rot == 0 ? get_gpr_dw0(r2) : binop(Iop_Or64, binop(Iop_Shl64,
   6769           get_gpr_dw0(r2), mkU8(rot)), binop(Iop_Shr64, get_gpr_dw0(r2),
   6770           mkU8(64 - rot))));
   6771    if (from <= to) {
   6772       mask = ~0ULL;
   6773       mask = (mask >> from) & (mask << (63 - to));
   6774       maskc = ~mask;
   6775    } else {
   6776       maskc = ~0ULL;
   6777       maskc = (maskc >> (to + 1)) & (maskc << (64 - from));
   6778       mask = ~maskc;
   6779    }
   6780    assign(result, binop(Iop_And64, binop(Iop_Xor64, get_gpr_dw0(r1), mkexpr(op2)
   6781           ), mkU64(mask)));
   6782    if (t_bit == 0) {
   6783       put_gpr_dw0(r1, binop(Iop_Or64, binop(Iop_And64, get_gpr_dw0(r1),
   6784                   mkU64(maskc)), mkexpr(result)));
   6785    }
   6786    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6787 
   6788    return "rxsbg";
   6789 }
   6790 
   6791 static HChar *
   6792 s390_irgen_ROSBG(UChar r1, UChar r2, UChar i3, UChar i4, UChar i5)
   6793 {
   6794    UChar from;
   6795    UChar to;
   6796    UChar rot;
   6797    UChar t_bit;
   6798    ULong mask;
   6799    ULong maskc;
   6800    IRTemp result = newTemp(Ity_I64);
   6801    IRTemp op2 = newTemp(Ity_I64);
   6802 
   6803    from = i3 & 63;
   6804    to = i4 & 63;
   6805    rot = i5 & 63;
   6806    t_bit = i3 & 128;
   6807    assign(op2, rot == 0 ? get_gpr_dw0(r2) : binop(Iop_Or64, binop(Iop_Shl64,
   6808           get_gpr_dw0(r2), mkU8(rot)), binop(Iop_Shr64, get_gpr_dw0(r2),
   6809           mkU8(64 - rot))));
   6810    if (from <= to) {
   6811       mask = ~0ULL;
   6812       mask = (mask >> from) & (mask << (63 - to));
   6813       maskc = ~mask;
   6814    } else {
   6815       maskc = ~0ULL;
   6816       maskc = (maskc >> (to + 1)) & (maskc << (64 - from));
   6817       mask = ~maskc;
   6818    }
   6819    assign(result, binop(Iop_And64, binop(Iop_Or64, get_gpr_dw0(r1), mkexpr(op2)
   6820           ), mkU64(mask)));
   6821    if (t_bit == 0) {
   6822       put_gpr_dw0(r1, binop(Iop_Or64, binop(Iop_And64, get_gpr_dw0(r1),
   6823                   mkU64(maskc)), mkexpr(result)));
   6824    }
   6825    s390_cc_thunk_putZ(S390_CC_OP_BITWISE, result);
   6826 
   6827    return "rosbg";
   6828 }
   6829 
   6830 static HChar *
   6831 s390_irgen_RISBG(UChar r1, UChar r2, UChar i3, UChar i4, UChar i5)
   6832 {
   6833    UChar from;
   6834    UChar to;
   6835    UChar rot;
   6836    UChar z_bit;
   6837    ULong mask;
   6838    ULong maskc;
   6839    IRTemp op2 = newTemp(Ity_I64);
   6840    IRTemp result = newTemp(Ity_I64);
   6841 
   6842    from = i3 & 63;
   6843    to = i4 & 63;
   6844    rot = i5 & 63;
   6845    z_bit = i4 & 128;
   6846    assign(op2, rot == 0 ? get_gpr_dw0(r2) : binop(Iop_Or64, binop(Iop_Shl64,
   6847           get_gpr_dw0(r2), mkU8(rot)), binop(Iop_Shr64, get_gpr_dw0(r2),
   6848           mkU8(64 - rot))));
   6849    if (from <= to) {
   6850       mask = ~0ULL;
   6851       mask = (mask >> from) & (mask << (63 - to));
   6852       maskc = ~mask;
   6853    } else {
   6854       maskc = ~0ULL;
   6855       maskc = (maskc >> (to + 1)) & (maskc << (64 - from));
   6856       mask = ~maskc;
   6857    }
   6858    if (z_bit == 0) {
   6859       put_gpr_dw0(r1, binop(Iop_Or64, binop(Iop_And64, get_gpr_dw0(r1),
   6860                   mkU64(maskc)), binop(Iop_And64, mkexpr(op2), mkU64(mask))));
   6861    } else {
   6862       put_gpr_dw0(r1, binop(Iop_And64, mkexpr(op2), mkU64(mask)));
   6863    }
   6864    assign(result, get_gpr_dw0(r1));
   6865    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, op2);
   6866 
   6867    return "risbg";
   6868 }
   6869 
   6870 static HChar *
   6871 s390_irgen_SAR(UChar r1, UChar r2)
   6872 {
   6873    put_ar_w0(r1, get_gpr_w1(r2));
   6874    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   6875       s390_disasm(ENC3(MNM, AR, GPR), "sar", r1, r2);
   6876 
   6877    return "sar";
   6878 }
   6879 
   6880 static HChar *
   6881 s390_irgen_SLDA(UChar r1, IRTemp op2addr)
   6882 {
   6883    IRTemp p1 = newTemp(Ity_I64);
   6884    IRTemp p2 = newTemp(Ity_I64);
   6885    IRTemp op = newTemp(Ity_I64);
   6886    IRTemp result = newTemp(Ity_I64);
   6887    ULong sign_mask;
   6888    IRTemp shift_amount = newTemp(Ity_I64);
   6889 
   6890    assign(p1, unop(Iop_32Uto64, get_gpr_w1(r1)));
   6891    assign(p2, unop(Iop_32Uto64, get_gpr_w1(r1 + 1)));
   6892    assign(op, binop(Iop_Or64, binop(Iop_Shl64, mkexpr(p1), mkU8(32)), mkexpr(p2)
   6893           ));
   6894    sign_mask = 1ULL << 63;
   6895    assign(shift_amount, binop(Iop_And64, mkexpr(op2addr), mkU64(63)));
   6896    assign(result, binop(Iop_Or64, binop(Iop_And64, binop(Iop_Shl64, mkexpr(op),
   6897           unop(Iop_64to8, mkexpr(shift_amount))), mkU64(~sign_mask)),
   6898           binop(Iop_And64, mkexpr(op), mkU64(sign_mask))));
   6899    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   6900    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   6901    s390_cc_thunk_putZZ(S390_CC_OP_SHIFT_LEFT_64, op, shift_amount);
   6902 
   6903    return "slda";
   6904 }
   6905 
   6906 static HChar *
   6907 s390_irgen_SLDL(UChar r1, IRTemp op2addr)
   6908 {
   6909    IRTemp p1 = newTemp(Ity_I64);
   6910    IRTemp p2 = newTemp(Ity_I64);
   6911    IRTemp result = newTemp(Ity_I64);
   6912 
   6913    assign(p1, unop(Iop_32Uto64, get_gpr_w1(r1)));
   6914    assign(p2, unop(Iop_32Uto64, get_gpr_w1(r1 + 1)));
   6915    assign(result, binop(Iop_Shl64, binop(Iop_Or64, binop(Iop_Shl64, mkexpr(p1),
   6916           mkU8(32)), mkexpr(p2)), unop(Iop_64to8, binop(Iop_And64,
   6917           mkexpr(op2addr), mkU64(63)))));
   6918    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   6919    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   6920 
   6921    return "sldl";
   6922 }
   6923 
   6924 static HChar *
   6925 s390_irgen_SLA(UChar r1, IRTemp op2addr)
   6926 {
   6927    IRTemp uop = newTemp(Ity_I32);
   6928    IRTemp result = newTemp(Ity_I32);
   6929    UInt sign_mask;
   6930    IRTemp shift_amount = newTemp(Ity_I64);
   6931    IRTemp op = newTemp(Ity_I32);
   6932 
   6933    assign(op, get_gpr_w1(r1));
   6934    assign(uop, get_gpr_w1(r1));
   6935    sign_mask = 2147483648U;
   6936    assign(shift_amount, binop(Iop_And64, mkexpr(op2addr), mkU64(63)));
   6937    assign(result, binop(Iop_Or32, binop(Iop_And32, binop(Iop_Shl32, mkexpr(uop),
   6938           unop(Iop_64to8, mkexpr(shift_amount))), mkU32(~sign_mask)),
   6939           binop(Iop_And32, mkexpr(uop), mkU32(sign_mask))));
   6940    put_gpr_w1(r1, mkexpr(result));
   6941    s390_cc_thunk_putZZ(S390_CC_OP_SHIFT_LEFT_32, op, shift_amount);
   6942 
   6943    return "sla";
   6944 }
   6945 
   6946 static HChar *
   6947 s390_irgen_SLAK(UChar r1, UChar r3, IRTemp op2addr)
   6948 {
   6949    IRTemp uop = newTemp(Ity_I32);
   6950    IRTemp result = newTemp(Ity_I32);
   6951    UInt sign_mask;
   6952    IRTemp shift_amount = newTemp(Ity_I64);
   6953    IRTemp op = newTemp(Ity_I32);
   6954 
   6955    assign(op, get_gpr_w1(r3));
   6956    assign(uop, get_gpr_w1(r3));
   6957    sign_mask = 2147483648U;
   6958    assign(shift_amount, binop(Iop_And64, mkexpr(op2addr), mkU64(63)));
   6959    assign(result, binop(Iop_Or32, binop(Iop_And32, binop(Iop_Shl32, mkexpr(uop),
   6960           unop(Iop_64to8, mkexpr(shift_amount))), mkU32(~sign_mask)),
   6961           binop(Iop_And32, mkexpr(uop), mkU32(sign_mask))));
   6962    put_gpr_w1(r1, mkexpr(result));
   6963    s390_cc_thunk_putZZ(S390_CC_OP_SHIFT_LEFT_32, op, shift_amount);
   6964 
   6965    return "slak";
   6966 }
   6967 
   6968 static HChar *
   6969 s390_irgen_SLAG(UChar r1, UChar r3, IRTemp op2addr)
   6970 {
   6971    IRTemp uop = newTemp(Ity_I64);
   6972    IRTemp result = newTemp(Ity_I64);
   6973    ULong sign_mask;
   6974    IRTemp shift_amount = newTemp(Ity_I64);
   6975    IRTemp op = newTemp(Ity_I64);
   6976 
   6977    assign(op, get_gpr_dw0(r3));
   6978    assign(uop, get_gpr_dw0(r3));
   6979    sign_mask = 9223372036854775808ULL;
   6980    assign(shift_amount, binop(Iop_And64, mkexpr(op2addr), mkU64(63)));
   6981    assign(result, binop(Iop_Or64, binop(Iop_And64, binop(Iop_Shl64, mkexpr(uop),
   6982           unop(Iop_64to8, mkexpr(shift_amount))), mkU64(~sign_mask)),
   6983           binop(Iop_And64, mkexpr(uop), mkU64(sign_mask))));
   6984    put_gpr_dw0(r1, mkexpr(result));
   6985    s390_cc_thunk_putZZ(S390_CC_OP_SHIFT_LEFT_64, op, shift_amount);
   6986 
   6987    return "slag";
   6988 }
   6989 
   6990 static HChar *
   6991 s390_irgen_SLL(UChar r1, IRTemp op2addr)
   6992 {
   6993    put_gpr_w1(r1, binop(Iop_Shl32, get_gpr_w1(r1), unop(Iop_64to8,
   6994               binop(Iop_And64, mkexpr(op2addr), mkU64(63)))));
   6995 
   6996    return "sll";
   6997 }
   6998 
   6999 static HChar *
   7000 s390_irgen_SLLK(UChar r1, UChar r3, IRTemp op2addr)
   7001 {
   7002    put_gpr_w1(r1, binop(Iop_Shl32, get_gpr_w1(r3), unop(Iop_64to8,
   7003               binop(Iop_And64, mkexpr(op2addr), mkU64(63)))));
   7004 
   7005    return "sllk";
   7006 }
   7007 
   7008 static HChar *
   7009 s390_irgen_SLLG(UChar r1, UChar r3, IRTemp op2addr)
   7010 {
   7011    put_gpr_dw0(r1, binop(Iop_Shl64, get_gpr_dw0(r3), unop(Iop_64to8,
   7012                binop(Iop_And64, mkexpr(op2addr), mkU64(63)))));
   7013 
   7014    return "sllg";
   7015 }
   7016 
   7017 static HChar *
   7018 s390_irgen_SRDA(UChar r1, IRTemp op2addr)
   7019 {
   7020    IRTemp p1 = newTemp(Ity_I64);
   7021    IRTemp p2 = newTemp(Ity_I64);
   7022    IRTemp result = newTemp(Ity_I64);
   7023 
   7024    assign(p1, unop(Iop_32Uto64, get_gpr_w1(r1)));
   7025    assign(p2, unop(Iop_32Uto64, get_gpr_w1(r1 + 1)));
   7026    assign(result, binop(Iop_Sar64, binop(Iop_Or64, binop(Iop_Shl64, mkexpr(p1),
   7027           mkU8(32)), mkexpr(p2)), unop(Iop_64to8, binop(Iop_And64,
   7028           mkexpr(op2addr), mkU64(63)))));
   7029    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   7030    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   7031    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, result);
   7032 
   7033    return "srda";
   7034 }
   7035 
   7036 static HChar *
   7037 s390_irgen_SRDL(UChar r1, IRTemp op2addr)
   7038 {
   7039    IRTemp p1 = newTemp(Ity_I64);
   7040    IRTemp p2 = newTemp(Ity_I64);
   7041    IRTemp result = newTemp(Ity_I64);
   7042 
   7043    assign(p1, unop(Iop_32Uto64, get_gpr_w1(r1)));
   7044    assign(p2, unop(Iop_32Uto64, get_gpr_w1(r1 + 1)));
   7045    assign(result, binop(Iop_Shr64, binop(Iop_Or64, binop(Iop_Shl64, mkexpr(p1),
   7046           mkU8(32)), mkexpr(p2)), unop(Iop_64to8, binop(Iop_And64,
   7047           mkexpr(op2addr), mkU64(63)))));
   7048    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));
   7049    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result)));
   7050 
   7051    return "srdl";
   7052 }
   7053 
   7054 static HChar *
   7055 s390_irgen_SRA(UChar r1, IRTemp op2addr)
   7056 {
   7057    IRTemp result = newTemp(Ity_I32);
   7058    IRTemp op = newTemp(Ity_I32);
   7059 
   7060    assign(op, get_gpr_w1(r1));
   7061    assign(result, binop(Iop_Sar32, mkexpr(op), unop(Iop_64to8, binop(Iop_And64,
   7062           mkexpr(op2addr), mkU64(63)))));
   7063    put_gpr_w1(r1, mkexpr(result));
   7064    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, result);
   7065 
   7066    return "sra";
   7067 }
   7068 
   7069 static HChar *
   7070 s390_irgen_SRAK(UChar r1, UChar r3, IRTemp op2addr)
   7071 {
   7072    IRTemp result = newTemp(Ity_I32);
   7073    IRTemp op = newTemp(Ity_I32);
   7074 
   7075    assign(op, get_gpr_w1(r3));
   7076    assign(result, binop(Iop_Sar32, mkexpr(op), unop(Iop_64to8, binop(Iop_And64,
   7077           mkexpr(op2addr), mkU64(63)))));
   7078    put_gpr_w1(r1, mkexpr(result));
   7079    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, result);
   7080 
   7081    return "srak";
   7082 }
   7083 
   7084 static HChar *
   7085 s390_irgen_SRAG(UChar r1, UChar r3, IRTemp op2addr)
   7086 {
   7087    IRTemp result = newTemp(Ity_I64);
   7088    IRTemp op = newTemp(Ity_I64);
   7089 
   7090    assign(op, get_gpr_dw0(r3));
   7091    assign(result, binop(Iop_Sar64, mkexpr(op), unop(Iop_64to8, binop(Iop_And64,
   7092           mkexpr(op2addr), mkU64(63)))));
   7093    put_gpr_dw0(r1, mkexpr(result));
   7094    s390_cc_thunk_putS(S390_CC_OP_LOAD_AND_TEST, result);
   7095 
   7096    return "srag";
   7097 }
   7098 
   7099 static HChar *
   7100 s390_irgen_SRL(UChar r1, IRTemp op2addr)
   7101 {
   7102    IRTemp op = newTemp(Ity_I32);
   7103 
   7104    assign(op, get_gpr_w1(r1));
   7105    put_gpr_w1(r1, binop(Iop_Shr32, mkexpr(op), unop(Iop_64to8, binop(Iop_And64,
   7106               mkexpr(op2addr), mkU64(63)))));
   7107 
   7108    return "srl";
   7109 }
   7110 
   7111 static HChar *
   7112 s390_irgen_SRLK(UChar r1, UChar r3, IRTemp op2addr)
   7113 {
   7114    IRTemp op = newTemp(Ity_I32);
   7115 
   7116    assign(op, get_gpr_w1(r3));
   7117    put_gpr_w1(r1, binop(Iop_Shr32, mkexpr(op), unop(Iop_64to8, binop(Iop_And64,
   7118               mkexpr(op2addr), mkU64(63)))));
   7119 
   7120    return "srlk";
   7121 }
   7122 
   7123 static HChar *
   7124 s390_irgen_SRLG(UChar r1, UChar r3, IRTemp op2addr)
   7125 {
   7126    IRTemp op = newTemp(Ity_I64);
   7127 
   7128    assign(op, get_gpr_dw0(r3));
   7129    put_gpr_dw0(r1, binop(Iop_Shr64, mkexpr(op), unop(Iop_64to8, binop(Iop_And64,
   7130                mkexpr(op2addr), mkU64(63)))));
   7131 
   7132    return "srlg";
   7133 }
   7134 
   7135 static HChar *
   7136 s390_irgen_ST(UChar r1, IRTemp op2addr)
   7137 {
   7138    store(mkexpr(op2addr), get_gpr_w1(r1));
   7139 
   7140    return "st";
   7141 }
   7142 
   7143 static HChar *
   7144 s390_irgen_STY(UChar r1, IRTemp op2addr)
   7145 {
   7146    store(mkexpr(op2addr), get_gpr_w1(r1));
   7147 
   7148    return "sty";
   7149 }
   7150 
   7151 static HChar *
   7152 s390_irgen_STG(UChar r1, IRTemp op2addr)
   7153 {
   7154    store(mkexpr(op2addr), get_gpr_dw0(r1));
   7155 
   7156    return "stg";
   7157 }
   7158 
   7159 static HChar *
   7160 s390_irgen_STRL(UChar r1, UInt i2)
   7161 {
   7162    store(mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)i2 << 1)),
   7163          get_gpr_w1(r1));
   7164 
   7165    return "strl";
   7166 }
   7167 
   7168 static HChar *
   7169 s390_irgen_STGRL(UChar r1, UInt i2)
   7170 {
   7171    store(mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)i2 << 1)),
   7172          get_gpr_dw0(r1));
   7173 
   7174    return "stgrl";
   7175 }
   7176 
   7177 static HChar *
   7178 s390_irgen_STC(UChar r1, IRTemp op2addr)
   7179 {
   7180    store(mkexpr(op2addr), get_gpr_b7(r1));
   7181 
   7182    return "stc";
   7183 }
   7184 
   7185 static HChar *
   7186 s390_irgen_STCY(UChar r1, IRTemp op2addr)
   7187 {
   7188    store(mkexpr(op2addr), get_gpr_b7(r1));
   7189 
   7190    return "stcy";
   7191 }
   7192 
   7193 static HChar *
   7194 s390_irgen_STCH(UChar r1, IRTemp op2addr)
   7195 {
   7196    store(mkexpr(op2addr), get_gpr_b3(r1));
   7197 
   7198    return "stch";
   7199 }
   7200 
   7201 static HChar *
   7202 s390_irgen_STCM(UChar r1, UChar r3, IRTemp op2addr)
   7203 {
   7204    UChar mask;
   7205    UChar n;
   7206 
   7207    mask = (UChar)r3;
   7208    n = 0;
   7209    if ((mask & 8) != 0) {
   7210       store(mkexpr(op2addr), get_gpr_b4(r1));
   7211       n = n + 1;
   7212    }
   7213    if ((mask & 4) != 0) {
   7214       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b5(r1));
   7215       n = n + 1;
   7216    }
   7217    if ((mask & 2) != 0) {
   7218       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b6(r1));
   7219       n = n + 1;
   7220    }
   7221    if ((mask & 1) != 0) {
   7222       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b7(r1));
   7223    }
   7224 
   7225    return "stcm";
   7226 }
   7227 
   7228 static HChar *
   7229 s390_irgen_STCMY(UChar r1, UChar r3, IRTemp op2addr)
   7230 {
   7231    UChar mask;
   7232    UChar n;
   7233 
   7234    mask = (UChar)r3;
   7235    n = 0;
   7236    if ((mask & 8) != 0) {
   7237       store(mkexpr(op2addr), get_gpr_b4(r1));
   7238       n = n + 1;
   7239    }
   7240    if ((mask & 4) != 0) {
   7241       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b5(r1));
   7242       n = n + 1;
   7243    }
   7244    if ((mask & 2) != 0) {
   7245       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b6(r1));
   7246       n = n + 1;
   7247    }
   7248    if ((mask & 1) != 0) {
   7249       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b7(r1));
   7250    }
   7251 
   7252    return "stcmy";
   7253 }
   7254 
   7255 static HChar *
   7256 s390_irgen_STCMH(UChar r1, UChar r3, IRTemp op2addr)
   7257 {
   7258    UChar mask;
   7259    UChar n;
   7260 
   7261    mask = (UChar)r3;
   7262    n = 0;
   7263    if ((mask & 8) != 0) {
   7264       store(mkexpr(op2addr), get_gpr_b0(r1));
   7265       n = n + 1;
   7266    }
   7267    if ((mask & 4) != 0) {
   7268       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b1(r1));
   7269       n = n + 1;
   7270    }
   7271    if ((mask & 2) != 0) {
   7272       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b2(r1));
   7273       n = n + 1;
   7274    }
   7275    if ((mask & 1) != 0) {
   7276       store(binop(Iop_Add64, mkexpr(op2addr), mkU64(n)), get_gpr_b3(r1));
   7277    }
   7278 
   7279    return "stcmh";
   7280 }
   7281 
   7282 static HChar *
   7283 s390_irgen_STH(UChar r1, IRTemp op2addr)
   7284 {
   7285    store(mkexpr(op2addr), get_gpr_hw3(r1));
   7286 
   7287    return "sth";
   7288 }
   7289 
   7290 static HChar *
   7291 s390_irgen_STHY(UChar r1, IRTemp op2addr)
   7292 {
   7293    store(mkexpr(op2addr), get_gpr_hw3(r1));
   7294 
   7295    return "sthy";
   7296 }
   7297 
   7298 static HChar *
   7299 s390_irgen_STHRL(UChar r1, UInt i2)
   7300 {
   7301    store(mkU64(guest_IA_curr_instr + ((ULong)(Long)(Int)i2 << 1)),
   7302          get_gpr_hw3(r1));
   7303 
   7304    return "sthrl";
   7305 }
   7306 
   7307 static HChar *
   7308 s390_irgen_STHH(UChar r1, IRTemp op2addr)
   7309 {
   7310    store(mkexpr(op2addr), get_gpr_hw1(r1));
   7311 
   7312    return "sthh";
   7313 }
   7314 
   7315 static HChar *
   7316 s390_irgen_STFH(UChar r1, IRTemp op2addr)
   7317 {
   7318    store(mkexpr(op2addr), get_gpr_w0(r1));
   7319 
   7320    return "stfh";
   7321 }
   7322 
   7323 static HChar *
   7324 s390_irgen_STOC(UChar r1, IRTemp op2addr)
   7325 {
   7326    /* condition is checked in format handler */
   7327    store(mkexpr(op2addr), get_gpr_w1(r1));
   7328 
   7329    return "stoc";
   7330 }
   7331 
   7332 static HChar *
   7333 s390_irgen_STOCG(UChar r1, IRTemp op2addr)
   7334 {
   7335    /* condition is checked in format handler */
   7336    store(mkexpr(op2addr), get_gpr_dw0(r1));
   7337 
   7338    return "stocg";
   7339 }
   7340 
   7341 static HChar *
   7342 s390_irgen_STPQ(UChar r1, IRTemp op2addr)
   7343 {
   7344    store(mkexpr(op2addr), get_gpr_dw0(r1));
   7345    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(8)), get_gpr_dw0(r1 + 1));
   7346 
   7347    return "stpq";
   7348 }
   7349 
   7350 static HChar *
   7351 s390_irgen_STRVH(UChar r1, IRTemp op2addr)
   7352 {
   7353    store(mkexpr(op2addr), get_gpr_b7(r1));
   7354    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(1)), get_gpr_b6(r1));
   7355 
   7356    return "strvh";
   7357 }
   7358 
   7359 static HChar *
   7360 s390_irgen_STRV(UChar r1, IRTemp op2addr)
   7361 {
   7362    store(mkexpr(op2addr), get_gpr_b7(r1));
   7363    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(1)), get_gpr_b6(r1));
   7364    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(2)), get_gpr_b5(r1));
   7365    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(3)), get_gpr_b4(r1));
   7366 
   7367    return "strv";
   7368 }
   7369 
   7370 static HChar *
   7371 s390_irgen_STRVG(UChar r1, IRTemp op2addr)
   7372 {
   7373    store(mkexpr(op2addr), get_gpr_b7(r1));
   7374    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(1)), get_gpr_b6(r1));
   7375    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(2)), get_gpr_b5(r1));
   7376    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(3)), get_gpr_b4(r1));
   7377    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(4)), get_gpr_b3(r1));
   7378    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(5)), get_gpr_b2(r1));
   7379    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(6)), get_gpr_b1(r1));
   7380    store(binop(Iop_Add64, mkexpr(op2addr), mkU64(7)), get_gpr_b0(r1));
   7381 
   7382    return "strvg";
   7383 }
   7384 
   7385 static HChar *
   7386 s390_irgen_SR(UChar r1, UChar r2)
   7387 {
   7388    IRTemp op1 = newTemp(Ity_I32);
   7389    IRTemp op2 = newTemp(Ity_I32);
   7390    IRTemp result = newTemp(Ity_I32);
   7391 
   7392    assign(op1, get_gpr_w1(r1));
   7393    assign(op2, get_gpr_w1(r2));
   7394    assign(result, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)));
   7395    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, op1, op2);
   7396    put_gpr_w1(r1, mkexpr(result));
   7397 
   7398    return "sr";
   7399 }
   7400 
   7401 static HChar *
   7402 s390_irgen_SGR(UChar r1, UChar r2)
   7403 {
   7404    IRTemp op1 = newTemp(Ity_I64);
   7405    IRTemp op2 = newTemp(Ity_I64);
   7406    IRTemp result = newTemp(Ity_I64);
   7407 
   7408    assign(op1, get_gpr_dw0(r1));
   7409    assign(op2, get_gpr_dw0(r2));
   7410    assign(result, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)));
   7411    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_64, op1, op2);
   7412    put_gpr_dw0(r1, mkexpr(result));
   7413 
   7414    return "sgr";
   7415 }
   7416 
   7417 static HChar *
   7418 s390_irgen_SGFR(UChar r1, UChar r2)
   7419 {
   7420    IRTemp op1 = newTemp(Ity_I64);
   7421    IRTemp op2 = newTemp(Ity_I64);
   7422    IRTemp result = newTemp(Ity_I64);
   7423 
   7424    assign(op1, get_gpr_dw0(r1));
   7425    assign(op2, unop(Iop_32Sto64, get_gpr_w1(r2)));
   7426    assign(result, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)));
   7427    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_64, op1, op2);
   7428    put_gpr_dw0(r1, mkexpr(result));
   7429 
   7430    return "sgfr";
   7431 }
   7432 
   7433 static HChar *
   7434 s390_irgen_SRK(UChar r3, UChar r1, UChar r2)
   7435 {
   7436    IRTemp op2 = newTemp(Ity_I32);
   7437    IRTemp op3 = newTemp(Ity_I32);
   7438    IRTemp result = newTemp(Ity_I32);
   7439 
   7440    assign(op2, get_gpr_w1(r2));
   7441    assign(op3, get_gpr_w1(r3));
   7442    assign(result, binop(Iop_Sub32, mkexpr(op2), mkexpr(op3)));
   7443    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, op2, op3);
   7444    put_gpr_w1(r1, mkexpr(result));
   7445 
   7446    return "srk";
   7447 }
   7448 
   7449 static HChar *
   7450 s390_irgen_SGRK(UChar r3, UChar r1, UChar r2)
   7451 {
   7452    IRTemp op2 = newTemp(Ity_I64);
   7453    IRTemp op3 = newTemp(Ity_I64);
   7454    IRTemp result = newTemp(Ity_I64);
   7455 
   7456    assign(op2, get_gpr_dw0(r2));
   7457    assign(op3, get_gpr_dw0(r3));
   7458    assign(result, binop(Iop_Sub64, mkexpr(op2), mkexpr(op3)));
   7459    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_64, op2, op3);
   7460    put_gpr_dw0(r1, mkexpr(result));
   7461 
   7462    return "sgrk";
   7463 }
   7464 
   7465 static HChar *
   7466 s390_irgen_S(UChar r1, IRTemp op2addr)
   7467 {
   7468    IRTemp op1 = newTemp(Ity_I32);
   7469    IRTemp op2 = newTemp(Ity_I32);
   7470    IRTemp result = newTemp(Ity_I32);
   7471 
   7472    assign(op1, get_gpr_w1(r1));
   7473    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   7474    assign(result, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)));
   7475    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, op1, op2);
   7476    put_gpr_w1(r1, mkexpr(result));
   7477 
   7478    return "s";
   7479 }
   7480 
   7481 static HChar *
   7482 s390_irgen_SY(UChar r1, IRTemp op2addr)
   7483 {
   7484    IRTemp op1 = newTemp(Ity_I32);
   7485    IRTemp op2 = newTemp(Ity_I32);
   7486    IRTemp result = newTemp(Ity_I32);
   7487 
   7488    assign(op1, get_gpr_w1(r1));
   7489    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   7490    assign(result, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)));
   7491    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, op1, op2);
   7492    put_gpr_w1(r1, mkexpr(result));
   7493 
   7494    return "sy";
   7495 }
   7496 
   7497 static HChar *
   7498 s390_irgen_SG(UChar r1, IRTemp op2addr)
   7499 {
   7500    IRTemp op1 = newTemp(Ity_I64);
   7501    IRTemp op2 = newTemp(Ity_I64);
   7502    IRTemp result = newTemp(Ity_I64);
   7503 
   7504    assign(op1, get_gpr_dw0(r1));
   7505    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   7506    assign(result, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)));
   7507    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_64, op1, op2);
   7508    put_gpr_dw0(r1, mkexpr(result));
   7509 
   7510    return "sg";
   7511 }
   7512 
   7513 static HChar *
   7514 s390_irgen_SGF(UChar r1, IRTemp op2addr)
   7515 {
   7516    IRTemp op1 = newTemp(Ity_I64);
   7517    IRTemp op2 = newTemp(Ity_I64);
   7518    IRTemp result = newTemp(Ity_I64);
   7519 
   7520    assign(op1, get_gpr_dw0(r1));
   7521    assign(op2, unop(Iop_32Sto64, load(Ity_I32, mkexpr(op2addr))));
   7522    assign(result, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)));
   7523    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_64, op1, op2);
   7524    put_gpr_dw0(r1, mkexpr(result));
   7525 
   7526    return "sgf";
   7527 }
   7528 
   7529 static HChar *
   7530 s390_irgen_SH(UChar r1, IRTemp op2addr)
   7531 {
   7532    IRTemp op1 = newTemp(Ity_I32);
   7533    IRTemp op2 = newTemp(Ity_I32);
   7534    IRTemp result = newTemp(Ity_I32);
   7535 
   7536    assign(op1, get_gpr_w1(r1));
   7537    assign(op2, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   7538    assign(result, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)));
   7539    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, op1, op2);
   7540    put_gpr_w1(r1, mkexpr(result));
   7541 
   7542    return "sh";
   7543 }
   7544 
   7545 static HChar *
   7546 s390_irgen_SHY(UChar r1, IRTemp op2addr)
   7547 {
   7548    IRTemp op1 = newTemp(Ity_I32);
   7549    IRTemp op2 = newTemp(Ity_I32);
   7550    IRTemp result = newTemp(Ity_I32);
   7551 
   7552    assign(op1, get_gpr_w1(r1));
   7553    assign(op2, unop(Iop_16Sto32, load(Ity_I16, mkexpr(op2addr))));
   7554    assign(result, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)));
   7555    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, op1, op2);
   7556    put_gpr_w1(r1, mkexpr(result));
   7557 
   7558    return "shy";
   7559 }
   7560 
   7561 static HChar *
   7562 s390_irgen_SHHHR(UChar r3 __attribute__((unused)), UChar r1, UChar r2)
   7563 {
   7564    IRTemp op2 = newTemp(Ity_I32);
   7565    IRTemp op3 = newTemp(Ity_I32);
   7566    IRTemp result = newTemp(Ity_I32);
   7567 
   7568    assign(op2, get_gpr_w0(r1));
   7569    assign(op3, get_gpr_w0(r2));
   7570    assign(result, binop(Iop_Sub32, mkexpr(op2), mkexpr(op3)));
   7571    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, op2, op3);
   7572    put_gpr_w0(r1, mkexpr(result));
   7573 
   7574    return "shhhr";
   7575 }
   7576 
   7577 static HChar *
   7578 s390_irgen_SHHLR(UChar r3 __attribute__((unused)), UChar r1, UChar r2)
   7579 {
   7580    IRTemp op2 = newTemp(Ity_I32);
   7581    IRTemp op3 = newTemp(Ity_I32);
   7582    IRTemp result = newTemp(Ity_I32);
   7583 
   7584    assign(op2, get_gpr_w0(r1));
   7585    assign(op3, get_gpr_w1(r2));
   7586    assign(result, binop(Iop_Sub32, mkexpr(op2), mkexpr(op3)));
   7587    s390_cc_thunk_putSS(S390_CC_OP_SIGNED_SUB_32, op2, op3);
   7588    put_gpr_w0(r1, mkexpr(result));
   7589 
   7590    return "shhlr";
   7591 }
   7592 
   7593 static HChar *
   7594 s390_irgen_SLR(UChar r1, UChar r2)
   7595 {
   7596    IRTemp op1 = newTemp(Ity_I32);
   7597    IRTemp op2 = newTemp(Ity_I32);
   7598    IRTemp result = newTemp(Ity_I32);
   7599 
   7600    assign(op1, get_gpr_w1(r1));
   7601    assign(op2, get_gpr_w1(r2));
   7602    assign(result, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)));
   7603    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_32, op1, op2);
   7604    put_gpr_w1(r1, mkexpr(result));
   7605 
   7606    return "slr";
   7607 }
   7608 
   7609 static HChar *
   7610 s390_irgen_SLGR(UChar r1, UChar r2)
   7611 {
   7612    IRTemp op1 = newTemp(Ity_I64);
   7613    IRTemp op2 = newTemp(Ity_I64);
   7614    IRTemp result = newTemp(Ity_I64);
   7615 
   7616    assign(op1, get_gpr_dw0(r1));
   7617    assign(op2, get_gpr_dw0(r2));
   7618    assign(result, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)));
   7619    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_64, op1, op2);
   7620    put_gpr_dw0(r1, mkexpr(result));
   7621 
   7622    return "slgr";
   7623 }
   7624 
   7625 static HChar *
   7626 s390_irgen_SLGFR(UChar r1, UChar r2)
   7627 {
   7628    IRTemp op1 = newTemp(Ity_I64);
   7629    IRTemp op2 = newTemp(Ity_I64);
   7630    IRTemp result = newTemp(Ity_I64);
   7631 
   7632    assign(op1, get_gpr_dw0(r1));
   7633    assign(op2, unop(Iop_32Uto64, get_gpr_w1(r2)));
   7634    assign(result, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)));
   7635    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_64, op1, op2);
   7636    put_gpr_dw0(r1, mkexpr(result));
   7637 
   7638    return "slgfr";
   7639 }
   7640 
   7641 static HChar *
   7642 s390_irgen_SLRK(UChar r3, UChar r1, UChar r2)
   7643 {
   7644    IRTemp op2 = newTemp(Ity_I32);
   7645    IRTemp op3 = newTemp(Ity_I32);
   7646    IRTemp result = newTemp(Ity_I32);
   7647 
   7648    assign(op2, get_gpr_w1(r2));
   7649    assign(op3, get_gpr_w1(r3));
   7650    assign(result, binop(Iop_Sub32, mkexpr(op2), mkexpr(op3)));
   7651    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_32, op2, op3);
   7652    put_gpr_w1(r1, mkexpr(result));
   7653 
   7654    return "slrk";
   7655 }
   7656 
   7657 static HChar *
   7658 s390_irgen_SLGRK(UChar r3, UChar r1, UChar r2)
   7659 {
   7660    IRTemp op2 = newTemp(Ity_I64);
   7661    IRTemp op3 = newTemp(Ity_I64);
   7662    IRTemp result = newTemp(Ity_I64);
   7663 
   7664    assign(op2, get_gpr_dw0(r2));
   7665    assign(op3, get_gpr_dw0(r3));
   7666    assign(result, binop(Iop_Sub64, mkexpr(op2), mkexpr(op3)));
   7667    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_64, op2, op3);
   7668    put_gpr_dw0(r1, mkexpr(result));
   7669 
   7670    return "slgrk";
   7671 }
   7672 
   7673 static HChar *
   7674 s390_irgen_SL(UChar r1, IRTemp op2addr)
   7675 {
   7676    IRTemp op1 = newTemp(Ity_I32);
   7677    IRTemp op2 = newTemp(Ity_I32);
   7678    IRTemp result = newTemp(Ity_I32);
   7679 
   7680    assign(op1, get_gpr_w1(r1));
   7681    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   7682    assign(result, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)));
   7683    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_32, op1, op2);
   7684    put_gpr_w1(r1, mkexpr(result));
   7685 
   7686    return "sl";
   7687 }
   7688 
   7689 static HChar *
   7690 s390_irgen_SLY(UChar r1, IRTemp op2addr)
   7691 {
   7692    IRTemp op1 = newTemp(Ity_I32);
   7693    IRTemp op2 = newTemp(Ity_I32);
   7694    IRTemp result = newTemp(Ity_I32);
   7695 
   7696    assign(op1, get_gpr_w1(r1));
   7697    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   7698    assign(result, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)));
   7699    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_32, op1, op2);
   7700    put_gpr_w1(r1, mkexpr(result));
   7701 
   7702    return "sly";
   7703 }
   7704 
   7705 static HChar *
   7706 s390_irgen_SLG(UChar r1, IRTemp op2addr)
   7707 {
   7708    IRTemp op1 = newTemp(Ity_I64);
   7709    IRTemp op2 = newTemp(Ity_I64);
   7710    IRTemp result = newTemp(Ity_I64);
   7711 
   7712    assign(op1, get_gpr_dw0(r1));
   7713    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   7714    assign(result, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)));
   7715    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_64, op1, op2);
   7716    put_gpr_dw0(r1, mkexpr(result));
   7717 
   7718    return "slg";
   7719 }
   7720 
   7721 static HChar *
   7722 s390_irgen_SLGF(UChar r1, IRTemp op2addr)
   7723 {
   7724    IRTemp op1 = newTemp(Ity_I64);
   7725    IRTemp op2 = newTemp(Ity_I64);
   7726    IRTemp result = newTemp(Ity_I64);
   7727 
   7728    assign(op1, get_gpr_dw0(r1));
   7729    assign(op2, unop(Iop_32Uto64, load(Ity_I32, mkexpr(op2addr))));
   7730    assign(result, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)));
   7731    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_64, op1, op2);
   7732    put_gpr_dw0(r1, mkexpr(result));
   7733 
   7734    return "slgf";
   7735 }
   7736 
   7737 static HChar *
   7738 s390_irgen_SLFI(UChar r1, UInt i2)
   7739 {
   7740    IRTemp op1 = newTemp(Ity_I32);
   7741    UInt op2;
   7742    IRTemp result = newTemp(Ity_I32);
   7743 
   7744    assign(op1, get_gpr_w1(r1));
   7745    op2 = i2;
   7746    assign(result, binop(Iop_Sub32, mkexpr(op1), mkU32(op2)));
   7747    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_32, op1, mktemp(Ity_I32,
   7748                        mkU32(op2)));
   7749    put_gpr_w1(r1, mkexpr(result));
   7750 
   7751    return "slfi";
   7752 }
   7753 
   7754 static HChar *
   7755 s390_irgen_SLGFI(UChar r1, UInt i2)
   7756 {
   7757    IRTemp op1 = newTemp(Ity_I64);
   7758    ULong op2;
   7759    IRTemp result = newTemp(Ity_I64);
   7760 
   7761    assign(op1, get_gpr_dw0(r1));
   7762    op2 = (ULong)i2;
   7763    assign(result, binop(Iop_Sub64, mkexpr(op1), mkU64(op2)));
   7764    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_64, op1, mktemp(Ity_I64,
   7765                        mkU64(op2)));
   7766    put_gpr_dw0(r1, mkexpr(result));
   7767 
   7768    return "slgfi";
   7769 }
   7770 
   7771 static HChar *
   7772 s390_irgen_SLHHHR(UChar r3 __attribute__((unused)), UChar r1, UChar r2)
   7773 {
   7774    IRTemp op2 = newTemp(Ity_I32);
   7775    IRTemp op3 = newTemp(Ity_I32);
   7776    IRTemp result = newTemp(Ity_I32);
   7777 
   7778    assign(op2, get_gpr_w0(r1));
   7779    assign(op3, get_gpr_w0(r2));
   7780    assign(result, binop(Iop_Sub32, mkexpr(op2), mkexpr(op3)));
   7781    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_32, op2, op3);
   7782    put_gpr_w0(r1, mkexpr(result));
   7783 
   7784    return "slhhhr";
   7785 }
   7786 
   7787 static HChar *
   7788 s390_irgen_SLHHLR(UChar r3 __attribute__((unused)), UChar r1, UChar r2)
   7789 {
   7790    IRTemp op2 = newTemp(Ity_I32);
   7791    IRTemp op3 = newTemp(Ity_I32);
   7792    IRTemp result = newTemp(Ity_I32);
   7793 
   7794    assign(op2, get_gpr_w0(r1));
   7795    assign(op3, get_gpr_w1(r2));
   7796    assign(result, binop(Iop_Sub32, mkexpr(op2), mkexpr(op3)));
   7797    s390_cc_thunk_putZZ(S390_CC_OP_UNSIGNED_SUB_32, op2, op3);
   7798    put_gpr_w0(r1, mkexpr(result));
   7799 
   7800    return "slhhlr";
   7801 }
   7802 
   7803 static HChar *
   7804 s390_irgen_SLBR(UChar r1, UChar r2)
   7805 {
   7806    IRTemp op1 = newTemp(Ity_I32);
   7807    IRTemp op2 = newTemp(Ity_I32);
   7808    IRTemp result = newTemp(Ity_I32);
   7809    IRTemp borrow_in = newTemp(Ity_I32);
   7810 
   7811    assign(op1, get_gpr_w1(r1));
   7812    assign(op2, get_gpr_w1(r2));
   7813    assign(borrow_in, binop(Iop_Sub32, mkU32(1), binop(Iop_Shr32,
   7814           s390_call_calculate_cc(), mkU8(1))));
   7815    assign(result, binop(Iop_Sub32, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)),
   7816           mkexpr(borrow_in)));
   7817    s390_cc_thunk_putZZZ(S390_CC_OP_UNSIGNED_SUBB_32, op1, op2, borrow_in);
   7818    put_gpr_w1(r1, mkexpr(result));
   7819 
   7820    return "slbr";
   7821 }
   7822 
   7823 static HChar *
   7824 s390_irgen_SLBGR(UChar r1, UChar r2)
   7825 {
   7826    IRTemp op1 = newTemp(Ity_I64);
   7827    IRTemp op2 = newTemp(Ity_I64);
   7828    IRTemp result = newTemp(Ity_I64);
   7829    IRTemp borrow_in = newTemp(Ity_I64);
   7830 
   7831    assign(op1, get_gpr_dw0(r1));
   7832    assign(op2, get_gpr_dw0(r2));
   7833    assign(borrow_in, unop(Iop_32Uto64, binop(Iop_Sub32, mkU32(1),
   7834           binop(Iop_Shr32, s390_call_calculate_cc(), mkU8(1)))));
   7835    assign(result, binop(Iop_Sub64, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)),
   7836           mkexpr(borrow_in)));
   7837    s390_cc_thunk_putZZZ(S390_CC_OP_UNSIGNED_SUBB_64, op1, op2, borrow_in);
   7838    put_gpr_dw0(r1, mkexpr(result));
   7839 
   7840    return "slbgr";
   7841 }
   7842 
   7843 static HChar *
   7844 s390_irgen_SLB(UChar r1, IRTemp op2addr)
   7845 {
   7846    IRTemp op1 = newTemp(Ity_I32);
   7847    IRTemp op2 = newTemp(Ity_I32);
   7848    IRTemp result = newTemp(Ity_I32);
   7849    IRTemp borrow_in = newTemp(Ity_I32);
   7850 
   7851    assign(op1, get_gpr_w1(r1));
   7852    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   7853    assign(borrow_in, binop(Iop_Sub32, mkU32(1), binop(Iop_Shr32,
   7854           s390_call_calculate_cc(), mkU8(1))));
   7855    assign(result, binop(Iop_Sub32, binop(Iop_Sub32, mkexpr(op1), mkexpr(op2)),
   7856           mkexpr(borrow_in)));
   7857    s390_cc_thunk_putZZZ(S390_CC_OP_UNSIGNED_SUBB_32, op1, op2, borrow_in);
   7858    put_gpr_w1(r1, mkexpr(result));
   7859 
   7860    return "slb";
   7861 }
   7862 
   7863 static HChar *
   7864 s390_irgen_SLBG(UChar r1, IRTemp op2addr)
   7865 {
   7866    IRTemp op1 = newTemp(Ity_I64);
   7867    IRTemp op2 = newTemp(Ity_I64);
   7868    IRTemp result = newTemp(Ity_I64);
   7869    IRTemp borrow_in = newTemp(Ity_I64);
   7870 
   7871    assign(op1, get_gpr_dw0(r1));
   7872    assign(op2, load(Ity_I64, mkexpr(op2addr)));
   7873    assign(borrow_in, unop(Iop_32Uto64, binop(Iop_Sub32, mkU32(1),
   7874           binop(Iop_Shr32, s390_call_calculate_cc(), mkU8(1)))));
   7875    assign(result, binop(Iop_Sub64, binop(Iop_Sub64, mkexpr(op1), mkexpr(op2)),
   7876           mkexpr(borrow_in)));
   7877    s390_cc_thunk_putZZZ(S390_CC_OP_UNSIGNED_SUBB_64, op1, op2, borrow_in);
   7878    put_gpr_dw0(r1, mkexpr(result));
   7879 
   7880    return "slbg";
   7881 }
   7882 
   7883 static HChar *
   7884 s390_irgen_SVC(UChar i)
   7885 {
   7886    IRTemp sysno = newTemp(Ity_I64);
   7887 
   7888    if (i != 0) {
   7889       assign(sysno, mkU64(i));
   7890    } else {
   7891       assign(sysno, unop(Iop_32Uto64, get_gpr_w1(1)));
   7892    }
   7893    system_call(mkexpr(sysno));
   7894 
   7895    return "svc";
   7896 }
   7897 
   7898 static HChar *
   7899 s390_irgen_TM(UChar i2, IRTemp op1addr)
   7900 {
   7901    UChar mask;
   7902    IRTemp value = newTemp(Ity_I8);
   7903 
   7904    mask = i2;
   7905    assign(value, load(Ity_I8, mkexpr(op1addr)));
   7906    s390_cc_thunk_putZZ(S390_CC_OP_TEST_UNDER_MASK_8, value, mktemp(Ity_I8,
   7907                        mkU8(mask)));
   7908 
   7909    return "tm";
   7910 }
   7911 
   7912 static HChar *
   7913 s390_irgen_TMY(UChar i2, IRTemp op1addr)
   7914 {
   7915    UChar mask;
   7916    IRTemp value = newTemp(Ity_I8);
   7917 
   7918    mask = i2;
   7919    assign(value, load(Ity_I8, mkexpr(op1addr)));
   7920    s390_cc_thunk_putZZ(S390_CC_OP_TEST_UNDER_MASK_8, value, mktemp(Ity_I8,
   7921                        mkU8(mask)));
   7922 
   7923    return "tmy";
   7924 }
   7925 
   7926 static HChar *
   7927 s390_irgen_TMHH(UChar r1, UShort i2)
   7928 {
   7929    UShort mask;
   7930    IRTemp value = newTemp(Ity_I16);
   7931 
   7932    mask = i2;
   7933    assign(value, get_gpr_hw0(r1));
   7934    s390_cc_thunk_putZZ(S390_CC_OP_TEST_UNDER_MASK_16, value, mktemp(Ity_I16,
   7935                        mkU16(mask)));
   7936 
   7937    return "tmhh";
   7938 }
   7939 
   7940 static HChar *
   7941 s390_irgen_TMHL(UChar r1, UShort i2)
   7942 {
   7943    UShort mask;
   7944    IRTemp value = newTemp(Ity_I16);
   7945 
   7946    mask = i2;
   7947    assign(value, get_gpr_hw1(r1));
   7948    s390_cc_thunk_putZZ(S390_CC_OP_TEST_UNDER_MASK_16, value, mktemp(Ity_I16,
   7949                        mkU16(mask)));
   7950 
   7951    return "tmhl";
   7952 }
   7953 
   7954 static HChar *
   7955 s390_irgen_TMLH(UChar r1, UShort i2)
   7956 {
   7957    UShort mask;
   7958    IRTemp value = newTemp(Ity_I16);
   7959 
   7960    mask = i2;
   7961    assign(value, get_gpr_hw2(r1));
   7962    s390_cc_thunk_putZZ(S390_CC_OP_TEST_UNDER_MASK_16, value, mktemp(Ity_I16,
   7963                        mkU16(mask)));
   7964 
   7965    return "tmlh";
   7966 }
   7967 
   7968 static HChar *
   7969 s390_irgen_TMLL(UChar r1, UShort i2)
   7970 {
   7971    UShort mask;
   7972    IRTemp value = newTemp(Ity_I16);
   7973 
   7974    mask = i2;
   7975    assign(value, get_gpr_hw3(r1));
   7976    s390_cc_thunk_putZZ(S390_CC_OP_TEST_UNDER_MASK_16, value, mktemp(Ity_I16,
   7977                        mkU16(mask)));
   7978 
   7979    return "tmll";
   7980 }
   7981 
   7982 static HChar *
   7983 s390_irgen_EFPC(UChar r1)
   7984 {
   7985    put_gpr_w1(r1, get_fpc_w0());
   7986 
   7987    return "efpc";
   7988 }
   7989 
   7990 static HChar *
   7991 s390_irgen_LER(UChar r1, UChar r2)
   7992 {
   7993    put_fpr_w0(r1, get_fpr_w0(r2));
   7994 
   7995    return "ler";
   7996 }
   7997 
   7998 static HChar *
   7999 s390_irgen_LDR(UChar r1, UChar r2)
   8000 {
   8001    put_fpr_dw0(r1, get_fpr_dw0(r2));
   8002 
   8003    return "ldr";
   8004 }
   8005 
   8006 static HChar *
   8007 s390_irgen_LXR(UChar r1, UChar r2)
   8008 {
   8009    put_fpr_dw0(r1, get_fpr_dw0(r2));
   8010    put_fpr_dw0(r1 + 2, get_fpr_dw0(r2 + 2));
   8011 
   8012    return "lxr";
   8013 }
   8014 
   8015 static HChar *
   8016 s390_irgen_LE(UChar r1, IRTemp op2addr)
   8017 {
   8018    put_fpr_w0(r1, load(Ity_F32, mkexpr(op2addr)));
   8019 
   8020    return "le";
   8021 }
   8022 
   8023 static HChar *
   8024 s390_irgen_LD(UChar r1, IRTemp op2addr)
   8025 {
   8026    put_fpr_dw0(r1, load(Ity_F64, mkexpr(op2addr)));
   8027 
   8028    return "ld";
   8029 }
   8030 
   8031 static HChar *
   8032 s390_irgen_LEY(UChar r1, IRTemp op2addr)
   8033 {
   8034    put_fpr_w0(r1, load(Ity_F32, mkexpr(op2addr)));
   8035 
   8036    return "ley";
   8037 }
   8038 
   8039 static HChar *
   8040 s390_irgen_LDY(UChar r1, IRTemp op2addr)
   8041 {
   8042    put_fpr_dw0(r1, load(Ity_F64, mkexpr(op2addr)));
   8043 
   8044    return "ldy";
   8045 }
   8046 
   8047 static HChar *
   8048 s390_irgen_LFPC(IRTemp op2addr)
   8049 {
   8050    put_fpc_w0(load(Ity_I32, mkexpr(op2addr)));
   8051 
   8052    return "lfpc";
   8053 }
   8054 
   8055 static HChar *
   8056 s390_irgen_LZER(UChar r1)
   8057 {
   8058    put_fpr_w0(r1, mkF32i(0x0));
   8059 
   8060    return "lzer";
   8061 }
   8062 
   8063 static HChar *
   8064 s390_irgen_LZDR(UChar r1)
   8065 {
   8066    put_fpr_dw0(r1, mkF64i(0x0));
   8067 
   8068    return "lzdr";
   8069 }
   8070 
   8071 static HChar *
   8072 s390_irgen_LZXR(UChar r1)
   8073 {
   8074    put_fpr_dw0(r1, mkF64i(0x0));
   8075    put_fpr_dw0(r1 + 2, mkF64i(0x0));
   8076 
   8077    return "lzxr";
   8078 }
   8079 
   8080 static HChar *
   8081 s390_irgen_SRNM(IRTemp op2addr)
   8082 {
   8083    UInt mask;
   8084 
   8085    mask = 3;
   8086    put_fpc_w0(binop(Iop_Or32, binop(Iop_And32, get_fpc_w0(), mkU32(~mask)),
   8087               binop(Iop_And32, unop(Iop_64to32, mkexpr(op2addr)), mkU32(mask)))
   8088               );
   8089 
   8090    return "srnm";
   8091 }
   8092 
   8093 static HChar *
   8094 s390_irgen_SFPC(UChar r1)
   8095 {
   8096    put_fpc_w0(get_gpr_w1(r1));
   8097 
   8098    return "sfpc";
   8099 }
   8100 
   8101 static HChar *
   8102 s390_irgen_STE(UChar r1, IRTemp op2addr)
   8103 {
   8104    store(mkexpr(op2addr), get_fpr_w0(r1));
   8105 
   8106    return "ste";
   8107 }
   8108 
   8109 static HChar *
   8110 s390_irgen_STD(UChar r1, IRTemp op2addr)
   8111 {
   8112    store(mkexpr(op2addr), get_fpr_dw0(r1));
   8113 
   8114    return "std";
   8115 }
   8116 
   8117 static HChar *
   8118 s390_irgen_STEY(UChar r1, IRTemp op2addr)
   8119 {
   8120    store(mkexpr(op2addr), get_fpr_w0(r1));
   8121 
   8122    return "stey";
   8123 }
   8124 
   8125 static HChar *
   8126 s390_irgen_STDY(UChar r1, IRTemp op2addr)
   8127 {
   8128    store(mkexpr(op2addr), get_fpr_dw0(r1));
   8129 
   8130    return "stdy";
   8131 }
   8132 
   8133 static HChar *
   8134 s390_irgen_STFPC(IRTemp op2addr)
   8135 {
   8136    store(mkexpr(op2addr), get_fpc_w0());
   8137 
   8138    return "stfpc";
   8139 }
   8140 
   8141 static HChar *
   8142 s390_irgen_AEBR(UChar r1, UChar r2)
   8143 {
   8144    IRTemp op1 = newTemp(Ity_F32);
   8145    IRTemp op2 = newTemp(Ity_F32);
   8146    IRTemp result = newTemp(Ity_F32);
   8147 
   8148    assign(op1, get_fpr_w0(r1));
   8149    assign(op2, get_fpr_w0(r2));
   8150    assign(result, triop(Iop_AddF32, mkU32(Irrm_NEAREST), mkexpr(op1),
   8151           mkexpr(op2)));
   8152    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_32, result);
   8153    put_fpr_w0(r1, mkexpr(result));
   8154 
   8155    return "aebr";
   8156 }
   8157 
   8158 static HChar *
   8159 s390_irgen_ADBR(UChar r1, UChar r2)
   8160 {
   8161    IRTemp op1 = newTemp(Ity_F64);
   8162    IRTemp op2 = newTemp(Ity_F64);
   8163    IRTemp result = newTemp(Ity_F64);
   8164 
   8165    assign(op1, get_fpr_dw0(r1));
   8166    assign(op2, get_fpr_dw0(r2));
   8167    assign(result, triop(Iop_AddF64, mkU32(Irrm_NEAREST), mkexpr(op1),
   8168           mkexpr(op2)));
   8169    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_64, result);
   8170    put_fpr_dw0(r1, mkexpr(result));
   8171 
   8172    return "adbr";
   8173 }
   8174 
   8175 static HChar *
   8176 s390_irgen_AEB(UChar r1, IRTemp op2addr)
   8177 {
   8178    IRTemp op1 = newTemp(Ity_F32);
   8179    IRTemp op2 = newTemp(Ity_F32);
   8180    IRTemp result = newTemp(Ity_F32);
   8181 
   8182    assign(op1, get_fpr_w0(r1));
   8183    assign(op2, load(Ity_F32, mkexpr(op2addr)));
   8184    assign(result, triop(Iop_AddF32, mkU32(Irrm_NEAREST), mkexpr(op1),
   8185           mkexpr(op2)));
   8186    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_32, result);
   8187    put_fpr_w0(r1, mkexpr(result));
   8188 
   8189    return "aeb";
   8190 }
   8191 
   8192 static HChar *
   8193 s390_irgen_ADB(UChar r1, IRTemp op2addr)
   8194 {
   8195    IRTemp op1 = newTemp(Ity_F64);
   8196    IRTemp op2 = newTemp(Ity_F64);
   8197    IRTemp result = newTemp(Ity_F64);
   8198 
   8199    assign(op1, get_fpr_dw0(r1));
   8200    assign(op2, load(Ity_F64, mkexpr(op2addr)));
   8201    assign(result, triop(Iop_AddF64, mkU32(Irrm_NEAREST), mkexpr(op1),
   8202           mkexpr(op2)));
   8203    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_64, result);
   8204    put_fpr_dw0(r1, mkexpr(result));
   8205 
   8206    return "adb";
   8207 }
   8208 
   8209 static HChar *
   8210 s390_irgen_CEFBR(UChar r1, UChar r2)
   8211 {
   8212    IRTemp op2 = newTemp(Ity_I32);
   8213 
   8214    assign(op2, get_gpr_w1(r2));
   8215    put_fpr_w0(r1, binop(Iop_I32StoF32, mkU32(Irrm_NEAREST), mkexpr(op2)));
   8216 
   8217    return "cefbr";
   8218 }
   8219 
   8220 static HChar *
   8221 s390_irgen_CDFBR(UChar r1, UChar r2)
   8222 {
   8223    IRTemp op2 = newTemp(Ity_I32);
   8224 
   8225    assign(op2, get_gpr_w1(r2));
   8226    put_fpr_dw0(r1, unop(Iop_I32StoF64, mkexpr(op2)));
   8227 
   8228    return "cdfbr";
   8229 }
   8230 
   8231 static HChar *
   8232 s390_irgen_CEGBR(UChar r1, UChar r2)
   8233 {
   8234    IRTemp op2 = newTemp(Ity_I64);
   8235 
   8236    assign(op2, get_gpr_dw0(r2));
   8237    put_fpr_w0(r1, binop(Iop_I64StoF32, mkU32(Irrm_NEAREST), mkexpr(op2)));
   8238 
   8239    return "cegbr";
   8240 }
   8241 
   8242 static HChar *
   8243 s390_irgen_CDGBR(UChar r1, UChar r2)
   8244 {
   8245    IRTemp op2 = newTemp(Ity_I64);
   8246 
   8247    assign(op2, get_gpr_dw0(r2));
   8248    put_fpr_dw0(r1, binop(Iop_I64StoF64, mkU32(Irrm_NEAREST), mkexpr(op2)));
   8249 
   8250    return "cdgbr";
   8251 }
   8252 
   8253 static HChar *
   8254 s390_irgen_CFEBR(UChar r3, UChar r1, UChar r2)
   8255 {
   8256    IRTemp op = newTemp(Ity_F32);
   8257    IRTemp result = newTemp(Ity_I32);
   8258 
   8259    assign(op, get_fpr_w0(r2));
   8260    assign(result, binop(Iop_F32toI32S, mkU32(encode_rounding_mode(r3)),
   8261           mkexpr(op)));
   8262    put_gpr_w1(r1, mkexpr(result));
   8263    s390_cc_thunk_putF(S390_CC_OP_BFP_32_TO_INT_32, op);
   8264 
   8265    return "cfebr";
   8266 }
   8267 
   8268 static HChar *
   8269 s390_irgen_CFDBR(UChar r3, UChar r1, UChar r2)
   8270 {
   8271    IRTemp op = newTemp(Ity_F64);
   8272    IRTemp result = newTemp(Ity_I32);
   8273 
   8274    assign(op, get_fpr_dw0(r2));
   8275    assign(result, binop(Iop_F64toI32S, mkU32(encode_rounding_mode(r3)),
   8276           mkexpr(op)));
   8277    put_gpr_w1(r1, mkexpr(result));
   8278    s390_cc_thunk_putF(S390_CC_OP_BFP_64_TO_INT_32, op);
   8279 
   8280    return "cfdbr";
   8281 }
   8282 
   8283 static HChar *
   8284 s390_irgen_CGEBR(UChar r3, UChar r1, UChar r2)
   8285 {
   8286    IRTemp op = newTemp(Ity_F32);
   8287    IRTemp result = newTemp(Ity_I64);
   8288 
   8289    assign(op, get_fpr_w0(r2));
   8290    assign(result, binop(Iop_F32toI64S, mkU32(encode_rounding_mode(r3)),
   8291           mkexpr(op)));
   8292    put_gpr_dw0(r1, mkexpr(result));
   8293    s390_cc_thunk_putF(S390_CC_OP_BFP_32_TO_INT_64, op);
   8294 
   8295    return "cgebr";
   8296 }
   8297 
   8298 static HChar *
   8299 s390_irgen_CGDBR(UChar r3, UChar r1, UChar r2)
   8300 {
   8301    IRTemp op = newTemp(Ity_F64);
   8302    IRTemp result = newTemp(Ity_I64);
   8303 
   8304    assign(op, get_fpr_dw0(r2));
   8305    assign(result, binop(Iop_F64toI64S, mkU32(encode_rounding_mode(r3)),
   8306           mkexpr(op)));
   8307    put_gpr_dw0(r1, mkexpr(result));
   8308    s390_cc_thunk_putF(S390_CC_OP_BFP_64_TO_INT_64, op);
   8309 
   8310    return "cgdbr";
   8311 }
   8312 
   8313 static HChar *
   8314 s390_irgen_DEBR(UChar r1, UChar r2)
   8315 {
   8316    IRTemp op1 = newTemp(Ity_F32);
   8317    IRTemp op2 = newTemp(Ity_F32);
   8318    IRTemp result = newTemp(Ity_F32);
   8319 
   8320    assign(op1, get_fpr_w0(r1));
   8321    assign(op2, get_fpr_w0(r2));
   8322    assign(result, triop(Iop_DivF32, mkU32(Irrm_NEAREST), mkexpr(op1),
   8323           mkexpr(op2)));
   8324    put_fpr_w0(r1, mkexpr(result));
   8325 
   8326    return "debr";
   8327 }
   8328 
   8329 static HChar *
   8330 s390_irgen_DDBR(UChar r1, UChar r2)
   8331 {
   8332    IRTemp op1 = newTemp(Ity_F64);
   8333    IRTemp op2 = newTemp(Ity_F64);
   8334    IRTemp result = newTemp(Ity_F64);
   8335 
   8336    assign(op1, get_fpr_dw0(r1));
   8337    assign(op2, get_fpr_dw0(r2));
   8338    assign(result, triop(Iop_DivF64, mkU32(Irrm_NEAREST), mkexpr(op1),
   8339           mkexpr(op2)));
   8340    put_fpr_dw0(r1, mkexpr(result));
   8341 
   8342    return "ddbr";
   8343 }
   8344 
   8345 static HChar *
   8346 s390_irgen_DEB(UChar r1, IRTemp op2addr)
   8347 {
   8348    IRTemp op1 = newTemp(Ity_F32);
   8349    IRTemp op2 = newTemp(Ity_F32);
   8350    IRTemp result = newTemp(Ity_F32);
   8351 
   8352    assign(op1, get_fpr_w0(r1));
   8353    assign(op2, load(Ity_F32, mkexpr(op2addr)));
   8354    assign(result, triop(Iop_DivF32, mkU32(Irrm_NEAREST), mkexpr(op1),
   8355           mkexpr(op2)));
   8356    put_fpr_w0(r1, mkexpr(result));
   8357 
   8358    return "deb";
   8359 }
   8360 
   8361 static HChar *
   8362 s390_irgen_DDB(UChar r1, IRTemp op2addr)
   8363 {
   8364    IRTemp op1 = newTemp(Ity_F64);
   8365    IRTemp op2 = newTemp(Ity_F64);
   8366    IRTemp result = newTemp(Ity_F64);
   8367 
   8368    assign(op1, get_fpr_dw0(r1));
   8369    assign(op2, load(Ity_F64, mkexpr(op2addr)));
   8370    assign(result, triop(Iop_DivF64, mkU32(Irrm_NEAREST), mkexpr(op1),
   8371           mkexpr(op2)));
   8372    put_fpr_dw0(r1, mkexpr(result));
   8373 
   8374    return "ddb";
   8375 }
   8376 
   8377 static HChar *
   8378 s390_irgen_LTEBR(UChar r1, UChar r2)
   8379 {
   8380    IRTemp result = newTemp(Ity_F32);
   8381 
   8382    assign(result, get_fpr_w0(r2));
   8383    put_fpr_w0(r1, mkexpr(result));
   8384    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_32, result);
   8385 
   8386    return "ltebr";
   8387 }
   8388 
   8389 static HChar *
   8390 s390_irgen_LTDBR(UChar r1, UChar r2)
   8391 {
   8392    IRTemp result = newTemp(Ity_F64);
   8393 
   8394    assign(result, get_fpr_dw0(r2));
   8395    put_fpr_dw0(r1, mkexpr(result));
   8396    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_64, result);
   8397 
   8398    return "ltdbr";
   8399 }
   8400 
   8401 static HChar *
   8402 s390_irgen_LCEBR(UChar r1, UChar r2)
   8403 {
   8404    IRTemp result = newTemp(Ity_F32);
   8405 
   8406    assign(result, unop(Iop_NegF32, get_fpr_w0(r2)));
   8407    put_fpr_w0(r1, mkexpr(result));
   8408    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_32, result);
   8409 
   8410    return "lcebr";
   8411 }
   8412 
   8413 static HChar *
   8414 s390_irgen_LCDBR(UChar r1, UChar r2)
   8415 {
   8416    IRTemp result = newTemp(Ity_F64);
   8417 
   8418    assign(result, unop(Iop_NegF64, get_fpr_dw0(r2)));
   8419    put_fpr_dw0(r1, mkexpr(result));
   8420    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_64, result);
   8421 
   8422    return "lcdbr";
   8423 }
   8424 
   8425 static HChar *
   8426 s390_irgen_LDEBR(UChar r1, UChar r2)
   8427 {
   8428    IRTemp op = newTemp(Ity_F32);
   8429 
   8430    assign(op, get_fpr_w0(r2));
   8431    put_fpr_dw0(r1, unop(Iop_F32toF64, mkexpr(op)));
   8432 
   8433    return "ldebr";
   8434 }
   8435 
   8436 static HChar *
   8437 s390_irgen_LDEB(UChar r1, IRTemp op2addr)
   8438 {
   8439    IRTemp op = newTemp(Ity_F32);
   8440 
   8441    assign(op, load(Ity_F32, mkexpr(op2addr)));
   8442    put_fpr_dw0(r1, unop(Iop_F32toF64, mkexpr(op)));
   8443 
   8444    return "ldeb";
   8445 }
   8446 
   8447 static HChar *
   8448 s390_irgen_LEDBR(UChar r1, UChar r2)
   8449 {
   8450    IRTemp op = newTemp(Ity_F64);
   8451 
   8452    assign(op, get_fpr_dw0(r2));
   8453    put_fpr_w0(r1, binop(Iop_F64toF32, mkU32(Irrm_NEAREST), mkexpr(op)));
   8454 
   8455    return "ledbr";
   8456 }
   8457 
   8458 static HChar *
   8459 s390_irgen_MEEBR(UChar r1, UChar r2)
   8460 {
   8461    IRTemp op1 = newTemp(Ity_F32);
   8462    IRTemp op2 = newTemp(Ity_F32);
   8463    IRTemp result = newTemp(Ity_F32);
   8464 
   8465    assign(op1, get_fpr_w0(r1));
   8466    assign(op2, get_fpr_w0(r2));
   8467    assign(result, triop(Iop_MulF32, mkU32(Irrm_NEAREST), mkexpr(op1),
   8468           mkexpr(op2)));
   8469    put_fpr_w0(r1, mkexpr(result));
   8470 
   8471    return "meebr";
   8472 }
   8473 
   8474 static HChar *
   8475 s390_irgen_MDBR(UChar r1, UChar r2)
   8476 {
   8477    IRTemp op1 = newTemp(Ity_F64);
   8478    IRTemp op2 = newTemp(Ity_F64);
   8479    IRTemp result = newTemp(Ity_F64);
   8480 
   8481    assign(op1, get_fpr_dw0(r1));
   8482    assign(op2, get_fpr_dw0(r2));
   8483    assign(result, triop(Iop_MulF64, mkU32(Irrm_NEAREST), mkexpr(op1),
   8484           mkexpr(op2)));
   8485    put_fpr_dw0(r1, mkexpr(result));
   8486 
   8487    return "mdbr";
   8488 }
   8489 
   8490 static HChar *
   8491 s390_irgen_MEEB(UChar r1, IRTemp op2addr)
   8492 {
   8493    IRTemp op1 = newTemp(Ity_F32);
   8494    IRTemp op2 = newTemp(Ity_F32);
   8495    IRTemp result = newTemp(Ity_F32);
   8496 
   8497    assign(op1, get_fpr_w0(r1));
   8498    assign(op2, load(Ity_F32, mkexpr(op2addr)));
   8499    assign(result, triop(Iop_MulF32, mkU32(Irrm_NEAREST), mkexpr(op1),
   8500           mkexpr(op2)));
   8501    put_fpr_w0(r1, mkexpr(result));
   8502 
   8503    return "meeb";
   8504 }
   8505 
   8506 static HChar *
   8507 s390_irgen_MDB(UChar r1, IRTemp op2addr)
   8508 {
   8509    IRTemp op1 = newTemp(Ity_F64);
   8510    IRTemp op2 = newTemp(Ity_F64);
   8511    IRTemp result = newTemp(Ity_F64);
   8512 
   8513    assign(op1, get_fpr_dw0(r1));
   8514    assign(op2, load(Ity_F64, mkexpr(op2addr)));
   8515    assign(result, triop(Iop_MulF64, mkU32(Irrm_NEAREST), mkexpr(op1),
   8516           mkexpr(op2)));
   8517    put_fpr_dw0(r1, mkexpr(result));
   8518 
   8519    return "mdb";
   8520 }
   8521 
   8522 static HChar *
   8523 s390_irgen_SEBR(UChar r1, UChar r2)
   8524 {
   8525    IRTemp op1 = newTemp(Ity_F32);
   8526    IRTemp op2 = newTemp(Ity_F32);
   8527    IRTemp result = newTemp(Ity_F32);
   8528 
   8529    assign(op1, get_fpr_w0(r1));
   8530    assign(op2, get_fpr_w0(r2));
   8531    assign(result, triop(Iop_SubF32, mkU32(Irrm_NEAREST), mkexpr(op1),
   8532           mkexpr(op2)));
   8533    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_32, result);
   8534    put_fpr_w0(r1, mkexpr(result));
   8535 
   8536    return "sebr";
   8537 }
   8538 
   8539 static HChar *
   8540 s390_irgen_SDBR(UChar r1, UChar r2)
   8541 {
   8542    IRTemp op1 = newTemp(Ity_F64);
   8543    IRTemp op2 = newTemp(Ity_F64);
   8544    IRTemp result = newTemp(Ity_F64);
   8545 
   8546    assign(op1, get_fpr_dw0(r1));
   8547    assign(op2, get_fpr_dw0(r2));
   8548    assign(result, triop(Iop_SubF64, mkU32(Irrm_NEAREST), mkexpr(op1),
   8549           mkexpr(op2)));
   8550    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_64, result);
   8551    put_fpr_dw0(r1, mkexpr(result));
   8552 
   8553    return "sdbr";
   8554 }
   8555 
   8556 static HChar *
   8557 s390_irgen_SEB(UChar r1, IRTemp op2addr)
   8558 {
   8559    IRTemp op1 = newTemp(Ity_F32);
   8560    IRTemp op2 = newTemp(Ity_F32);
   8561    IRTemp result = newTemp(Ity_F32);
   8562 
   8563    assign(op1, get_fpr_w0(r1));
   8564    assign(op2, load(Ity_F32, mkexpr(op2addr)));
   8565    assign(result, triop(Iop_SubF32, mkU32(Irrm_NEAREST), mkexpr(op1),
   8566           mkexpr(op2)));
   8567    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_32, result);
   8568    put_fpr_w0(r1, mkexpr(result));
   8569 
   8570    return "seb";
   8571 }
   8572 
   8573 static HChar *
   8574 s390_irgen_SDB(UChar r1, IRTemp op2addr)
   8575 {
   8576    IRTemp op1 = newTemp(Ity_F64);
   8577    IRTemp op2 = newTemp(Ity_F64);
   8578    IRTemp result = newTemp(Ity_F64);
   8579 
   8580    assign(op1, get_fpr_dw0(r1));
   8581    assign(op2, load(Ity_F64, mkexpr(op2addr)));
   8582    assign(result, triop(Iop_SubF64, mkU32(Irrm_NEAREST), mkexpr(op1),
   8583           mkexpr(op2)));
   8584    s390_cc_thunk_putF(S390_CC_OP_BFP_RESULT_64, result);
   8585    put_fpr_dw0(r1, mkexpr(result));
   8586 
   8587    return "sdb";
   8588 }
   8589 
   8590 
   8591 static HChar *
   8592 s390_irgen_CLC(UChar length, IRTemp start1, IRTemp start2)
   8593 {
   8594    IRTemp len = newTemp(Ity_I64);
   8595 
   8596    assign(len, mkU64(length));
   8597    s390_irgen_CLC_EX(len, start1, start2);
   8598 
   8599    return "clc";
   8600 }
   8601 
   8602 static HChar *
   8603 s390_irgen_CLCL(UChar r1, UChar r2)
   8604 {
   8605    IRTemp addr1 = newTemp(Ity_I64);
   8606    IRTemp addr2 = newTemp(Ity_I64);
   8607    IRTemp addr1_load = newTemp(Ity_I64);
   8608    IRTemp addr2_load = newTemp(Ity_I64);
   8609    IRTemp len1 = newTemp(Ity_I32);
   8610    IRTemp len2 = newTemp(Ity_I32);
   8611    IRTemp r1p1 = newTemp(Ity_I32);   /* contents of r1 + 1 */
   8612    IRTemp r2p1 = newTemp(Ity_I32);   /* contents of r2 + 1 */
   8613    IRTemp single1 = newTemp(Ity_I8);
   8614    IRTemp single2 = newTemp(Ity_I8);
   8615    IRTemp pad = newTemp(Ity_I8);
   8616 
   8617    assign(addr1, get_gpr_dw0(r1));
   8618    assign(r1p1, get_gpr_w1(r1 + 1));
   8619    assign(len1, binop(Iop_And32, mkexpr(r1p1), mkU32(0x00ffffff)));
   8620    assign(addr2, get_gpr_dw0(r2));
   8621    assign(r2p1, get_gpr_w1(r2 + 1));
   8622    assign(len2, binop(Iop_And32, mkexpr(r2p1), mkU32(0x00ffffff)));
   8623    assign(pad, get_gpr_b4(r2 + 1));
   8624 
   8625    /* len1 == 0 and len2 == 0? Exit */
   8626    s390_cc_set(0);
   8627    next_insn_if(binop(Iop_CmpEQ32, binop(Iop_Or32, mkexpr(len1),
   8628                                          mkexpr(len2)), mkU32(0)));
   8629 
   8630    /* Because mkite evaluates both the then-clause and the else-clause
   8631       we cannot load directly from addr1 here. If len1 is 0, then adddr1
   8632       may be NULL and loading from there would segfault. So we provide a
   8633       valid dummy address in that case. Loading from there does no harm and
   8634       the value will be discarded at runtime. */
   8635    assign(addr1_load,
   8636           mkite(binop(Iop_CmpEQ32, mkexpr(len1), mkU32(0)),
   8637                 mkU64(guest_IA_curr_instr), mkexpr(addr1)));
   8638    assign(single1,
   8639           mkite(binop(Iop_CmpEQ32, mkexpr(len1), mkU32(0)),
   8640                 mkexpr(pad), load(Ity_I8, mkexpr(addr1_load))));
   8641 
   8642    assign(addr2_load,
   8643           mkite(binop(Iop_CmpEQ32, mkexpr(len2), mkU32(0)),
   8644                 mkU64(guest_IA_curr_instr), mkexpr(addr2)));
   8645    assign(single2,
   8646           mkite(binop(Iop_CmpEQ32, mkexpr(len2), mkU32(0)),
   8647                 mkexpr(pad), load(Ity_I8, mkexpr(addr2_load))));
   8648 
   8649    s390_cc_thunk_put2(S390_CC_OP_UNSIGNED_COMPARE, single1, single2, False);
   8650    /* Fields differ ? */
   8651    next_insn_if(binop(Iop_CmpNE8, mkexpr(single1), mkexpr(single2)));
   8652 
   8653    /* Update len1 and addr1, unless len1 == 0. */
   8654    put_gpr_dw0(r1,
   8655                mkite(binop(Iop_CmpEQ32, mkexpr(len1), mkU32(0)),
   8656                      mkexpr(addr1),
   8657                      binop(Iop_Add64, mkexpr(addr1), mkU64(1))));
   8658 
   8659    /* When updating len1 we must not modify bits (r1+1)[0:39] */
   8660    put_gpr_w1(r1 + 1,
   8661               mkite(binop(Iop_CmpEQ32, mkexpr(len1), mkU32(0)),
   8662                     binop(Iop_And32, mkexpr(r1p1), mkU32(0xFF000000u)),
   8663                     binop(Iop_Sub32, mkexpr(r1p1), mkU32(1))));
   8664 
   8665    /* Update len2 and addr2, unless len2 == 0. */
   8666    put_gpr_dw0(r2,
   8667                mkite(binop(Iop_CmpEQ32, mkexpr(len2), mkU32(0)),
   8668                      mkexpr(addr2),
   8669                      binop(Iop_Add64, mkexpr(addr2), mkU64(1))));
   8670 
   8671    /* When updating len2 we must not modify bits (r2+1)[0:39] */
   8672    put_gpr_w1(r2 + 1,
   8673               mkite(binop(Iop_CmpEQ32, mkexpr(len2), mkU32(0)),
   8674                     binop(Iop_And32, mkexpr(r2p1), mkU32(0xFF000000u)),
   8675                     binop(Iop_Sub32, mkexpr(r2p1), mkU32(1))));
   8676 
   8677    iterate();
   8678 
   8679    return "clcl";
   8680 }
   8681 
   8682 static HChar *
   8683 s390_irgen_CLCLE(UChar r1, UChar r3, IRTemp pad2)
   8684 {
   8685    IRTemp addr1, addr3, addr1_load, addr3_load, len1, len3, single1, single3;
   8686 
   8687    addr1 = newTemp(Ity_I64);
   8688    addr3 = newTemp(Ity_I64);
   8689    addr1_load = newTemp(Ity_I64);
   8690    addr3_load = newTemp(Ity_I64);
   8691    len1 = newTemp(Ity_I64);
   8692    len3 = newTemp(Ity_I64);
   8693    single1 = newTemp(Ity_I8);
   8694    single3 = newTemp(Ity_I8);
   8695 
   8696    assign(addr1, get_gpr_dw0(r1));
   8697    assign(len1, get_gpr_dw0(r1 + 1));
   8698    assign(addr3, get_gpr_dw0(r3));
   8699    assign(len3, get_gpr_dw0(r3 + 1));
   8700 
   8701    /* len1 == 0 and len3 == 0? Exit */
   8702    s390_cc_set(0);
   8703    next_insn_if(binop(Iop_CmpEQ64,binop(Iop_Or64, mkexpr(len1),
   8704                                         mkexpr(len3)), mkU64(0)));
   8705 
   8706    /* A mux requires both ways to be possible. This is a way to prevent clcle
   8707       from reading from addr1 if it should read from the pad. Since the pad
   8708       has no address, just read from the instruction, we discard that anyway */
   8709    assign(addr1_load,
   8710           mkite(binop(Iop_CmpEQ64, mkexpr(len1), mkU64(0)),
   8711                 mkU64(guest_IA_curr_instr), mkexpr(addr1)));
   8712 
   8713    /* same for addr3 */
   8714    assign(addr3_load,
   8715           mkite(binop(Iop_CmpEQ64, mkexpr(len3), mkU64(0)),
   8716                 mkU64(guest_IA_curr_instr), mkexpr(addr3)));
   8717 
   8718    assign(single1,
   8719           mkite(binop(Iop_CmpEQ64, mkexpr(len1), mkU64(0)),
   8720                 unop(Iop_64to8, mkexpr(pad2)),
   8721                 load(Ity_I8, mkexpr(addr1_load))));
   8722 
   8723    assign(single3,
   8724           mkite(binop(Iop_CmpEQ64, mkexpr(len3), mkU64(0)),
   8725                 unop(Iop_64to8, mkexpr(pad2)),
   8726                 load(Ity_I8, mkexpr(addr3_load))));
   8727 
   8728    s390_cc_thunk_put2(S390_CC_OP_UNSIGNED_COMPARE, single1, single3, False);
   8729    /* Both fields differ ? */
   8730    next_insn_if(binop(Iop_CmpNE8, mkexpr(single1), mkexpr(single3)));
   8731 
   8732    /* If a length in 0 we must not change this length and the address */
   8733    put_gpr_dw0(r1,
   8734                mkite(binop(Iop_CmpEQ64, mkexpr(len1), mkU64(0)),
   8735                      mkexpr(addr1),
   8736                      binop(Iop_Add64, mkexpr(addr1), mkU64(1))));
   8737 
   8738    put_gpr_dw0(r1 + 1,
   8739                mkite(binop(Iop_CmpEQ64, mkexpr(len1), mkU64(0)),
   8740                      mkU64(0), binop(Iop_Sub64, mkexpr(len1), mkU64(1))));
   8741 
   8742    put_gpr_dw0(r3,
   8743                mkite(binop(Iop_CmpEQ64, mkexpr(len3), mkU64(0)),
   8744                      mkexpr(addr3),
   8745                      binop(Iop_Add64, mkexpr(addr3), mkU64(1))));
   8746 
   8747    put_gpr_dw0(r3 + 1,
   8748                mkite(binop(Iop_CmpEQ64, mkexpr(len3), mkU64(0)),
   8749                      mkU64(0), binop(Iop_Sub64, mkexpr(len3), mkU64(1))));
   8750 
   8751    iterate();
   8752 
   8753    return "clcle";
   8754 }
   8755 
   8756 
   8757 static void
   8758 s390_irgen_XC_EX(IRTemp length, IRTemp start1, IRTemp start2)
   8759 {
   8760    s390_irgen_xonc(Iop_Xor8, length, start1, start2);
   8761 }
   8762 
   8763 
   8764 static void
   8765 s390_irgen_NC_EX(IRTemp length, IRTemp start1, IRTemp start2)
   8766 {
   8767    s390_irgen_xonc(Iop_And8, length, start1, start2);
   8768 }
   8769 
   8770 
   8771 static void
   8772 s390_irgen_OC_EX(IRTemp length, IRTemp start1, IRTemp start2)
   8773 {
   8774    s390_irgen_xonc(Iop_Or8, length, start1, start2);
   8775 }
   8776 
   8777 
   8778 static void
   8779 s390_irgen_CLC_EX(IRTemp length, IRTemp start1, IRTemp start2)
   8780 {
   8781    IRTemp current1 = newTemp(Ity_I8);
   8782    IRTemp current2 = newTemp(Ity_I8);
   8783    IRTemp counter = newTemp(Ity_I64);
   8784 
   8785    assign(counter, get_counter_dw0());
   8786    put_counter_dw0(mkU64(0));
   8787 
   8788    assign(current1, load(Ity_I8, binop(Iop_Add64, mkexpr(start1),
   8789                                        mkexpr(counter))));
   8790    assign(current2, load(Ity_I8, binop(Iop_Add64, mkexpr(start2),
   8791                                        mkexpr(counter))));
   8792    s390_cc_thunk_put2(S390_CC_OP_UNSIGNED_COMPARE, current1, current2,
   8793                       False);
   8794 
   8795    /* Both fields differ ? */
   8796    next_insn_if(binop(Iop_CmpNE8, mkexpr(current1), mkexpr(current2)));
   8797 
   8798    /* Check for end of field */
   8799    put_counter_dw0(binop(Iop_Add64, mkexpr(counter), mkU64(1)));
   8800    iterate_if(binop(Iop_CmpNE64, mkexpr(counter), mkexpr(length)));
   8801    put_counter_dw0(mkU64(0));
   8802 }
   8803 
   8804 static void
   8805 s390_irgen_MVC_EX(IRTemp length, IRTemp start1, IRTemp start2)
   8806 {
   8807    IRTemp counter = newTemp(Ity_I64);
   8808 
   8809    assign(counter, get_counter_dw0());
   8810 
   8811    store(binop(Iop_Add64, mkexpr(start1), mkexpr(counter)),
   8812          load(Ity_I8, binop(Iop_Add64, mkexpr(start2), mkexpr(counter))));
   8813 
   8814    /* Check for end of field */
   8815    put_counter_dw0(binop(Iop_Add64, mkexpr(counter), mkU64(1)));
   8816    iterate_if(binop(Iop_CmpNE64, mkexpr(counter), mkexpr(length)));
   8817    put_counter_dw0(mkU64(0));
   8818 }
   8819 
   8820 static void
   8821 s390_irgen_TR_EX(IRTemp length, IRTemp start1, IRTemp start2)
   8822 {
   8823    IRTemp op = newTemp(Ity_I8);
   8824    IRTemp op1 = newTemp(Ity_I8);
   8825    IRTemp result = newTemp(Ity_I64);
   8826    IRTemp counter = newTemp(Ity_I64);
   8827 
   8828    assign(counter, get_counter_dw0());
   8829 
   8830    assign(op, load(Ity_I8, binop(Iop_Add64, mkexpr(start1), mkexpr(counter))));
   8831 
   8832    assign(result, binop(Iop_Add64, unop(Iop_8Uto64, mkexpr(op)), mkexpr(start2)));
   8833 
   8834    assign(op1, load(Ity_I8, mkexpr(result)));
   8835    store(binop(Iop_Add64, mkexpr(start1), mkexpr(counter)), mkexpr(op1));
   8836 
   8837    put_counter_dw0(binop(Iop_Add64, mkexpr(counter), mkU64(1)));
   8838    iterate_if(binop(Iop_CmpNE64, mkexpr(counter), mkexpr(length)));
   8839    put_counter_dw0(mkU64(0));
   8840 }
   8841 
   8842 
   8843 static void
   8844 s390_irgen_EX_SS(UChar r, IRTemp addr2,
   8845                  void (*irgen)(IRTemp length, IRTemp start1, IRTemp start2),
   8846                  int lensize)
   8847 {
   8848    struct SS {
   8849       unsigned int op :  8;
   8850       unsigned int l  :  8;
   8851       unsigned int b1 :  4;
   8852       unsigned int d1 : 12;
   8853       unsigned int b2 :  4;
   8854       unsigned int d2 : 12;
   8855    };
   8856    union {
   8857       struct SS dec;
   8858       unsigned long bytes;
   8859    } ss;
   8860    IRTemp cond;
   8861    IRDirty *d;
   8862    IRTemp torun;
   8863 
   8864    IRTemp start1 = newTemp(Ity_I64);
   8865    IRTemp start2 = newTemp(Ity_I64);
   8866    IRTemp len = newTemp(lensize == 64 ? Ity_I64 : Ity_I32);
   8867    cond = newTemp(Ity_I1);
   8868    torun = newTemp(Ity_I64);
   8869 
   8870    assign(torun, load(Ity_I64, mkexpr(addr2)));
   8871    /* Start with a check that the saved code is still correct */
   8872    assign(cond, binop(Iop_CmpNE64, mkexpr(torun), mkU64(last_execute_target)));
   8873    /* If not, save the new value */
   8874    d = unsafeIRDirty_0_N (0, "s390x_dirtyhelper_EX", &s390x_dirtyhelper_EX,
   8875                           mkIRExprVec_1(mkexpr(torun)));
   8876    d->guard = mkexpr(cond);
   8877    stmt(IRStmt_Dirty(d));
   8878 
   8879    /* and restart */
   8880    stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_TISTART),
   8881                    mkU64(guest_IA_curr_instr)));
   8882    stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_TILEN), mkU64(4)));
   8883    restart_if(mkexpr(cond));
   8884 
   8885    ss.bytes = last_execute_target;
   8886    assign(start1, binop(Iop_Add64, mkU64(ss.dec.d1),
   8887           ss.dec.b1 != 0 ? get_gpr_dw0(ss.dec.b1) : mkU64(0)));
   8888    assign(start2, binop(Iop_Add64, mkU64(ss.dec.d2),
   8889           ss.dec.b2 != 0 ? get_gpr_dw0(ss.dec.b2) : mkU64(0)));
   8890    assign(len, unop(lensize == 64 ? Iop_8Uto64 : Iop_8Uto32, binop(Iop_Or8,
   8891           r != 0 ? get_gpr_b7(r): mkU8(0), mkU8(ss.dec.l))));
   8892    irgen(len, start1, start2);
   8893 
   8894    last_execute_target = 0;
   8895 }
   8896 
   8897 static HChar *
   8898 s390_irgen_EX(UChar r1, IRTemp addr2)
   8899 {
   8900    switch(last_execute_target & 0xff00000000000000ULL) {
   8901    case 0:
   8902    {
   8903       /* no code information yet */
   8904       IRDirty *d;
   8905 
   8906       /* so safe the code... */
   8907       d = unsafeIRDirty_0_N (0, "s390x_dirtyhelper_EX", &s390x_dirtyhelper_EX,
   8908                              mkIRExprVec_1(load(Ity_I64, mkexpr(addr2))));
   8909       stmt(IRStmt_Dirty(d));
   8910       /* and restart */
   8911       stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_TISTART),
   8912                       mkU64(guest_IA_curr_instr)));
   8913       stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_TILEN), mkU64(4)));
   8914       restart_if(IRExpr_Const(IRConst_U1(True)));
   8915 
   8916       /* we know that this will be invalidated */
   8917       put_IA(mkaddr_expr(guest_IA_next_instr));
   8918       dis_res->whatNext = Dis_StopHere;
   8919       dis_res->jk_StopHere = Ijk_TInval;
   8920       break;
   8921    }
   8922 
   8923    case 0xd200000000000000ULL:
   8924       /* special case MVC */
   8925       s390_irgen_EX_SS(r1, addr2, s390_irgen_MVC_EX, 64);
   8926       return "mvc via ex";
   8927 
   8928    case 0xd500000000000000ULL:
   8929       /* special case CLC */
   8930       s390_irgen_EX_SS(r1, addr2, s390_irgen_CLC_EX, 64);
   8931       return "clc via ex";
   8932 
   8933    case 0xd700000000000000ULL:
   8934       /* special case XC */
   8935       s390_irgen_EX_SS(r1, addr2, s390_irgen_XC_EX, 32);
   8936       return "xc via ex";
   8937 
   8938    case 0xd600000000000000ULL:
   8939       /* special case OC */
   8940       s390_irgen_EX_SS(r1, addr2, s390_irgen_OC_EX, 32);
   8941       return "oc via ex";
   8942 
   8943    case 0xd400000000000000ULL:
   8944       /* special case NC */
   8945       s390_irgen_EX_SS(r1, addr2, s390_irgen_NC_EX, 32);
   8946       return "nc via ex";
   8947 
   8948    case 0xdc00000000000000ULL:
   8949       /* special case TR */
   8950       s390_irgen_EX_SS(r1, addr2, s390_irgen_TR_EX, 64);
   8951       return "tr via ex";
   8952 
   8953    default:
   8954    {
   8955       /* everything else will get a self checking prefix that also checks the
   8956          register content */
   8957       IRDirty *d;
   8958       UChar *bytes;
   8959       IRTemp cond;
   8960       IRTemp orperand;
   8961       IRTemp torun;
   8962 
   8963       cond = newTemp(Ity_I1);
   8964       orperand = newTemp(Ity_I64);
   8965       torun = newTemp(Ity_I64);
   8966 
   8967       if (r1 == 0)
   8968          assign(orperand, mkU64(0));
   8969       else
   8970          assign(orperand, unop(Iop_8Uto64,get_gpr_b7(r1)));
   8971       /* This code is going to be translated */
   8972       assign(torun, binop(Iop_Or64, load(Ity_I64, mkexpr(addr2)),
   8973              binop(Iop_Shl64, mkexpr(orperand), mkU8(48))));
   8974 
   8975       /* Start with a check that saved code is still correct */
   8976       assign(cond, binop(Iop_CmpNE64, mkexpr(torun),
   8977              mkU64(last_execute_target)));
   8978       /* If not, save the new value */
   8979       d = unsafeIRDirty_0_N (0, "s390x_dirtyhelper_EX", &s390x_dirtyhelper_EX,
   8980                              mkIRExprVec_1(mkexpr(torun)));
   8981       d->guard = mkexpr(cond);
   8982       stmt(IRStmt_Dirty(d));
   8983 
   8984       /* and restart */
   8985       stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_TISTART), mkU64(guest_IA_curr_instr)));
   8986       stmt(IRStmt_Put(S390X_GUEST_OFFSET(guest_TILEN), mkU64(4)));
   8987       restart_if(mkexpr(cond));
   8988 
   8989       /* Now comes the actual translation */
   8990       bytes = (UChar *) &last_execute_target;
   8991       s390_decode_and_irgen(bytes, ((((bytes[0] >> 6) + 1) >> 1) + 1) << 1,
   8992                             dis_res);
   8993       if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   8994          vex_printf("    which was executed by\n");
   8995       /* dont make useless translations in the next execute */
   8996       last_execute_target = 0;
   8997    }
   8998    }
   8999    return "ex";
   9000 }
   9001 
   9002 static HChar *
   9003 s390_irgen_EXRL(UChar r1, UInt offset)
   9004 {
   9005    IRTemp addr = newTemp(Ity_I64);
   9006    /* we might save one round trip because we know the target */
   9007    if (!last_execute_target)
   9008       last_execute_target = *(ULong *)(HWord)
   9009                              (guest_IA_curr_instr + offset * 2UL);
   9010    assign(addr, mkU64(guest_IA_curr_instr + offset * 2UL));
   9011    s390_irgen_EX(r1, addr);
   9012    return "exrl";
   9013 }
   9014 
   9015 static HChar *
   9016 s390_irgen_IPM(UChar r1)
   9017 {
   9018    // As long as we dont support SPM, lets just assume 0 as program mask
   9019    put_gpr_b4(r1, unop(Iop_32to8, binop(Iop_Or32, mkU32(0 /* program mask */),
   9020                        binop(Iop_Shl32, s390_call_calculate_cc(), mkU8(4)))));
   9021 
   9022    return "ipm";
   9023 }
   9024 
   9025 
   9026 static HChar *
   9027 s390_irgen_SRST(UChar r1, UChar r2)
   9028 {
   9029    IRTemp address = newTemp(Ity_I64);
   9030    IRTemp next = newTemp(Ity_I64);
   9031    IRTemp delim = newTemp(Ity_I8);
   9032    IRTemp counter = newTemp(Ity_I64);
   9033    IRTemp byte = newTemp(Ity_I8);
   9034 
   9035    assign(address, get_gpr_dw0(r2));
   9036    assign(next, get_gpr_dw0(r1));
   9037 
   9038    assign(counter, get_counter_dw0());
   9039    put_counter_dw0(mkU64(0));
   9040 
   9041    // start = next?  CC=2 and out r1 and r2 unchanged
   9042    s390_cc_set(2);
   9043    put_gpr_dw0(r2, binop(Iop_Sub64, mkexpr(address), mkexpr(counter)));
   9044    next_insn_if(binop(Iop_CmpEQ64, mkexpr(address), mkexpr(next)));
   9045 
   9046    assign(byte, load(Ity_I8, mkexpr(address)));
   9047    assign(delim, get_gpr_b7(0));
   9048 
   9049    // byte = delim? CC=1, R1=address
   9050    s390_cc_set(1);
   9051    put_gpr_dw0(r1,  mkexpr(address));
   9052    next_insn_if(binop(Iop_CmpEQ8, mkexpr(delim), mkexpr(byte)));
   9053 
   9054    // else: all equal, no end yet, loop
   9055    put_counter_dw0(binop(Iop_Add64, mkexpr(counter), mkU64(1)));
   9056    put_gpr_dw0(r1, mkexpr(next));
   9057    put_gpr_dw0(r2, binop(Iop_Add64, mkexpr(address), mkU64(1)));
   9058 
   9059    iterate();
   9060 
   9061    return "srst";
   9062 }
   9063 
   9064 static HChar *
   9065 s390_irgen_CLST(UChar r1, UChar r2)
   9066 {
   9067    IRTemp address1 = newTemp(Ity_I64);
   9068    IRTemp address2 = newTemp(Ity_I64);
   9069    IRTemp end = newTemp(Ity_I8);
   9070    IRTemp counter = newTemp(Ity_I64);
   9071    IRTemp byte1 = newTemp(Ity_I8);
   9072    IRTemp byte2 = newTemp(Ity_I8);
   9073 
   9074    assign(address1, get_gpr_dw0(r1));
   9075    assign(address2, get_gpr_dw0(r2));
   9076    assign(end, get_gpr_b7(0));
   9077    assign(counter, get_counter_dw0());
   9078    put_counter_dw0(mkU64(0));
   9079    assign(byte1, load(Ity_I8, mkexpr(address1)));
   9080    assign(byte2, load(Ity_I8, mkexpr(address2)));
   9081 
   9082    // end in both? all equal, reset r1 and r2 to start values
   9083    s390_cc_set(0);
   9084    put_gpr_dw0(r1, binop(Iop_Sub64, mkexpr(address1), mkexpr(counter)));
   9085    put_gpr_dw0(r2, binop(Iop_Sub64, mkexpr(address2), mkexpr(counter)));
   9086    next_insn_if(binop(Iop_CmpEQ8, mkU8(0),
   9087                       binop(Iop_Or8,
   9088                             binop(Iop_Xor8, mkexpr(byte1), mkexpr(end)),
   9089                             binop(Iop_Xor8, mkexpr(byte2), mkexpr(end)))));
   9090 
   9091    put_gpr_dw0(r1, mkexpr(address1));
   9092    put_gpr_dw0(r2, mkexpr(address2));
   9093 
   9094    // End found in string1
   9095    s390_cc_set(1);
   9096    next_insn_if(binop(Iop_CmpEQ8, mkexpr(end), mkexpr(byte1)));
   9097 
   9098    // End found in string2
   9099    s390_cc_set(2);
   9100    next_insn_if(binop(Iop_CmpEQ8, mkexpr(end), mkexpr(byte2)));
   9101 
   9102    // string1 < string2
   9103    s390_cc_set(1);
   9104    next_insn_if(binop(Iop_CmpLT32U, unop(Iop_8Uto32, mkexpr(byte1)),
   9105                       unop(Iop_8Uto32, mkexpr(byte2))));
   9106 
   9107    // string2 < string1
   9108    s390_cc_set(2);
   9109    next_insn_if(binop(Iop_CmpLT32U, unop(Iop_8Uto32, mkexpr(byte2)),
   9110                       unop(Iop_8Uto32, mkexpr(byte1))));
   9111 
   9112    // else: all equal, no end yet, loop
   9113    put_counter_dw0(binop(Iop_Add64, mkexpr(counter), mkU64(1)));
   9114    put_gpr_dw0(r1, binop(Iop_Add64, get_gpr_dw0(r1), mkU64(1)));
   9115    put_gpr_dw0(r2, binop(Iop_Add64, get_gpr_dw0(r2), mkU64(1)));
   9116 
   9117    iterate();
   9118 
   9119    return "clst";
   9120 }
   9121 
   9122 static void
   9123 s390_irgen_load_multiple_32bit(UChar r1, UChar r3, IRTemp op2addr)
   9124 {
   9125    UChar reg;
   9126    IRTemp addr = newTemp(Ity_I64);
   9127 
   9128    assign(addr, mkexpr(op2addr));
   9129    reg = r1;
   9130    do {
   9131       IRTemp old = addr;
   9132 
   9133       reg %= 16;
   9134       put_gpr_w1(reg, load(Ity_I32, mkexpr(addr)));
   9135       addr = newTemp(Ity_I64);
   9136       assign(addr, binop(Iop_Add64, mkexpr(old), mkU64(4)));
   9137       reg++;
   9138    } while (reg != (r3 + 1));
   9139 }
   9140 
   9141 static HChar *
   9142 s390_irgen_LM(UChar r1, UChar r3, IRTemp op2addr)
   9143 {
   9144    s390_irgen_load_multiple_32bit(r1, r3, op2addr);
   9145 
   9146    return "lm";
   9147 }
   9148 
   9149 static HChar *
   9150 s390_irgen_LMY(UChar r1, UChar r3, IRTemp op2addr)
   9151 {
   9152    s390_irgen_load_multiple_32bit(r1, r3, op2addr);
   9153 
   9154    return "lmy";
   9155 }
   9156 
   9157 static HChar *
   9158 s390_irgen_LMH(UChar r1, UChar r3, IRTemp op2addr)
   9159 {
   9160    UChar reg;
   9161    IRTemp addr = newTemp(Ity_I64);
   9162 
   9163    assign(addr, mkexpr(op2addr));
   9164    reg = r1;
   9165    do {
   9166       IRTemp old = addr;
   9167 
   9168       reg %= 16;
   9169       put_gpr_w0(reg, load(Ity_I32, mkexpr(addr)));
   9170       addr = newTemp(Ity_I64);
   9171       assign(addr, binop(Iop_Add64, mkexpr(old), mkU64(4)));
   9172       reg++;
   9173    } while (reg != (r3 + 1));
   9174 
   9175    return "lmh";
   9176 }
   9177 
   9178 static HChar *
   9179 s390_irgen_LMG(UChar r1, UChar r3, IRTemp op2addr)
   9180 {
   9181    UChar reg;
   9182    IRTemp addr = newTemp(Ity_I64);
   9183 
   9184    assign(addr, mkexpr(op2addr));
   9185    reg = r1;
   9186    do {
   9187       IRTemp old = addr;
   9188 
   9189       reg %= 16;
   9190       put_gpr_dw0(reg, load(Ity_I64, mkexpr(addr)));
   9191       addr = newTemp(Ity_I64);
   9192       assign(addr, binop(Iop_Add64, mkexpr(old), mkU64(8)));
   9193       reg++;
   9194    } while (reg != (r3 + 1));
   9195 
   9196    return "lmg";
   9197 }
   9198 
   9199 static void
   9200 s390_irgen_store_multiple_32bit(UChar r1, UChar r3, IRTemp op2addr)
   9201 {
   9202    UChar reg;
   9203    IRTemp addr = newTemp(Ity_I64);
   9204 
   9205    assign(addr, mkexpr(op2addr));
   9206    reg = r1;
   9207    do {
   9208       IRTemp old = addr;
   9209 
   9210       reg %= 16;
   9211       store(mkexpr(addr), get_gpr_w1(reg));
   9212       addr = newTemp(Ity_I64);
   9213       assign(addr, binop(Iop_Add64, mkexpr(old), mkU64(4)));
   9214       reg++;
   9215    } while( reg != (r3 + 1));
   9216 }
   9217 
   9218 static HChar *
   9219 s390_irgen_STM(UChar r1, UChar r3, IRTemp op2addr)
   9220 {
   9221    s390_irgen_store_multiple_32bit(r1, r3, op2addr);
   9222 
   9223    return "stm";
   9224 }
   9225 
   9226 static HChar *
   9227 s390_irgen_STMY(UChar r1, UChar r3, IRTemp op2addr)
   9228 {
   9229    s390_irgen_store_multiple_32bit(r1, r3, op2addr);
   9230 
   9231    return "stmy";
   9232 }
   9233 
   9234 static HChar *
   9235 s390_irgen_STMH(UChar r1, UChar r3, IRTemp op2addr)
   9236 {
   9237    UChar reg;
   9238    IRTemp addr = newTemp(Ity_I64);
   9239 
   9240    assign(addr, mkexpr(op2addr));
   9241    reg = r1;
   9242    do {
   9243       IRTemp old = addr;
   9244 
   9245       reg %= 16;
   9246       store(mkexpr(addr), get_gpr_w0(reg));
   9247       addr = newTemp(Ity_I64);
   9248       assign(addr, binop(Iop_Add64, mkexpr(old), mkU64(4)));
   9249       reg++;
   9250    } while( reg != (r3 + 1));
   9251 
   9252    return "stmh";
   9253 }
   9254 
   9255 static HChar *
   9256 s390_irgen_STMG(UChar r1, UChar r3, IRTemp op2addr)
   9257 {
   9258    UChar reg;
   9259    IRTemp addr = newTemp(Ity_I64);
   9260 
   9261    assign(addr, mkexpr(op2addr));
   9262    reg = r1;
   9263    do {
   9264       IRTemp old = addr;
   9265 
   9266       reg %= 16;
   9267       store(mkexpr(addr), get_gpr_dw0(reg));
   9268       addr = newTemp(Ity_I64);
   9269       assign(addr, binop(Iop_Add64, mkexpr(old), mkU64(8)));
   9270       reg++;
   9271    } while( reg != (r3 + 1));
   9272 
   9273    return "stmg";
   9274 }
   9275 
   9276 static void
   9277 s390_irgen_xonc(IROp op, IRTemp length, IRTemp start1, IRTemp start2)
   9278 {
   9279    IRTemp old1 = newTemp(Ity_I8);
   9280    IRTemp old2 = newTemp(Ity_I8);
   9281    IRTemp new1 = newTemp(Ity_I8);
   9282    IRTemp counter = newTemp(Ity_I32);
   9283    IRTemp addr1 = newTemp(Ity_I64);
   9284 
   9285    assign(counter, get_counter_w0());
   9286 
   9287    assign(addr1, binop(Iop_Add64, mkexpr(start1),
   9288                        unop(Iop_32Uto64, mkexpr(counter))));
   9289 
   9290    assign(old1, load(Ity_I8, mkexpr(addr1)));
   9291    assign(old2, load(Ity_I8, binop(Iop_Add64, mkexpr(start2),
   9292                                    unop(Iop_32Uto64,mkexpr(counter)))));
   9293    assign(new1, binop(op, mkexpr(old1), mkexpr(old2)));
   9294 
   9295    /* Special case: xc is used to zero memory */
   9296    if (op == Iop_Xor8) {
   9297       store(mkexpr(addr1),
   9298             mkite(binop(Iop_CmpEQ64, mkexpr(start1), mkexpr(start2)),
   9299                   mkU8(0), mkexpr(new1)));
   9300    } else
   9301       store(mkexpr(addr1), mkexpr(new1));
   9302    put_counter_w1(binop(Iop_Or32, unop(Iop_8Uto32, mkexpr(new1)),
   9303                         get_counter_w1()));
   9304 
   9305    /* Check for end of field */
   9306    put_counter_w0(binop(Iop_Add32, mkexpr(counter), mkU32(1)));
   9307    iterate_if(binop(Iop_CmpNE32, mkexpr(counter), mkexpr(length)));
   9308    s390_cc_thunk_put1(S390_CC_OP_BITWISE, mktemp(Ity_I32, get_counter_w1()),
   9309                       False);
   9310    put_counter_dw0(mkU64(0));
   9311 }
   9312 
   9313 static HChar *
   9314 s390_irgen_XC(UChar length, IRTemp start1, IRTemp start2)
   9315 {
   9316    IRTemp len = newTemp(Ity_I32);
   9317 
   9318    assign(len, mkU32(length));
   9319    s390_irgen_xonc(Iop_Xor8, len, start1, start2);
   9320 
   9321    return "xc";
   9322 }
   9323 
   9324 static void
   9325 s390_irgen_XC_sameloc(UChar length, UChar b, UShort d)
   9326 {
   9327    IRTemp counter = newTemp(Ity_I32);
   9328    IRTemp start = newTemp(Ity_I64);
   9329    IRTemp addr  = newTemp(Ity_I64);
   9330 
   9331    assign(start,
   9332           binop(Iop_Add64, mkU64(d), b != 0 ? get_gpr_dw0(b) : mkU64(0)));
   9333 
   9334    if (length < 8) {
   9335       UInt i;
   9336 
   9337       for (i = 0; i <= length; ++i) {
   9338          store(binop(Iop_Add64, mkexpr(start), mkU64(i)), mkU8(0));
   9339       }
   9340    } else {
   9341      assign(counter, get_counter_w0());
   9342 
   9343      assign(addr, binop(Iop_Add64, mkexpr(start),
   9344                         unop(Iop_32Uto64, mkexpr(counter))));
   9345 
   9346      store(mkexpr(addr), mkU8(0));
   9347 
   9348      /* Check for end of field */
   9349      put_counter_w0(binop(Iop_Add32, mkexpr(counter), mkU32(1)));
   9350      iterate_if(binop(Iop_CmpNE32, mkexpr(counter), mkU32(length)));
   9351 
   9352      /* Reset counter */
   9353      put_counter_dw0(mkU64(0));
   9354    }
   9355 
   9356    s390_cc_thunk_put1(S390_CC_OP_BITWISE, mktemp(Ity_I32, mkU32(0)), False);
   9357 
   9358    if (UNLIKELY(vex_traceflags & VEX_TRACE_FE))
   9359       s390_disasm(ENC3(MNM, UDLB, UDXB), "xc", d, length, b, d, 0, b);
   9360 }
   9361 
   9362 static HChar *
   9363 s390_irgen_NC(UChar length, IRTemp start1, IRTemp start2)
   9364 {
   9365    IRTemp len = newTemp(Ity_I32);
   9366 
   9367    assign(len, mkU32(length));
   9368    s390_irgen_xonc(Iop_And8, len, start1, start2);
   9369 
   9370    return "nc";
   9371 }
   9372 
   9373 static HChar *
   9374 s390_irgen_OC(UChar length, IRTemp start1, IRTemp start2)
   9375 {
   9376    IRTemp len = newTemp(Ity_I32);
   9377 
   9378    assign(len, mkU32(length));
   9379    s390_irgen_xonc(Iop_Or8, len, start1, start2);
   9380 
   9381    return "oc";
   9382 }
   9383 
   9384 
   9385 static HChar *
   9386 s390_irgen_MVC(UChar length, IRTemp start1, IRTemp start2)
   9387 {
   9388    IRTemp len = newTemp(Ity_I64);
   9389 
   9390    assign(len, mkU64(length));
   9391    s390_irgen_MVC_EX(len, start1, start2);
   9392 
   9393    return "mvc";
   9394 }
   9395 
   9396 static HChar *
   9397 s390_irgen_MVCL(UChar r1, UChar r2)
   9398 {
   9399    IRTemp addr1 = newTemp(Ity_I64);
   9400    IRTemp addr2 = newTemp(Ity_I64);
   9401    IRTemp addr2_load = newTemp(Ity_I64);
   9402    IRTemp r1p1 = newTemp(Ity_I32);   /* contents of r1 + 1 */
   9403    IRTemp r2p1 = newTemp(Ity_I32);   /* contents of r2 + 1 */
   9404    IRTemp len1 = newTemp(Ity_I32);
   9405    IRTemp len2 = newTemp(Ity_I32);
   9406    IRTemp pad = newTemp(Ity_I8);
   9407    IRTemp single = newTemp(Ity_I8);
   9408 
   9409    assign(addr1, get_gpr_dw0(r1));
   9410    assign(r1p1, get_gpr_w1(r1 + 1));
   9411    assign(len1, binop(Iop_And32, mkexpr(r1p1), mkU32(0x00ffffff)));
   9412    assign(addr2, get_gpr_dw0(r2));
   9413    assign(r2p1, get_gpr_w1(r2 + 1));
   9414    assign(len2, binop(Iop_And32, mkexpr(r2p1), mkU32(0x00ffffff)));
   9415    assign(pad, get_gpr_b4(r2 + 1));
   9416 
   9417    /* len1 == 0 ? */
   9418    s390_cc_thunk_put2(S390_CC_OP_UNSIGNED_COMPARE, len1, len2, False);
   9419    next_insn_if(binop(Iop_CmpEQ32, mkexpr(len1), mkU32(0)));
   9420 
   9421    /* Check for destructive overlap:
   9422       addr1 > addr2 && addr2 + len1 > addr1 && (addr2 + len2) > addr1 */
   9423    s390_cc_set(3);
   9424    IRTemp cond1 = newTemp(Ity_I32);
   9425    assign(cond1, unop(Iop_1Uto32,
   9426                       binop(Iop_CmpLT64U, mkexpr(addr2), mkexpr(addr1))));
   9427    IRTemp cond2 = newTemp(Ity_I32);
   9428    assign(cond2, unop(Iop_1Uto32,
   9429                       binop(Iop_CmpLT64U, mkexpr(addr1),
   9430                             binop(Iop_Add64, mkexpr(addr2),
   9431                                   unop(Iop_32Uto64, mkexpr(len1))))));
   9432    IRTemp cond3 = newTemp(Ity_I32);
   9433    assign(cond3, unop(Iop_1Uto32,
   9434                       binop(Iop_CmpLT64U,
   9435                             mkexpr(addr1),
   9436                             binop(Iop_Add64, mkexpr(addr2),
   9437                                   unop(Iop_32Uto64, mkexpr(len2))))));
   9438 
   9439    next_insn_if(binop(Iop_CmpEQ32,
   9440                       binop(Iop_And32,
   9441                             binop(Iop_And32, mkexpr(cond1), mkexpr(cond2)),
   9442                             mkexpr(cond3)),
   9443                       mkU32(1)));
   9444 
   9445    /* See s390_irgen_CLCL for explanation why we cannot load directly
   9446       and need two steps. */
   9447    assign(addr2_load,
   9448           mkite(binop(Iop_CmpEQ32, mkexpr(len2), mkU32(0)),
   9449                 mkU64(guest_IA_curr_instr), mkexpr(addr2)));
   9450    assign(single,
   9451           mkite(binop(Iop_CmpEQ32, mkexpr(len2), mkU32(0)),
   9452                 mkexpr(pad), load(Ity_I8, mkexpr(addr2_load))));
   9453 
   9454    store(mkexpr(addr1), mkexpr(single));
   9455 
   9456    /* Update addr1 and len1 */
   9457    put_gpr_dw0(r1, binop(Iop_Add64, mkexpr(addr1), mkU64(1)));
   9458    put_gpr_w1(r1 + 1, binop(Iop_Sub32, mkexpr(r1p1), mkU32(1)));
   9459 
   9460    /* Update addr2 and len2 */
   9461    put_gpr_dw0(r2,
   9462                mkite(binop(Iop_CmpEQ32, mkexpr(len2), mkU32(0)),
   9463                      mkexpr(addr2),
   9464                      binop(Iop_Add64, mkexpr(addr2), mkU64(1))));
   9465 
   9466    /* When updating len2 we must not modify bits (r2+1)[0:39] */
   9467    put_gpr_w1(r2 + 1,
   9468               mkite(binop(Iop_CmpEQ32, mkexpr(len2), mkU32(0)),
   9469                     binop(Iop_And32, mkexpr(r2p1), mkU32(0xFF000000u)),
   9470                     binop(Iop_Sub32, mkexpr(r2p1), mkU32(1))));
   9471 
   9472    s390_cc_thunk_put2(S390_CC_OP_UNSIGNED_COMPARE, len1, len2, False);
   9473    iterate_if(binop(Iop_CmpNE32, mkexpr(len1), mkU32(1)));
   9474 
   9475    return "mvcl";
   9476 }
   9477 
   9478 
   9479 static HChar *
   9480 s390_irgen_MVCLE(UChar r1, UChar r3, IRTemp pad2)
   9481 {
   9482    IRTemp addr1, addr3, addr3_load, len1, len3, single;
   9483 
   9484    addr1 = newTemp(Ity_I64);
   9485    addr3 = newTemp(Ity_I64);
   9486    addr3_load = newTemp(Ity_I64);
   9487    len1 = newTemp(Ity_I64);
   9488    len3 = newTemp(Ity_I64);
   9489    single = newTemp(Ity_I8);
   9490 
   9491    assign(addr1, get_gpr_dw0(r1));
   9492    assign(len1, get_gpr_dw0(r1 + 1));
   9493    assign(addr3, get_gpr_dw0(r3));
   9494    assign(len3, get_gpr_dw0(r3 + 1));
   9495 
   9496    // len1 == 0 ?
   9497    s390_cc_thunk_put2(S390_CC_OP_UNSIGNED_COMPARE, len1, len3, False);
   9498    next_insn_if(binop(Iop_CmpEQ64,mkexpr(len1), mkU64(0)));
   9499 
   9500    /* This is a hack to prevent mvcle from reading from addr3 if it
   9501       should read from the pad. Since the pad has no address, just
   9502       read from the instruction, we discard that anyway */
   9503    assign(addr3_load,
   9504           mkite(binop(Iop_CmpEQ64, mkexpr(len3), mkU64(0)),
   9505                 mkU64(guest_IA_curr_instr), mkexpr(addr3)));
   9506 
   9507    assign(single,
   9508           mkite(binop(Iop_CmpEQ64, mkexpr(len3), mkU64(0)),
   9509                 unop(Iop_64to8, mkexpr(pad2)),
   9510                 load(Ity_I8, mkexpr(addr3_load))));
   9511    store(mkexpr(addr1), mkexpr(single));
   9512 
   9513    put_gpr_dw0(r1, binop(Iop_Add64, mkexpr(addr1), mkU64(1)));
   9514 
   9515    put_gpr_dw0(r1 + 1, binop(Iop_Sub64, mkexpr(len1), mkU64(1)));
   9516 
   9517    put_gpr_dw0(r3,
   9518                mkite(binop(Iop_CmpEQ64, mkexpr(len3), mkU64(0)),
   9519                      mkexpr(addr3),
   9520                      binop(Iop_Add64, mkexpr(addr3), mkU64(1))));
   9521 
   9522    put_gpr_dw0(r3 + 1,
   9523                mkite(binop(Iop_CmpEQ64, mkexpr(len3), mkU64(0)),
   9524                      mkU64(0), binop(Iop_Sub64, mkexpr(len3), mkU64(1))));
   9525 
   9526    s390_cc_thunk_put2(S390_CC_OP_UNSIGNED_COMPARE, len1, len3, False);
   9527    iterate_if(binop(Iop_CmpNE64, mkexpr(len1), mkU64(1)));
   9528 
   9529    return "mvcle";
   9530 }
   9531 
   9532 static HChar *
   9533 s390_irgen_MVST(UChar r1, UChar r2)
   9534 {
   9535    IRTemp addr1 = newTemp(Ity_I64);
   9536    IRTemp addr2 = newTemp(Ity_I64);
   9537    IRTemp end = newTemp(Ity_I8);
   9538    IRTemp byte = newTemp(Ity_I8);
   9539    IRTemp counter = newTemp(Ity_I64);
   9540 
   9541    assign(addr1, get_gpr_dw0(r1));
   9542    assign(addr2, get_gpr_dw0(r2));
   9543    assign(counter, get_counter_dw0());
   9544    assign(end, get_gpr_b7(0));
   9545    assign(byte, load(Ity_I8, binop(Iop_Add64, mkexpr(addr2),mkexpr(counter))));
   9546    store(binop(Iop_Add64,mkexpr(addr1),mkexpr(counter)), mkexpr(byte));
   9547 
   9548    // We use unlimited as cpu-determined number
   9549    put_counter_dw0(binop(Iop_Add64, mkexpr(counter), mkU64(1)));
   9550    iterate_if(binop(Iop_CmpNE8, mkexpr(end), mkexpr(byte)));
   9551 
   9552    // and always set cc=1 at the end + update r1
   9553    s390_cc_set(1);
   9554    put_gpr_dw0(r1, binop(Iop_Add64, mkexpr(addr1), mkexpr(counter)));
   9555    put_counter_dw0(mkU64(0));
   9556 
   9557    return "mvst";
   9558 }
   9559 
   9560 static void
   9561 s390_irgen_divide_64to32(IROp op, UChar r1, IRTemp op2)
   9562 {
   9563    IRTemp op1 = newTemp(Ity_I64);
   9564    IRTemp result = newTemp(Ity_I64);
   9565 
   9566    assign(op1, binop(Iop_32HLto64,
   9567                      get_gpr_w1(r1),         // high 32 bits
   9568                      get_gpr_w1(r1 + 1)));   // low  32 bits
   9569    assign(result, binop(op, mkexpr(op1), mkexpr(op2)));
   9570    put_gpr_w1(r1, unop(Iop_64HIto32, mkexpr(result)));   // remainder
   9571    put_gpr_w1(r1 + 1, unop(Iop_64to32, mkexpr(result))); // quotient
   9572 }
   9573 
   9574 static void
   9575 s390_irgen_divide_128to64(IROp op, UChar r1, IRTemp op2)
   9576 {
   9577    IRTemp op1 = newTemp(Ity_I128);
   9578    IRTemp result = newTemp(Ity_I128);
   9579 
   9580    assign(op1, binop(Iop_64HLto128,
   9581                      get_gpr_dw0(r1),         // high 64 bits
   9582                      get_gpr_dw0(r1 + 1)));   // low  64 bits
   9583    assign(result, binop(op, mkexpr(op1), mkexpr(op2)));
   9584    put_gpr_dw0(r1, unop(Iop_128HIto64, mkexpr(result)));   // remainder
   9585    put_gpr_dw0(r1 + 1, unop(Iop_128to64, mkexpr(result))); // quotient
   9586 }
   9587 
   9588 static void
   9589 s390_irgen_divide_64to64(IROp op, UChar r1, IRTemp op2)
   9590 {
   9591    IRTemp op1 = newTemp(Ity_I64);
   9592    IRTemp result = newTemp(Ity_I128);
   9593 
   9594    assign(op1, get_gpr_dw0(r1 + 1));
   9595    assign(result, binop(op, mkexpr(op1), mkexpr(op2)));
   9596    put_gpr_dw0(r1, unop(Iop_128HIto64, mkexpr(result)));   // remainder
   9597    put_gpr_dw0(r1 + 1, unop(Iop_128to64, mkexpr(result))); // quotient
   9598 }
   9599 
   9600 static HChar *
   9601 s390_irgen_DR(UChar r1, UChar r2)
   9602 {
   9603    IRTemp op2 = newTemp(Ity_I32);
   9604 
   9605    assign(op2, get_gpr_w1(r2));
   9606 
   9607    s390_irgen_divide_64to32(Iop_DivModS64to32, r1, op2);
   9608 
   9609    return "dr";
   9610 }
   9611 
   9612 static HChar *
   9613 s390_irgen_D(UChar r1, IRTemp op2addr)
   9614 {
   9615    IRTemp op2 = newTemp(Ity_I32);
   9616 
   9617    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   9618 
   9619    s390_irgen_divide_64to32(Iop_DivModS64to32, r1, op2);
   9620 
   9621    return "d";
   9622 }
   9623 
   9624 static HChar *
   9625 s390_irgen_DLR(UChar r1, UChar r2)
   9626 {
   9627    IRTemp op2 = newTemp(Ity_I32);
   9628 
   9629    assign(op2, get_gpr_w1(r2));
   9630 
   9631    s390_irgen_divide_64to32(Iop_DivModU64to32, r1, op2);
   9632 
   9633    return "dr";
   9634 }
   9635 
   9636 static HChar *
   9637 s390_irgen_DL(UChar r1, IRTemp op2addr)
   9638 {
   9639    IRTemp op2 = newTemp(Ity_I32);
   9640 
   9641    assign(op2, load(Ity_I32, mkexpr(op2addr)));
   9642 
   9643    s390_irgen_divide_64to32(Iop_DivModU64to32, r1, op2);
   9644 
   9645    return "dl";
   9646 }
   9647 
   9648 static HChar *
   9649 <