hdis86-0.2: Interface to the udis86 disassembler for x86 and x86-64 / AMD64

Hdis86.Types

Contents

Description

Types provided by the disassembler.

Synopsis

Instructions

data Instruction Source

An x86 / AMD64 CPU instruction.

The destination Operand (if any) will precede the source Operands.

Constructors

Inst 

data Prefix Source

Prefixes, used to modify an instruction.

Constructors

Seg Segment

Segment override

Rex

REX prefix; enables certain 64-bit features

OperSize

Operand size override

AddrSize

Address size override

Lock

Perform memory operations atomically

Rep

Repeat

RepE

Repeat while equal

RepNE

Repeat while not equal

data Operand Source

Instruction operands.

Constructors

Mem Memory

Memory access

Reg Register

Register

Ptr Pointer

Segmented pointer

Imm (Immediate Word64)

Immediate value

Jump (Immediate Int64)

Immediate value, for a relative jump

Const (Immediate Word64)

Constant value

data Memory Source

A memory-access operand.

Constructors

Memory 

Fields

mSize :: WordSize

Size of the word in memory

mBase :: Register

Base register

mIndex :: Register

Index register

mScale :: Word8

Scale of index

mOffset :: Immediate Int64

Displacement / offset value

data Pointer Source

A segmented pointer operand.

Constructors

Pointer 

Fields

pSegment :: Word16

Segment

pOffset :: Immediate Word32

Offset, 16 or 32 bits

data Immediate t Source

An immediate operand.

Constructors

Immediate 

Fields

iSize :: WordSize

Size of the field

iValue :: t

Immediate value, e.g Int64 or Word64

Instances

Registers

data Register Source

An x86 / AMD64 register.

Constructors

RegNone

No register specified.

Reg8 GPR Half

Either 8-bit half of the low 16 bits of a general-purpose register

Reg16 GPR

Low 16 bits of a general-purpose register (full register in 16-bit mode)

Reg32 GPR

Low 32 bits of a general-purpose register (full register in 32-bit mode)

Reg64 GPR

Full 64-bit general-purpose register

RegSeg Segment

Segment register

RegCtl ControlRegister

Control register

RegDbg DebugRegister

Debug register

RegMMX MMXRegister

MMX register

RegX87 X87Register

x87 floating point unit register

RegXMM XMMRegister

XMM register

RegIP

Instruction pointer

data GPR Source

A general-purpose register.

The names are taken from the 64-bit architecture, but they map onto other modes in the obvious way.

Constructors

RAX 
RCX 
RDX 
RBX 
RSP 
RBP 
RSI 
RDI 
R8 
R9 
R10 
R11 
R12 
R13 
R14 
R15 

data Half Source

Indicates which half of a 16-bit register is used as an 8-bit register.

Constructors

L

Low or least significant 8 bits

H

High or most significant 8 bits

Word sizes

data WordSize Source

Machine word sizes.

Some fields, such as immediate operands, come in different widths. We store the equivalent integer value in a Word64, along with a WordSize to indicate the original width.

Constructors

Bits0

Field not present, value will be 0

Bits8 
Bits16 
Bits32 
Bits48 
Bits64 
Bits80 

wordSize :: Word8 -> Maybe WordSizeSource

Convert a number of bits to a WordSize.

bitsInWord :: WordSize -> Word8Source

Number of bits in a word of a given size.

Instruction with metadata

data Metadata Source

An instruction with full metadata.

Constructors

Metadata 

Fields

mdOffset :: Word64

Offset of the start of this instruction

mdLength :: Word

Length of this instruction in bytes

mdHex :: String

Hexadecimal representation of this instruction

mdBytes :: ByteString

Bytes that make up this instruction

mdAssembly :: String

Assembly code for this instruction

mdInst :: Instruction

The instruction itself

Configuration

data Config Source

Overall configuration of the disassembler.

Constructors

Config 

Fields

cfgVendor :: Vendor

CPU vendor; determines the instruction set used

cfgCPUMode :: CPUMode

Disassemble 16-, 32-, or 64-bit code

cfgSyntax :: Syntax

Syntax to use when generating assembly

cfgOrigin :: Word64

Address where the first instruction would live in memory

data Vendor Source

CPU vendors, supporting slightly different instruction sets.

Constructors

Intel 
AMD 

data CPUMode Source

CPU execution mode.

Constructors

Mode16

16-bit mode

Mode32

32-bit mode

Mode64

64-bit mode

data Syntax Source

Selection of assembly output syntax.

Constructors

SyntaxNone

Don't generate assembly syntax

SyntaxIntel

Intel- / NASM-like syntax

SyntaxATT

AT&T- / gas-like syntax

Common configurations

Opcodes

data Opcode Source

Constructors

I3dnow 
Iaaa 
Iaad 
Iaam 
Iaas 
Iadc 
Iadd 
Iaddpd 
Iaddps 
Iaddsd 
Iaddss 
Iaddsubpd 
Iaddsubps 
Iand 
Iandpd 
Iandps 
Iandnpd 
Iandnps 
Iarpl 
Imovsxd 
Ibound 
Ibsf 
Ibsr 
Ibswap 
Ibt 
Ibtc 
Ibtr 
Ibts 
Icall 
Icbw 
Icwde 
Icdqe 
Iclc 
Icld 
Iclflush 
Iclgi 
Icli 
Iclts 
Icmc 
Icmovo 
Icmovno 
Icmovb 
Icmovae 
Icmovz 
Icmovnz 
Icmovbe 
Icmova 
Icmovs 
Icmovns 
Icmovp 
Icmovnp 
Icmovl 
Icmovge 
Icmovle 
Icmovg 
Icmp 
Icmppd 
Icmpps 
Icmpsb 
Icmpsw 
Icmpsd 
Icmpsq 
Icmpss 
Icmpxchg 
Icmpxchg8b 
Icomisd 
Icomiss 
Icpuid 
Icvtdq2pd 
Icvtdq2ps 
Icvtpd2dq 
Icvtpd2pi 
Icvtpd2ps 
Icvtpi2ps 
Icvtpi2pd 
Icvtps2dq 
Icvtps2pi 
Icvtps2pd 
Icvtsd2si 
Icvtsd2ss 
Icvtsi2ss 
Icvtss2si 
Icvtss2sd 
Icvttpd2pi 
Icvttpd2dq 
Icvttps2dq 
Icvttps2pi 
Icvttsd2si 
Icvtsi2sd 
Icvttss2si 
Icwd 
Icdq 
Icqo 
Idaa 
Idas 
Idec 
Idiv 
Idivpd 
Idivps 
Idivsd 
Idivss 
Iemms 
Ienter 
If2xm1 
Ifabs 
Ifadd 
Ifaddp 
Ifbld 
Ifbstp 
Ifchs 
Ifclex 
Ifcmovb 
Ifcmove 
Ifcmovbe 
Ifcmovu 
Ifcmovnb 
Ifcmovne 
Ifcmovnbe 
Ifcmovnu 
Ifucomi 
Ifcom 
Ifcom2 
Ifcomp3 
Ifcomi 
Ifucomip 
Ifcomip 
Ifcomp 
Ifcomp5 
Ifcompp 
Ifcos 
Ifdecstp 
Ifdiv 
Ifdivp 
Ifdivr 
Ifdivrp 
Ifemms 
Iffree 
Iffreep 
Ificom 
Ificomp 
Ifild 
Ifncstp 
Ifninit 
Ifiadd 
Ifidivr 
Ifidiv 
Ifisub 
Ifisubr 
Ifist 
Ifistp 
Ifisttp 
Ifld 
Ifld1 
Ifldl2t 
Ifldl2e 
Ifldlpi 
Ifldlg2 
Ifldln2 
Ifldz 
Ifldcw 
Ifldenv 
Ifmul 
Ifmulp 
Ifimul 
Ifnop 
Ifpatan 
Ifprem 
Ifprem1 
Ifptan 
Ifrndint 
Ifrstor 
Ifnsave 
Ifscale 
Ifsin 
Ifsincos 
Ifsqrt 
Ifstp 
Ifstp1 
Ifstp8 
Ifstp9 
Ifst 
Ifnstcw 
Ifnstenv 
Ifnstsw 
Ifsub 
Ifsubp 
Ifsubr 
Ifsubrp 
Iftst 
Ifucom 
Ifucomp 
Ifucompp 
Ifxam 
Ifxch 
Ifxch4 
Ifxch7 
Ifxrstor 
Ifxsave 
Ifpxtract 
Ifyl2x 
Ifyl2xp1 
Ihaddpd 
Ihaddps 
Ihlt 
Ihsubpd 
Ihsubps 
Iidiv 
Iin 
Iimul 
Iinc 
Iinsb 
Iinsw 
Iinsd 
Iint1 
Iint3 
Iint 
Iinto 
Iinvd 
Iinvlpg 
Iinvlpga 
Iiretw 
Iiretd 
Iiretq 
Ijo 
Ijno 
Ijb 
Ijae 
Ijz 
Ijnz 
Ijbe 
Ija 
Ijs 
Ijns 
Ijp 
Ijnp 
Ijl 
Ijge 
Ijle 
Ijg 
Ijcxz 
Ijecxz 
Ijrcxz 
Ijmp 
Ilahf 
Ilar 
Ilddqu 
Ildmxcsr 
Ilds 
Ilea 
Iles 
Ilfs 
Ilgs 
Ilidt 
Ilss 
Ileave 
Ilfence 
Ilgdt 
Illdt 
Ilmsw 
Ilock 
Ilodsb 
Ilodsw 
Ilodsd 
Ilodsq 
Iloopnz 
Iloope 
Iloop 
Ilsl 
Iltr 
Imaskmovq 
Imaxpd 
Imaxps 
Imaxsd 
Imaxss 
Imfence 
Iminpd 
Iminps 
Iminsd 
Iminss 
Imonitor 
Imov 
Imovapd 
Imovaps 
Imovd 
Imovddup 
Imovdqa 
Imovdqu 
Imovdq2q 
Imovhpd 
Imovhps 
Imovlhps 
Imovlpd 
Imovlps 
Imovhlps 
Imovmskpd 
Imovmskps 
Imovntdq 
Imovnti 
Imovntpd 
Imovntps 
Imovntq 
Imovq 
Imovqa 
Imovq2dq 
Imovsb 
Imovsw 
Imovsd 
Imovsq 
Imovsldup 
Imovshdup 
Imovss 
Imovsx 
Imovupd 
Imovups 
Imovzx 
Imul 
Imulpd 
Imulps 
Imulsd 
Imulss 
Imwait 
Ineg 
Inop 
Inot 
Ior 
Iorpd 
Iorps 
Iout 
Ioutsb 
Ioutsw 
Ioutsd 
Ioutsq 
Ipacksswb 
Ipackssdw 
Ipackuswb 
Ipaddb 
Ipaddw 
Ipaddq 
Ipaddsb 
Ipaddsw 
Ipaddusb 
Ipaddusw 
Ipand 
Ipandn 
Ipause 
Ipavgb 
Ipavgw 
Ipcmpeqb 
Ipcmpeqw 
Ipcmpeqd 
Ipcmpgtb 
Ipcmpgtw 
Ipcmpgtd 
Ipextrw 
Ipinsrw 
Ipmaddwd 
Ipmaxsw 
Ipmaxub 
Ipminsw 
Ipminub 
Ipmovmskb 
Ipmulhuw 
Ipmulhw 
Ipmullw 
Ipmuludq 
Ipop 
Ipopa 
Ipopad 
Ipopfw 
Ipopfd 
Ipopfq 
Ipor 
Iprefetch 
Iprefetchnta 
Iprefetcht0 
Iprefetcht1 
Iprefetcht2 
Ipsadbw 
Ipshufd 
Ipshufhw 
Ipshuflw 
Ipshufw 
Ipslldq 
Ipsllw 
Ipslld 
Ipsllq 
Ipsraw 
Ipsrad 
Ipsrlw 
Ipsrld 
Ipsrlq 
Ipsrldq 
Ipsubb 
Ipsubw 
Ipsubd 
Ipsubq 
Ipsubsb 
Ipsubsw 
Ipsubusb 
Ipsubusw 
Ipunpckhbw 
Ipunpckhwd 
Ipunpckhdq 
Ipunpckhqdq 
Ipunpcklbw 
Ipunpcklwd 
Ipunpckldq 
Ipunpcklqdq 
Ipi2fw 
Ipi2fd 
Ipf2iw 
Ipf2id 
Ipfnacc 
Ipfpnacc 
Ipfcmpge 
Ipfmin 
Ipfrcp 
Ipfrsqrt 
Ipfsub 
Ipfadd 
Ipfcmpgt 
Ipfmax 
Ipfrcpit1 
Ipfrspit1 
Ipfsubr 
Ipfacc 
Ipfcmpeq 
Ipfmul 
Ipfrcpit2 
Ipmulhrw 
Ipswapd 
Ipavgusb 
Ipush 
Ipusha 
Ipushad 
Ipushfw 
Ipushfd 
Ipushfq 
Ipxor 
Ircl 
Ircr 
Irol 
Iror 
Ircpps 
Ircpss 
Irdmsr 
Irdpmc 
Irdtsc 
Irdtscp 
Irepne 
Irep 
Iret 
Iretf 
Irsm 
Irsqrtps 
Irsqrtss 
Isahf 
Isal 
Isalc 
Isar 
Ishl 
Ishr 
Isbb 
Iscasb 
Iscasw 
Iscasd 
Iscasq 
Iseto 
Isetno 
Isetb 
Isetnb 
Isetz 
Isetnz 
Isetbe 
Iseta 
Isets 
Isetns 
Isetp 
Isetnp 
Isetl 
Isetge 
Isetle 
Isetg 
Isfence 
Isgdt 
Ishld 
Ishrd 
Ishufpd 
Ishufps 
Isidt 
Isldt 
Ismsw 
Isqrtps 
Isqrtpd 
Isqrtsd 
Isqrtss 
Istc 
Istd 
Istgi 
Isti 
Iskinit 
Istmxcsr 
Istosb 
Istosw 
Istosd 
Istosq 
Istr 
Isub 
Isubpd 
Isubps 
Isubsd 
Isubss 
Iswapgs 
Isyscall 
Isysenter 
Isysexit 
Isysret 
Itest 
Iucomisd 
Iucomiss 
Iud2 
Iunpckhpd 
Iunpckhps 
Iunpcklps 
Iunpcklpd 
Iverr 
Iverw 
Ivmcall 
Ivmclear 
Ivmxon 
Ivmptrld 
Ivmptrst 
Ivmresume 
Ivmxoff 
Ivmrun 
Ivmmcall 
Ivmload 
Ivmsave 
Iwait 
Iwbinvd 
Iwrmsr 
Ixadd 
Ixchg 
Ixlatb 
Ixor 
Ixorpd 
Ixorps 
Idb 
Iinvalid 
Id3vil 
Ina 
Igrp_reg 
Igrp_rm 
Igrp_vendor 
Igrp_x87 
Igrp_mode 
Igrp_osize 
Igrp_asize 
Igrp_mod 
Inone