一个很强大的killprocess - VB

VB编程 blackfeather

 

结束进程有N^N种方法,比较常见的就是openprocess 然后terminateprocess,

hPro = OpenProcess(1&, -1&, pid)

TerminateProcess hPro, 0&

CloseHandle hPro

最简单的代码,对付一般的进程还可以,但是遇到一些变态的或者系统进程就比较无奈。翻了翻硬盘,找到一个杀进程的代码,貌似由炉子大仙写的,我整理了一下代码,做成了模块,贴出来

代码:

Option Explicit

Private Declare Function AdjustTokenPrivileges _
                Lib "advapi32.dll" (ByVal TokenHandle As Long, _
                                    ByVal DisableAllPriv As Long, _
                                    ByRef NewState As TOKEN_PRIVILEGES, _
                                    ByVal BufferLength As Long, _
                                    ByRef PreviousState As TOKEN_PRIVILEGES, _
                                    ByRef pReturnLength As Long) As Long
Private Declare Function GetCurrentProcess _
                Lib "kernel32" () As Long
Private Declare Function LookupPrivilegeValue _
                Lib "advapi32.dll" _
                Alias "LookupPrivilegeValueA" (ByVal lpSystemName As Any, _
                                               ByVal lpName As String, _
                                               lpLuid As LUID) As Long
Private Declare Function OpenProcessToken _
                Lib "advapi32.dll" (ByVal ProcessHandle As Long, _
                                    ByVal DesiredAccess As Long, _
                                    TokenHandle As Long) As Long

Private Type MEMORY_CHUNKS
        Address As Long
        pData As Long
        Length As Long
End Type
Private Type LUID
        UsedPart As Long
        IgnoredForNowHigh32BitPart As Long
End Type '

Private Type TOKEN_PRIVILEGES
        PrivilegeCount As Long
        TheLuid As LUID
        Attributes As Long
End Type
Private Const SE_CREATE_TOKEN = "SeCreateTokenPrivilege"
Private Const SE_ASSIGNPRIMARYTOKEN = "SeAssignPrimaryTokenPrivilege"
Private Const SE_LOCK_MEMORY = "SeLockMemoryPrivilege"
Private Const SE_INCREASE_QUOTA = "SeIncreaseQuotaPrivilege"
Private Const SE_UNSOLICITED_INPUT = "SeUnsolicitedInputPrivilege"
Private Const SE_MACHINE_ACCOUNT = "SeMachineAccountPrivilege"
Private Const SE_TCB = "SeTcbPrivilege"
Private Const SE_SECURITY = "SeSecurityPrivilege"
Private Const SE_TAKE_OWNERSHIP = "SeTakeOwnershipPrivilege"
Private Const SE_LOAD_DRIVER = "SeLoadDriverPrivilege"
Private Const SE_SYSTEM_PROFILE = "SeSystemProfilePrivilege"
Private Const SE_SYSTEMTIME = "SeSystemtimePrivilege"
Private Const SE_PROF_SINGLE_PROCESS = "SeProfileSingleProcessPrivilege"
Private Const SE_INC_BASE_PRIORITY = "SeIncreaseBasePriorityPrivilege"
Private Const SE_CREATE_PAGEFILE = "SeCreatePagefilePrivilege"
Private Const SE_CREATE_PERMANENT = "SeCreatePermanentPrivilege"
Private Const SE_BACKUP = "SeBackupPrivilege"
Private Const SE_RESTORE = "SeRestorePrivilege"
Private Const SE_SHUTDOWN = "SeShutdownPrivilege"
Private Const SE_DEBUG = "SeDebugPrivilege"
Private Const SE_AUDIT = "SeAuditPrivilege"
Private Const SE_SYSTEM_ENVIRONMENT = "SeSystemEnvironmentPrivilege"
Private Const SE_CHANGE_NOTIFY = "SeChangeNotifyPrivilege"
Private Const SE_REMOTE_SHUTDOWN = "SeRemoteShutdownPrivilege"
Private Const SE_PRIVILEGE_ENABLED As Long = &H2
Private Const TOKEN_QUERY As Long = &H8
Private Const TOKEN_ADJUST_PRIVILEGES As Long = &H20

Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Const LVM_FIRST As Long = &H1000
Private Const LVS_EX_FULLROWSELECT As Long = &H20
Private Const LVM_SETEXTENDEDLISTVIEWSTYLE As Long = LVM_FIRST + 54
Private Const LVM_GETEXTENDEDLISTVIEWSTYLE As Long = LVM_FIRST + 55

Private Enum SYSTEM_INFORMATION_CLASS
        SystemBasicInformation
        SystemProcessorInformation             '// obsolete...delete
        SystemPerformanceInformation
        SystemTimeOfDayInformation
        SystemPathInformation
        SystemProcessInformation
        SystemCallCountInformation
        SystemDeviceInformation
        SystemProcessorPerformanceInformation
        SystemFlagsInformation
        SystemCallTimeInformation
        SystemModuleInformation
        SystemLocksInformation
        SystemStackTraceInformation
        SystemPagedPoolInformation
        SystemNonPagedPoolInformation
        SystemHandleInformation
        SystemObjectInformation
        SystemPageFileInformation
        SystemVdmInstemulInformation
        SystemVdmBopInformation
        SystemFileCacheInformation
        SystemPoolTagInformation
        SystemInterruptInformation
        SystemDpcBehaviorInformation
        SystemFullMemoryInformation
        SystemLoadGdiDriverInformation
        SystemUnloadGdiDriverInformation
        SystemTimeAdjustmentInformation
        SystemSummaryMemoryInformation
        SystemMirrorMemoryInformation
        SystemPerformanceTraceInformation
        SystemObsolete0
        SystemExceptionInformation
        SystemCrashDumpStateInformation
        SystemKernelDebuggerInformation
        SystemContextSwitchInformation
        SystemRegistryQuotaInformation
        SystemExtendServiceTableInformation
        SystemPrioritySeperation
        SystemVerifierAddDriverInformation
        SystemVerifierRemoveDriverInformation
        SystemProcessorIdleInformation
        SystemLegacyDriverInformation
        SystemCurrentTimeZoneInformation
        SystemLookasideInformation
        SystemTimeSlipNotification
        SystemSessionCreate
        SystemSessionDetach
        SystemSessionInformation
        SystemRangeStartInformation
        SystemVerifierInformation
        SystemVerifierThunkExtend
        SystemSessionProcessInformation
        SystemLoadGdiDriverInSystemSpace
        SystemNumaProcessorMap
        SystemPrefetcherInformation
        SystemExtendedProcessInformation
        SystemRecommendedSharedDataAlignment
        SystemComPlusPackage
        SystemNumaAvailableMemory
        SystemProcessorPowerInformation
        SystemEmulationBasicInformation
        SystemEmulationProcessorInformation
        SystemExtendedHandleInformation
        SystemLostDelayedWriteInformation
        SystemBigPoolInformation
        SystemSessionPoolTagInformation
        SystemSessionMappedViewInformation
        SystemHotpatchInformation
        SystemObjectSecurityMode
        SystemWatchdogTimerHandler
        SystemWatchdogTimerInformation
        SystemLogicalProcessorInformation
        SystemWow64SharedInformation
        SystemRegisterFirmwareTableInformationHandler
        SystemFirmwareTableInformation
        SystemModuleInformationEx
        SystemVerifierTriageInformation
        SystemSuperfetchInformation
        SystemMemoryListInformation
        SystemFileCacheInformationEx
        MaxSystemInfoClass  '// MaxSystemInfoClass should always be the last enum
End Enum
Private Declare Function ZwQuerySystemInformation _
                Lib "NTDLL.DLL" (ByVal SystemInformationClass As SYSTEM_INFORMATION_CLASS, _
                                 ByVal pSystemInformation As Long, _
                                 ByVal SystemInformationLength As Long, _
                                 ByRef ReturnLength As Long) As Long
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 SYSTEM_HANDLE_INFORMATION
        NumberOfHandles As Long
        Handles(1 To 1) As SYSTEM_HANDLE_TABLE_ENTRY_INFO
End Type
Private Const STATUS_INFO_LENGTH_MISMATCH = &HC0000004
Private Const STATUS_ACCESS_DENIED = &HC0000022
Private Declare Function ZwWriteVirtualMemory _
               Lib "NTDLL.DLL" (ByVal ProcessHandle As Long, _
                                ByVal BaseAddress As Long, _
                                ByVal pBuffer As Long, _
                                ByVal NumberOfBytesToWrite As Long, _
                                ByRef NumberOfBytesWritten As Long) As Long
Private Declare Function ZwOpenProcess _
               Lib "NTDLL.DLL" (ByRef ProcessHandle As Long, _
                                ByVal AccessMask As Long, _
                                ByRef ObjectAttributes As OBJECT_ATTRIBUTES, _
                                ByRef ClientId As CLIENT_ID) As Long
Private Type OBJECT_ATTRIBUTES
        Length As Long
        RootDirectory As Long
        ObjectName As Long 'PUNICODE_STRING 的指针
        Attributes As Long
        SecurityDescriptor As Long
        SecurityQualityOfService As Long
End Type
Private Type CLIENT_ID
        UniqueProcess As Long
        UniqueThread  As Long
End Type
Private Const PROCESS_QUERY_INFORMATION As Long = &H400
Private Const STATUS_INVALID_CID As Long = &HC000000B
Private Declare Function ZwClose _
               Lib "NTDLL.DLL" (ByVal ObjectHandle As Long) As Long
Private Const ZwGetCurrentProcess As Long = -1 '//0xFFFFFFFF
Private Const ZwGetCurrentThread As Long = -2 '//0xFFFFFFFE
Private Const ZwCurrentProcess As Long = ZwGetCurrentProcess
Private Const ZwCurrentThread As Long = ZwGetCurrentThread
Private Declare Function ZwCreateJobObject _
               Lib "NTDLL.DLL" (ByRef JobHandle As Long, _
                                ByVal DesiredAccess As Long, _
                                ByRef ObjectAttributes As OBJECT_ATTRIBUTES) As Long
Private Declare Function ZwAssignProcessToJobObject _
               Lib "NTDLL.DLL" (ByVal JobHandle As Long, _
                                ByVal ProcessHandle As Long) As Long
Private Declare Function ZwTerminateJobObject _
               Lib "NTDLL.DLL" (ByVal JobHandle As Long, _
                                ByVal ExitStatus As Long) As Long
Private Const OBJ_INHERIT = &H2
Private Const STANDARD_RIGHTS_REQUIRED As Long = &HF0000
Private Const SYNCHRONIZE As Long = &H100000
Private Const JOB_OBJECT_ALL_ACCESS As Long = STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or &H1F
Private Const PROCESS_DUP_HANDLE As Long = &H40
Private Const PROCESS_ALL_ACCESS As Long = (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or &HFFF)
Private Const THREAD_ALL_ACCESS As Long = (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or &H3FF)
Private Const OB_TYPE_PROCESS As Long = &H5 '// hard code
Private Type PROCESS_BASIC_INFORMATION
        ExitStatus As Long 'NTSTATUS
        PebBaseAddress As Long 'PPEB
        AffinityMask As Long 'ULONG_PTR
        BasePriority As Long 'KPRIORITY
        UniqueProcessId As Long 'ULONG_PTR
        InheritedFromUniqueProcessId As Long 'ULONG_PTR
End Type
Private Declare Function ZwDuplicateObject _
               Lib "NTDLL.DLL" (ByVal SourceProcessHandle As Long, _
                                ByVal SourceHandle As Long, _
                                ByVal TargetProcessHandle As Long, _
                                ByRef TargetHandle As Long, _
                                ByVal DesiredAccess As Long, _
                                ByVal HandleAttributes As Long, _
                                ByVal Options As Long) As Long
Private Const DUPLICATE_CLOSE_SOURCE = &H1            '// winnt
Private Const DUPLICATE_SAME_ACCESS = &H2                '// winnt
Private Const DUPLICATE_SAME_ATTRIBUTES = &H4
Private Declare Function ZwQueryInformationProcess _
               Lib "NTDLL.DLL" (ByVal ProcessHandle As Long, _
                                ByVal ProcessInformationClass As PROCESSINFOCLASS, _
                                ByVal ProcessInformation As Long, _
                                ByVal ProcessInformationLength As Long, _
                                ByRef ReturnLength As Long) As Long
Private Enum PROCESSINFOCLASS
        ProcessBasicInformation
        ProcessQuotaLimits
        ProcessIoCounters
        ProcessVmCounters
        ProcessTimes
        ProcessBasePriority
        ProcessRaisePriority
        ProcessDebugPort
        ProcessExceptionPort
        ProcessAccessToken
        ProcessLdtInformation
        ProcessLdtSize
        ProcessDefaultHardErrorMode
        ProcessIoPortHandlers           '// Note: this is kernel mode only
        ProcessPooledUsageAndLimits
        ProcessWorkingSetWatch
        ProcessUserModeIOPL
        ProcessEnableAlignmentFaultFixup
        ProcessPriorityClass
        ProcessWx86Information
        ProcessHandleCount
        ProcessAffinityMask
        ProcessPriorityBoost
        ProcessDeviceMap
        ProcessSessionInformation
        ProcessForegroundInformation
        ProcessWow64Information
        ProcessImageFileName
        ProcessLUIDDeviceMapsEnabled
        ProcessBreakOnTermination
        ProcessDebugObjectHandle
        ProcessDebugFlags
        ProcessHandleTracing
        ProcessIoPriority
        ProcessExecuteFlags
        ProcessResourceManagement
        ProcessCookie
        ProcessImageInformation
        MaxProcessInfoClass             '// MaxProcessInfoClass should always be the last enum
End Enum
Private Const STATUS_SUCCESS As Long = &H0
Private Const STATUS_INVALID_PARAMETER As Long = &HC000000D
Private Declare Function EnumProcesses _
                Lib "psapi.dll" (ByVal lpidProcess As Long, _
                                 ByVal cb As Long, _
                                 ByRef cbNeeded As Long) As Long
Private Declare Function Api_GetProcessImageFileName Lib "psapi.dll" Alias "GetProcessImageFileNameA" (ByVal hProcess As Long, ByVal lpImageFileName As String, ByVal nSize As Long) As Long
Private Declare Function EnumProcessModules Lib "psapi.dll" (ByVal hProcess As Long, ByRef lphModule As Long, ByVal cb As Long, ByRef lpcbNeeded As Long) As Long
Private Declare Function GetModuleFileNameEx Lib "psapi.dll" Alias "GetModuleFileNameExA" (ByVal hProcess As Long, ByVal hModule As Long, ByVal lpFileName As String, ByVal nSize As Long) As Long
Private Declare Function ZwTerminateProcess _
               Lib "NTDLL.DLL" (ByVal ProcessHandle As Long, _
                                ByVal ExitStatus As Long) As Long
Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)

Private Function NT_SUCCESS(ByVal Status As Long) As Boolean
        NT_SUCCESS = (Status >= 0)
End Function

Private Sub CopyMemory(ByVal Dest As Long, ByVal Src As Long, ByVal cch As Long)
Dim Written As Long
        Call ZwWriteVirtualMemory(ZwCurrentProcess, Dest, Src, cch, Written)
End Sub

Private Function IsItemInArray(ByVal dwItem, ByRef dwArray() As Long) As Boolean
Dim Index As Long
        For Index = LBound(dwArray) To UBound(dwArray)
                If (dwItem = dwArray(Index)) Then IsItemInArray = True: Exit Function '// found
        Next
        IsItemInArray = False
End Function

Private Sub AddItemToArray(ByVal dwItem As Long, ByRef dwArray() As Long)
On Error GoTo ErrHdl

        If (IsItemInArray(dwItem, dwArray)) Then Exit Sub '// found
       
        ReDim Preserve dwArray(UBound(dwArray) + 1)
        dwArray(UBound(dwArray)) = dwItem
ErrHdl:
       
End Sub


Private Function EnablePrivilege(ByVal seName As String) As Boolean
        On Error Resume Next
        Dim p_lngRtn As Long
        Dim p_lngToken As Long
        Dim p_lngBufferLen As Long
        Dim p_typLUID As LUID
        Dim p_typTokenPriv As TOKEN_PRIVILEGES
        Dim p_typPrevTokenPriv As TOKEN_PRIVILEGES
        p_lngRtn = OpenProcessToken(GetCurrentProcess(), TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY, p_lngToken)

        If p_lngRtn = 0 Then
                EnablePrivilege = False
                Exit Function
        End If

        If Err.LastDllError <> 0 Then
                EnablePrivilege = False
                Exit Function
        End If

        p_lngRtn = LookupPrivilegeValue(0&, seName, p_typLUID)

        If p_lngRtn = 0 Then
                EnablePrivilege = False
                Exit Function
        End If

        p_typTokenPriv.PrivilegeCount = 1
        p_typTokenPriv.Attributes = SE_PRIVILEGE_ENABLED
        p_typTokenPriv.TheLuid = p_typLUID
        EnablePrivilege = (AdjustTokenPrivileges(p_lngToken, False, p_typTokenPriv, Len(p_typPrevTokenPriv), p_typPrevTokenPriv, p_lngBufferLen) <> 0)
End Function

'函数需要 SE_DEBUG 特权。
'FlowerCode 的方法
'dwDesiredAccess: 需要的访问权
'bInhert: 句柄可以继承
'ProcessId: 进程 ID

Private Function OpenProcess(ByVal dwDesiredAccess As Long, ByVal bInhert As Boolean, ByVal ProcessId As Long) As Long
        Dim st As Long
        Dim cid As CLIENT_ID
        Dim oa As OBJECT_ATTRIBUTES
        Dim NumOfHandle As Long
        Dim pbi As PROCESS_BASIC_INFORMATION
        Dim I As Long
        Dim hProcessToDup As Long, hProcessCur As Long, hProcessToRet As Long
        oa.Length = Len(oa)
        If (bInhert) Then oa.Attributes = oa.Attributes Or OBJ_INHERIT
        cid.UniqueProcess = ProcessId + 1 '// 呵呵.
        st = ZwOpenProcess(hProcessToRet, dwDesiredAccess, oa, cid)
        If (NT_SUCCESS(st)) Then OpenProcess = hProcessToRet: Exit Function
        st = STATUS_SUCCESS
        Dim bytBuf() As Byte
        Dim arySize As Long: arySize = &H20000 '// 128KB
        Do
                ReDim bytBuf(arySize)
                st = ZwQuerySystemInformation(SystemHandleInformation, VarPtr(bytBuf(0)), arySize, 0&)
                If (Not NT_SUCCESS(st)) Then
                        If (st <> STATUS_INFO_LENGTH_MISMATCH) Then
                                Erase bytBuf
                                Exit Function
                        End If
                Else
                        Exit Do
                End If

                arySize = arySize * 2
                ReDim bytBuf(arySize)
        Loop
        NumOfHandle = 0
        Call CopyMemory(VarPtr(NumOfHandle), VarPtr(bytBuf(0)), Len(NumOfHandle))
        Dim h_info() As SYSTEM_HANDLE_TABLE_ENTRY_INFO
        ReDim h_info(NumOfHandle)
        Call CopyMemory(VarPtr(h_info(0)), VarPtr(bytBuf(0)) + Len(NumOfHandle), Len(h_info(0)) * NumOfHandle)
        For I = LBound(h_info) To UBound(h_info)
                With h_info(I)
                        If (.ObjectTypeIndex = OB_TYPE_PROCESS) Then 'OB_TYPE_PROCESS is hardcode, you'd better get it dynamiclly
                                cid.UniqueProcess = .UniqueProcessId
                                st = ZwOpenProcess(hProcessToDup, PROCESS_DUP_HANDLE, oa, cid)
                                If (NT_SUCCESS(st)) Then
                                        st = ZwDuplicateObject(hProcessToDup, .HandleValue, ZwCurrentProcess, hProcessCur, PROCESS_ALL_ACCESS, 0, DUPLICATE_SAME_ATTRIBUTES)
                                        If (NT_SUCCESS(st)) Then
                                                st = ZwQueryInformationProcess(hProcessCur, ProcessBasicInformation, VarPtr(pbi), Len(pbi), 0)
                                                If (NT_SUCCESS(st)) Then
                                                        If (pbi.UniqueProcessId = ProcessId) Then
                                                                st = ZwDuplicateObject(hProcessToDup, .HandleValue, ZwGetCurrentProcess, hProcessToRet, dwDesiredAccess, OBJ_INHERIT, DUPLICATE_SAME_ATTRIBUTES)
                                                                If (NT_SUCCESS(st)) Then OpenProcess = hProcessToRet
                                                        End If
                                                End If
                                        End If
                                        st = ZwClose(hProcessCur)
                                End If
                                st = ZwClose(hProcessToDup)
                        End If
                End With
        Next
        Erase h_info
End Function

'ret val: bSuccess
'willy123 的方法
'hProcess: 进程句柄
'ExitStatus: 退出状态

Private Function TerminateProcess(ByVal hProcess As Long, ByVal ExitStatus As Long) As Boolean
        Dim st As Long
        Dim hJob As Long
        Dim oa As OBJECT_ATTRIBUTES
        TerminateProcess = False
        oa.Length = Len(oa)
        st = ZwCreateJobObject(hJob, JOB_OBJECT_ALL_ACCESS, oa)
        If (NT_SUCCESS(st)) Then
                st = ZwAssignProcessToJobObject(hJob, hProcess)
                If (NT_SUCCESS(st)) Then
                        st = ZwTerminateJobObject(hJob, ExitStatus)
                        If (NT_SUCCESS(st)) Then TerminateProcess = True
                End If
                ZwClose (hJob)
        End If
End Function


Public Function TerminateProc(ByVal pid As Long) As Boolean

Dim hproc As Long
hproc = OpenProcess(PROCESS_ALL_ACCESS, False, pid)
TerminateProc = TerminateProcess(hproc, 0)
ZwClose (hproc)

End Function

 


调用方式 TerminateProc 进程PID ,至于怎么获得PID就不说了

 

 

评论列表:

发表评论: