VB PE導出/輸入表演示(讀文件版)

frmMain.fm

VERSION 5.00
Begin VB.Form frmMain
   BorderStyle     =   1  'Fixed Single
   Caption         =   "PE導出/輸入表演示"
   ClientHeight    =   5655
   ClientLeft      =   45
   ClientTop       =   435
   ClientWidth     =   7890
   LinkTopic       =   "Form1"
   LockControls    =   -1  'True
   MaxButton       =   0   'False
   MinButton       =   0   'False
   ScaleHeight     =   5655
   ScaleWidth      =   7890
   StartUpPosition =   2  '屏幕中心
   Begin VB.CommandButton cmdPath
      Caption         =   "..."
      Height          =   315
      Left            =   6960
      TabIndex        =   1
      Top             =   80
      Width           =   885
   End
   Begin VB.TextBox txtPath
      Height          =   285
      Left            =   0
      TabIndex        =   0
      Top             =   90
      Width           =   6915
   End
   Begin VB.CommandButton cmdExit
      Cancel          =   -1  'True
      Caption         =   "退出(&C)"
      Height          =   375
      Left            =   6660
      TabIndex        =   6
      Top             =   5160
      Width           =   1185
   End
   Begin VB.CommandButton cmdImport
      Caption         =   "輸入表(&I)"
      Height          =   375
      Left            =   5460
      TabIndex        =   5
      Top             =   5160
      Width           =   1185
   End
   Begin VB.CommandButton cmdExport
      Caption         =   "導出表(&E)"
      Height          =   375
      Left            =   4260
      TabIndex        =   4
      Top             =   5160
      Width           =   1185
   End
   Begin VB.ListBox lstImport
      Height          =   4560
      Left            =   3960
      TabIndex        =   3
      Top             =   450
      Width           =   3915
   End
   Begin VB.ListBox lstExport
      Height          =   4560
      Left            =   0
      TabIndex        =   2
      Top             =   450
      Width           =   3915
   End
End
Attribute VB_Name = "frmMain"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = False
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
    If Trim(txtPath.Text) = "" Then
        MsgBox "請輸入文件路徑!!", vbCritical, "提示"
        txtPath.SetFocus
        Exit Sub
    End If
    If Dir(txtPath.Text, 1 Or 2 Or 4) = "" Then
        MsgBox "目標文件不存在!!", vbCritical, "提示"
        txtPath.SetFocus
        Exit Sub
    End If
    lstExport.Clear
    If GetExportTable(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
    If Trim(txtPath.Text) = "" Then
        MsgBox "請輸入文件路徑!!", vbCritical, "提示"
        txtPath.SetFocus
        Exit Sub
    End If
    If Dir(txtPath.Text, 1 Or 2 Or 4) = "" Then
        MsgBox "目標文件不存在!!", vbCritical, "提示"
        Exit Sub
    End If
    lstImport.Clear

    If GetImportTable(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 cmdPath_Click()
    txtPath.Text = ShowDialogFile(Me.hWnd, 1, "請選擇文件", "", "文件 (*.*)" & Chr(0) & "*.*", "", "")
End Sub

Private Sub Form_Initialize()
    InitCommonControls
End Sub

modBrowse.bas

Attribute VB_Name = "modBrowse"
Option Explicit
Private Const BIF_RETURNONLYFSDIRS = 1

Private Const BIF_DONTGOBELOWDOMAIN = 2

Private Const OFN_HIDEREADONLY = &H4

Private Const OFN_PATHMUSTEXIST = &H800

Private Const OFN_FILEMUSTEXIST = &H1000

Private Const OFN_OVERWRITEPROMPT = &H2

Private Declare Function SHBrowseForFolder Lib "shell32" (lpbi As BrowseInfo) As Long

Private Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As Long, ByVal lpBuffer As String) As Long

Private Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal lpString1 As String, ByVal lpString2 As String) As Long

Private Type BrowseInfo
    hWndOwner As Long
    pIDLRoot As Long
    pszDisplayName As Long
    lpszTitle As Long
    ulFlags  As Long
    lpfnCallback   As Long
    lParam   As Long
    iImage   As Long
End Type

Private Declare Function GetOpenFileName Lib "comdlg32.dll" Alias "GetOpenFileNameA" (pOpenfilename As OPENFILENAME) As Long

Private Declare Function GetSaveFileName Lib "comdlg32.dll" Alias "GetSaveFileNameA" (pOpenfilename As OPENFILENAME) As Long

Private Type OPENFILENAME
    lStructSize As Long
    hWnd As Long
    hInstance As Long
    lpstrFilter As String
    lpstrCustomFilter As String
    nMaxCustFilter As Long
    nFilterIndex As Long
    lpstrFile As String
    nMaxFile As Long
    lpstrFileTitle As String
    nMaxFileTitle As Long
    lpstrInitialDir As String
    lpstrTitle As String
    Flags As Long
    nFileOffset As Integer
    nFileExtension As Integer
    lpstrDefExt As String
    lCustData As Long
    lpfnHook As Long
    lpTemplateName As String
End Type

Public Declare Function MessageBox Lib "user32" Alias "MessageBoxA" (ByVal hWnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal wType As Long) As Long

Public Function GetFolderPath(ByVal objControl As TextBox, ByVal hWndOwner As Long)
    Dim lpIDList As Long
    Dim sBuffer As String
    Dim szTitle As String
    Dim tBrowseInfo As BrowseInfo

    szTitle = "請選擇源路徑:"
    With tBrowseInfo
        .hWndOwner = hWndOwner
        .lpszTitle = lstrcat(szTitle, "")
        .ulFlags = BIF_RETURNONLYFSDIRS + BIF_DONTGOBELOWDOMAIN
    End With

    lpIDList = SHBrowseForFolder(tBrowseInfo)

    If (lpIDList) Then
        sBuffer = Space(256)
        SHGetPathFromIDList lpIDList, sBuffer
        sBuffer = Left(sBuffer, InStr(sBuffer, vbNullChar) - 1)
        objControl.Text = sBuffer
    End If
End Function

Public Function ShowDialogFile(hWnd As Long, wMode As Integer, szDialogTitle As String, szFilename As String, szFilter As String, szDefDir As String, szDefExt As String) As String
    Dim x As Long, OFN As OPENFILENAME, szFile As String, szFileTitle As String
   
    OFN.lStructSize = Len(OFN)
    OFN.hWnd = hWnd
    OFN.lpstrTitle = szDialogTitle
    OFN.lpstrFile = szFilename & String$(250 - Len(szFilename), 0)
    OFN.nMaxFile = 255
    OFN.lpstrFileTitle = String$(255, 0)
    OFN.nMaxFileTitle = 255
    OFN.lpstrFilter = szFilter
    OFN.nFilterIndex = 1
    OFN.lpstrInitialDir = szDefDir
    OFN.lpstrDefExt = szDefExt

    If wMode = 1 Then
        OFN.Flags = OFN_HIDEREADONLY Or OFN_PATHMUSTEXIST Or OFN_FILEMUSTEXIST
        x = GetOpenFileName(OFN)
    Else
        OFN.Flags = OFN_HIDEREADONLY Or OFN_OVERWRITEPROMPT Or OFN_PATHMUSTEXIST
        x = GetSaveFileName(OFN)
    End If
   
    If x <> 0 Then
        If InStr(OFN.lpstrFile, Chr$(0)) > 0 Then
            szFile = Left$(OFN.lpstrFile, InStr(OFN.lpstrFile, Chr$(0)) - 1)
        End If
        ShowDialogFile = szFile
    Else
        ShowDialogFile = ""
    End If
   
End Function


modPEInfo.bas

Attribute VB_Name = "modPEInfo"

Option Explicit

Private Const FILE_MAP_READ = 4
Private Const PAGE_READONLY = &H2
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_DATA32
    AddressOfData As Long 'IMAGE_IMPORT_BY_NAME
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 Function RvaToOffset(pSections() As IMAGE_SECTION_HEADER, ByVal intSectionNumbers As Integer, ByVal dwRvaAddr As Long) As Long
    Dim i As Integer
    Dim dwAposRAV As Long
    Dim dwOffset As Long
    On Error GoTo ErrHandle
    For i = 0 To intSectionNumbers - 1
        If dwRvaAddr >= pSections(i).VirtualAddress And _
            dwRvaAddr < pSections(i).VirtualAddress + pSections(i).Address Then
            dwAposRAV = dwRvaAddr - pSections(i).VirtualAddress
            dwOffset = pSections(i).PData + dwAposRAV
            RvaToOffset = dwOffset
            Exit Function
        End If
    Next
ErrHandle:
    '這裏是溢出了設置爲0即可
    RvaToOffset = 0
End Function

'獲取RVA地址
Private Function OffsetToRva(pSections() As IMAGE_SECTION_HEADER, ByVal intSectionNumbers As Integer, ByVal dwOffset As Long) As Long
    Dim i As Integer
    Dim dwAposOffset As Long
    Dim dwRAV As Long
    On Error GoTo ErrHandle
    For i = 0 To intSectionNumbers - 1
        If dwOffset >= pSections(i).PData And _
            dwOffset < pSections(i).PData + pSections(i).SizeOfData Then
            dwAposRAV = dwOffset - pSections(i).PData
            dwRAV = pSections(i).VirtualAddress + dwAposRAV
            OffsetToRva = dwRAV
            Exit Function
        End If
    Next
ErrHandle:
    '這裏是溢出了設置爲0即可
    OffsetToRva = 0
End Function

Public Function GetImportTable(ByVal strFilePath As String, pImportInfo As ImportInfo) As Boolean
    Dim hFile 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_DATA32, lngTunk As Long
    Dim bytBuffer(129) As Byte
    Dim pDosHear As IMAGE_DOS_HEADER
    Dim pName As IMAGE_IMPORT_BY_NAME
    Dim hAddr As Long, dwReads As Long
    Dim pSections() As IMAGE_SECTION_HEADER
    hFile = CreateFile(ByVal strFilePath, ByVal &H80000000, FILE_SHARE_READ, ByVal 0&, ByVal 3, ByVal 0&, ByVal 0&)
    If (hFile > 0) Then
        SetFilePointer hFile, 0, ByVal 0&, 0
        ReadFile hFile, pDosHear, Len(pDosHear), dwReads, ByVal 0&
        If pDosHear.Magic <> &H5A4D Then
            Exit Function
        End If
        SetFilePointer hFile, pDosHear.lfanew, ByVal 0&, 0
        '獲取PE IMAGE_NT_HEADERS結構
        ReadFile hFile, pNTHeader, Len(pNTHeader), dwReads, ByVal 0&
        If pNTHeader.Signature <> IMAGE_NT_SIGNATURE Then
            Exit Function
        End If
        '檢查是否有輸入表結構
        If pNTHeader.OptionalHeader.DataEntries(1).DataRVA = 0 Then
            CloseHandle hFile
            Exit Function
        End If
        ReDim pSections(pNTHeader.FileHeader.NumberOfSections - 1)
        ReadFile hFile, pSections(0), Len(pSections(0)) * pNTHeader.FileHeader.NumberOfSections, dwReads, ByVal 0&

        i = 0
        Do While 1
            '獲取IMAGE_THUNK_DATA32結構在文件中的真實地址
            hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, pNTHeader.OptionalHeader.DataEntries(1).DataRVA + j * Len(pImport))
            SetFilePointer hFile, hAddr, ByVal 0&, 0
            ReadFile hFile, pImport, Len(pImport), dwReads, ByVal 0&
            If pImport.FirstThunk = 0 And pImport.Characteristics = 0 Then
                Exit Do
            End If
            '獲取模塊名稱
            hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, pImport.pName)
            SetFilePointer hFile, hAddr, ByVal 0&, 0
            ReadFile hFile, bytBuffer(0), 130, dwReads, 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
                    hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, pImport.Characteristics + i * 4)
                Else
                    hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, pImport.FirstThunk + i * 4)
                End If
                If hAddr = 0 Then Exit Do
                SetFilePointer hFile, hAddr, ByVal 0&, 0
                ReadFile hFile, pTunk, Len(pTunk), dwReads, ByVal 0&
                If pTunk.AddressOfData = 0 Then Exit Do
                hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, pTunk.AddressOfData)
                SetFilePointer hFile, hAddr, ByVal 0&, 0
                ReDim Preserve pImportInfo.pDetailInfo(j).strFuns(i)
                If hAddr <= 0 Then
                    Debug.Print "       ----函數爲:"
                    pImportInfo.pDetailInfo(j).strFuns(i) = ""
                Else
                    ReadFile hFile, pName, Len(pName), dwReads, ByVal 0&
                    strTmp = StrConv(pName.pName, vbUnicode)
                    strTmp = Left(strTmp, InStr(strTmp, Chr(0)) - 1)
                    Debug.Print "       ----函數爲:" & strTmp
                    pImportInfo.pDetailInfo(j).strFuns(i) = strTmp
                End If
                strTmp = ""
                i = i + 1
            Loop
            j = j + 1
        Loop
    End If
    CloseHandle hFile
    GetImportTable = True
End Function

Public Function GetExportTable(ByVal strFilePath As String, pExportInfo As ExportInfo) As Boolean
    Dim hFile 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 hAddr As Long, dwReads As Long
    Dim pSections() As IMAGE_SECTION_HEADER
    hFile = CreateFile(ByVal strFilePath, ByVal &H80000000, FILE_SHARE_READ, ByVal 0&, ByVal 3, ByVal 0&, ByVal 0&)
    If (hFile > 0) Then
        SetFilePointer hFile, 0, ByVal 0&, 0
        ReadFile hFile, pDosHear, Len(pDosHear), dwReads, ByVal 0&
        If pDosHear.Magic <> &H5A4D Then
            Exit Function
        End If
        SetFilePointer hFile, pDosHear.lfanew, ByVal 0&, 0
        '獲取PE IMAGE_NT_HEADERS結構
        ReadFile hFile, pNTHeader, Len(pNTHeader), dwReads, ByVal 0&
        If pNTHeader.Signature <> IMAGE_NT_SIGNATURE Then
            Exit Function
        End If
        '檢查是否有輸入表結構
        If pNTHeader.OptionalHeader.DataEntries(0).DataRVA = 0 Then
            CloseHandle hFile
            Exit Function
        End If
        ReDim pSections(pNTHeader.FileHeader.NumberOfSections - 1)
        ReadFile hFile, pSections(0), Len(pSections(0)) * pNTHeader.FileHeader.NumberOfSections, dwReads, ByVal 0&
        For i = 0 To pNTHeader.FileHeader.NumberOfSections - 1
            '獲取基數用於計算RAV和真實文件地址
            If pSections(i).PData <> 0 And pSections(i).VirtualAddress <> 0 Then
                mdwVAddr = pSections(i).VirtualAddress
                mdwPAddr = pSections(i).PData
                Exit For
            End If
        Next
        '如果基數中有一個不爲0就退出
        If mdwVAddr = 0 Or mdwPAddr = 0 Then
            CloseHandle hFile
            Exit Function
        End If
        '獲取導出表文件地址
        hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, pNTHeader.OptionalHeader.DataEntries(0).DataRVA)
        SetFilePointer hFile, hAddr, ByVal 0&, 0
        '讀取導出表
        ReadFile hFile, pExport, Len(pExport), dwReads, ByVal 0&
        '獲取模塊名稱文件地址
        hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, pExport.pName)
        SetFilePointer hFile, hAddr, ByVal 0&, 0
        '獲取模塊名稱
        ReadFile hFile, bytBuffer(0), 130, dwReads, 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
            hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, pExport.AddressOfNames + i * 4)
            SetFilePointer hFile, hAddr, ByVal 0&, 0
            ReadFile hFile, hAddr, 4, dwReads, ByVal 0&
            hAddr = RvaToOffset(pSections, pNTHeader.FileHeader.NumberOfSections, hAddr)
            SetFilePointer hFile, hAddr, ByVal 0&, 0
            If hAddr <> 0 Then
                ReadFile hFile, bytBuffer(0), 130, dwReads, 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
            strTmp = ""
        Next

    End If
    CloseHandle hFile
    GetExportTable = True
End Function

發表評論
所有評論
還沒有人評論,想成為第一個評論的人麼? 請在上方評論欄輸入並且點擊發布.
相關文章