Link to home
Start Free TrialLog in
Avatar of ITKnightMare
ITKnightMare

asked on

Loading EXE Into Memory Then Jumping to It

How would you load an EXE into Memory, then Jump to the Memory?

I am trying to protect this EXE which is the client to a game but I don't have the source code to the exe.

I want to MAKE SURE nobody is connecting to the server with an edited client.


I thought of couple different ways of doing this, but none of my ways seem to be efficient.

Finally I thought of, why not embedd the EXE into my EXE, then run it through MD5 or something.  And fire it up if it wasn't edited.

However, here's where my problem began.  To run the exe, I have to write it to a temp file first.  I can't do that because then people
will just run the temp file and connect to the server.  So I though or running the embedded EXE without writing it to file.

Only only way of doing that is if I Loaded the EXE into memory and jumped to the memory.  I heard of this being done in 8086 Assembly or
something like that which I have no clue about.

How would I do this in VB6?  Or VB.NET is also fine, I am familiar with both.
Avatar of cool12399
cool12399

Hi,

It's kind of messy, you have to use a few API calls (VB wasn't designed to allow you to do that), and I believe it would be running in 'protected' memory.

Basically you'd need to use VarPtr, StrPtr, and ObjPtr functions, along with the AddressOf.
Take a look here for more information:
http://support.microsoft.com/kb/q199824/

Is your client written in VB6? Smartest thing would be to simply make that an additional form. Otherwise how are you going to embed it (easily) -- are you creating a byte array with the info?
ANyways, after you've got the address of your memory location, I believe you'd simply use the 'call' procedure, and/or you could try using a callback procedure (in which case you'd need to use C++ as well).

>>if I Loaded the EXE into memory and jumped to the memory
Keyword being "I". You'll be bypassing the windows-loader and will have to do everything it does to accomplish this. Something along the lines of retrieving the PE's header, determining the sections (this includes imported functions which need to be resolved completely.. ie: one function may use a function from another) to map into memory from that (and at which offsets). I'm not sure how to go about executing mapped memory, however. A bit far-fetched to investigate!

I do believe some games already implement this, though. Possibly "Continuum" which I think is developed by a lead-programmer for Kazaa. This has been done to prevent "cheating" from debuggers (memory alteration).
Avatar of ITKnightMare

ASKER

I'll give 500 more points.

That's 1000 points to someone who can show me a VB code that protects an EXE.
>>It's kind of messy, you have to use a few API calls (VB wasn't designed to allow you to do that), and I believe it would be running in 'protected' >>memory.

cool12399, What are those API calls you have mentioned?

Search everything about the API RtlMoveMemory (-:

>>I'll give 500 more points.
You can only offer a maximum of 500 points for a single question.

As for this question, if there isn't already an example, I doubt anybody would want to try to provide one from scratch because it'd take a very long time. If you're serious about this, here are articles of the PE files.

"An In-Depth Look into the Win32 Portable Executable File Format"
http://msdn.microsoft.com/msdnmag/issues/02/02/PE/default.aspx

"An In-Depth Look into the Win32 Portable Executable File Format, Part 2"
http://msdn.microsoft.com/msdnmag/issues/02/03/PE2/default.aspx
@zzzzzooc:
>> You can only offer a maximum of 500 points for a single question.
Umm... no; as long as I ask another valid question within VB6 parameters, and award that question to the person of my choosing... I am sure you got my drift.

As for your "PE" links... *sigh*, Folsk as I satated above many many times... I am not looking for links! I want CODE! The links are just BS mainly (no offense) and even EE's ToS states that, if you want to be fully recognized, don't provide links and run away. Provide CODE.

So folks... please! I'm sure thre is SOMEONE out there that knows what the heck I'm talking about! I mean, infogaters seems to be the closest.

@infogaters:

Bro I coudln't find it. Would you mind locating this info and posting it here please?

Thx,
>>I am not looking for links! I want CODE!
As I said before, you probably won't get any direct solution for this unless one is already done (ie: must be linked to). Undertaking a project like this is very difficult if you lack a proper understanding of how PE files are structured on disk and loaded into memory (by the Windows loader). It'd still be a large project if you DID have a good understanding of them.

>>if you want to be fully recognized, don't provide links and run away
I, and probably others, don't care about recognition. I try to help and since I doubted nobody would provide any for this topic, I decided to point you in the correct direction. Either way, it's apparent you don't understand the complexity of what you're asking for.
....

@zzzzzooc:
I am fully aware of the complexity of this project, which is why I specifically chose to ask it here, "The EXPERTS' EXCHANGE" as in the "BEST IN THE FIELD'S TRADE POST"... I would expect ppl to post links and run in different forums/mediums; but not here!

@All:

For now I temp. solved my issue with using ACProtect. I encyrpted the EXE and updated various strings to change the EXE's format completely. It seems to be working, but either way I am going to still need an answe rot this pretty soon. At this point, I am now even willing to PAY REAL MONEY (USD) for help.

If you are willing, please contact me at : knightmare (at) gmail (dot) com

P.S. Admin/mod, I am fully aware of the ToS stating no posting of email addresses, but as various users have pointed out this is necessary to get the help I have been seeking. Please do not remove/edit my post. Thank you!
>>I would expect ppl to post links and run in different forums/mediums; but not here!
The time people offer to help is their own and is just for the sake of helping people. Large projects like this would require too much time for most to bother with (as you can tell from the number of different people contributing to this).

If you need a starting point though, the below should help. It's partially based on a delphi example and several articles. It IS NOT FUNCTIONAL but should give a general layout of what to do. If you note problems with ProcessImports(), the .VirtualAddress refers to the file-offset with I believe the sectionalignments pre-calculated. So to get the correct offset in some PEs, you need to calculate the byte-difference from all of the alignments (should be sectionalignment but could be filealignment.. didn't look into it). Also, some memory may be incorrectly written and some RVAs may require adjusting. Overall, it's a bit complicated for me to debug. ;-)


Form1:
--------------------
Option Explicit

Private Type IMAGE_FILE_HEADER
    Machine As Integer
    NumberOfSections As Integer
    TimeDateStamp As Long
    PointerToSymbolTable As Long
    NumberOfSymbols As Long
    SizeOfOptionalHeader As Integer
    Characteristics As Integer
End Type

Private Type IMAGE_DATA_DIRECTORY
    VirtualAddress As Long
    Size As Long
End Type

Private Type IMAGE_OPTIONAL_HEADER
    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(15) As IMAGE_DATA_DIRECTORY
End Type

Private Type IMAGE_SECTION_HEADER
    Name1(7) As Byte
    VirtualSize As Long
    VirtualAddress As Long
    SizeOfRawData As Long
    PointerToRawData As Long
    PointerToRelocations As Long
    PointerToLinenumbers As Long
    NumberOfRelocations As Integer
    NumberOfLinenumbers As Integer
    Characteristics As Long
End Type

Private Type IMAGE_IMPORT_DESCRIPTOR
    OriginalFirstThunk  As Long
    TimeDateStamp  As Long
    ForwarderChain  As Long
    Name1  As Long
    FirstThunk  As Long
End Type

'Private Type IMAGE_IMPORT_BY_NAME
'    Hint(1) As Byte
'    Name1 As String * 255 'not proper!!
'End Type

Private Type IMAGE_THUNK_DATA
    Ptr As Long
End Type

Private Type IMAGE_NT_HEADERS32
    Signature As String * 4
    FileHeader As IMAGE_FILE_HEADER
    OptionalHeader As IMAGE_OPTIONAL_HEADER
End Type

Private Const IMAGE_DOS_SIGNATURE   As String = "MZ"
Private Const IMAGE_NT_SIGNATURE    As String = "PE"

Private Const IMAGE_SCN_MEM_NOT_CACHED As Long = &H4000000
Private Const IMAGE_SCN_MEM_EXECUTE As Long = &H20000000
Private Const IMAGE_SCN_MEM_READ As Long = &H40000000
Private Const IMAGE_SCN_MEM_WRITE As Long = &H80000000
Private Const IMAGE_SCN_CNT_CODE As Long = &H20

Private Const MEM_COMMIT As Long = &H1000
Private Const MEM_RESERVE As Long = &H2000

Private Const PAGE_NOCACHE As Long = &H200
Private Const PAGE_EXECUTE_READWRITE As Long = &H40
Private Const PAGE_EXECUTE_WRITECOPY As Long = &H80
Private Const PAGE_EXECUTE_READ As Long = &H20
Private Const PAGE_EXECUTE As Long = &H10
Private Const PAGE_READONLY As Long = &H2
Private Const PAGE_WRITECOPY As Long = &H8
Private Const PAGE_NOACCESS As Long = &H1
Private Const PAGE_READWRITE As Long = &H4

Private Const PROCESS_VM_OPERATION As Long = (&H8)
Private Const PROCESS_VM_READ As Long = (&H10)
Private Const PROCESS_VM_WRITE As Long = (&H20)


'Private Const IMAGE_ORDINAL_FLAG32 = &H80000000

Private Declare Function VirtualAllocEx Lib "kernel32.dll" (ByVal hProcess As Long, ByRef lpAddress As Any, ByRef dwSize As Long, ByVal flAllocationType As Long, ByVal flProtect 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 VirtualProtectEx Lib "kernel32.dll" (ByVal hProcess As Long, ByRef lpAddress As Any, ByVal dwSize As Long, ByVal flNewProtect As Long, ByRef lpflOldProtect As Long) As Long
Private Declare Function GetCurrentProcessId Lib "kernel32" () As Long
Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
Private Declare Function GetProcAddress Lib "kernel32" (ByVal hModule As Long, ByVal lpProcName As String) 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 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 CreateThread Lib "kernel32" (lpThreadAttributes As Any, ByVal dwStackSize As Long, ByVal lpStartAddress As Long, lpParameter As Any, ByVal dwCreationFlags As Long, lpThreadID As Long) As Long

Private hFile As Integer
Private hProcess As Long

Private ImageNtHeaders  As IMAGE_NT_HEADERS32
Private ImageNtHeadersOffset As Long
Private ImageBase As Long
Private ImageSectionBase As Long
Private Sub Form_Load()
    Call Load("c:\test2.exe")
End Sub
Private Function Validate() As Long
    Dim bytHdrDOS(1) As Byte, lngTemp As Long
    Get #hFile, 1, bytHdrDOS
    If StrConv(bytHdrDOS, vbUnicode) = IMAGE_DOS_SIGNATURE Then
        Get #hFile, 60 + 1, lngTemp
        Get #hFile, lngTemp + 1, ImageNtHeaders
        If Left$(ImageNtHeaders.Signature, 2) = IMAGE_NT_SIGNATURE Then
            Validate = lngTemp
        End If
    End If
End Function
Private Function Load(ByVal strFile As String) As Boolean
    Dim lngOldProtect As Long
    If (strFile = vbNullString) Or (Dir$(strFile) = vbNullString) Then
        Exit Function
    End If
    hFile = FreeFile
    Open strFile For Binary Access Read As #hFile
        ImageNtHeadersOffset = Validate
        If ImageNtHeadersOffset <> 0 Then
            hProcess = OpenProcess(PROCESS_VM_OPERATION Or PROCESS_VM_READ Or PROCESS_VM_WRITE, False, GetCurrentProcessId)
            ImageBase = VirtualAllocEx(hProcess, ByVal 0, ByVal CLng(ImageNtHeaders.OptionalHeader.SizeOfImage), MEM_RESERVE, PAGE_NOACCESS)
            ImageSectionBase = VirtualAllocEx(hProcess, ByVal ImageBase, ByVal CLng(ImageNtHeaders.OptionalHeader.SizeOfHeaders), MEM_COMMIT, PAGE_READWRITE)
            Call WriteProcessMemory(hProcess, ByVal ImageSectionBase, ImageNtHeaders, ByVal CLng(ImageNtHeaders.OptionalHeader.SizeOfHeaders), ByVal 0)
            Call VirtualProtectEx(hProcess, ByVal ImageSectionBase, ByVal CLng(ImageNtHeaders.OptionalHeader.SizeOfHeaders), PAGE_READONLY, lngOldProtect)
            Call ProcessSections
            Call ProcessImports
            '------------->
            'Dim t As Long
            'Call CreateThread(ByVal 0&, ByVal 0&, ByVal CLng(ImageBase + ImageNtHeaders.OptionalHeader.AddressOfEntryPoint), ByVal 0&, ByVal 0&, t)
            '<-------------
        End If
    Close #hFile
End Function
Private Sub ProcessImports()
    Dim ImageImports() As IMAGE_IMPORT_DESCRIPTOR
    Dim ImageThunks1() As IMAGE_THUNK_DATA
    Dim ImageThunks2() As IMAGE_THUNK_DATA
    Dim intCnt As Integer
    Dim lngLoop As Long
    Dim lngOffset As Long
    Dim hLib As Long
    Dim hProc As Long
    Dim intOrd As Integer
    With ImageNtHeaders.OptionalHeader.DataDirectory(1)
        ReDim ImageImports((.Size / Len(ImageImports(0))) - 1)
        Get #hFile, .VirtualAddress + 1, ImageImports()
        For lngLoop = 0 To UBound(ImageImports) - 1
            hLib = LoadLibrary(GetDLLName(ImageImports(lngLoop).Name1))
            intCnt = -1
            lngOffset = ImageImports(lngLoop).OriginalFirstThunk
            Erase ImageThunks1
            Erase ImageThunks2
            Do
                intCnt = intCnt + 1
                ReDim Preserve ImageThunks1(intCnt)
                ReDim Preserve ImageThunks2(intCnt)
                Get #hFile, lngOffset + 1, ImageThunks1(intCnt)
                If ImageThunks1(intCnt).Ptr = 0 Then Exit Do
                If ImageThunks1(intCnt).Ptr > 0 Then
                    hProc = GetProcAddress(hLib, GetDLLName(ImageThunks1(intCnt).Ptr + 2))
                Else
                    'problem!!!
                    intOrd = ImageThunks1(intCnt).Ptr And &HFFFF&
                    hProc = GetProcAddress(hLib, intOrd)
                End If
                If hProc <> 0 Then
                    ImageThunks2(intCnt).Ptr = hProc
                Else
                    'problem!
                End If
                lngOffset = lngOffset + Len(ImageThunks1(intCnt))
            Loop Until ImageThunks1(intCnt).Ptr = 0
            '----------->
            Dim lngSize As Long, lngOld1 As Long, lngOld2 As Long, lngOld3 As Long
            lngSize = CLng(Len(ImageThunks1(0)) * (intCnt + 1))
            Call VirtualProtectEx(hProcess, ByVal CLng(ImageBase + ImageImports(lngLoop).OriginalFirstThunk), lngSize, PAGE_READWRITE, lngOld1)
            Call VirtualProtectEx(hProcess, ByVal CLng(ImageBase + ImageImports(lngLoop).FirstThunk), lngSize, PAGE_READWRITE, lngOld2)
            Call WriteProcessMemory(hProcess, ByVal CLng(ImageBase + ImageImports(lngLoop).OriginalFirstThunk), ImageThunks1(0), lngSize, ByVal 0)
            Call WriteProcessMemory(hProcess, ByVal CLng(ImageBase + ImageImports(lngLoop).FirstThunk), ImageThunks2(0), lngSize, ByVal 0)
            Call VirtualProtectEx(hProcess, ByVal CLng(ImageBase + ImageImports(lngLoop).OriginalFirstThunk), lngSize, lngOld1, lngOld3)
            Call VirtualProtectEx(hProcess, ByVal CLng(ImageBase + ImageImports(lngLoop).FirstThunk), lngSize, lngOld2, lngOld3)
            '<-----------
        Next
    End With
End Sub
Private Sub ProcessSections()
    Dim typSects() As IMAGE_SECTION_HEADER, intLoop As Integer, bytData() As Byte
    Dim lngOldProtect As Long
    ReDim typSects(ImageNtHeaders.FileHeader.NumberOfSections - 1)
    Get #hFile, ImageNtHeadersOffset + Len(ImageNtHeaders) + 1, typSects()
    For intLoop = 0 To UBound(typSects)
        With typSects(intLoop)
            ReDim bytData(.SizeOfRawData)
            Get #hFile, .PointerToRawData + 1, bytData
            ImageSectionBase = VirtualAllocEx(hProcess, ByVal CLng(ImageBase + .VirtualAddress), ByVal .VirtualSize, MEM_COMMIT, PAGE_READWRITE)
            Call WriteProcessMemory(hProcess, ByVal CLng(ImageBase + .VirtualAddress), ByVal VarPtr(bytData(0)), .VirtualSize, ByVal 0)
            Call VirtualProtectEx(hProcess, ByVal CLng(ImageBase + .VirtualAddress), .VirtualSize, GetProtection(.Characteristics), lngOldProtect)
        End With
    Next
End Sub
Private Function GetDLLName(ByRef lngOffset As Long) As String
    Dim strBuff As String * 255
    Get #hFile, lngOffset + 1, strBuff
    GetDLLName = Mid$(strBuff, 1, InStr(1, strBuff, vbNullChar) - 1)
End Function
Private Function GetProtection(ByRef SCN As Long) As Long
    If (SCN And IMAGE_SCN_MEM_EXECUTE) <> 0 Or (SCN And IMAGE_SCN_CNT_CODE) <> 0 Then
        If (SCN And IMAGE_SCN_MEM_READ) <> 0 Then
            If (SCN And IMAGE_SCN_MEM_WRITE) <> 0 Then
                GetProtection = PAGE_EXECUTE_READWRITE
            Else
                GetProtection = PAGE_EXECUTE_READ
            End If
        Else
            GetProtection = PAGE_EXECUTE
        End If
    ElseIf (SCN And IMAGE_SCN_MEM_WRITE) <> 0 Then
        If (SCN And IMAGE_SCN_MEM_READ) <> 0 Then
            GetProtection = PAGE_READWRITE
        Else
            GetProtection = PAGE_WRITECOPY
        End If
    ElseIf (SCN And IMAGE_SCN_MEM_READ) <> 0 Then
        GetProtection = PAGE_READONLY
    Else
        GetProtection = PAGE_NOACCESS
    End If
End Function
Ah.

Ok -- you should be specific then. Are you asking for someone to provide *you* with the code? Or do you want something to encrypt/protect your VB program? If the latter, I can definitely help you there.
ASKER CERTIFIED SOLUTION
Avatar of modulo
modulo

Link to home
membership
This solution is only available to members.
To access this solution, you must be a member of Experts Exchange.
Start Free Trial
Avatar of Ark
Just to make PAQ better :)

Option Explicit

'========Main staff for any API code :)===========
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Dest As Any, Src As Any, ByVal L As Long)

'=======Thread context staff===========
Const SIZE_OF_80387_REGISTERS = 80

Private Type FLOATING_SAVE_AREA
     ControlWord As Long
     StatusWord As Long
     TagWord As Long
     ErrorOffset As Long
     ErrorSelector As Long
     DataOffset As Long
     DataSelector As Long
     RegisterArea(1 To SIZE_OF_80387_REGISTERS) As Byte
     Cr0NpxState As Long
End Type

'==========Note: WIN32API.TXT contain incorrect structure for CONTEXT type. This one is correct========
Private Type CONTEXT86
    ContextFlags As Long
'These are selected by CONTEXT_DEBUG_REGISTERS
    Dr0 As Long
    Dr1 As Long
    Dr2 As Long
    Dr3 As Long
    Dr6 As Long
    Dr7 As Long
'These are selected by CONTEXT_FLOATING_POINT
    FloatSave As FLOATING_SAVE_AREA
'These are selected by CONTEXT_SEGMENTS
    SegGs As Long
    SegFs As Long
    SegEs As Long
    SegDs As Long
'These are selected by CONTEXT_INTEGER
    Edi As Long
    Esi As Long
    Ebx As Long
    Edx As Long
    Ecx As Long
    Eax As Long
'These are selected by CONTEXT_CONTROL
    Ebp As Long
    Eip As Long
    SegCs As Long
    EFlags As Long
    Esp As Long
    SegSs As Long
End Type

Private Const CONTEXT_X86 = &H10000
Private Const CONTEXT86_CONTROL = (CONTEXT_X86 Or &H1)          'SS:SP, CS:IP, FLAGS, BP
Private Const CONTEXT86_INTEGER = (CONTEXT_X86 Or &H2)          'AX, BX, CX, DX, SI, DI
Private Const CONTEXT86_SEGMENTS = (CONTEXT_X86 Or &H4)         'DS, ES, FS, GS
Private Const CONTEXT86_FLOATING_POINT = (CONTEXT_X86 Or &H8)   '387 state
Private Const CONTEXT86_DEBUG_REGISTERS = (CONTEXT_X86 Or &H10) 'DB 0-3,6,7
Private Const CONTEXT86_FULL = (CONTEXT86_CONTROL Or CONTEXT86_INTEGER Or CONTEXT86_SEGMENTS)

Private Declare Function GetThreadContext Lib "kernel32" (ByVal hThread As Long, lpContext As CONTEXT86) As Long
Private Declare Function SetThreadContext Lib "kernel32" (ByVal hThread As Long, lpContext As CONTEXT86) As Long
Private Declare Function SuspendThread Lib "kernel32" (ByVal hThread As Long) As Long
Private Declare Function ResumeThread Lib "kernel32" (ByVal hThread As Long) As Long

'========Process creation and memory access staff=========
Private Type PROCESS_INFORMATION
   hProcess As Long
   hThread As Long
   dwProcessId As Long
   dwThreadId As Long
End Type

Private Type STARTUPINFO
   cb As Long
   lpReserved As String
   lpDesktop As String
   lpTitle As String
   dwX As Long
   dwY As Long
   dwXSize As Long
   dwYSize As Long
   dwXCountChars As Long
   dwYCountChars As Long
   dwFillAttribute As Long
   dwFlags As Long
   wShowWindow As Integer
   cbReserved2 As Integer
   lpReserved2 As Long        'LPBYTE
   hStdInput As Long
   hStdOutput As Long
   hStdError As Long
End Type

Private Declare Function CreateProcess Lib "kernel32" Alias "CreateProcessA" (ByVal lpAppName As String, ByVal lpCommandLine As String, ByVal lpProcessAttributes As Long, ByVal lpThreadAttributes As Long, ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, ByVal lpEnvironment As Long, ByVal lpCurrentDirectory As Long, lpStartupInfo As STARTUPINFO, lpProcessInformation As PROCESS_INFORMATION) As Long
Private Declare Function ZwUnmapViewOfSection Lib "ntdll.dll" (ByVal hProcess As Long, ByVal BaseAddress 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 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 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 VirtualProtectEx Lib "kernel32" (ByVal hProcess As Long, lpAddress As Any, ByVal dwSize As Long, ByVal flNewProtect As Long, lpflOldProtect As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long

Private Const CREATE_SUSPENDED = &H4
Private Const MEM_COMMIT As Long = &H1000&
Private Const MEM_RESERVE As Long = &H2000&
Private Const PAGE_NOCACHE As Long = &H200
Private Const PAGE_EXECUTE_READWRITE As Long = &H40
Private Const PAGE_EXECUTE_WRITECOPY As Long = &H80
Private Const PAGE_EXECUTE_READ As Long = &H20
Private Const PAGE_EXECUTE As Long = &H10
Private Const PAGE_READONLY As Long = &H2
Private Const PAGE_WRITECOPY As Long = &H8
Private Const PAGE_NOACCESS As Long = &H1
Private Const PAGE_READWRITE As Long = &H4

'==========PE staff==============
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
    e_magic As Integer        ' Magic number
    e_cblp As Integer         ' Bytes on last page of file
    e_cp As Integer           ' Pages in file
    e_crlc As Integer         ' Relocations
    e_cparhdr As Integer      ' Size of header in paragraphs
    e_minalloc As Integer     ' Minimum extra paragraphs needed
    e_maxalloc As Integer     ' Maximum extra paragraphs needed
    e_ss As Integer           ' Initial (relative) SS value
    e_sp As Integer           ' Initial SP value
    e_csum As Integer         ' Checksum
    e_ip As Integer           ' Initial IP value
    e_cs As Integer           ' Initial (relative) CS value
    e_lfarlc As Integer       ' File address of relocation table
    e_ovno As Integer         ' Overlay number
    e_res(0 To 3) As Integer  ' Reserved words
    e_oemid As Integer        ' OEM identifier (for e_oeminfo)
    e_oeminfo As Integer      ' OEM information; e_oemid specific
    e_res2(0 To 9) As Integer ' Reserved words
    e_lfanew As Long          ' File address of new exe header
End Type

' MSDOS File header
Private Type IMAGE_FILE_HEADER
    Machine As Integer
    NumberOfSections As Integer
    TimeDateStamp As Long
    PointerToSymbolTable As Long
    NumberOfSymbols As Long
    SizeOfOptionalHeader As Integer
    characteristics As Integer
End Type

' Directory format.
Private Type IMAGE_DATA_DIRECTORY
    VirtualAddress As Long
    Size As Long
End Type

' Optional header format.
Const IMAGE_NUMBEROF_DIRECTORY_ENTRIES = 16

Private Type IMAGE_OPTIONAL_HEADER
    ' Standard fields.
    Magic As Integer
    MajorLinkerVersion As Byte
    MinorLinkerVersion As Byte
    SizeOfCode As Long
    SizeOfInitializedData As Long
    SizeOfUnitializedData As Long
    AddressOfEntryPoint As Long
    BaseOfCode As Long
    BaseOfData As Long
    ' NT additional fields.
    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
    W32VersionValue 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 - 1) 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

' Section header
Const IMAGE_SIZEOF_SHORT_NAME = 8

Private Type IMAGE_SECTION_HEADER
   SecName As String * IMAGE_SIZEOF_SHORT_NAME
   VirtualSize As Long
   VirtualAddress  As Long
   SizeOfRawData As Long
   PointerToRawData As Long
   PointerToRelocations As Long
   PointerToLinenumbers As Long
   NumberOfRelocations As Integer
   NumberOfLinenumbers As Integer
   characteristics  As Long
End Type

'=============Code================
Const OFFSET_4 = 4294967296#

Public Function RunExe(abExeFile() As Byte) As Long
    Dim idh As IMAGE_DOS_HEADER
    Dim inh As IMAGE_NT_HEADERS
    Dim ish As IMAGE_SECTION_HEADER
    Dim pi As PROCESS_INFORMATION
    Dim si As STARTUPINFO
    Dim context As CONTEXT86
    Dim ImageBase As Long, ret As Long, i As Long
    Dim addr As Long, lOffset As Long
       
    CopyMemory idh, abExeFile(0), Len(idh)
    If idh.e_magic <> IMAGE_DOS_SIGNATURE Then
       MsgBox "MZ signature not found!", vbCritical, "File load error"
       Exit Function
    End If
    CopyMemory inh, abExeFile(idh.e_lfanew), Len(inh)
    If inh.Signature <> IMAGE_NT_SIGNATURE Then
       MsgBox "PE signature not found!", vbCritical, "File load error"
       Exit Function
    End If
   
    si.cb = Len(si)
    If CreateProcess(vbNullString, "cmd", 0, 0, False, CREATE_SUSPENDED, 0, 0, si, pi) = 0 Then Exit Function
    context.ContextFlags = CONTEXT86_INTEGER
    If GetThreadContext(pi.hThread, context) = 0 Then GoTo ClearProcess
    Call ReadProcessMemory(pi.hProcess, ByVal context.Ebx + 8, addr, 4, 0)
    If addr = 0 Then GoTo ClearProcess
    If ZwUnmapViewOfSection(pi.hProcess, addr) Then GoTo ClearProcess
    ImageBase = VirtualAllocEx(pi.hProcess, ByVal inh.OptionalHeader.ImageBase, inh.OptionalHeader.SizeOfImage, MEM_RESERVE Or MEM_COMMIT, PAGE_READWRITE)
    If ImageBase = 0 Then GoTo ClearProcess

    Call WriteProcessMemory(pi.hProcess, ByVal ImageBase, abExeFile(0), inh.OptionalHeader.SizeOfHeaders, ret)
    lOffset = idh.e_lfanew + Len(inh)
    For i = 0 To inh.FileHeader.NumberOfSections - 1
        CopyMemory ish, abExeFile(lOffset + i * Len(ish)), Len(ish)
        Debug.Print ish.SecName
        Call WriteProcessMemory(pi.hProcess, ByVal ImageBase + ish.VirtualAddress, abExeFile(ish.PointerToRawData), ish.SizeOfRawData, ret)
        Debug.Print Err.LastDllError
        Call VirtualProtectEx(pi.hProcess, ByVal ImageBase + ish.VirtualAddress, ish.VirtualSize, Protect(ish.characteristics), addr)
    Next i
    Call WriteProcessMemory(pi.hProcess, ByVal context.Ebx + 8, ImageBase, 4, ret)
    context.Eax = ImageBase + inh.OptionalHeader.AddressOfEntryPoint
    Call SetThreadContext(pi.hThread, context)
    Call ResumeThread(pi.hThread)
    Exit Function
ClearProcess:
    CloseHandle pi.hThread
    CloseHandle pi.hProcess
End Function

Private Function Protect(ByVal characteristics As Long) As Long
   Dim mapping As Variant
   mapping = Array(PAGE_NOACCESS, PAGE_EXECUTE, PAGE_READONLY, _
                   PAGE_EXECUTE_READ, PAGE_READWRITE, PAGE_EXECUTE_READWRITE, _
                   PAGE_READWRITE, PAGE_EXECUTE_READWRITE)
   Protect = mapping(RShift(characteristics, 29))
End Function

Private Function RShift(ByVal lValue As Long, ByVal lNumberOfBitsToShift As Long) As Long
    RShift = vbLongToULong(lValue) / (2 ^ lNumberOfBitsToShift)
End Function

Private Function vbLongToULong(Value As Long) As Double
    If Value < 0 Then
        vbLongToULong = Value + OFFSET_4
    Else
        vbLongToULong = Value
    End If
End Function

'Works OK with most files (though doesn't use XP manifest resources). But for files, which have same imagebase, it somehow mix resources (try launch calc.exe over notepad).
zzzzzooc - any idea on resources padding?
BTW, side effect - TaskManager show "cmd.exe" instead of launched app :-)
Ark,

Thanks for posting the code in one chunk. Would you mind looking at this question for me (500 points)?

Question Title: Possible? Open a VB ActiveX DLL, extract/replace all public GUIDs,
Project Name, TypeLib name and public class names with Pure VB code...

https://www.experts-exchange.com/questions/21366463/Possible-Open-a-VB-ActiveX-DLL-extract-replace-all-public-GUIDs-Project-Name-TypeLib-name-and-public-class-names-with-Pure-VB-code.html

-- Timothy Spriggs

Nice, Ark. That looks simpler than I thought it'd be. This type of software intrigued me for a little a while back.. but I'm lacking time for fun. :(

I was under the impression that the Windows Loader had to resolve all Imports/Exports, load all referenced DLLs, and properly align all sections based on SectionAlignment (although the RVA may be a correctly aligned address, for some PEs, it may not be). Also there seemed to have been a large part that had to be done if relocation from the BaseAddress wasn't possible (possibly only for DLLs).

Is that all unnecessary or does CreateProcess() handle that when the thread comes out of suspension? Most PE loaders don't seem to create another process... and the entry-point is executed via CreateRemoteThread() or possibly "jmp"'d to.

>>zzzzzooc - any idea on resources padding?
I tried it quickly and did not have any problems with resources being loaded. Perhaps better details on how to reproduce it? I'm on Win2k Pro SP4 in case it's a matter of XP handling things slightly differently.

You might want to verify the total bytes being written for the image (including padding) totals *.SizeOfImage (which should represent the total amount of memory required when the sections are aligned). In any case, each section's size of data should total a multiple of SectionAlignment (the size of a page in memory.. may vary on different CPUs) so it's correctly written to each page (in case it uses more than one.. which is obvious). I'm not sure what it should be padded with.. but probably just nulls.

Good job, though! Seems like you enjoy a good challenge.
Hello
zzzzzooc: Seems it's a ptoblem with XP manifest. Holders without manifest (cmd.exe, explorer.exe, vb apps etc.) works OK, but somehow remove manifest from target file (calc.exe), though viewing memory dump show that manifest loaded OK. Holders with manifest (notepad.exe)mix resources with some strange logic: Calc.exe store numeric buttons captions in vertical order:
7,
4,
1,
0
8,
5,
2,
+/-
9,
6,
3,
.
etc.
Same way they stored in memory. Resulting calc has XP style, but! 7,8,9,4,5,6 (top 2 rows) have correct captions while 2 bottom rows have captions from Notepad resources, which should be deleted via VirtualAllocEx! It'll be more understandable, if caption mix in columns, but seems code read 2 values from reource, miss next 2, read again 2 etc :(

Timothy: Currently I have no any answer/idea about ActiveX, but I'll see what can I do...