Hola, proba con esto, vos ponelo despues en un listview, lo que hace es enumerar los iconos del system tray, tambien te saca el nombre del proceso que pertenece al Hwnd de la ventana de cada proceso y el icono del mismo, y de paso te dice el tooltiptext que tiene el icono...en windows XP funciona bien.
Option Explicit
Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function DrawIconEx Lib "user32" (ByVal hdc As Long, ByVal xLeft As Long, ByVal yTop As Long, ByVal hIcon As Long, ByVal cxWidth As Long, ByVal cyWidth As Long, ByVal istepIfAniCur As Long, ByVal hbrFlickerFreeDraw As Long, ByVal diFlags As Long) 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
Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function VirtualFreeEx Lib "kernel32" (ByVal hProcess As Long, lpAddress As Any, ByRef dwSize As Long, ByVal dwFreeType As Long) As Long
Private Declare Function VirtualAllocEx Lib "kernel32" (ByVal hProcess As Long, lpAddress As Any, ByRef dwSize As Long, ByVal flAllocationType As Long, ByVal flProtect As Long) As Long
Private Declare Function ReadProcessMemory Lib "kernel32" (ByVal hProcess As Long, lpBaseAddress As Any, lpBuffer As Any, ByVal nSize As Long, Optional lpNumberOfBytesWritten As Long) As Long
Private Declare Function WriteProcessMemory Lib "kernel32" (ByVal hProcess As Long, lpBaseAddress As Any, lpBuffer As Any, ByVal nSize As Long, Optional lpNumberOfBytesWritten As Long) As Long
Private Declare Function EnumProcessModules Lib "psapi" (ByVal hProcess As Long, ByRef lphModule As Long, ByVal cb As Long, ByRef lpcbNeeded As Long) As Long
Private Declare Function GetModuleFileNameEx Lib "psapi" Alias "GetModuleFileNameExA" (ByVal hProcess As Long, ByVal hModule As Long, ByVal ModuleName As String, ByVal nSize As Long) As Long
Const PROCESS_QUERY_INFORMATION = (&H400)
Const PROCESS_VM_READ = (&H10)
Const PROCESS_VM_WRITE = (&H20)
Const PROCESS_VM_OPERATION = (&H8)
Const MEM_COMMIT = &H1000
Const MEM_RESERVE = &H2000
Const MEM_RELEASE = &H8000
Const PAGE_READWRITE = &H4
Const MAX_PATH = 260
Const WM_USER = &H400
Const TB_BUTTONCOUNT = (WM_USER + 24)
Const TB_GETBUTTON = (WM_USER + 23)
Const TB_GETBUTTONTEXTA = (WM_USER + 45)
Private Type TBBUTTON
iBitmap As Long
idCommand As Long
fsState As Byte
fsStyle As Byte
dwData As Long
iString As Long
End Type
Private Type TRAYDATA
hWnd As Long
uID As Long
uCallbackMessage As Long
Reserved1 As Long
Reserved2 As Long
hIcon As Long
End Type
Private Sub Form_Load()
Dim hSysTray As Long, pID As Long, hProcess As Long, N As Long, Y As Long, L As Long
Dim tbb As TBBUTTON, lptbb As Long, td As TRAYDATA, lptd As Long, S As String * 128
BackColor = vbWhite
AutoRedraw = True
hSysTray = GetNotificationWindow
GetWindowThreadProcessId hSysTray, pID
hProcess = OpenProcess(PROCESS_VM_READ Or PROCESS_VM_WRITE Or PROCESS_VM_OPERATION, 0, pID)
lptbb = VirtualAllocEx(hProcess, ByVal 0&, Len(tbb), MEM_COMMIT Or MEM_RESERVE, PAGE_READWRITE)
lptd = VirtualAllocEx(hProcess, ByVal 0&, Len(td), MEM_COMMIT Or MEM_RESERVE, PAGE_READWRITE)
L = VirtualAllocEx(hProcess, ByVal 0&, Len(S), MEM_COMMIT Or MEM_RESERVE, PAGE_READWRITE)
N = SendMessage(hSysTray, TB_BUTTONCOUNT, 0, ByVal 0&)
For N = 0 To N - 1
SendMessage hSysTray, TB_GETBUTTON, N, ByVal lptbb
SendMessage hSysTray, TB_GETBUTTONTEXTA, N, ByVal L
ReadProcessMemory hProcess, ByVal L, ByVal S, Len(S)
Debug.Print Split(S, vbNullChar)(0)
ReadProcessMemory hProcess, ByVal lptbb, tbb, Len(tbb)
ReadProcessMemory hProcess, ByVal tbb.dwData, td, Len(td)
If (td.Reserved1 And 1) = 0 Then
DrawIconEx hdc, 2, Y, td.hIcon, 16, 16, 0, 0, 3
CurrentX = 20 * Screen.TwipsPerPixelX
CurrentY = (Y + 2) * Screen.TwipsPerPixelY
Print GetProcessNameFromHwnd(td.hWnd)
Y = Y + 18
End If
Next
VirtualFreeEx 0, lptbb, 0, MEM_RELEASE
VirtualFreeEx 0, lptd, 0, MEM_RELEASE
CloseHandle hProcess
End Sub
Private Function GetNotificationWindow() As Long
Dim H As Long
H = FindWindowEx(0, 0, "Shell_TrayWnd", vbNullString)
H = FindWindowEx(H, 0, "TrayNotifyWnd", vbNullString)
H = FindWindowEx(H, 0, "SysPager", vbNullString)
GetNotificationWindow = FindWindowEx(H, 0, "ToolbarWindow32", vbNullString)
End Function
Private Function GetProcessNameFromHwnd(ByVal hWnd As Long) As String
Dim ProcessId As Long, hProcess As Long, hModule As Long, S As String * MAX_PATH
GetWindowThreadProcessId hWnd, ProcessId
hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or PROCESS_VM_READ, 0, ProcessId)
EnumProcessModules hProcess, hModule, 1, ByVal 0
GetModuleFileNameEx hProcess, hModule, S, MAX_PATH
GetProcessNameFromHwnd = Left$(S, InStr(S, vbNullChar) - 1)
CloseHandle hProcess
End Function
saludos.