Adam Caudill

Security Leader, Researcher, Developer, Writer, & Photographer

CloseApp

This post was imported from an old blog archive, and predates the creation of AdamCaudill.com.

This is a useful function to close a program based on a windows caption, this should work for any top-level window. Paste all this into a standard module, save it. Then call CloseApp("Notepad") or whatever the name of the window is, it’s nice & simple and should close the program instantly.

This requires Windows 2000 plus, for older versions of Windows a different method is required, that isn’t covered here, seeing as Windows 2000 and better require special privileges to forcefully close a program.

(Note: your user account must have ‘Debug’ privileges for this code to work, this means if you aren’t an administrator or a member of the ‘Debuggers’ group, this code will fail to execute).

The Code:

Option Explicit

Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal hHandle As Long, ByVal dwMilliseconds As Long) As Long
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare Function PostMessage Lib "user32" Alias "PostMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function IsWindow Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function TerminateProcess Lib "kernel32" (ByVal hProcess As Long, ByVal uExitCode As Long) As Long
Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) 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 GetCurrentProcess Lib "kernel32" () As Long
Private Declare Function OpenProcessToken Lib "advapi32.dll" (ByVal ProcessHandle As Long, ByVal DesiredAccess As Long, TokenHandle As Long) As Long
Private Declare Function LookupPrivilegeValue Lib "advapi32.dll" Alias "LookupPrivilegeValueA" (ByVal lpSystemName As String, ByVal lpName As String, lpLuid As LUID) As Long
Private Declare Function AdjustTokenPrivileges Lib "advapi32.dll" (ByVal TokenHandle As Long, ByVal DisableAllPrivileges As Long, NewState As TOKEN_PRIVILEGES, ByVal BufferLength As Long, PreviousState As TOKEN_PRIVILEGES, ReturnLength As Long) As Long

Const WM_CLOSE = &H10
Const INFINITE = &HFFFFFFFF
Const PROCESS_ALL_ACCESS = &H1F0FFF
Const TOKEN_ADJUST_PRIVILEGES = &H20
Const TOKEN_QUERY = &H8
Const ANYSIZE_ARRAY = 1
Const SE_DEBUG_NAME = "SeDebugPrivilege"
Const SE_PRIVILEGE_ENABLED = &H2

Type LARGE_INTEGER
    lowpart As Long
    highpart As Long
End Type

Type LUID
    lowpart As Long
    highpart As Long
End Type

Type LUID_AND_ATTRIBUTES
    pLuid As LUID
    Attributes As Long
End Type

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

Public Sub CloseApp(strTitle As String)
    Dim hWindow As Long
    Dim lngResult As Long
    Dim lngReturnValue As Long
    Dim lngProcessH As Long
    Dim hToken As Long
    Dim hProcess As Long
    Dim hProcessID As Long
    Dim lResult As Long
    hWindow = FindWindow(vbNullString, strTitle)
    lngReturnValue = PostMessage(hWindow, WM_CLOSE, vbNull, vbNull)
    lngResult = WaitForSingleObject(hWindow, INFINITE)
    'Does the handle still exist?
    DoEvents
    hWindow = FindWindow(vbNullString, strTitle)
    If IsWindow(hWindow) = 1 Then
        hProcess = GetCurrentProcess
        lngReturnValue = GetWindowThreadProcessId(hWindow, hProcessID)
        lResult = OpenProcessToken(hProcess, TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY, hToken)
        If lResult = 0 Then
            Exit Sub
        End If
        lResult = SetPrivilege(hToken, SE_DEBUG_NAME, True)
        If lResult = False Then
            Exit Sub
        End If
        lngProcessH = OpenProcess(PROCESS_ALL_ACCESS, 0&, hProcessID)
        lResult = SetPrivilege(hToken, SE_DEBUG_NAME, False)
        If lResult = False Then
            Exit Sub
        End If
        lngReturnValue = TerminateProcess(lngProcessH, 0&)
        DoEvents
    End If
End Sub

Private Function SetPrivilege(hToken As Long, Privilege As String, bSetFlag As Boolean) As Boolean
    Dim TP As TOKEN_PRIVILEGES          ' Used in getting the current
    ' token privileges
    Dim TPPrevious As TOKEN_PRIVILEGES  ' Used in setting the new
    ' token privileges
    Dim LUID As LUID                    ' Stores the Local Unique
    ' Identifier - refer to MSDN
    Dim cbPrevious As Long              ' Previous size of the
    ' TOKEN_PRIVILEGES structure
    Dim lResult As Long                 ' Result of various API calls
    ' Grab the size of the TOKEN_PRIVILEGES structure,
    ' used in making the API calls.
    cbPrevious = Len(TP)
    ' Grab the LUID for the request privilege.
    lResult = LookupPrivilegeValue("", Privilege, LUID)
    ' If LoopupPrivilegeValue fails, the return result will be zero.
    ' Test to make sure that the call succeeded.
    If (lResult = 0) Then
        SetPrivilege = False
    End If
    ' Set up basic information for a call.
    ' You want to retrieve the current privileges
    ' of the token under concern before you can modify them.
    TP.PrivilegeCount = 1
    TP.Privileges(0).pLuid = LUID
    TP.Privileges(0).Attributes = 0
    SetPrivilege = lResult
    ' You need to acquire the current privileges first
    lResult = AdjustTokenPrivileges(hToken, -1, TP, Len(TP), _
        TPPrevious, cbPrevious)
    ' If AdjustTokenPrivileges fails, the return result is zero,
    ' test for success.
    If (lResult = 0) Then
        SetPrivilege = False
    End If
    ' Now you can set the token privilege information
    ' to what the user is requesting.
    TPPrevious.PrivilegeCount = 1
    TPPrevious.Privileges(0).pLuid = LUID
    ' either enable or disable the privilege,
    ' depending on what the user wants.
    Select Case bSetFlag
        Case True: TPPrevious.Privileges(0).Attributes = _
            TPPrevious.Privileges(0).Attributes Or _
            (SE_PRIVILEGE_ENABLED)
        Case False: TPPrevious.Privileges(0).Attributes = _
            TPPrevious.Privileges(0).Attributes Xor _
            (SE_PRIVILEGE_ENABLED And _
            TPPrevious.Privileges(0).Attributes)
    End Select
    ' Call adjust the token privilege information.
    lResult = AdjustTokenPrivileges(hToken, -1, TPPrevious, _
        cbPrevious, TP, cbPrevious)
    ' Determine your final result of this function.
    If (lResult = 0) Then
        ' You were not able to set the privilege on this token.
        SetPrivilege = False
    Else
        ' You managed to modify the token privilege
        SetPrivilege = True
    End If
End Function

Adam Caudill


Related Posts

  • APISettings

    This post was imported from an old blog archive, and predates the creation of AdamCaudill.com. Visual Basic provides a less than elegant method of saving data in the Windows registry, the GetSetting & SaveSetting functions. These functions store setting in HKEY_CURRENT_USER\Software\VB and VBA Program Settings\<AppName>\<Section> not very pretty is it? The APISettings module is a drop-in replacement using pure Win32 API for its processing power and increased stability. The reason for developing this and for making it drop-in compatible is to all those new to the Win32 API to add its functionality with minimal difficulty.

  • Conexant (formerly Rockwell) Softmodem HSF Modem

    This post was imported from an old blog archive, and predates the creation of AdamCaudill.com. I was actually rather lucky to have this brand of WinModem, as the good people over at Linuxant.com offer a very high quality driver that makes installation a breeze! But, they have recently changed their marketing methods and charge $15 for the driver, so these really lives no viable, free alternative (a rarity to say the least for linux).

  • Back From New York

    This post was imported from an old blog archive, and predates the creation of AdamCaudill.com. Wow, the summer’s over and I’m finally home! After spending the last five months in New York (quite a difference from my native Florida), I’ve finally made it back home. Much has happened while I’ve been away, not the least of which is the death of Imspire and a few related projects. While giving up on these dreams has been difficult, I believe the result will be for the best.

  • Trojan Source and Why It Matters

    Yesterday the news hit of a new vulnerability that threatens the security of all code; dubbed Trojan Source by the researchers from the University of Cambridge. From an initial analysis, it does seem to impact just about everything, and the status of fixes is very hit or miss at this point. But the real question is, does this even matter? Is this issue worth spending your time on? Let’s look closer.

  • Juniper, Backdoors, and Code Reviews

    Researchers are still working to understand the impact of the Juniper incident – the details of how the VPN traffic decryption backdoor are still not fully understood. That such devastating backdoors could make it in to such a security-critical product, and remain for years undetected has shocked many (and pushed many others deeper into their cynicism). There are though, some questions that are far more important in the long run: