|
本帖最后由 Tesla.Angela 于 2010-8-1 23:14 编辑
TaOpenThread:参考了0x7E的思路和代码
TaTerminateThread:修改了Zzzians的代码
更新内容:在TaTerminateThread中把待结束线程的寄存器值全部清零。
fMain.frm:
- Option Explicit
- Private Sub cmdKillThread_Click()
- TaKillThread CLng(Text1.Text)
- End Sub
- Private Sub Form_Load()
- RtlAdjustPrivilege 20, 1, 0, 0
- End Sub
复制代码
mGetHandle.bas:
- Option Explicit
- Private Declare Function ZwDuplicateObject Lib "NTDLL.DLL" (ByVal hps As Long, ByVal hs As Long, ByVal ho As Long, ByRef hr As Long, Optional ByVal ac As Long = 2035711, Optional ByVal ha As Long = 0, Optional ByVal op As Long = 4) As Long
- Private Declare Function ZwOpenProcess Lib "NTDLL.DLL" (H As Long, ByVal a As Long, b As Any, c As Any) As Long
- Private Declare Function ZwQuerySystemInformation Lib "NTDLL.DLL" (ByVal t As Long, p As Any, ByVal n As Long, r As Long) As Long
- Private Declare Function ZwOpenProcessToken Lib "ntdll" (ByVal H As Long, ByVal a As Long, H As Long) As Long
- Private Declare Function MovMem Lib "NTDLL.DLL" Alias "RtlMoveMemory" (ByVal pD As Long, ByVal ps As Long, Optional ByVal nL As Long = 4) As Long
- Private Declare Function ZwClose Lib "NTDLL.DLL" (ByVal H As Long) As Long
- Private Declare Function CsrGetProcessId Lib "NTDLL.DLL" () As Long
- Private Declare Function ZwQueryInformationThread Lib "NTDLL.DLL" (ByVal hThread As Long, ByVal ThreadInformationClass As Long, ByVal ThreadInformation As Long, ByVal ThreadInformationLength As Long, ReturnLength As Long) As Long
- Private Declare Function OpenThread Lib "kernel32.dll" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwThreadId As Long) As Long
- Private Type CLIENT_ID
- UniqueProcess As Long
- UniqueThread As Long
- End Type
- Private Type THREAD_BASIC_INFORMATION
- ExitStatus As Long
- TebBaseAddress As Long
- ClientId As CLIENT_ID
- AffinityMask As Long
- Priority As Long
- BasePriority As Long
- End Type
- Private Type SYSTEM_HANDLE_TABLE_ENTRY_INFO
- UniqueProcessId As Integer
- CreatorBackTraceIndex As Integer
- ObjectTypeIndex As Byte
- HandleAttributes As Byte
- HandleValue As Integer
- pObject As Long
- GrantedAccess As Long
- End Type
- Private Type OBJECT_ATTRIBUTES
- Length As Long
- RootDirectory As Long
- ObjectName As Long
- Attributes As Long
- SecurityDescriptor As Long
- SecurityQualityOfService As Long
- End Type
- Private Function OpenPs(ByVal pid As Long, Optional acs As Long = &H40)
- Dim b As OBJECT_ATTRIBUTES, c As CLIENT_ID, H As Long, st As Long
- c.UniqueProcess = pid
- st = ZwOpenProcess(H, acs, b, c)
- If st = 0 Then OpenPs = H
- End Function
- Private Function hToTid(ByVal H As Long) As Long
- Dim tbi As THREAD_BASIC_INFORMATION
- Dim st As Long
- st = ZwQueryInformationThread(H, 0&, VarPtr(tbi), 28, ByVal 0&)
- If st = 0 Then hToTid = tbi.ClientId.UniqueThread
- End Function
- Public Function DuplicateThreadHandle(ByVal tid As Long, ByVal OTT As Long) As Long
- Dim st() As SYSTEM_HANDLE_TABLE_ENTRY_INFO, buf() As Long, Csr As Long, hCsr As Long
- Dim cnt As Long, i As Long, rtn As Long, Sx As Long
- ReDim buf(4) As Long
- Sx = ZwQuerySystemInformation(16, buf(0), 20, 0)
- cnt = buf(0) * 4
- ReDim buf(cnt) As Long
- Sx = ZwQuerySystemInformation(16, buf(0), cnt * 4 + 4, 0)
- ReDim st(buf(0) - 1) As SYSTEM_HANDLE_TABLE_ENTRY_INFO
- MovMem VarPtr(st(0)), VarPtr(buf(1)), cnt
- Erase buf
- Csr = CsrGetProcessId()
- hCsr = OpenPs(Csr)
- If hCsr = 0 Then Exit Function
- For i = 0 To cnt / 4 - 1
- With st(i)
- If .ObjectTypeIndex = OTT And .UniqueProcessId = Csr Then
- Sx = ZwDuplicateObject(hCsr, .HandleValue, -1, rtn, 2032639)
- If hToTid(rtn) = tid Then
- DuplicateThreadHandle = rtn
- Exit For
- Else
- ZwClose rtn
- End If
- End If
- End With
- Next i
- ZwClose hCsr
- End Function
- Public Function TaOpenThread(ByVal dwThreadId As Long) As Long
- Dim hOut As Long
- hOut = OpenThread(2032639, 0, dwThreadId)
- If hOut = 0 Then
- hOut = DuplicateThreadHandle(dwThreadId, 6) '2k/xp/2k3
- End If
- If hOut = 0 Then
- hOut = DuplicateThreadHandle(dwThreadId, 7) 'vista/08/7
- End If
- TaOpenThread = hOut
- End Function
复制代码
mTerminate.bas:
- Option Explicit
- Public Declare Function RtlAdjustPrivilege Lib "ntdll" _
- (ByVal Privilege As Long, ByVal Newvalue As Long, ByVal NewThread As Long, Oldvalue As Long) As Long
- Public Declare Function NtSuspendThread _
- Lib "NTDLL.DLL" (ByVal ThreadHandle As Long, _
- ByRef PreviousSuspendCount As Long) As Long
- Public Declare Function NtResumeThread _
- Lib "NTDLL.DLL" (ByVal ThreadHandle As Long, _
- ByRef SuspendCount As Long) As Long
- Public Declare Function NtSetContextThread _
- Lib "NTDLL.DLL" (ByVal ThreadHandle As Long, _
- ByRef ThreadContext As CONTEXT) As Long
- Public Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
- Public Declare Function GetProcAddress Lib "kernel32" (ByVal hModule As Long, ByVal lpProcName As String) As Long
- Public Declare Function OpenThread Lib "kernel32.dll" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwThreadId As Long) As Long
- Private Declare Function PostThreadMessage Lib "user32.dll" Alias "PostThreadMessageA" (ByVal idThread As Long, ByVal msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
- Public 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 &H50) As Byte
- Cr0NpxState As Long
- End Type
- Public Type CONTEXT
- ContextFlags As Long
- Dr0 As Long
- Dr1 As Long
- Dr2 As Long
- Dr3 As Long
- Dr6 As Long
- Dr7 As Long
- FloatSave As FLOATING_SAVE_AREA
- SegGs As Long
- SegFs As Long
- SegEs As Long
- SegDs As Long
- Edi As Long
- Esi As Long
- Ebx As Long
- Edx As Long
- Ecx As Long
- Eax As Long
- Ebp As Long
- Eip As Long '这个邪恶
- SegCs As Long
- EFlags As Long
- Esp As Long
- SegSs As Long
- ExtendedRegisters(1 To &H200) As Byte
- End Type
- Public Const CONTEXT_i386 As Long = &H10000
- Public Const CONTEXT_i486 As Long = &H10000
- Public Const CONTEXT_CONTROL As Long = (CONTEXT_i386 Or &H1)
- Public Const CONTEXT_INTEGER As Long = (CONTEXT_i386 Or &H2)
- Public Const CONTEXT_SEGMENTS As Long = (CONTEXT_i386 Or &H4)
- Public Const CONTEXT_FLOATING_POINT As Long = (CONTEXT_i386 Or &H8)
- Public Const CONTEXT_DEBUG_REGISTERS As Long = (CONTEXT_i386 Or &H10)
- Public Const CONTEXT_EXTENDED_REGISTERS As Long = (CONTEXT_i386 Or &H20)
- Public Const CONTEXT_FULL As Long = (CONTEXT_CONTROL Or CONTEXT_INTEGER Or CONTEXT_SEGMENTS)
- Public Const CONTEXT_ALL As Long = (CONTEXT_CONTROL Or CONTEXT_INTEGER Or CONTEXT_SEGMENTS Or CONTEXT_FLOATING_POINT Or CONTEXT_DEBUG_REGISTERS Or CONTEXT_EXTENDED_REGISTERS)
- Public Function TaTerminateThread(ByVal hThread As Long) As Long
- Dim ctx As CONTEXT
- Dim Ret As Long, hApiAddr As Long, hModule As Long
- ctx.ContextFlags = CONTEXT_ALL
- hModule = GetModuleHandle("kernel32.dll")
- hApiAddr = GetProcAddress(hModule, "ExitThread")
- ctx.Eip = hApiAddr
- ctx.Eax = 0
- ctx.Ebp = 0
- ctx.Ebx = 0
- ctx.Ecx = 0
- ctx.Edi = 0
- ctx.Edx = 0
- ctx.Esi = 0
- Call NtSuspendThread(hThread, Ret)
- TaTerminateThread = IIf(NtSetContextThread(hThread, ctx), 0, 1)
- Call NtResumeThread(hThread, Ret)
- End Function
- Public Sub TaKillThread(ByVal dwThreadId As Long)
- Dim hThread As Long
- hThread = TaOpenThread(dwThreadId)
- If hThread <> 0 Then
- TaTerminateThread (hThread)
- End If
- End Sub
复制代码 |
|