Принцип работы очень прост, модуль содержит шеллкод написанный на VB6 который внедряется в процесс "зомби" и ждет завершения программы. После завершения программы шеллкод удаляет файлы которые пользователь передал в него, т.е. исключаются какие-либо блокировки со стороны EXE файла, поэтому мы можем все удалять даже сам EXE. После выполнения всех действий шеллкод завершает работу процесса "зомби".
Сам модуль:
- Код: Выделить всё
' //
' // modSelfCleaning by The trick
' //
Option Explicit
Private Const STARTF_USESHOWWINDOW As Long = &H1
Private Const SW_HIDE As Long = 0
Private Const CREATE_SUSPENDED As Long = &H4
Private Const MEM_COMMIT As Long = &H1000&
Private Const MEM_RESERVE As Long = &H2000&
Private Const MEM_RELEASE As Long = &H8000&
Private Const PAGE_EXECUTE_READWRITE As Long = &H40&
Private Const DUPLICATE_SAME_ACCESS As Long = &H2
Private Const DUPLICATE_CLOSE_SOURCE As Long = &H1
Private Const INFINITE As Long = &HFFFFFFFF
Private Const WAIT_OBJECT_0 As Long = 0
Private Type tFunctionsTable
pWaitForSingleObject As Long
pExitProcess As Long
pCloseHandle As Long
pDeleteFile As Long
plstrlen As Long
End Type
Private Type tThreadData
lNumberOfEntries As Long ' // Number of items in strings table
pStringTable As Long ' // Pointer to strings table
tFuncTable As tFunctionsTable ' // Functions table
hMainExe As Long ' // Handle of main exe
End Type
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 Long
lpDesktop As Long
lpTitle As Long
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
hStdInput As Long
hStdOutput As Long
hStdError As Long
End Type
Private Declare Function CreateProcess Lib "kernel32" _
Alias "CreateProcessW" ( _
ByVal lpApplicationName As Long, _
ByVal lpCommandLine As Long, _
lpProcessAttributes As Any, _
lpThreadAttributes As Any, _
ByVal bInheritHandles As Long, _
ByVal dwCreationFlags As Long, _
lpEnvironment As Any, _
ByVal lpCurrentDirectory As Long, _
lpStartupInfo As STARTUPINFO, _
lpProcessInformation As PROCESS_INFORMATION) As Long
Private Declare Function CloseHandle Lib "kernel32" ( _
ByVal hObject As Long) As Long
Private Declare Function GetModuleHandle Lib "kernel32" _
Alias "GetModuleHandleW" ( _
ByVal lpModuleName As Long) As Long
Private Declare Function GetProcAddress Lib "kernel32" ( _
ByVal hModule As Long, _
ByVal lpProcName As String) As Long
Private Declare Function VirtualAllocEx Lib "kernel32.dll" ( _
ByVal hProcess As Long, _
lpAddress As Any, _
ByVal dwSize As Long, _
ByVal flAllocationType As Long, _
ByVal flProtect As Long) As Long
Private Declare Function VirtualFreeEx Lib "kernel32.dll" ( _
ByVal hProcess As Long, _
lpAddress As Any, _
ByVal dwSize As Long, _
ByVal dwFreeType As Long) As Long
Private Declare Function DuplicateHandle Lib "kernel32" ( _
ByVal hSourceProcessHandle As Long, _
ByVal hSourceHandle As Long, _
ByVal hTargetProcessHandle As Long, _
ByRef lpTargetHandle As Any, _
ByVal dwDesiredAccess As Long, _
ByVal bInheritHandle As Long, _
ByVal dwOptions As Long) As Long
Private Declare Function GetCurrentProcess Lib "kernel32" () As Long
Private Declare Function WriteProcessMemory Lib "kernel32" ( _
ByVal hProcess As Long, _
ByVal lpBaseAddress As Long, _
lpBuffer As Any, _
ByVal nSize As Long, _
lpNumberOfBytesWritten As Long) As Long
Private Declare Function CreateRemoteThread Lib "kernel32" ( _
ByVal hProcess As Long, _
lpThreadAttributes As Any, _
ByVal dwStackSize As Long, _
ByVal lpStartAddress As Long, _
lpParameter As Any, _
ByVal dwCreationFlags As Long, _
lpThreadId As Long) As Long
Private Declare Function TerminateProcess Lib "kernel32" ( _
ByVal hProcess As Long, _
ByVal uExitCode As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" _
Alias "RtlMoveMemory" ( _
ByRef Destination As Any, _
ByRef Source As Any, _
ByVal Length As Long)
' // Wait for program termination and delete all passed files
Public Function CleanFiles( _
ParamArray vFiles() As Variant) As Boolean
Dim tdParam As tThreadData
Dim bStrTable() As Byte
Dim hKernel32 As Long
Dim hProcess As Long
Dim hThread As Long
Dim pData As Long
Dim pParam As Long
Dim pCode As Long
Dim lDataSize As Long
Dim lCodeSize As Long
Dim bRet As Long
Dim bInIDE As Boolean
' // Check if code is in ide
Debug.Assert MakeTrue(bInIDE)
If bInIDE Then
MsgBox "You should compile to Native code", vbExclamation
CleanFiles = True
Exit Function
End If
' // Setup TrickCallPointers
PatchFunc AddressOf CloseHandle_Proto
PatchFunc AddressOf DeleteFileW_Proto
PatchFunc AddressOf ExitProcess_Proto
PatchFunc AddressOf lstrlenW_Proto
PatchFunc AddressOf WaitForSingleObject_Proto
hKernel32 = GetModuleHandle(StrPtr("kernel32"))
If hKernel32 = 0 Then
GoTo CleanUp
End If
' // Fill functions table
With tdParam.tFuncTable
.pCloseHandle = GetProcAddress(hKernel32, "CloseHandle")
.pDeleteFile = GetProcAddress(hKernel32, "DeleteFileW")
.pExitProcess = GetProcAddress(hKernel32, "ExitProcess")
.pWaitForSingleObject = GetProcAddress(hKernel32, "WaitForSingleObject")
.plstrlen = GetProcAddress(hKernel32, "lstrlenW")
End With
' // Make string table
tdParam.lNumberOfEntries = StringTableToByteArray(bStrTable(), vFiles)
If tdParam.lNumberOfEntries = 0 Then
GoTo CleanUp
End If
' // Run "Zombie" process
hProcess = RunZombieProcess()
If hProcess = 0 Then
GoTo CleanUp
End If
' // Place handle of main exe
If DuplicateHandle(GetCurrentProcess(), GetCurrentProcess(), hProcess, _
tdParam.hMainExe, 0, False, DUPLICATE_SAME_ACCESS) = 0 Then
GoTo CleanUp
End If
' // Alloc memory in the EXE
lCodeSize = GetAddress(AddressOf END_OF_SHELLCODE) - GetAddress(AddressOf BEGIN_OF_SHELLCODE)
lDataSize = UBound(bStrTable) + 1 + LenB(tdParam) + lCodeSize
pData = VirtualAllocEx(hProcess, ByVal 0&, lDataSize, _
MEM_COMMIT Or MEM_RESERVE, PAGE_EXECUTE_READWRITE)
If pData = 0 Then
GoTo CleanUp
End If
' // Place string table
If WriteProcessMemory(hProcess, pData, bStrTable(0), UBound(bStrTable) + 1, 0) = 0 Then
GoTo CleanUp
End If
' // Place param
tdParam.pStringTable = pData
pParam = pData + UBound(bStrTable) + 1
If WriteProcessMemory(hProcess, pParam, tdParam, LenB(tdParam), 0) = 0 Then
GoTo CleanUp
End If
' // Place code
pCode = pParam + LenB(tdParam)
If WriteProcessMemory(hProcess, pCode, ByVal GetAddress(AddressOf ShellcodeProc), lCodeSize, 0) = 0 Then
GoTo CleanUp
End If
' // Run code
hThread = CreateRemoteThread(hProcess, ByVal 0&, 0, pCode, ByVal pParam, 0, 0)
If hThread = 0 Then
GoTo CleanUp
End If
bRet = True
CleanUp:
CloseHandle hThread
If Not bRet Then
If pData Then
VirtualFreeEx hProcess, ByVal pData, 0, MEM_RELEASE
End If
If tdParam.hMainExe Then
DuplicateHandle hProcess, tdParam.hMainExe, 0, 0, ByVal 0&, 0, DUPLICATE_CLOSE_SOURCE
End If
If hProcess Then
TerminateProcess hProcess, 0
CloseHandle (hProcess)
End If
End If
CleanFiles = bRet
End Function
' // Run "Zombie" process
Private Function RunZombieProcess() As Long
Dim pi As PROCESS_INFORMATION
Dim si As STARTUPINFO
si.cb = Len(si)
si.dwFlags = STARTF_USESHOWWINDOW
si.wShowWindow = SW_HIDE
If CreateProcess(StrPtr(Environ("ComSpec")), 0, ByVal 0&, ByVal 0&, False, CREATE_SUSPENDED, ByVal 0, 0, si, pi) = 0 Then
Exit Function
End If
CloseHandle pi.hThread
RunZombieProcess = pi.hProcess
End Function
' // Serialize string table
Private Function StringTableToByteArray( _
ByRef bOutData() As Byte, _
ParamArray vStringTable() As Variant) As Long
Dim bData() As Byte: Dim lDataCount As Long
Dim lIndex As Long: Dim sTmpString As String
Dim vVar As Variant
For Each vVar In vStringTable(0)
If VarType(vVar) <> vbString Then GoTo continue
sTmpString = vVar
ReDim Preserve bData(lDataCount + LenB(sTmpString) + 2)
' // Copy string to buffer with null-terminating character
CopyMemory bData(lDataCount), ByVal StrPtr(sTmpString), LenB(sTmpString) + 2
lDataCount = lDataCount + LenB(sTmpString) + 2
StringTableToByteArray = StringTableToByteArray + 1
continue:
Next
bOutData() = bData
End Function
Private Function GetAddress( _
ByVal pAddress As Long) As Long
GetAddress = pAddress
End Function
Private Function BEGIN_OF_SHELLCODE() As Long
BEGIN_OF_SHELLCODE = 1
End Function
Private Sub ShellcodeProc( _
ByRef tdParam As tThreadData)
Dim lIndex As Long
With tdParam
' // Wait process termination
If WaitForSingleObject_Proto(.tFuncTable.pWaitForSingleObject, .hMainExe, INFINITE) <> WAIT_OBJECT_0 Then
Exit Sub
End If
For lIndex = 0 To .lNumberOfEntries - 1
DeleteFileW_Proto .tFuncTable.pDeleteFile, .pStringTable
' // Next string
.pStringTable = .pStringTable + (lstrlenW_Proto(.tFuncTable.plstrlen, .pStringTable) + 1) * 2
Next
' // Close handle
CloseHandle_Proto .tFuncTable.pCloseHandle, .hMainExe
' // Exit process
ExitProcess_Proto .tFuncTable.pExitProcess, 0
End With
End Sub
Private Function WaitForSingleObject_Proto( _
ByVal pAddress As Long, _
ByVal hHandle As Long, _
ByVal dwMilliseconds As Long) As Long
End Function
Private Sub ExitProcess_Proto( _
ByVal pAddress As Long, _
ByVal uExitCode As Long)
End Sub
Private Function CloseHandle_Proto( _
ByVal pAddress As Long, _
ByVal hObject As Long) As Long
End Function
Private Function DeleteFileW_Proto( _
ByVal pAddress As Long, _
ByVal lpFileName As Long) As Long
End Function
Private Function lstrlenW_Proto( _
ByVal pAddress As Long, _
ByVal lpString As Long) As Long
End Function
Private Function END_OF_SHELLCODE() As Long
END_OF_SHELLCODE = 2
End Function
Для того чтобы обеспечить удаление файлов после работы EXE нужно вызвать функцию CleanFiles передавая в качестве параметра список файлов для удаления. Можно вызвать эту функцию как в начале работы приложения, в этом случае файлы будут удалены даже если приложение завершилось аварийно, так и в конце работы приложения.
Этот модуль использует модуль modTrickCallPointers для вызова функций по указателю. В аттаче небольшой пример использования который распаковывает внутренний OCX, а после завершения приложения удаляет его и собственный EXE файл.
https://www.youtube.com/watch?v=VprmDrtHyPE