Home | History | Annotate | Download | only in vb6
      1 VERSION 1.0 CLASS
      2 BEGIN
      3   MultiUse = -1  'True
      4   Persistable = 0  'NotPersistable
      5   DataBindingBehavior = 0  'vbNone
      6   DataSourceBehavior  = 0  'vbNone
      7   MTSTransactionMode  = 0  'NotAnMTSObject
      8 END
      9 Attribute VB_Name = "CInstruction"
     10 Attribute VB_GlobalNameSpace = False
     11 Attribute VB_Creatable = True
     12 Attribute VB_PredeclaredId = False
     13 Attribute VB_Exposed = False
     14 Option Explicit
     15 
     16 'Capstone Disassembly Engine bindings for VB6
     17 'Contributed by FireEye FLARE Team
     18 'Author:  David Zimmer <david.zimmer (a] fireeye.com>, <dzzie (a] yahoo.com>
     19 'License: Apache
     20 'Copyright: FireEye 2017
     21 
     22 
     23 'Public Type cs_insn
     24 '                              ' Instruction ID (basically a numeric ID for the instruction mnemonic)
     25 '                              ' Find the instruction id in the '[ARCH]_insn' enum in the header file
     26 '                              ' of corresponding architecture, such as 'arm_insn' in arm.h for ARM,
     27 '                              ' 'x86_insn' in x86.h for X86, etc...
     28 '                              ' available even when CS_OPT_DETAIL = CS_OPT_OFF
     29 '                              ' NOTE: in Skipdata mode, "data" instruction has 0 for this id field. UNSIGNED
     30 '    id As Long                '
     31 '    align As Long             'not sure why it needs this..but it does..
     32 '    address As Currency       ' Address (EIP) of this instruction available even when CS_OPT_DETAIL = CS_OPT_OFF UNSIGNED
     33 '    size As Integer           ' Size of this instruction available even when CS_OPT_DETAIL = CS_OPT_OFF UNSIGNED
     34 '    bytes(0 To 15) As Byte    ' Machine bytes of this instruction, with number of bytes indicated by @size above available even when CS_OPT_DETAIL = CS_OPT_OFF
     35 '    mnemonic(0 To 31) As Byte ' Ascii text of instruction mnemonic available even when CS_OPT_DETAIL = CS_OPT_OFF
     36 '    op_str(0 To 159) As Byte  ' Ascii text of instruction operands available even when CS_OPT_DETAIL = CS_OPT_OFF
     37 '
     38 '                              ' Pointer to cs_detail.
     39 '                              ' NOTE: detail pointer is only valid when both requirements below are met:
     40 '                              ' (1) CS_OP_DETAIL = CS_OPT_ON
     41 '                              ' (2) Engine is not in Skipdata mode (CS_OP_SKIPDATA option set to CS_OPT_ON)
     42 '                              ' NOTE 2: when in Skipdata mode, or when detail mode is OFF, even if this pointer
     43 '                              '  is not NULL, its content is still irrelevant.
     44 '    lpDetail As Long          '  points to a cs_detail structure NOTE: only available when CS_OPT_DETAIL = CS_OPT_ON
     45 '
     46 'End Type
     47 
     48 Public ID As Long
     49 Public address As Currency
     50 Public size As Long
     51 Private m_bytes() As Byte
     52 Public instruction As String
     53 Public operand As String
     54 Public lpDetails As Long
     55 Public parent As CDisassembler
     56 
     57 Public details As CInstDetails 'may be null
     58 
     59 Property Get bytes() As Byte()
     60     bytes = Me.bytes()
     61 End Property
     62 
     63 Property Get byteDump(Optional padding = 15) As String
     64     Dim b As String, i As Long
     65     For i = 0 To UBound(m_bytes)
     66         b = b & hhex(m_bytes(i)) & " "
     67     Next
     68     byteDump = rpad(b, padding)
     69 End Property
     70 
     71 Property Get text() As String
     72    
     73     text = cur2str(address) & "    " & byteDump & "    " & instruction & " " & operand
     74     
     75 End Property
     76 
     77 Function toString() As String
     78     
     79     Dim r() As String
     80     
     81     push r, "CInstruction: "
     82     push r, String(40, "-")
     83     push r, "Id: " & Hex(ID)
     84     push r, "address: " & cur2str(address)
     85     push r, "size: " & Hex(size)
     86     push r, "bytes: " & byteDump()
     87     push r, "instruction: " & instruction
     88     push r, "operand: " & operand
     89     push r, "lpDetails: " & Hex(lpDetails)
     90     
     91     If Not details Is Nothing Then
     92         push r, details.toString()
     93     End If
     94     
     95     toString = Join(r, vbCrLf)
     96     
     97 End Function
     98 
     99 Friend Sub LoadInstruction(instAry As Long, index As Long, parent As CDisassembler)
    100 
    101     Dim inst As cs_insn
    102     Dim i As Long
    103     
    104     getInstruction instAry, index, VarPtr(inst), LenB(inst)
    105     
    106     ID = inst.ID
    107     address = inst.address
    108     size = inst.size
    109     lpDetails = inst.lpDetail
    110     Set Me.parent = parent
    111     
    112     m_bytes() = inst.bytes
    113     ReDim Preserve m_bytes(size - 1)
    114     
    115     For i = 0 To UBound(inst.mnemonic)
    116         If inst.mnemonic(i) = 0 Then Exit For
    117         instruction = instruction & Chr(inst.mnemonic(i))
    118     Next
    119     
    120     For i = 0 To UBound(inst.op_str)
    121         If inst.op_str(i) = 0 Then Exit For
    122         operand = operand & Chr(inst.op_str(i))
    123     Next
    124 
    125     If lpDetails = 0 Then Exit Sub
    126     Set details = New CInstDetails
    127     details.LoadDetails lpDetails, parent
    128     
    129 End Sub
    130 
    131 
    132     
    133 
    134