Search code examples
vb664-bitdll-injection

dll injector 32 bits and x64 dll file don't work in notepad.exe x64


I have a DLL injector compiled with Visual Basic 6 and I'm trying to inject my DLL (x64) on x64 notepad.exe, but nothing works.

I had searched on web about this and saw this:

[IMPORTANT: 32-BIT / 64-BIT]

This is a portability table:

  • 32bit program inject 32bit dll in a 32bit target
  • 32bit program inject 64bit dll in a 64bit target
  • 64bit program inject 32bit dll in a 32bit target
  • 64bit program inject 64bit dll in a 64bit target

If this is true, so my injector should is working.

Can someone help me please?

Code used:

Module1.bas

Option Explicit

Private Const INFINITE                  As Long = &HFFFF

Private Const TOKEN_ADJUST_PRIVILEGES   As Long = &H20
Private Const TOKEN_QUERY               As Long = &H8
Private Const SE_PRIVILEGE_ENABLED      As Long = &H2
Private Const ANYSIZE_ARRAY             As Long = 1

Private Const SE_DEBUG_NAME             As String = "SeDebugPrivilege"

Private Const PAGE_READWRITE            As Long = &H4
Private Const MEM_RELEASE               As Long = &H8000
Private Const MEM_COMMIT                As Long = &H1000

Private Const STANDARD_RIGHTS_REQUIRED  As Long = &HF0000
Private Const SYNCHRONIZE               As Long = &H100000
Private Const PROCESS_VM_OPERATION As Long = (&H8)
Private Const PROCESS_VM_WRITE As Long = (&H20)

Private Const TH32CS_SNAPPROCESS As Long = 2&


Private Const PROCESS_ALL_ACCESS        As Long = _
                                        (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or PROCESS_VM_WRITE Or PROCESS_VM_OPERATION Or &HFFF)

Private Type PROCESSENTRY32
    dwSize As Long
    cntUsage As Long
    th32ProcessID As Long
    th32DefaultHeapID As Long
    th32ModuleID As Long
    cntThreads As Long
    th32ParentProcessID As Long
    pcPriClassBase As Long
    dwFlags As Long
    szexeFile As String * 260
End Type

Private Type Luid
    lowpart                     As Long
    highpart                    As Long
End Type

Private Type LUID_AND_ATTRIBUTES
    pLuid                       As Luid
    Attributes                  As Long
End Type

Private Type TOKEN_PRIVILEGES
    PrivilegeCount              As Long
    Privileges(ANYSIZE_ARRAY)   As LUID_AND_ATTRIBUTES
End Type

Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Private Declare Function GetProcAddress Lib "kernel32" (ByVal hModule As Long, ByVal lpProcName As String) As Long
Private Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
Private Declare Function VirtualAllocEx Lib "kernel32" (ByVal hProcess As Long, ByVal lpAddress As Long, ByVal dwSize As Long, ByVal flAllocationType As Long, ByVal flProtect As Long) As Long
Private Declare Function WriteProcessMemory Lib "kernel32" (ByVal hProcess As Long, lpBaseAddress As Any, lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function CreateRemoteThread Lib "kernel32" (ByVal hProcess As Long, lpThreadAttributes As Long, ByVal dwStackSize As Long, lpStartAddress As Long, lpParameter As Any, ByVal dwCreationFlags As Long, lpThreadId As Long) As Long
Private Declare Function VirtualFreeEx Lib "kernel32.dll" (ByVal hProcess As Long, ByRef lpAddress As Any, ByRef dwSize As Long, ByVal dwFreeType As Long) As Long
Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal hHandle As Long, ByVal dwMilliseconds As Long) As Long
Private Declare Function OpenProcessToken Lib "advapi32" (ByVal ProcessHandle As Long, ByVal DesiredAccess As Long, TokenHandle As Long) As Long
Private Declare Function LookupPrivilegeValue Lib "advapi32" Alias "LookupPrivilegeValueA" (ByVal lpSystemName As String, ByVal lpName As String, lpLuid As Luid) As Long
Private Declare Function AdjustTokenPrivileges Lib "advapi32" (ByVal TokenHandle As Long, ByVal DisableAllPrivileges As Long, NewState As TOKEN_PRIVILEGES, ByVal BufferLength As Long, PreviousState As Any, ReturnLength As Long) As Long
Private Declare Function GetCurrentProcess Lib "kernel32" () As Long
Private Declare Function CreateToolhelp32Snapshot Lib "kernel32.dll" (ByVal lFlags As Long, lProcessID As Long) As Long
Private Declare Function ProcessFirst Lib "kernel32.dll" Alias "Process32First" (ByVal hSnapshot As Long, uProcess As PROCESSENTRY32) As Long
Private Declare Function ProcessNext Lib "kernel32.dll" Alias "Process32Next" (ByVal hSnapshot As Long, uProcess As PROCESSENTRY32) As Long


Public Function InjectByPID(ByVal sDllPath As String, ByVal lProcessID As Long) As Boolean
    Dim lProc As Long
    Dim lLibAdd As Long
    Dim lMem As Long
    Dim lRet As Long
    Dim lThread As Long

    On Local Error GoTo InjectByPID_Error

    '//Adjust token privileges to open system processes
    Call AdjustPrivileges(GetCurrentProcess)

    '// Open the process with all access
    lProc = OpenProcess(PROCESS_ALL_ACCESS, False, lProcessID)
    If lProc = 0 Then GoTo InjectByPID_Error

    '// Get the address of LoadLibrary
    lLibAdd = GetProcAddress(GetModuleHandle("kernel32.dll"), "LoadLibraryA")
    If lLibAdd = 0 Then GoTo InjectByPID_Error

    '// Allocate memory to hold the path to the Dll File in the process's memory
    lMem = VirtualAllocEx(lProc, 0, Len(sDllPath), MEM_COMMIT, PAGE_READWRITE)
    If lMem = 0 Then GoTo InjectByPID_Error

    '// Write the path to the Dll File in the location just created
    Call WriteProcessMemory(lProc, ByVal lMem, ByVal sDllPath, Len(sDllPath), lRet)
    If lRet = 0 Then GoTo InjectByPID_Error

    '// Create a remote thread that starts begins at the LoadLibrary function and _
     is passed are memory pointer
    lThread = CreateRemoteThread(lProc, ByVal 0, 0, ByVal lLibAdd, ByVal lMem, 0, 0&)
    If lThread = 0 Then GoTo InjectByPID_Error

    '// Wait for the thread to finish
    Call WaitForSingleObject(lThread, INFINITE)

    '// Free the memory created on the other process
    Call VirtualFreeEx(lProc, lMem, Len(sDllPath), MEM_RELEASE)

    '//Release the handle to the other process
    Call CloseHandle(lProc)

    InjectByPID = True

    On Error GoTo 0
    Exit Function

InjectByPID_Error:
    '// Free the memory created on the other process
    Call VirtualFreeEx(lProc, lMem, Len(sDllPath), MEM_RELEASE)
    '//Release the handle to the other process
    Call CloseHandle(lProc)
End Function

Public Function AdjustPrivileges(ByVal lProcessID As Long) As Boolean
    Dim lToken              As Long
    Dim tTOKEN_PRIVILEGES   As TOKEN_PRIVILEGES

    On Local Error GoTo AdjustPrivileges_Error

    If Not OpenProcessToken(lProcessID, TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY, lToken) = 0 Then
        With tTOKEN_PRIVILEGES
            If LookupPrivilegeValue(vbNullString, SE_DEBUG_NAME, .Privileges(0).pLuid) = 0 Then
                Exit Function
            End If
            .PrivilegeCount = 1
            .Privileges(0).Attributes = SE_PRIVILEGE_ENABLED
        End With
        If Not AdjustTokenPrivileges(lToken, 0, tTOKEN_PRIVILEGES, Len(tTOKEN_PRIVILEGES), 0&, 0&) = 0 Then
            AdjustPrivileges = True
        End If
    End If

    On Error GoTo 0
    Exit Function

AdjustPrivileges_Error:

End Function

'Get PID
Public Function whereISmyFUFUprocess(ByVal ProcessName As String) As Long
    Dim procSnapshot As Long
    Dim uProcess As PROCESSENTRY32
    Dim success As Long
    Dim ProcessId As Long
    Dim ProcessId_found As Boolean

    ProcessId_found = False
     
    procSnapshot = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0&)

    If procSnapshot = -1 Then Exit Function

    uProcess.dwSize = Len(uProcess)
    success = ProcessFirst(procSnapshot, uProcess)

    If success = 1 Then
        Do
            If LCase(VBA.Left$(uProcess.szexeFile, InStr(1, uProcess.szexeFile, Chr(0)) - 1)) = LCase(ProcessName) Then
                ProcessId = uProcess.th32ProcessID
                Debug.Print "First process found with PID: " & ProcessId
                    If ProcessId_found = True Then
                        Debug.Print "Second process found with PID: " & ProcessId
                        whereISmyFUFUprocess = ProcessId
                        Exit Do
                    End If
                  ProcessId_found = True
            End If
        Loop While ProcessNext(procSnapshot, uProcess)

    End If
     
    If whereISmyFUFUprocess = 0 Then
        whereISmyFUFUprocess = ProcessId
    End If
     
    Call CloseHandle(procSnapshot)
     
End Function

Form 1

Private Declare Sub Sleep Lib "kernel32.dll" (ByVal dwMilliseconds As Long)


Private Sub Command1_Click()

Dim PID As Long


' // Run Notepad
    Shell "notepad.exe", vbNormalFocus
    
    Sleep 1000
    
   PID = whereISmyFUFUprocess("notepad.exe")
   
   Sleep 1000
   
   InjectByPID "Project1.dll", PID

End Sub

Solution

  • OK. This may not be a complete/direct answer, as it only offers the directions you could take to solve your problem; also, I'm not versed in amd64 assembly code so I cannot help you on that.

    According to this article, for CreateRemoteThread() to work on 64-bit processes it needs to be called from another 64-bit process (NOTE: this answer is based on that assumption, which I didn't test).

    Knowing that, you have three (3) options:

    1. Use a x64 proxy to call CreateRemoteThread() on behalf of your x86/VB6 injector. Everything else is done in VB6, including the injection of bootstrapping code.

      • Requirements: a x64 executable built with your language and tools of choice (the proxy) and some hand-written, amd64 machine code to be called by the proxy (the bootstrapping code).
      • Difficulty: Challenging (unless writing & debugging hand-written amd64 assembly code is among your favorite pastimes)
      • Advantages: Relatively speaking, none.
      • Disadvantages: Two-part injector plus you need to write some amd64 machine code to inject your DLL. Unnecessary complex.
      • Pseudo code/program flow: (1) x86 injector acquires process ID, and then handle to target (x64) process; (2) x86 injector allocates a block of memory into the target (x64) process big enough to hold the path to the DLL being injected as well as the amd64 bootstrapping code responsible for loading that DLL into the remote process; (3) x86 injector writes to the allocated memory the DLL path and bootstrapping code; (4) x86 injector executes the x64 proxy and passes to it the duplicated process handle and the pointer to the allocated memory (offset to the entry point of the bootstrapping code if it doesn't start at the beginning of the allocated memory block); (5) x64 proxy calls CreateRemoteThread() with the process handle and entry point address of the bootstrapping code; (6) bootstrapping code gets module address of "kernel32.dll", proc. address of LoadLibraryW() and loads the DLL from the path provided; remote thread continues from there; (7) in the mean time, x64 proxy returns to the x86 injector result of the CreateRemoteThread() call.
    2. Well, if we're adding a dependency on a x64 proxy for our injection, why not have it do the whole DLL loading thing instead of some bootstrapping code. The x64 proxy is then also responsible (at least) of resolving the address of, and calling, LoadLibraryW() to load our DLL into the target process.

      The easiest path is to have the x86 injector find the process ID of the target, and when the target process is a 64-bit one, pass that process ID & path of the injected DLL to the x64 proxy so it does the injection instead.

      • Requirements: a x64 executable built with your language and tools of choice (the proxy).
      • Difficulty: Easy; just need knowledge of another language that builds for the x64 platform
      • Advantages: No more amd64 machine code to mess with.
      • Disadvantages: Still a two-part injector.
      • Pseudo code/program flow: (1) x86 injector acquires ID of target (x64) process; (2) x86 injector executes the x64 proxy and passes to it the target process ID and path of the DLL to be injected; (3) x64 proxy allocates memory within the target process, writes to it the DLL path, and then resolves & calls LoadLibraryW() through CreateRemoteThread() along with the address pointing to the DLL path we're injecting into the remote process; remote thread continues from there; (4) after the CreateRemoteThread() call (or before if something fails), the x64 proxy returns to the x86 injector the result of the call or any error it encountered.
    3. Make use of the Heaven's Gate (concept here; example of use here) to run amd64 code from within your x86, VB6-built injector.

      • Requirements: some (machine-compiled) amd64 code that will call GetModuleHandle(), LoadLibraryW() and CreateRemoteThread() (that the easy part...);

        ...and the whole lot of x86 code that we need to allocate within our process the space to put the amd64 machine-code bytes, fix the stack to load 64-bit binaries, load the amd64 build of kernel32.dll using LdrLoadDll() of ntdll.dll [[ either by hooking and patching RtlEqualUnicodeString() of ntdll.dll, so we can load "kernel32.dll" a second time but at another address, *or* by freeing the loaded, 32-bit kernel32.dll and replacing it with the 64-bit one while we're running the amd64 code ]], switch to 64-bit mode, and then cleanup and undo everything to get back safely into x86 mode.
      • Difficulty: Hard. Not sure everything can be done in VB6 (specifically, that stack-related part).
      • Advantages: One-part injector.
      • Disadvantages: If implemented well, none.
      • Pseudo code/program flow: You should read the article at http://rce.co/knockin-on-heavens-gate-dynamic-processor-mode-switching/ and look at the code (HeavenInjector) that has been written exactly for doing what you're trying to do, i.e. injecting libraries into 64-bit processes from a 32-bit one. Another example of implementation for this technique would be the WOW64Ext Library.

    Hopefully, after reading this you should have an idea of what to try next.