Rizin
unix-like reverse engineering framework and cli tools
|
#include "sh_il.h"
#include <rz_il/rz_il_opbuilder_begin.h>
#include "../../../asm/arch/sh/regs.h"
#include <rz_il/rz_il_opbuilder_end.h>
Go to the source code of this file.
Classes | |
struct | sh_param_helper_t |
Helper struct to take care of converting operands to IL. More... | |
Macros | |
#define | SH_U_ADDR(x) UN(SH_ADDR_SIZE, x) |
#define | SH_S_ADDR(x) SN(SH_ADDR_SIZE, x) |
#define | SH_U_REG(x) UN(SH_REG_SIZE, (x)) |
#define | SH_S_REG(x) SN(SH_REG_SIZE, (x)) |
#define | SH_BIT(x) UN(1, x) |
#define | SH_TRUE SH_U_REG(1) |
#define | SH_FALSE SH_U_REG(0) |
#define | sh_il_get_pure_param(x) sh_il_get_param(op->param[x], op->scaling).pure |
#define | sh_il_set_pure_param(x, val) sh_il_set_param(op->param[x], val, op->scaling) |
#define | sh_il_get_effective_addr_param(x) sh_il_get_effective_addr(op->param[x], op->scaling) |
#define | sh_il_get_privilege() sh_il_get_privilege_ctx(ctx) |
#define | sh_il_get_reg(reg) sh_il_get_reg_ctx(reg, ctx) |
#define | sh_il_set_reg(reg, val) sh_il_set_reg_ctx(reg, val, ctx) |
#define | sh_il_get_effective_addr(x, y) sh_il_get_effective_addr_pc_ctx(x, y, pc, ctx) |
#define | sh_il_get_param(x, y) sh_il_get_param_pc_ctx(x, y, pc, ctx) |
#define | sh_il_set_param(x, y, z) sh_il_set_param_pc_ctx(x, y, z, pc, ctx) |
Typedefs | |
typedef struct sh_param_helper_t | SHParamHelper |
Helper struct to take care of converting operands to IL. More... | |
typedef RzILOpEffect *(* | sh_il_op) (const SHOp *op, ut64 pc, RzAnalysis *analysis, SHILContext *ctx) |
Variables | |
static const char * | sh_global_registers [] |
static const sh_il_op | sh_ops [SH_OP_SIZE] |
Lookup table for the IL lifting handlers for the various instructions. More... | |
Converts SuperH-4 instructions to RzIL statements References:
Both the above references are almost the same
op
doesn NOT mean operand. It is more akin to instruction or opcode. In majority of the places, it means the type of instructionDefinition in file sh_il.c.
#define sh_il_get_effective_addr | ( | x, | |
y | |||
) | sh_il_get_effective_addr_pc_ctx(x, y, pc, ctx) |
#define sh_il_get_effective_addr_param | ( | x | ) | sh_il_get_effective_addr(op->param[x], op->scaling) |
#define sh_il_get_param | ( | x, | |
y | |||
) | sh_il_get_param_pc_ctx(x, y, pc, ctx) |
#define sh_il_get_privilege | ( | ) | sh_il_get_privilege_ctx(ctx) |
#define sh_il_get_pure_param | ( | x | ) | sh_il_get_param(op->param[x], op->scaling).pure |
#define sh_il_set_param | ( | x, | |
y, | |||
z | |||
) | sh_il_set_param_pc_ctx(x, y, z, pc, ctx) |
typedef RzILOpEffect*(* sh_il_op) (const SHOp *op, ut64 pc, RzAnalysis *analysis, SHILContext *ctx) |
typedef struct sh_param_helper_t SHParamHelper |
Helper struct to take care of converting operands to IL.
Convert an unsigned 12 bit num
to signed 12 bit num I have used 16 bits to represent the numbers involved here, but the 4 most significant bits are the same, so for all purposes these are basically 12 bit numbers extended to 16 bits.
num |
Definition at line 276 of file sh_il.c.
References num.
Referenced by sh_il_get_effective_addr_pc_ctx().
RZ_IPI RzAnalysisILConfig* rz_sh_il_config | ( | RZ_NONNULL RzAnalysis * | analysis | ) |
Initialize new config for the SuperH IL.
analysis | RzAnalysis instance |
Definition at line 1784 of file sh_il.c.
References NULL, r, rz_analysis_il_config_new(), rz_return_val_if_fail, and SH_ADDR_SIZE.
RZ_IPI bool rz_sh_il_opcode | ( | RZ_NONNULL RzAnalysis * | analysis, |
RZ_NONNULL RzAnalysisOp * | aop, | ||
ut64 | pc, | ||
RZ_BORROW RZ_NONNULL const SHOp * | op, | ||
RZ_NULLABLE SHILContext * | ctx | ||
) |
Store the lifted IL for op
in aop
This function also takes care of initializing and adding the privilege mode local variable if required.
analysis | RzAnalysis instance |
aop | |
pc | Program counter |
op | |
ctx | Context variables for the current IL lifting |
Definition at line 1759 of file sh_il.c.
References NULL, pc, RZ_LOG_ERROR, rz_return_val_if_fail, sh_apply_effects(), sh_il_initialize_privilege(), SH_OP_SIZE, and sh_ops.
Referenced by sh_op().
|
static |
Apply the effects in order: pre
, target
, post
The good thing about this function is that any of the arguments can be NULL which implies that they do not exist/matter, and the final effect woulds be calculated without these NULL arguments (keeping in mind the above order)
target | |
pre | |
post |
Definition at line 407 of file sh_il.c.
References append, NULL, post(), and SEQ2.
Referenced by rz_sh_il_opcode(), sh_il_mov(), and sh_il_set_param_pc_ctx().
Definition at line 48 of file sh_il.c.
References reg, and SH_BANKED_REG_COUNT.
Referenced by sh_get_banked_reg(), sh_il_get_reg_ctx(), and sh_il_set_reg_ctx().
Get the register name for reg
in bank bank
.
reg | Register index |
bank | Bank number |
Definition at line 97 of file sh_il.c.
References NULL, reg, sh_banked_reg(), SH_BANKED_REG_COUNT, and sh_global_registers.
Referenced by sh_il_get_reg_ctx(), sh_il_ldc(), sh_il_set_reg_ctx(), and sh_il_stc().
|
static |
ADD Rm, Rn Rn + Rm -> Rn 0011nnnnmmmm1100
ADD imm, Rn Rn + imm -> Rn 0111nnnniiiiiiii
Definition at line 689 of file sh_il.c.
References ADD, sh_il_get_pure_param, and sh_il_set_pure_param.
|
static |
ADDC Rm, Rn Rn + Rm + T -> Rn carry -> T 0011nnnnmmmm1110
Definition at line 699 of file sh_il.c.
References ADD, SEQ3, SETG, SETL, sh_il_get_pure_param, sh_il_get_status_reg_bit(), sh_il_is_add_carry(), sh_il_set_pure_param, SH_REG_SIZE, SH_SR_T, UNSIGNED, and VARL.
|
static |
ADDV Rm, Rn Rn + Rm -> Rn overflow -> T 0011nnnnmmmm1111
Definition at line 714 of file sh_il.c.
References ADD, SEQ3, SETG, SETL, sh_il_get_pure_param, sh_il_is_add_overflow(), sh_il_set_pure_param, SH_SR_T, and VARL.
|
static |
AND Rm, Rn Rn & Rm -> Rn 0010nnnnmmmm1001
AND imm, R0 R0 & imm -> R0 11001001iiiiiiii
AND.B imm, @(R0, GBR) (R0 + GBR) & imm -> (R0 + GBR) 11001101iiiiiiii
Definition at line 1090 of file sh_il.c.
References LOGAND, sh_il_get_pure_param, and sh_il_set_pure_param.
|
static |
|
static |
|
static |
Convert b
to SH_TRUE or SH_FALSE (bool zero-extended to SH_REG_SIZE)
b | RzILOpBool to be converted |
Definition at line 110 of file sh_il.c.
References b, ITE, SH_FALSE, and SH_TRUE.
Referenced by sh_il_div1(), and sh_il_get_status_reg_bit().
|
static |
BRA label disp * 2 + PC + 4 -> PC ; delayed branch 1010dddddddddddd TODO: Implement delayed branch
Definition at line 1397 of file sh_il.c.
References JMP, and sh_il_get_effective_addr_param.
|
static |
BRAF Rn Rn + PC + 4 -> PC ; delayed branch 0000nnnn00100011 TODO: Implement delayed branch
Definition at line 1407 of file sh_il.c.
References JMP, and sh_il_get_effective_addr_param.
|
static |
BSR label PC + 4 -> PR ; disp * 2 + PC + 4 -> PC ; delayed branch 1011dddddddddddd TODO: Implement delayed branch
Definition at line 1417 of file sh_il.c.
References ADD, JMP, pc, SEQ2, SETG, sh_il_get_effective_addr_param, and SH_U_ADDR.
|
static |
BSRF Rn PC + 4 -> PR ; Rn + PC + 4 -> PC ; delayed branch 0000nnnn00000011 TODO: Implement delayed branch
Definition at line 1427 of file sh_il.c.
References ADD, JMP, pc, SEQ2, SETG, sh_il_get_effective_addr_param, and SH_U_ADDR.
|
static |
|
static |
|
static |
|
static |
CLRS 0 -> S 0000000001001000
Definition at line 1475 of file sh_il.c.
|
static |
|
static |
|
static |
|
static |
|
static |
|
static |
|
static |
|
static |
|
static |
CMP/STR Rm, Rn When any bytes are equal, 1 -> T ; Otherwise, 0 -> T 0010nnnnmmmm1100
Definition at line 795 of file sh_il.c.
References BITS_PER_BYTE, EQ, LOGAND, LOGXOR, OR, SEQ2, SETG, SETL, sh_il_get_pure_param, SH_SR_T, SH_U_REG, SHIFTR0, and VARL.
|
static |
DIV0S Rm, Rn MSB of Rn -> Q ; MSB of Rm -> M, M^Q -> T 0010nnnnmmmm0111
Definition at line 855 of file sh_il.c.
References MSB, SEQ3, SETG, sh_il_get_pure_param, SH_SR_M, SH_SR_Q, SH_SR_T, VARG, and XOR.
|
static |
|
static |
DIV1 Rm, Rn 1-step division (Rn ÷ Rm) ; Calculation result -> T 0011nnnnmmmm0100
Definition at line 815 of file sh_il.c.
References ADD, BRANCH, cond, EQ, LOGAND, LOGOR, LOGXOR, regress::m, MSB, NON_ZERO, NULL, SEQ2, SEQ3, SEQ4, SETG, SETL, sh_il_bool_to_bv(), sh_il_get_pure_param, sh_il_set_pure_param, SH_SR_M, SH_SR_Q, SH_SR_T, SH_U_REG, SHIFTL0, SUB, VARG, VARL, and XOR.
|
static |
DMULS.L Rm, Rn Signed, Rn * Rm -> MAC ; 32 * 32 -> 64 bits 0011nnnnmmmm1101
Definition at line 877 of file sh_il.c.
References LOGAND, MUL, SEQ3, SETG, SETL, sh_il_get_pure_param, SH_REG_SIZE, SH_U_REG, SHIFTR0, SIGNED, UN, UNSIGNED, and VARL.
|
static |
DMULU.L Rm, Rn Unsigned, Rn * Rm -> MAC ; 32 * 32 -> 64 bits 0011nnnnmmmm0101
Definition at line 889 of file sh_il.c.
References LOGAND, MUL, SEQ3, SETG, SETL, sh_il_get_pure_param, SH_REG_SIZE, SH_U_REG, SHIFTR0, UN, UNSIGNED, and VARL.
|
static |
DT Rn Rn - 1 -> Rn ; When Rn = 0, 1 -> T ; Otherwise 0 -> T 0100nnnn00010000
Definition at line 901 of file sh_il.c.
References IS_ZERO, SEQ2, SETG, sh_il_get_pure_param, sh_il_set_pure_param, SH_SR_T, SH_U_REG, and SUB.
|
static |
EXTS.B Rm, Rn Rm sign-extended from byte -> Rn 0110nnnnmmmm1110
EXTS.W Rm, Rn Rm sign-extended from word -> Rn 0110nnnnmmmm1111
Definition at line 914 of file sh_il.c.
References sh_il_get_pure_param, and sh_il_set_pure_param.
|
static |
EXTU.B Rm, Rn Rm zero-extended from byte -> Rn 0110nnnnmmmm1100
EXTU.W Rm, Rn Rm zero-extended from word -> Rn 0110nnnnmmmm1101
Definition at line 927 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_reg, SH_REG_SIZE, and UNSIGNED.
|
static |
Get the effective address obtained from the given param
and scaling
.
param | |
scaling | |
pc | Program counter |
ctx | SHILContext instance |
Definition at line 289 of file sh_il.c.
References ADD, convert_to_st12(), LOGAND, sh_param_t::mode, MUL, NULL, sh_param_t::param, pc, RZ_LOG_WARN, SH_GBR_INDIRECT_DISP, SH_GBR_INDIRECT_INDEXED, sh_il_get_reg, SH_PC_RELATIVE12, SH_PC_RELATIVE8, SH_PC_RELATIVE_DISP, SH_PC_RELATIVE_REG, SH_REG_IND_R0, SH_REG_INDIRECT, SH_REG_INDIRECT_D, SH_REG_INDIRECT_DISP, SH_REG_INDIRECT_I, SH_REG_INDIRECT_INDEXED, SH_S_ADDR, SH_SCALING_L, sh_scaling_size, SH_U_ADDR, SHIFTL0, st8, and VARG.
|
static |
Convert the param
with scaling
to it's IL representation.
param | |
scaling | |
pc | Program counter |
ctx | SHILContext instance |
Definition at line 342 of file sh_il.c.
References ADD, BITS_PER_BYTE, LOADW, sh_param_t::mode, NULL, sh_param_t::param, sh_param_helper_t::post, sh_param_helper_t::pre, sh_param_helper_t::pure, RZ_LOG_ERROR, SH_GBR_INDIRECT_DISP, SH_GBR_INDIRECT_INDEXED, sh_il_get_effective_addr, sh_il_get_reg, sh_il_set_reg, SH_IMM_S, SH_IMM_U, SH_PC_RELATIVE12, SH_PC_RELATIVE8, SH_PC_RELATIVE_DISP, SH_PC_RELATIVE_REG, SH_REG_DIRECT, SH_REG_INDIRECT, SH_REG_INDIRECT_D, SH_REG_INDIRECT_DISP, SH_REG_INDIRECT_I, SH_REG_INDIRECT_INDEXED, SH_SCALING_INVALID, SH_SCALING_L, sh_scaling_size, SH_U_ADDR, SN, SUB, UN, and UNSIGNED.
|
static |
Get the privilege mode Do NOT call this before initializing privilege through sh_il_initialize_privilege
Otherwise, the local variable would not have been initialized For all the liftings, this is taken care of in rz_sh_il_opcode
ctx | SHILContext instance used to store the whether privilege was checked or not |
Definition at line 205 of file sh_il.c.
References VARL.
|
static |
Get register corresponding to reg
index This function is smart enough to give the correct register in case of banked registers or status register.
reg | |
ctx | SHILContext instance |
Definition at line 222 of file sh_il.c.
References ITE, reg, sh_banked_reg(), sh_get_banked_reg(), sh_il_get_privilege, sh_il_get_status_reg(), SH_REG_IND_SR, sh_registers, and VARG.
|
static |
Return the status register (sr), calculated by shifting all the status register bits at the correct offsets.
Definition at line 131 of file sh_il.c.
References LOGOR, sh_il_get_status_reg_bit(), SH_REG_SIZE, SH_SR_B, SH_SR_D, SH_SR_F, SH_SR_I, SH_SR_M, SH_SR_Q, SH_SR_R, SH_SR_S, SH_SR_T, SH_U_REG, SHIFTL0, UNSIGNED, val, and VARG.
Referenced by sh_il_get_reg_ctx().
|
static |
We need this because sometimes we would want an RzILOpBitvector
back when we ask for a status reg bit, so this returns us an RzILOpBitvector instead of the RzILOpBool
returned when using VARG
bit | The status register bit global variable name |
Definition at line 122 of file sh_il.c.
References bit, sh_il_bool_to_bv(), and VARG.
Referenced by sh_il_addc(), sh_il_get_status_reg(), sh_il_movt(), sh_il_negc(), and sh_il_subc().
|
static |
Set the value of the local variable "_priv" This exists so that the privilege mode IL doesn't have to be duplicated everywhere, instead one can directly use the local variable.
Definition at line 192 of file sh_il.c.
References AND, SETL, SH_SR_D, SH_SR_R, and VARG.
Referenced by rz_sh_il_opcode().
|
static |
|
static |
Check if there was a carry in the addition of x
and y
to get res
Here res
= x
+ y
(+ 1, optional) This function can also be used of there was a carry bit added as well.
Pass in local variables to this function because otherwise the DUP
s inside it will lead to an unnecessarily long IL
res | |
x | |
y |
Definition at line 501 of file sh_il.c.
References AND, DUP, INV, MSB, OR, x, and xr.
Referenced by sh_il_addc().
|
static |
Check if there was a overflow in the addition of x
and y
to get res
Here res
= x
+ y
.
Pass in local variables to this function because otherwise the DUP
s inside it will lead to an unnecessarily long IL
res | |
x | |
y |
Definition at line 570 of file sh_il.c.
References AND, DUP, INV, MSB, OR, and x.
Referenced by sh_il_addv().
|
static |
Check if there was a borrow in the subtraction of x
and y
to get res
Here res
= x
- y
(- 1, optional) This function can also be used of there was a borrow bit added as well.
Pass in local variables to this function because otherwise the DUP
s inside it will lead to an unnecessarily long IL
res | |
x | |
y |
Definition at line 536 of file sh_il.c.
References AND, DUP, INV, MSB, OR, and x.
Referenced by sh_il_negc(), and sh_il_subc().
|
static |
Check if there was a underflow in the subtraction of x
and y
to get res
Here res
= x
- y
.
Pass in local variables to this function because otherwise the DUP
s inside it will lead to an unnecessarily long IL
res | |
x | |
y |
Definition at line 598 of file sh_il.c.
References AND, DUP, INV, MSB, OR, and x.
Referenced by sh_il_subv().
|
static |
JMP @Rn Rn -> PC ; delayed branch 0100nnnn00101011 TODO: Implement delayed branch
Definition at line 1437 of file sh_il.c.
References JMP, and sh_il_get_effective_addr_param.
|
static |
JSR @Rn PC + 4 -> PR ; Rn -> PC ; delayed branch 0100nnnn00001011 TODO: Implement delayed branch
Definition at line 1447 of file sh_il.c.
References ADD, JMP, pc, SEQ2, SETG, sh_il_get_effective_addr_param, and SH_U_ADDR.
|
static |
LDC Rm, REG REG := SR/GBR/VBR/SSR/SPC/DBR/Rn_BANK Rm -> REG PRIVILEGED (Only GBR is not privileged)
LDC.L @Rm+, REG REG := SR/GBR/VBR/SSR/SPC/DBR/Rn_BANK (Rm) -> REG ; Rm + 4 -> Rm PRIVILEGED (Only GBR is not privileged)
Definition at line 1499 of file sh_il.c.
References BRANCH, EMPTY, NULL, sh_param_helper_t::post, sh_param_helper_t::pure, SEQ2, SETG, sh_get_banked_reg(), sh_il_get_param, sh_il_get_privilege, sh_il_get_pure_param, sh_il_set_pure_param, SH_REG_IND_GBR, SH_SCALING_INVALID, SH_SCALING_L, and sh_valid_gpr().
|
static |
LDS Rm, REG REG := MACH/MACL/PR Rm -> REG
LDS.L @Rm+, REG REG := MACH/MACL/PR (Rm) -> REG ; Rm + 4 -> Rm
Definition at line 1538 of file sh_il.c.
References NOP, sh_param_helper_t::post, sh_param_helper_t::pure, SEQ2, sh_il_get_param, sh_il_get_pure_param, sh_il_set_pure_param, SH_SCALING_INVALID, and SH_SCALING_L.
|
static |
MAC.L @Rm+, @Rn+ Rn * Rm + MAC -> MAC (Signed) (32 * 32 + 64 -> 64 bits) Rn + 4 -> Rn ; Rm + 4 -> Rm 0000nnnnmmmm1111
When S bit is enabled, the MAC addition is a saturation operation of 48 bits So only the lower 48 bits of result and MAC are considered
MAC.W @Rm+, @Rn+ Rn * Rm + MAC -> MAC (Signed) (16 * 16 + 64 -> 64 bits) Rn + 2 -> Rn ; Rm + 2 -> Rm 0000nnnnmmmm1111
When S bit is enabled, the MAC addition is a saturation operation of 32 bits So only the lower 32 bits of result and MAC are considered (which is basically MACL register)
Definition at line 950 of file sh_il.c.
References ADD, add(), BRANCH, LOGAND, LOGOR, mul(), MUL, NULL, sh_param_helper_t::post, sh_param_helper_t::pure, SEQ2, SEQ3, SEQ6, SEQ7, SETG, SETL, sh_il_get_param, SH_REG_SIZE, SH_SCALING_L, SH_SCALING_W, SH_SR_S, SH_U_REG, SHIFTL0, SHIFTR0, SIGNED, UN, UNSIGNED, VARG, and VARL.
|
static |
MOV family instructions
Definition at line 626 of file sh_il.c.
References sh_param_helper_t::post, sh_param_helper_t::pre, sh_param_helper_t::pure, sh_apply_effects(), sh_il_get_param, and sh_il_set_pure_param.
|
static |
MOVCA.L R0, @Rn R0 -> (Rn) (without fetching cache block) 0000nnnn11000011
Definition at line 1553 of file sh_il.c.
References sh_il_get_pure_param, and sh_il_set_pure_param.
|
static |
MOVT Rn T -> Rn 0000nnnn00101001
Definition at line 636 of file sh_il.c.
References sh_il_get_status_reg_bit(), sh_il_set_pure_param, SH_REG_SIZE, SH_SR_T, and UNSIGNED.
|
static |
MUL.L Rm, Rn Rn * Rm -> MACL (32 * 32 -> 32 bits) 0000nnnnmmmm0111
Definition at line 990 of file sh_il.c.
References MUL, SETG, and sh_il_get_pure_param.
|
static |
MULS.W Rm, Rn Rn * Rm -> MACL (Signed) (16 * 16 -> 32 bits) 0010nnnnmmmm1111
Definition at line 999 of file sh_il.c.
References regress::m, MUL, n, SEQ3, SETG, SETL, sh_il_get_pure_param, SH_REG_SIZE, SIGNED, and VARL.
|
static |
MULU.W Rm, Rn Rn * Rm -> MACL (Unsigned) (16 * 16 -> 32 bits) 0010nnnnmmmm1110
Definition at line 1012 of file sh_il.c.
References regress::m, MUL, n, SETG, sh_il_get_pure_param, SH_REG_SIZE, and UNSIGNED.
|
static |
NEG Rm, Rn 0 - Rm -> Rn 0110nnnnmmmm1011
Definition at line 1023 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_pure_param, SH_U_REG, and SUB.
|
static |
NEGC Rm, Rn 0 - Rm - T -> Rn ; borrow -> T 0110nnnnmmmm1010
Definition at line 1033 of file sh_il.c.
References SEQ3, SETG, SETL, sh_il_get_pure_param, sh_il_get_status_reg_bit(), sh_il_is_sub_borrow(), sh_il_set_pure_param, SH_SR_T, SH_U_REG, SUB, subvar(), and VARL.
|
static |
|
static |
NOT Rm, Rn ~Rm -> Rn 0110nnnnmmmm0111
Definition at line 1099 of file sh_il.c.
References LOGNOT, sh_il_get_pure_param, and sh_il_set_pure_param.
|
static |
OR Rm, Rn Rn | Rm -> Rn 0010nnnnmmmm1011
OR imm, R0 R0 | imm -> R0 11001011iiiiiiii
OR.B imm, @(R0, GBR) (R0 + GBR) | imm -> (R0 + GBR) 11001111iiiiiiii
Definition at line 1116 of file sh_il.c.
References LOGOR, sh_il_get_pure_param, and sh_il_set_pure_param.
|
static |
|
static |
|
static |
|
static |
|
static |
RTE SSR -> SR ; SPC -> PC ; delayed branch 0000000000101011 PRIVILEGED TODO: Implement delayed branch
Definition at line 1573 of file sh_il.c.
References BRANCH, EMPTY, JMP, SEQ2, sh_il_get_privilege, sh_il_set_status_reg(), and VARG.
|
static |
|
static |
Set the value of the param
at scaling
to val
This function is smart enough to also apply any effects corresponding to the param
.
param | |
val | |
scaling | |
pc | Program counter |
ctx | SHILContext instance |
Definition at line 440 of file sh_il.c.
References cast, sh_param_t::mode, NULL, sh_param_t::param, sh_param_helper_t::post, post(), sh_param_helper_t::pre, sh_param_helper_t::pure, RZ_FREE, RZ_LOG_ERROR, SEQ2, sh_apply_effects(), SH_GBR_INDIRECT_DISP, SH_GBR_INDIRECT_INDEXED, sh_il_get_effective_addr, sh_il_get_param, sh_il_set_reg, sh_il_signed(), SH_IMM_S, SH_IMM_U, SH_PC_RELATIVE12, SH_PC_RELATIVE8, SH_PC_RELATIVE_DISP, SH_PC_RELATIVE_REG, SH_REG_DIRECT, SH_REG_INDIRECT, SH_REG_INDIRECT_D, SH_REG_INDIRECT_DISP, SH_REG_INDIRECT_I, SH_REG_INDIRECT_INDEXED, SH_REG_SIZE, SH_SCALING_INVALID, SH_SCALING_L, STOREW, val, and VARL.
|
static |
Set the value of the register corresponding to index reg
to value val
This function is smart enough to set values correctly in case of banked registers or status register.
reg | |
val | |
ctx | SHILContext instance |
Definition at line 245 of file sh_il.c.
References BRANCH, reg, SEQ2, SETG, SETL, sh_banked_reg(), sh_get_banked_reg(), sh_il_get_privilege, sh_il_set_status_reg(), SH_REG_IND_SR, sh_registers, val, and VARL.
|
static |
Set the value of the status register (sr) to val
by setting the values of the individual status register bits.
val |
Definition at line 161 of file sh_il.c.
References LOGAND, LSB, SEQ2, SETG, SETL, SH_SR_B, SH_SR_D, SH_SR_F, SH_SR_I, SH_SR_M, SH_SR_Q, SH_SR_R, SH_SR_S, SH_SR_T, SH_U_REG, SHIFTR0, UN, UNSIGNED, val, and VARL.
Referenced by sh_il_rte(), and sh_il_set_reg_ctx().
|
static |
|
static |
|
static |
SHAD Rm, Rn If Rn >= 0, Rn << Rm -> Rn If Rn < 0, Rn >> Rm -> [MSB -> Rn] MSB -> Rn 0100nnnnmmmm1100
Definition at line 1225 of file sh_il.c.
References BRANCH, NEG, SEQ2, SETL, SGE, sh_il_get_pure_param, sh_il_set_pure_param, SHIFTL0, SHIFTRA, SN, UNSIGNED, and VARL.
|
static |
SHAL Rn T <- Rn <- 0 0100nnnn00100000
Definition at line 1239 of file sh_il.c.
References MSB, SEQ2, SETG, sh_il_get_pure_param, sh_il_set_pure_param, SH_SR_T, SH_U_REG, and SHIFTL0.
|
static |
SHAR Rn MSB -> Rn -> T 0100nnnn00100001
Definition at line 1250 of file sh_il.c.
References LSB, SEQ2, SETG, sh_il_get_pure_param, sh_il_set_pure_param, SH_SR_T, SH_U_REG, and SHIFTRA.
|
static |
SHLD Rm, Rn If Rn >= 0, Rn << Rm -> Rn If Rn < 0, Rn >> Rm -> [0 -> Rn] MSB -> Rn 0100nnnnmmmm1101
Definition at line 1263 of file sh_il.c.
References BRANCH, NEG, SEQ2, SETL, SGE, sh_il_get_pure_param, sh_il_set_pure_param, SHIFTL0, SHIFTR0, SN, UNSIGNED, and VARL.
|
static |
SHLL Rn T <- Rn <- 0 0100nnnn00000000
Definition at line 1278 of file sh_il.c.
References MSB, SEQ2, SETG, sh_il_get_pure_param, sh_il_set_pure_param, SH_SR_T, SH_U_REG, and SHIFTL0.
|
static |
SHLL16 Rn Rn << 16 -> Rn 0100nnnn00101000
Definition at line 1336 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_pure_param, SH_U_REG, and SHIFTL0.
|
static |
SHLL2 Rn Rn << 2 -> Rn 0100nnnn00001000
Definition at line 1300 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_pure_param, SH_U_REG, and SHIFTL0.
|
static |
SHLL8 Rn Rn << 8 -> Rn 0100nnnn00011000
Definition at line 1318 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_pure_param, SH_U_REG, and SHIFTL0.
|
static |
SHLR Rn 0 -> Rn -> T 0100nnnn00000001
Definition at line 1289 of file sh_il.c.
References LSB, SEQ2, SETG, sh_il_get_pure_param, sh_il_set_pure_param, SH_SR_T, SH_U_REG, and SHIFTR0.
|
static |
SHLR16 Rn Rn >> 16 -> Rn 0100nnnn00101001
Definition at line 1345 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_pure_param, SH_U_REG, and SHIFTR0.
|
static |
SHLR2 Rn Rn >> 2 -> Rn 0100nnnn00001001
Definition at line 1309 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_pure_param, SH_U_REG, and SHIFTR0.
|
static |
SHLR8 Rn Rn >> 8 -> Rn 0100nnnn00011001
Definition at line 1327 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_pure_param, SH_U_REG, and SHIFTR0.
RzILOpEffect* sh_il_signed | ( | unsigned int | len, |
RZ_OWN RzILOpPure * | val, | ||
const char * | cast_var, | ||
const char * | temp_var | ||
) |
Cast val
to len
bits This uses a local temp variable temp_var
to store the value val
and then casts the local variable temp_var
to its signed value and stores that value in the local variable cast_var
.
The purpose of this function is to remove the redundant IL block introduced by SIGNED
opbuilder macro (MSB
of val
for fill bits, and val
for value), and instead use a local variable to refer to val
in both the above places, making the IL dump much more concise and readable
TODO: Ideally this should be integrated in SIGNED
itself (need to be clever about it though)
len | |
val | |
cast_var | Casted variable name ; Use this variable to access the casted value in the caller |
temp_var | Temp variable name ; Do NOT use this variable outside this function |
Definition at line 82 of file sh_il.c.
References cast, init, len, MSB, rz_il_op_new_cast(), SEQ2, SETL, val, and VARL.
Referenced by sh_il_set_param_pc_ctx().
|
static |
|
static |
STC REG, Rn REG := SR/GBR/VBR/SSR/SPC/SGR/DBR/Rn_BANK REG -> Rn PRIVILEGED (Only GBR is not privileged)
STC.L REG, -Rn REG := SR/GBR/VBR/SSR/SPC/SGR/DBR/Rn_BANK Rn - 4 -> Rn ; REG -> (Rn) PRIVILEGED (Only GBR is not privileged)
Definition at line 1616 of file sh_il.c.
References BRANCH, EMPTY, NULL, sh_get_banked_reg(), sh_il_get_privilege, sh_il_get_pure_param, sh_il_set_pure_param, SH_REG_IND_GBR, sh_valid_gpr(), and VARG.
|
static |
STS REG, Rn REG := MACH/MACL/PR REG -> Rn
STS.L REG, -Rn REG := MACH/MACL/PR Rn + 4 -> Rn ; REG -> (Rn)
Definition at line 1645 of file sh_il.c.
References sh_il_get_pure_param, and sh_il_set_pure_param.
|
static |
SUB Rm, Rn Rn - Rm -> Rn 0011nnnnmmmm1000
Definition at line 1044 of file sh_il.c.
References sh_il_get_pure_param, sh_il_set_pure_param, and SUB.
|
static |
SUBC Rm, Rn Rn - Rm - T -> Rn ; borrow -> T 0011nnnnmmmm1010
Definition at line 1053 of file sh_il.c.
References SEQ3, SETG, SETL, sh_il_get_pure_param, sh_il_get_status_reg_bit(), sh_il_is_sub_borrow(), sh_il_set_pure_param, SH_SR_T, SUB, and VARL.
|
static |
SUBV Rm, Rn Rn - Rm -> Rn ; underflow -> T 0011nnnnmmmm1011
Definition at line 1068 of file sh_il.c.
References SEQ3, SETG, SETL, sh_il_get_pure_param, sh_il_is_sub_underflow(), sh_il_set_pure_param, SH_SR_T, SUB, and VARL.
|
static |
SWAP.B Rm, Rn Rm -> swap lower 2 bytes -> REG 0110nnnnmmmm1000
SWAP.W Rm, Rn Rm -> swap upper/lower words -> Rn 0110nnnnmmmm1001
Definition at line 649 of file sh_il.c.
References BITS_PER_BYTE, LOGAND, LOGOR, NULL, sh_il_get_param, sh_il_set_param, SH_SCALING_B, SH_SCALING_L, SH_SCALING_W, SH_U_REG, SHIFTL0, and SHIFTR0.
|
static |
|
static |
TST Rm, Rn If Rn & Rm = 0, 1 -> T ; Otherwise 0 -> T 0010nnnnmmmm1000
TST imm, R0 If R0 & imm = 0, 1 -> T ; Otherwise 0 -> T 11001000iiiiiiii
TST.B imm, @(R0, GBR) If (R0 + GBR) & imm = 0, 1 -> T ; Otherwise 0 -> T 11001100iiiiiiii
Definition at line 1145 of file sh_il.c.
References IS_ZERO, LOGAND, SETG, sh_il_get_pure_param, and SH_SR_T.
|
static |
Unimplemented instruction/opcode To be used for valid SuperH-4 instruction which yet haven't been lifted to the IL.
Definition at line 1653 of file sh_il.c.
References EMPTY, and RZ_LOG_WARN.
|
static |
XOR Rm, Rn Rn ^ Rm -> Rn 0010nnnnmmmm1010
XOR imm, R0 R0 ^ imm -> R0 11001010iiiiiiii
XOR.B imm, @(R0, GBR) (R0 + GBR) ^ imm -> (R0 + GBR) 11001110iiiiiiii
Definition at line 1162 of file sh_il.c.
References LOGXOR, sh_il_get_pure_param, and sh_il_set_pure_param.
|
static |
XTRCT Rm, Rn Rm:Rn middle 32 bits -> Rn 0010nnnnmmmm1101
Definition at line 674 of file sh_il.c.
References BITS_PER_BYTE, LOGOR, sh_il_get_pure_param, sh_il_set_pure_param, SH_U_REG, SHIFTL0, and SHIFTR0.
Definition at line 44 of file sh_il.c.
References reg, and SH_GPR_COUNT.
Referenced by sh_il_ldc(), and sh_il_stc().
|
static |
Registers available as global variables in the IL
Definition at line 55 of file sh_il.c.
Referenced by sh_get_banked_reg().
|
static |
Lookup table for the IL lifting handlers for the various instructions.
Definition at line 1665 of file sh_il.c.
Referenced by rz_sh_il_opcode().