VB怎么得到打开的程序的标题并且显示

VB怎么得到打开的程序的标题并且显示,第1张

利用API

Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long

Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long

查找你指定类名或窗口标题的窗口。

或者你使用 EnumWindows 枚举顶级窗口,使用 EnumChildWindows 枚举子窗口,或者使用 EnumThreadWindows 枚举与某个线程关联的所有非子窗口。

以记事本为例,系统中有多个记事本在运行。

模块代码:

Public Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long

Public Declare Function EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long

Public Declare Function IsWindowVisible Lib "user32" (ByVal hwnd As Long) As Long

Public Const GW_OWNER = 4

Public Declare Function GetWindow Lib "user32" (ByVal hwnd As Long, ByVal wCmd As Long) As Long

Public WndCaption As String

Public Function EnumWindowsProc(ByVal hwnd As Long, ByVal lParam As Long) As Boolean

Dim S As String

Dim a As Long

Dim v As Long

S = String(255, 0)

Call GetWindowText(hwnd, S, 255)

S = Left(S, InStr(S, Chr(0)) - 1)

v = GetWindow(hwnd, GW_OWNER)

a = IsWindowVisible(hwnd)

If Len(S) > 0 And a <> 0 And v = 0 And Right(S, 3) = "记事本" Then

WndCaption = WndCaption & S & vbCrLf

End If

EnumWindowsProc = True

End Function

窗体代码:

Private Sub Command1_Click()

EnumWindows AddressOf EnumWindowsProc, 0&

MsgBox WndCaption

End Sub

我在这里告诉楼上的几位朋友,这是完全可能的,因为此前我研究过这个问题,经过几番周折已经找出了方法,今天又经过几番周折我把核心部分摘出来了。

注:不要怪楼上几位朋友,因为这的确是个很复杂的过程,网上也找不到实例(我之前找了很久,没找到才自己动手),几乎是用API堆出来的。

'一模块,一窗体,一文本框(用于输入进程名),一列表框(用于显示所有标题),一命令按钮(开始)

'模块部分

Public Declare Function EnumWindows Lib "user32" _

(ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long

'枚举窗口

Public Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" _

(ByVal hWnd As Long, ByVal lpString As String, ByVal cch As Long) As Long

'获取窗口标题

Public Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" _

(ByVal hWnd As Long) As Long

'获取窗口标题长度

Public Declare Function Process32First Lib "kernel32" (ByVal hSnapshot As Long, lppe As PROCESSENTRY32) As Long

Public Declare Function Process32Next Lib "kernel32" (ByVal hSnapshot As Long, lppe As PROCESSENTRY32) As Long

Public Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hWnd As Long, lpdwProcessId As Long) As Long

Public Declare Function CreateToolhelp32Snapshot Lib "kernel32" (ByVal dwFlags As Long, ByVal th32ProcessID As Long) As Long

Public Declare Function IsWindowEnabled Lib "user32" (ByVal hWnd As Long) As Long

Public Declare Function IsWindowVisible Lib "user32" (ByVal hWnd As Long) As Long

Public Declare Function IsWindow Lib "user32" (ByVal hWnd As Long) As Long

Public Declare Function ShowWindow Lib "user32" (ByVal hWnd As Long, ByVal nCmdShow As Long) As Long

Public Type PROCESSENTRY32

dwSize As Long

cntUsage As Long

th32ProcessID As Long

th32DefaultHeapID As Long

th32ModuleID As Long

cntThreads As Long

th32ParentProcessID As Long

pcPriClassBase As Long

dwFlags As Long

szExeFile As String 1024

End Type

Public hwn As Long, SSS As String

Public Function EnumWindowsProc(ByVal hWnd As Long, ByVal lParam As Long) As Long '回调函数

Dim sSave As String, Ret As Long, windowProcessId As Long

Ret = GetWindowTextLength(hWnd)

sSave = Space(Ret)

GetWindowText hWnd, sSave, Ret + 1

GetWindowThreadProcessId hWnd, windowProcessId

If windowProcessId = Form1pid Then

If IsWindowEnabled(hWnd) = 1 Then

hwn = hWnd

SSS = SSS & hWnd & "|" '存储所有相关句柄进字符串sss

End If

End If

EnumWindowsProc = 2

End Function

Public Sub draw()

EnumWindows AddressOf EnumWindowsProc, ByVal 0&

End Sub

'窗体部分

Const TH32CS_SNAPHEAPLIST = &H1

Const TH32CS_SNAPPROCESS = &H2

Const TH32CS_SNAPTHREAD = &H4

Const TH32CS_SNAPMODULE = &H8

Const TH32CS_SNAPALL = (TH32CS_SNAPHEAPLIST Or TH32CS_SNAPPROCESS Or TH32CS_SNAPTHREAD Or TH32CS_SNAPMODULE)

Const TH32CS_INHERIT = &H80000000

Public pid As Long

Dim pname As String

Dim a As String, hw As Long

'原创函数,返回字符串中字串个数

Function lon(st As String, sr As String) As Long

Dim f As Long, g As Long

For f = 1 To Len(st)

If Mid(st, f, Len(sr)) = sr Then g = g + 1

lon = g

Next f

End Function

'原创函数:返回字符串中第几段字符。例:quduan("23,43,5,23",",",2)=43

Function quduan(pli As String, pl As String, n As Long) As String '取字符串指定段

Dim j As Integer

For i = 1 To Len(pli)

If Mid(pli, i, Len(pl)) = pl Then j = j + 1

Next i

Dim a() As String

a() = Split(pli, pl)

If n > j + 1 Then quduan = "": Exit Function

quduan = a(n - 1)

End Function

Private Sub Command1_Click()

a = LCase(Text1) 'text1为程序名,如notepadexe

Dim my As PROCESSENTRY32

Dim l As Long, l1 As Long, flag As Boolean, mName As String, i As Integer

Dim st As Long, mt As Long, it As Long, jt As Long, nt As String '筛选窗口变量列表

l = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)

If l Then mydwSize = 1060

If (Process32First(l, my)) Then '遍历第一个进程

Do

i = InStr(1, myszExeFile, Chr(0)) '返回chr(0)在各个进程中出现的位置

mName = LCase(Left(myszExeFile, i - 1)) '返回小写的(返回i-1的前n个字符,即正确的名称)

If mName = a Then pid = myth32ProcessID '得到启动程序PID

Loop Until (Process32Next(l, my) < 1)

End If

draw '模块过程用于枚举窗口句柄与PID对比

'筛选主程序有效窗口

If SSS <> "" Then 'sss为所得主程序句柄集合

Do While it <= lon(SSS, "|")

it = it + 1

st = Val(quduan(SSS, "|", it))

jt = GetWindowTextLength(st)

nt = Space(jt)

GetWindowText st, nt, jt + 1

List1AddItem nt '加载此程序下所有窗体的标题

If nt <> "" And IsWindowVisible(st) = 1 And IsWindow(st) = 1 And IsWindowEnabled(st) = 1 Then

ShowWindow st, 1 '显示可显示的窗口

End If

Loop

End If

End Sub

可获得所有标题,可调出主窗口,通常进程都有好多隐藏的各种各样的窗口,我拿QQ测试发现有17个隐藏窗口

首先找到需要查找的窗体句柄,然后用GetWindowText来获得窗体标题。如果GetWindowText函数的句柄是窗体内的一个子窗体,则可以获得子窗体的文字信息,子窗体可以是一个按钮,则可以获得按钮上的文字。

如果不知道目标窗体的句柄,不知道窗体的标题和Class名称,就不能用FindWindow来查找窗体句柄,这时可以用EnumWindows枚举出所有的窗体,然后依次查找窗体标题,直到找到想要的为止。

下面是一个枚举所有窗体名称的例子

'

'窗体代码:Form1frm

'

Option Explicit

Private Sub Command1_Click()

Dim ret As Long

ret = EnumWindows(AddressOf EnumWindowsProc, 0)

If ret = 0 Then

DebugPrint False

Else

DebugPrint True

End If

End Sub

'

'模块代码:Module1bas

'

Option Explicit

Public Declare Function EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long

Public Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long

Public Function EnumWindowsProc(ByVal hwnd As Long, ByVal lParam As Long) As Long

Dim lpBuffer As String 1024

Dim dwWindowCaption As String

Dim lpLength As Long

lpLength = GetWindowText(hwnd, lpBuffer, 1024)

dwWindowCaption = Left(lpBuffer, lpLength)

DebugPrint dwWindowCaption

If InStr(dwWindowCaption, "Word") > 0 Then

'停止查找函数返回0

EnumWindowsProc = 0

Else

'继续查找函数返回1

EnumWindowsProc = 1

End If

End Function

运行一下就能看到效果了。

Option Explicit

Private Declare Function GetForegroundWindow Lib "user32" () As Long

Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long

Private Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hwnd As Long) As Long

Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long

Private Sub Timer1_Timer()

Dim hwnd As Long

Dim tPid As Long

Dim alength As Long

Dim astr As String

hwnd = GetForegroundWindow()

Call GetWindowThreadProcessId(hwnd, tPid)

alength = GetWindowTextLength(hwnd)

astr = Space$(alength + 1)

Call GetWindowText(hwnd, astr, alength + 1)

Text1Text = "ID:" + Str(tPid)

Text2Text = "Caption:" + astr

End Sub

Private Declare Function GetForegroundWindow Lib "user32" () As Long

Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As LongPrivate Sub Timer1_Timer()

Dim h As Long

h = GetForegroundWindow

If h <> Mehwnd Then

Dim S As String

S = Space(255)

GetWindowText h, S, 255

Text1Text = S

End If

End Sub

需要api的支持,有人已经写出来了:

'获取任务栏窗体名称

Option Explicit

Public Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long

Public Declare Function GetWindow Lib "user32" (ByVal hwnd As Long, ByVal wCmd As Long) As Long

Public Declare Function IsWindowVisible Lib "user32" (ByVal hwnd As Long) As Long

Public Declare Function EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long

Public Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hwnd As Long) As Long

Public Const GW_OWNER = 4

Function lpfunc(ByVal hwnd As Long, ByVal lParam As Long) As Boolean

Dim pstr As String, Ret As Long

If IsWindowVisible(hwnd) = False Then GoTo continu

If GetWindow(hwnd, GW_OWNER) <> 0 Then GoTo continu

Ret = GetWindowTextLength(hwnd)

pstr = Space(Ret)

If GetWindowText(hwnd, pstr, Ret + 1) = 0 Then GoTo continu

If pstr <> "" And pstr <> "Program Manager" Then Form1List1AddItem pstr

continu:

lpfunc = True

End Function

Private Sub Command1_Click()

List1Clear

EnumWindows AddressOf lpfunc, ByVal 0&

End Sub

'根据窗体标题获取窗体句柄

Private Sub Command2_Click()

Dim i As Integer

Dim hwndNext As Long

Dim hwnd() As Long

i = 0

hwndNext = FindWindowEx(0, 0, vbNullString, "窗体标题")

Do While hwndNext <> 0

ReDim Preserve hwnd(i) As Long

hwnd(i) = hwndNext

i = i + 1

hwndNext = FindWindowEx(0, hwnd(i - 1), vbNullString, "窗体标题")

Loop

If i <> 0 Then

For i = 0 To UBound(hwnd)

List1AddItem hwnd(i)

Next

Else

MsgBox "未找到相应标题名的窗口"

End If

End Sub

Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long

Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long

Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwprocessid As Long) As Long

Dim HwndVal&, ChildHwnd&

Private Sub Command1_Click()

HwndVal = FindWindow(vbNullString, "窗体标题")

'Print "窗口句柄是:" & CStr(HwndVal) & Space(3) & "进程号是:" & CStr(ProcIDFromWnd(HwndVal))

ChildHwnd = FindWindowEx(HwndVal, 0, "Static", vbNullString)

'Text1 = "子句柄是:" & ChildHwnd

List1AddItem CStr(HwndVal) & vbTab & CStr(ProcIDFromWnd(HwndVal)) & vbTab & ChildHwnd

End Sub

他们都好麻烦!你只是需要获取窗体名字而已是吧?很简单'在模块中添加下面的API函数Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long 然后在FORM1窗体添加个command按钮和label标签Private Sub Command1_Click()

Dim 窗口句柄 As Long

窗口句柄 = FindWindow(vbNullString, "窗口标题")

Label1Caption = 窗口句柄

End Sub 这样就行咯这样就可以获取到了

以上就是关于VB怎么得到打开的程序的标题并且显示全部的内容,包括:VB怎么得到打开的程序的标题并且显示、vb 输入进程名 获取窗体标题、VB获得指定xxx.exe进程的窗口标题(包括子窗体)等相关内容解答,如果想了解更多相关内容,可以关注我们,你们的支持是我们更新的动力!

欢迎分享,转载请注明来源:内存溢出

原文地址: https://outofmemory.cn/web/10166528.html

(0)
打赏 微信扫一扫 微信扫一扫 支付宝扫一扫 支付宝扫一扫
上一篇 2023-05-05
下一篇 2023-05-05

发表评论

登录后才能评论

评论列表(0条)

保存