VB PE導出/輸入表演示(進程版)

frmMain.frm

Option Explicit
Private Declare Sub InitCommonControls Lib "comctl32.dll" ()

Private Function IsArraryInitialize(strArray() As String) As Boolean
    On Error GoTo ErrHandle
    Dim i As Long
    i = UBound(strArray)
    IsArraryInitialize = True
    Exit Function
ErrHandle:
    IsArraryInitialize = False
End Function

Private Function IsObjArraryInitialize(objArray() As ImportDetailInfo) As Boolean
    On Error GoTo ErrHandle
    Dim i As Long
    i = UBound(objArray)
    IsObjArraryInitialize = True
    Exit Function
ErrHandle:
    IsObjArraryInitialize = False
End Function

Private Sub cmdExit_Click()
    Unload Me
End Sub

Private Sub cmdExport_Click()
    Dim pExportInfo As ExportInfo, i As Integer
    lstExport.Clear
    Call GetProcessPath(Val(txtPath.Text))
    If GetExportTable(Val(txtPath.Text), pExportInfo) Then
        lstExport.AddItem pExportInfo.strDllName & "導出函數列表:"
        If IsArraryInitialize(pExportInfo.strFuns) Then
            For i = 0 To UBound(pExportInfo.strFuns)
                lstExport.AddItem "     " & pExportInfo.strFuns(i)
            Next
        End If
    End If
End Sub

Private Sub cmdImport_Click()
    Dim pImportInfo As ImportInfo, i As Integer, j As Integer
    lstImport.Clear
    Call GetProcessPath(Val(txtPath.Text))
    If GetImportTable(Val(txtPath.Text), pImportInfo) Then
        lstImport.AddItem pImportInfo.strExePath & "輸入函數列表:"
        If IsObjArraryInitialize(pImportInfo.pDetailInfo) Then
            For i = 0 To UBound(pImportInfo.pDetailInfo)
                lstImport.AddItem "     模塊:" & pImportInfo.pDetailInfo(i).strDllName & ""
                If IsArraryInitialize(pImportInfo.pDetailInfo(i).strFuns) Then
                    For j = 0 To UBound(pImportInfo.pDetailInfo(i).strFuns)
                        lstImport.AddItem "          " & pImportInfo.pDetailInfo(i).strFuns(j)
                    Next
                End If
            Next
        End If
    End If
End Sub

Private Sub Form_Initialize()
    InitCommonControls
End Sub

modPEInfo.bas


Option Explicit

Private Const PROCESS_QUERY_INFORMATION As Long = 1024
Private Const PROCESS_VM_READ As Long = 16

Private Declare Function ReadProcessMemory Lib "kernel32" (ByVal hProcess As Long, lpBaseAddress As Any, lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Private Declare Function OpenProcess Lib "kernel32.dll" (ByVal dwDesiredAccessas As Long, ByVal bInheritHandle As Long, ByVal dwProcId As Long) As Long

Private Declare Function NtQueryInformationProcess Lib "ntdll.dll" (ByVal ProcessHandle As Long, _
                                ByVal ProcessInformationClass As PROCESSINFOCLASS, _
                                ByVal ProcessInformation As Long, _
                                ByVal ProcessInformationLength As Long, _
                                ByRef ReturnLength As Long) As Long

Private Enum PROCESSINFOCLASS
    ProcessBasicInformation = 0
    ProcessQuotaLimits
    ProcessIoCounters
    ProcessVmCounters
    ProcessTimes
    ProcessBasePriority
    ProcessRaisePriority
    ProcessDebugPort
    ProcessExceptionPort
    ProcessAccessToken
    ProcessLdtInformation
    ProcessLdtSize
    ProcessDefaultHardErrorMode
    ProcessIoPortHandlers
    ProcessPooledUsageAndLimits
    ProcessWorkingSetWatch
    ProcessUserModeIOPL
    ProcessEnableAlignmentFaultFixup
    ProcessPriorityClass
    ProcessWx86Information
    ProcessHandleCount
    ProcessAffinityMask
    ProcessPriorityBoost
    ProcessDeviceMap
    ProcessSessionInformation
    ProcessForegroundInformation
    ProcessWow64Information
    ProcessImageFileName
    ProcessLUIDDeviceMapsEnabled
    ProcessBreakOnTermination
    ProcessDebugObjectHandle
    ProcessDebugFlags
    ProcessHandleTracing
    ProcessIoPriority
    ProcessExecuteFlags
    ProcessResourceManagement
    ProcessCookie
    ProcessImageInformation
    MaxProcessInfoClass
End Enum

Private Type PROCESS_BASIC_INFORMATION
    ExitStatus As Long 'NTSTATUS
    PebBaseAddress As Long 'PPEB
    AffinityMask As Long 'ULONG_PTR
    BasePriority As Long 'KPRIORITY
    UniqueProcessId As Long 'ULONG_PTR
    InheritedFromUniqueProcessId As Long 'ULONG_PTR
End Type


Private Enum ImageSignatureTypes
   IMAGE_DOS_SIGNATURE = &H5A4D     ''// MZ
   IMAGE_OS2_SIGNATURE = &H454E     ''// NE
   IMAGE_OS2_SIGNATURE_LE = &H454C  ''// LE
   IMAGE_VXD_SIGNATURE = &H454C     ''// LE
   IMAGE_NT_SIGNATURE = &H4550      ''// PE00
End Enum

Private Type IMAGE_DOS_HEADER
    Magic    As Integer
    cblp     As Integer
    cp       As Integer
    crlc     As Integer
    cparhdr  As Integer
    minalloc As Integer
    maxalloc As Integer
    ss       As Integer
    sp       As Integer
    csum     As Integer
    ip       As Integer
    cs       As Integer
    lfarlc   As Integer
    ovno     As Integer
    res(3)   As Integer
    oemid    As Integer
    oeminfo  As Integer
    res2(9)  As Integer
    lfanew      As Long
End Type

Private Type IMAGE_FILE_HEADER
    Machine              As Integer
    NumberOfSections     As Integer
    TimeDateStamp        As Long
    PointerToSymbolTable As Long
    NumberOfSymbols      As Long
    SizeOfOtionalHeader  As Integer
    Characteristics      As Integer  '標誌Dll
End Type

Private Type IMAGE_DATA_DIRECTORY
    DataRVA     As Long
    DataSize    As Long
End Type

Private Type IMAGE_OPTIONAL_HEADER
    Magic             As Integer
    MajorLinkVer      As Byte
    MinorLinkVer      As Byte
    CodeSize          As Long
    InitDataSize      As Long
    unInitDataSize    As Long
    EntryPoint        As Long
    CodeBase          As Long
    DataBase          As Long
    ImageBase         As Long
    SectionAlignment  As Long
    FileAlignment     As Long
    MajorOSVer        As Integer
    MinorOSVer        As Integer
    MajorImageVer     As Integer
    MinorImageVer     As Integer
    MajorSSVer        As Integer
    MinorSSVer        As Integer
    Win32Ver          As Long
    ImageSize         As Long
    HeaderSize        As Long
    Checksum          As Long
    Subsystem         As Integer
    DLLChars          As Integer
    StackRes          As Long
    StackCommit       As Long
    HeapReserve       As Long
    HeapCommit        As Long
    LoaderFlags       As Long
    RVAsAndSizes      As Long
    DataEntries(15)   As IMAGE_DATA_DIRECTORY
End Type

Private Type IMAGE_NT_HEADERS
    Signature As Long
    FileHeader As IMAGE_FILE_HEADER
    OptionalHeader As IMAGE_OPTIONAL_HEADER
End Type

Private Type IMAGE_SECTION_HEADER
    SectionName(7)    As Byte
    Address           As Long
    VirtualAddress    As Long
    SizeOfData        As Long
    PData             As Long
    PReloc            As Long
    PLineNums         As Long
    RelocCount        As Integer
    LineCount         As Integer
    Characteristics   As Long
End Type

Private Type IMAGE_IMPORT_DESCRIPTOR
    Characteristics As Long
    TimeDateStamp As Long
    ForwarderChain As Long
    pName As Long
    FirstThunk As Long
End Type

Private Type IMAGE_EXPORT_DIRECTORY
    Characteristics As Long
    TimeDateStamp As Long
    MajorVersion As Integer
    MinorVersion As Integer
    pName As Long
    Base As Long
    NumberOfFunctions As Long
    NumberOfNames As Long
    AddressOfFunctions As Long
    AddressOfNames As Long
    AddressOfNameOrdinals As Long
End Type

Private Type IMAGE_IMPORT_BY_NAME
    Hint As Integer
    pName(259) As Byte
'    pName As Integer
End Type

Private Type IMAGE_THUNK_DATA
    AddressOfData As IMAGE_IMPORT_BY_NAME
End Type

'typedef struct _IMAGE_IMPORT_DESCRIPTOR {
'    union {
'        DWORD   Characteristics;            // 0 for terminating null import descriptor
'        DWORD   OriginalFirstThunk;         // RVA to original unbound IAT (PIMAGE_THUNK_DATA)
'    };
'    DWORD   TimeDateStamp;                  // 0 if not bound,
'                                            // -1 if bound, and real date/time stamp
'                                            //     in IMAGE_DIRECTORY_ENTRY_BOUND_IMPORT (new BIND)
'                                            // O.W. date/time stamp of DLL bound to (Old BIND)
'
'    DWORD   ForwarderChain;                 // -1 if no forwarders
'    DWORD   Name;
'    DWORD   FirstThunk;                     // RVA to IAT (if bound this IAT has actual addresses)
'} IMAGE_IMPORT_DESCRIPTOR;
'typedef IMAGE_IMPORT_DESCRIPTOR UNALIGNED *PIMAGE_IMPORT_DESCRIPTOR;

'typedef struct _IMAGE_EXPORT_DIRECTORY {
'    DWORD   Characteristics;
'    DWORD   TimeDateStamp;
'    WORD    MajorVersion;
'    WORD    MinorVersion;
'    DWORD   Name;
'    DWORD   Base;
'    DWORD   NumberOfFunctions;
'    DWORD   NumberOfNames;
'    DWORD   AddressOfFunctions;     // RVA from base of image
'    DWORD   AddressOfNames;         // RVA from base of image
'    DWORD   AddressOfNameOrdinals;  // RVA from base of image
'} IMAGE_EXPORT_DIRECTORY, *PIMAGE_EXPORT_DIRECTORY;

'typedef struct _IMAGE_IMPORT_BY_NAME {
'    WORD    Hint;
'    BYTE    Name[1];
'} IMAGE_IMPORT_BY_NAME, *PIMAGE_IMPORT_BY_NAME;

'typedef struct _IMAGE_THUNK_DATA32 {
'    union {
'        PBYTE  ForwarderString;
'        PDWORD Function;
'        DWORD Ordinal;
'        PIMAGE_IMPORT_BY_NAME  AddressOfData;
'    } u1;
'} IMAGE_THUNK_DATA32;
'typedef IMAGE_THUNK_DATA32 * PIMAGE_THUNK_DATA32;

'Private Type IMAGE_RESOURCE_DIR
'    Characteristics   As Long
'    TimeStamp         As Long
'    MajorVersion      As Integer
'    MinorVersion      As Integer
'    NamedEntries      As Integer
'    IDEntries         As Integer
'End Type
'
'Private Type RESOURCE_DIR_ENTRY
'    Name              As Long
'    offset            As Long
'End Type
'
'Private Type RESOURCE_DATA_ENTRY
'    offset            As Long
'    Size              As Long
'    CodePage          As Long
'    Reserved          As Long
'End Type
'
'Private Type IconDescriptor
'    ID       As Long
'    offset   As Long
'    Size     As Long
'End Type

Public Type ExportInfo
    strDllName As String
    strFuns() As String
End Type

Public Type ImportDetailInfo
    strDllName As String
    strFuns() As String
End Type

Public Type ImportInfo
    strExePath As String
    pDetailInfo() As ImportDetailInfo
End Type

Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)

Private Const FILE_SHARE_READ = &H1
'***************************************************************************************************************************************************
'用於讀寫文件函數
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
'Private Declare Function ReadFile Lib "kernel32" (ByVal lngFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, lpOverlapped As Any) As Long
'Private Declare Function WriteFile Lib "kernel32" (ByVal lngFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, lpOverlapped As Any) As Long
'Private Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
'Private Declare Function SetFilePointer Lib "kernel32" (ByVal lngFile As Long, ByVal lDistanceToMove As Long, lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long) As Long
'Private Declare Function GetFileSize Lib "kernel32" (ByVal hFile As Long, lpFileSizeHigh As Long) As Long
'***************************************************************************************************************************************************

Private mobjBaseAddress As Long '進程基地址

'判斷Nt系列函數是否調用成功
Private Function NT_SUCCESS(ByVal nStatus As Long) As Boolean
    NT_SUCCESS = (nStatus >= 0)
End Function


'獲取進程路徑
Public Function GetProcessPath(ByVal dwProcessId As Long) As String
    Dim ntStatus As Long
    Dim objBasic As PROCESS_BASIC_INFORMATION
    Dim objFlink As Long
    Dim objPEB As Long, objLdr As Long
    Dim bytName(260 * 2 - 1) As Byte
    Dim strModuleName As String, objName As Long
    Dim hProcess As Long

    hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or PROCESS_VM_READ, 0, dwProcessId)
    If hProcess = 0 Then
        Exit Function
    End If
    Dim lngRet As Long, lngReturn As Long
    ntStatus = NtQueryInformationProcess(hProcess, ProcessBasicInformation, VarPtr(objBasic), Len(objBasic), ByVal 0&)
    If (NT_SUCCESS(ntStatus)) Then
        objPEB = objBasic.PebBaseAddress
        lngRet = ReadProcessMemory(hProcess, ByVal objPEB + &HC, objLdr, 4, ByVal 0&)
        lngRet = ReadProcessMemory(hProcess, ByVal objLdr + &HC, objFlink, 4, ByVal 0&)
        lngRet = ReadProcessMemory(hProcess, ByVal objFlink + &H18, mobjBaseAddress, 4, ByVal 0&)
        If mobjBaseAddress > 0 Then
            lngRet = ReadProcessMemory(hProcess, ByVal objFlink + &H28, objName, 4, ByVal 0&)
            lngRet = ReadProcessMemory(hProcess, ByVal objName, bytName(0), 260 * 2, ByVal 0&)
            strModuleName = bytName
            strModuleName = Left(strModuleName & Chr(0), InStr(strModuleName & Chr(0), Chr(0)) - 1)
            GetProcessPath = strModuleName
        End If
    End If
    CloseHandle hProcess
End Function

Public Function GetImportTable(ByVal dwProcessId As Long, pImportInfo As ImportInfo) As Boolean
    Dim hProcess As Long
    Dim pNTHeader      As IMAGE_NT_HEADERS
    Dim strTmp As String
    Dim i As Integer, j As Integer
    Dim pImport As IMAGE_IMPORT_DESCRIPTOR
    Dim pTunk As IMAGE_THUNK_DATA, lngTunk As Long
    Dim bytBuffer(129) As Byte
    Dim pDosHear As IMAGE_DOS_HEADER
    Dim hAddr As Long
    hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or PROCESS_VM_READ, 0, dwProcessId)
    If (hProcess > 0) Then
        Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress, pDosHear, Len(pDosHear), ByVal 0&)
        Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pDosHear.lfanew, pNTHeader, Len(pNTHeader), ByVal 0&)
        If pNTHeader.OptionalHeader.DataEntries(1).DataRVA = 0 Then Exit Function
        Do While 1
            Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pNTHeader.OptionalHeader.DataEntries(1).DataRVA + j * Len(pImport), pImport, Len(pImport), ByVal 0&)
            If pImport.FirstThunk = 0 And pImport.Characteristics = 0 Then
                Exit Do
            End If
            Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pImport.pName, bytBuffer(0), 130, ByVal 0&)
            strTmp = StrConv(bytBuffer, vbUnicode)
            strTmp = Left(strTmp, InStr(strTmp, Chr(0)) - 1)
            Debug.Print "DLL模塊爲:" & strTmp
            ReDim Preserve pImportInfo.pDetailInfo(j)
            pImportInfo.pDetailInfo(j).strDllName = strTmp
            i = 0
            Do While 1
                If pImport.Characteristics <> 0 Then
                    Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pImport.Characteristics + i * 4, hAddr, 4, ByVal 0&)
                Else
                    Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pImport.FirstThunk + i * 4, hAddr, 4, ByVal 0&)
                End If
                ReDim Preserve pImportInfo.pDetailInfo(j).strFuns(i)
                If hAddr = 0 Then Exit Do
                If hAddr > 0 Then
                    Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + hAddr, pTunk, Len(pTunk), ByVal 0&)
                    strTmp = StrConv(pTunk.AddressOfData.pName, vbUnicode)
                    strTmp = Left(strTmp, InStr(strTmp, Chr(0)) - 1)
                    Debug.Print "       ----函數爲:" & strTmp
                    pImportInfo.pDetailInfo(j).strFuns(i) = strTmp
                Else
                    pImportInfo.pDetailInfo(j).strFuns(i) = ""
                End If
                strTmp = ""
                i = i + 1
            Loop
            j = j + 1
        Loop
    End If
    CloseHandle hProcess
    GetImportTable = True
End Function

Public Function GetExportTable(ByVal dwProcessId As Long, pExportInfo As ExportInfo) As Boolean
    Dim hProcess As Long
    Dim pNTHeader      As IMAGE_NT_HEADERS
    Dim strTmp As String
    Dim i As Integer
    Dim pExport As IMAGE_EXPORT_DIRECTORY
    Dim bytBuffer(129) As Byte
    Dim pDosHear As IMAGE_DOS_HEADER
    Dim pName As IMAGE_IMPORT_BY_NAME
    Dim hAddr As Long
    hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or PROCESS_VM_READ, 0, dwProcessId)
    If (hProcess > 0) Then
        Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress, pDosHear, Len(pDosHear), ByVal 0&)
        Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pDosHear.lfanew, pNTHeader, Len(pNTHeader), ByVal 0&)
        If pNTHeader.OptionalHeader.DataEntries(0).DataRVA = 0 Then Exit Function
        Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pNTHeader.OptionalHeader.DataEntries(0).DataRVA, pExport, Len(pExport), ByVal 0&)
        Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pExport.pName, bytBuffer(0), 130, ByVal 0&)
        strTmp = StrConv(bytBuffer, vbUnicode)
        strTmp = Left(strTmp, InStr(strTmp, Chr(0)) - 1)
        Debug.Print "DLL模塊爲:" & strTmp
        pExportInfo.strDllName = strTmp
        ReDim pExportInfo.strFuns(pExport.NumberOfFunctions - 1)
        For i = 0 To pExport.NumberOfFunctions - 1
            Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + pExport.AddressOfNames + i * 4, hAddr, 4, ByVal 0&)
            If hAddr = 0 Then Exit For
            Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + hAddr, hAddr, 4, ByVal 0&)
            If hAddr <> 0 Then
                Call ReadProcessMemory(hProcess, ByVal mobjBaseAddress + hAddr, bytBuffer(0), 130, ByVal 0&)
                strTmp = StrConv(bytBuffer, vbUnicode)
                strTmp = Left(strTmp, InStr(strTmp, Chr(0)) - 1)
                Debug.Print "       ----函數爲:" & strTmp
                pExportInfo.strFuns(i) = strTmp
            Else
                pExportInfo.strFuns(i) = ""
            End If
        Next

    End If
    CloseHandle hProcess
    GetExportTable = True
End Function 

發佈了81 篇原創文章 · 獲贊 4 · 訪問量 35萬+
發表評論
所有評論
還沒有人評論,想成為第一個評論的人麼? 請在上方評論欄輸入並且點擊發布.
相關文章