Jaafar Tribak
Well-known Member
- Joined
- Dec 5, 2002
- Messages
- 9,797
- Office Version
- 2016
- Platform
- Windows
Spurred by the question asked recently by @audeser in this post, I took a deeper look and I arrived at the following little project which, as the title of the current thread suggests, it allows you to list all the functions exported by standard windows DLLs . This little vba project mimics to a certain extent what dll viewer softwares do (such as Dependency Walker, Dll Viewer, PE File Browser etc ). The code is entirely vba based + a few api calls. No third party dependencies required.
I hope this can be useful for someone.
DLLExportViewer.xlsm
1- API code in a Standard Module:
2- Code Usage example ( as per the workbook example)
Tested on Excel 2007 Win7 x32bit and Excel 2016 x64bit Win10 x64bit.
I hope this can be useful for someone.
DLLExportViewer.xlsm
1- API code in a Standard Module:
VBA Code:
Option Explicit
#If Win64 Then
Private Const NULL_PTR = 0^
Private Const PTR_SIZE = 8&
#Else
Private Const NULL_PTR = 0&
Private Const PTR_SIZE = 4&
#End If
#If VBA7 Then
Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
Private Declare PtrSafe Function MapAndLoad Lib "Imagehlp.dll" (ByVal ImageName As String, ByVal DLLPath As String, LoadedImage As LOADED_IMAGE, ByVal DotDLL As Long, ByVal ReadOnly As Long) As Long
Private Declare PtrSafe Function UnMapAndLoad Lib "Imagehlp.dll" (LoadedImage As LOADED_IMAGE) As Long
Private Declare PtrSafe Function ImageRvaToVa Lib "Imagehlp.dll" (ByVal NTHeaders As LongPtr, ByVal Base As LongPtr, ByVal RVA As LongPtr, ByVal LastRvaSection As LongPtr) As LongPtr
Private Declare PtrSafe Function lstrlenW Lib "kernel32" (ByVal lpsz As LongPtr) As Long
Private Declare PtrSafe Function GetModuleFileName Lib "kernel32" Alias "GetModuleFileNameA" (ByVal hModule As LongPtr, ByVal lpFileName As String, ByVal nSize As Long) As Long
Private Declare PtrSafe Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As LongPtr
Private Declare PtrSafe Function GetProcAddressByOrdinal Lib "kernel32" Alias "GetProcAddress" (ByVal hModule As LongPtr, ByVal nOrdinal As Long) As LongPtr
Private Declare PtrSafe Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As LongPtr
Private Declare PtrSafe Function FreeLibrary Lib "kernel32" (ByVal hLibModule As LongPtr) As Long
#Else
Private Enum LongPtr
[_]
End Enum
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
Private Declare Function MapAndLoad Lib "Imagehlp.dll" (ByVal ImageName As String, ByVal DLLPath As String, LoadedImage As LOADED_IMAGE, ByVal DotDLL As Long, ByVal ReadOnly As Long) As Long
Private Declare Function UnMapAndLoad Lib "Imagehlp.dll" (LoadedImage As LOADED_IMAGE) As Long
Private Declare Function ImageRvaToVa Lib "Imagehlp.dll" (ByVal NTHeaders As LongPtr, ByVal Base As LongPtr, ByVal RVA As LongPtr, ByVal LastRvaSection As LongPtr) As LongPtr
Private Declare Function lstrlenW Lib "kernel32" (ByVal lpsz As LongPtr) As Long
Private Declare Function GetModuleFileName Lib "kernel32" Alias "GetModuleFileNameA" (ByVal hModule As LongPtr, ByVal lpFileName As String, ByVal nSize As Long) As Long
Private Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As LongPtr
Private Declare Function GetProcAddressByOrdinal Lib "kernel32" Alias "GetProcAddress" (ByVal hModule As LongPtr, ByVal nOrdinal As Long) As LongPtr
Private Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As LongPtr
Private Declare Function FreeLibrary Lib "kernel32" (ByVal hLibModule As LongPtr) As Long
#End If
Private Type LIST_ENTRY
FLink As LongPtr
Blink As LongPtr
End Type
Private Type IMAGE_EXPORT_DIRECTORY
Characteristics As Long
TimeDateStamp As Long
MajorVersion As Integer
MinorVersion As Integer
Name As Long
Base As Long
NumberOfFunctions As Long
NumberOfNames As Long
AddressOfFunctions As Long
AddressOfNames As Long
AddressOfNameOrdinals As Long
End Type
Private Type LOADED_IMAGE
ModuleName As LongPtr
hFile As LongPtr
MappedAddress As LongPtr
FileHeader As LongPtr
LastRvaSection As LongPtr
NumberOfSections As Long
Sections As LongPtr
Characteristics As Long
fSystemImage As Byte
fDOSImage As Byte
Links As LIST_ENTRY
SizeOfImage As Long
End Type
Private Type IMAGE_FILE_HEADER
Machine As Integer
NumberOfSections As Integer
TimeDateStamp As LongPtr
PointerToSymbolTable As LongPtr
NumberOfSymbols As Long
SizeOfOptionalHeader As Integer
Characteristics As Integer
End Type
Private Type IMAGE_DATA_DIRECTORY
RVA As Long
Size As Long
End Type
Private Const IMAGE_NUMBEROF_DIRECTORY_ENTRIES = 16&
Private Type IMAGE_OPTIONAL_HEADER32
Magic As Integer
MajorLinkerVersion As Byte
MinorLinkerVersion As Byte
SizeOfCode As Long
SizeOfInitializedData As Long
SizeOfUninitializedData As Long
AddressOfEntryPoint As Long
BaseOfCode As Long
BaseOfData As Long
ImageBase As Long
SectionAlignment As Long
FileAlignment As Long
MajorOperatingSystemVersion As Integer
MinorOperatingSystemVersion As Integer
MajorImageVersion As Integer
MinorImageVersion As Integer
MajorSubsystemVersion As Integer
MinorSubsystemVersion As Integer
Win32VersionValue As Long
SizeOfImage As Long
SizeOfHeaders As Long
CheckSum As Long
Subsystem As Integer
DllCharacteristics As Integer
SizeOfStackReserve As Long
SizeOfStackCommit As Long
SizeOfHeapReserve As Long
SizeOfHeapCommit As Long
LoaderFlags As Long
NumberOfRvaAndSizes As Long
DataDirectory(0 To IMAGE_NUMBEROF_DIRECTORY_ENTRIES) As IMAGE_DATA_DIRECTORY
End Type
Private Type IMAGE_NT_HEADER '256 bytes.
Signature As Long
FileHeader As IMAGE_FILE_HEADER
OptionalHeader As IMAGE_OPTIONAL_HEADER32
End Type
Public Function GetPEBinaryExports(ByVal sFile As String) As Variant()
Const IMAGE_DIRECTORY_ENTRY_EXPORT = 0&
Dim uLoadedImage As LOADED_IMAGE
Dim uImageHeader As IMAGE_NT_HEADER
Dim uIEXPDIR As IMAGE_EXPORT_DIRECTORY
Dim hMod As LongPtr
Dim lRvaExportDirTable As LongPtr
Dim lVaExportDirTable As LongPtr
Dim lExportNamePointerTableVA As LongPtr
Dim lNextAddr As LongPtr
Dim lRVAFuncAddr As LongPtr
Dim pAddrOfOrdinalsArray As LongPtr
Dim pAddrOfFuncsArray As LongPtr
Dim lFirstOrdinal As Long
Dim lNumOfExports As Long
Dim lOrdinalIndex As Integer
Dim sExportName As String
Dim lRet As Long, i As Long
hMod = LoadLibrary(sFile)
If hMod = NULL_PTR Then
MsgBox "Module not loaded."
Exit Function
End If
If Len(Dir(sFile)) = 0 Then
sFile = ModuleFileName(sFile)
End If
lRet = MapAndLoad(sFile, "", uLoadedImage, True, True)
If lRet = 0& Then
MsgBox "MapAndLoad failed."
Exit Function
End If
With uLoadedImage
Call CopyMemory(ByVal VarPtr(uImageHeader), ByVal .FileHeader, LenB(uImageHeader))
lRvaExportDirTable = uImageHeader.OptionalHeader.DataDirectory(IMAGE_DIRECTORY_ENTRY_EXPORT).RVA
If lRvaExportDirTable = 0& Then
MsgBox "No export directory."
GoTo Xit
End If
lVaExportDirTable = ImageRvaToVa(.FileHeader, .MappedAddress, lRvaExportDirTable, NULL_PTR)
Call CopyMemory(ByVal VarPtr(uIEXPDIR), ByVal lVaExportDirTable, LenB(uIEXPDIR))
lNumOfExports = uIEXPDIR.NumberOfNames
If lNumOfExports Then
ReDim vExportsInfoArray(1 To lNumOfExports, 1 To 6) As Variant
lFirstOrdinal = uIEXPDIR.Base
lExportNamePointerTableVA = ImageRvaToVa(.FileHeader, .MappedAddress, uIEXPDIR.AddressOfNames, NULL_PTR)
Call CopyMemory(lNextAddr, ByVal lExportNamePointerTableVA, PTR_SIZE)
pAddrOfOrdinalsArray = hMod + uIEXPDIR.AddressOfNameOrdinals
pAddrOfFuncsArray = hMod + uIEXPDIR.AddressOfFunctions
For i = 0& To lNumOfExports - 1&
lNextAddr = ImageRvaToVa(.FileHeader, .MappedAddress, lNextAddr, NULL_PTR)
sExportName = LPSTRtoBSTR(lNextAddr)
Call CopyMemory(lOrdinalIndex, ByVal pAddrOfOrdinalsArray + (i * 2&), PTR_SIZE)
Call CopyMemory(lRVAFuncAddr, ByVal pAddrOfFuncsArray + (lOrdinalIndex * 4&), 4&)
vExportsInfoArray(i + 1&, 1&) = i + 1&
vExportsInfoArray(i + 1&, 2&) = sExportName
vExportsInfoArray(i + 1&, 3&) = lOrdinalIndex + lFirstOrdinal
vExportsInfoArray(i + 1&, 4&) = "&H" & Right(String$(8, "0") & Hex$(lRVAFuncAddr), 8&)
#If Win64 Then
vExportsInfoArray(i + 1&, 5&) = "&H" & Right(String$(16&, "0") & Hex$(GetProcAddressByOrdinal(hMod, lOrdinalIndex + lFirstOrdinal)), 16&)
#Else
vExportsInfoArray(i + 1&, 5&) = "&H" & Right(String$(8&, "0") & Hex$(GetProcAddressByOrdinal(hMod, lOrdinalIndex + lFirstOrdinal)), 8&)
#End If
vExportsInfoArray(i + 1&, 6&) = sFile
GetPEBinaryExports = vExportsInfoArray
lExportNamePointerTableVA = lExportNamePointerTableVA + 4&
Call CopyMemory(lNextAddr, ByVal lExportNamePointerTableVA, PTR_SIZE)
Next
Else
MsgBox sFile & " has no export functions."
End If
End With
Xit:
If hMod Then
Call FreeLibrary(hMod)
End If
lRet = UnMapAndLoad(uLoadedImage)
If lRet = 0& Then
MsgBox "UnMapAndLoad failed."
End If
End Function
Private Function LPSTRtoBSTR(ByVal lpString As LongPtr) As String
Dim lStrLen As Long
Dim lPosNullChar As Long
lStrLen = lstrlenW(lpString)
LPSTRtoBSTR = String$(lStrLen, 0&)
Call CopyMemory(ByVal StrPtr(LPSTRtoBSTR), ByVal lpString, lStrLen)
LPSTRtoBSTR = StrConv(LPSTRtoBSTR, vbUnicode)
lPosNullChar = InStr(1&, LPSTRtoBSTR, Chr(0&), vbBinaryCompare)
If lPosNullChar > 0& Then
LPSTRtoBSTR = Left$(LPSTRtoBSTR, lPosNullChar - 1&)
End If
End Function
Private Function ModuleFileName(ByVal ModuleName As String) As String
Dim sBuffer As String, lRet As Long, hMod As LongPtr
hMod = GetModuleHandle(ModuleName)
If hMod <> GetModuleHandle("") Then
sBuffer = Space(256)
lRet = GetModuleFileName(hMod, sBuffer, Len(sBuffer))
ModuleFileName = Left(sBuffer, lRet)
End If
End Function
2- Code Usage example ( as per the workbook example)
VBA Code:
Option Explicit
Private Sub ComboBox1_Change()
DllExportsInfoToSheet Me.ComboBox1
End Sub
Private Sub ComboBox2_Change()
DllExportsInfoToSheet Me.ComboBox2
End Sub
Private Sub DllExportsInfoToSheet(ByVal Combo As ComboBox)
Dim vExportsInfoArray() As Variant
Dim sFileName As String
sFileName = Combo.Text
vExportsInfoArray = GetPEBinaryExports(sFileName)
Range("A4:F3000, A2").ClearContents
If Not (Not vExportsInfoArray) Then
Range("A2") = "Exports Found" & vbNewLine & UBound(vExportsInfoArray)
Range("A4:F" & UBound(vExportsInfoArray, 1) + 3) = vExportsInfoArray
Range("A4:F" & UBound(vExportsInfoArray, 1) + 3).EntireColumn.AutoFit
End If
End Sub
Tested on Excel 2007 Win7 x32bit and Excel 2016 x64bit Win10 x64bit.
Last edited: