Introduction to VBA System Tray Notification
How to Show a System Tray Notification Balloon
How to Display Notification when Macro is Finished
Introduction to VBA System Tray Notification
Have you seen those balloons that popup on your start menu when an application is finished installing or updates are available? You know the ones. Wouldn’t it be great if you could make one of those when your Excel macros are done running?
Now you can!
Learn how to show a system tray notification balloon in your start menu the moment your macro is done by following this awesome Excel VBA tutorial. This is great when you’re running a macro that takes a really long time.
By following this tutorial, you’ll be free to let your macros run in the background while you catch up on some social media posts. The moment your macro is finished, you’ll get a notification balloon in your system tray telling you your macro is done.
How to Show a System Tray Notification Balloon
To create a System Tray Notification Balloon using Excel VBA, you need to create two items in your VBA editor:
- Create a blank UserForm and rename it
ufDone . - Create a new Module.
Your Project Explorer Pane should look something like this:
The UserForm will never be shown so it really can be blank. Trust me!
For Windows 10, you don’t technically need the UserForm for your balloons to pop-up, but you’d have to modify the code I present below to omit it. You might as well just stick with what I have.
There are two more steps you must do to create the Excel system tray notification functionality.
Paste this Code into your UserForm
Once you’ve created your UserForm and renamed it to
'***** Paste this in the code section of a UserForm titled "ufDone" *****
Private Sub UserForm_Initialize()
Me.Hide
End Sub
Private Sub UserForm_Activate()
Dim IconPath As String
#If VBA7 Then
Dim Me_hWnd As LongPtr, Me_Icon As Long, Me_Icon_Handle As LongPtr
#Else
Dim Me_hWnd As Long, Me_Icon As Long, Me_Icon_Handle As Long
#End If
Me.Hide
RemoveIconFromTray
Unhook
IconPath = Application.Path & Application.PathSeparator & "excel.exe"
Me_hWnd = FindWindowd("ThunderDFrame", Me.Caption)
Me_Icon_Handle = ExtractIcond(0, IconPath, 0)
Hook Me_hWnd
AddIconToTray Me_hWnd, 0, Me_Icon_Handle, ""
BalloonPopUp_1
Unload Me
End Sub
'*************************************************************************
Remember, you can access the Code section by right-clicking your UserForm and selecting “View Code.”
Paste this Code into your Module
Now that your UserForm is complete, there’s just one more snippet of code to paste. This time, copy and paste the following macros into the new module you created. In my example, the module is named
These macros are going to look complicated, but don’t worry! This is all background junk - I’ll make it super easy for you to create the balloon notifications.
Anyway, here’s the code you need to copy and paste into your module:
'***** Paste this code into your standard Module *****
Option Explicit
#If VBA7 Then
Declare PtrSafe Function SetForegroundWindow Lib "user32" (ByVal hWnd As LongPtr) As Long
Declare PtrSafe Function Shell_NotifyIcon Lib "shell32.dll" Alias "Shell_NotifyIconA" (ByVal dwMessage As Long, lpData As NOTIFYICONDATA) As LongPtr
Declare PtrSafe Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As LongPtr, ByVal hWnd As LongPtr, ByVal Msg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
#If Win64 Then
'Declare PtrSafe Function SetWindowLongPtr Lib "user32" Alias "SetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
#Else
Declare PtrSafe Function SetWindowLongPtr Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
#End If
Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
Declare PtrSafe Function ExtractIcon Lib "shell32.dll" Alias "ExtractIconA" (ByVal hInst As LongPtr, ByVal lpszExeFileName As String, ByVal nIconIndex As Long) As LongPtr
Declare PtrSafe Function GetForegroundWindow Lib "user32" () As LongPtr
Private FHandle As LongPtr
Private WndProc As LongPtr
#Else
Declare Function SetForegroundWindow Lib "user32" (ByVal hWnd As Long) As Long
Declare Function Shell_NotifyIcon Lib "shell32.dll" Alias "Shell_NotifyIconA" (ByVal dwMessage As Long, lpData As NOTIFYICONDATA) As Long
Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hWnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Declare Function ExtractIcon Lib "shell32.dll" Alias "ExtractIconA" (ByVal hInst As Long, ByVal lpszExeFileName As String, ByVal nIconIndex As Long) As Long
Declare Function GetForegroundWindow Lib "user32" () As Long
Private FHandle As Long
Private WndProc As Long
#End If
Public Const WM_LBUTTONDOWN = &H201
Public Const WM_LBUTTONUP = &H202
Public Const WM_LBUTTONDBL = &H203
Public Const WM_RBUTTONDOWN = &H204
Public Const WM_RBUTTONUP = &H205
Public Const WM_RBUTTONDBL = &H206
Public Const WM_ACTIVATEAPP = &H1C
Public Const NIS_HIDDEN = &H1
Public Const NIS_SHAREDICON = &H2
Public Const NIF_ICON = &H2
Public Const NIF_MESSAGE = &H1
Public Const NIF_TIP = &H4
Public Const NIF_STATE = &H8
Public Const NIF_INFO = &H10
Public Const NIF_GUID = &H20
Public Const NIM_ADD = &H0
Public Const NIM_MODIFY = &H1
Public Const NIM_DELETE = &H2
Public Const WM_MOUSEMOVE = &H200
Public Const MAX_TOOLTIP As Integer = 128
Public Const GWL_WNDPROC = (-4)
'shell version / NOTIFIYICONDATA struct size constants
Public Const NOTIFYICONDATA_V1_SIZE As Long = 88 'pre-5.0 structure size
Public Const NOTIFYICONDATA_V2_SIZE As Long = 488 'pre-6.0 structure size
Public Const NOTIFYICONDATA_V3_SIZE As Long = 504 '6.0+ structure size
Public nfIconData As NOTIFYICONDATA
' list the icon types for the balloon message..
Public Const vbNone = 0
Public Const vbInformation = 1
Public Const vbExclamation = 2
Public Const vbCritical = 3
Private Hooking As Boolean
Type GUID
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(0 To 7) As Byte
End Type
#If VBA7 Then
Type NOTIFYICONDATA
cbSize As Long
hWnd As LongPtr
uID As Long
uFlags As Long
uCallbackMessage As Long
hIcon As LongPtr
szTip As String * 128
dwState As Long
dwStateMask As Long
szInfo As String * 256
uTimeout As Long
szInfoTitle As String * 64
dwInfoFlags As Long
guidItem As GUID
End Type
#Else
Type NOTIFYICONDATA
cbSize As Long
hWnd As Long
uID As Long
uFlags As Long
uCallbackMessage As Long
hIcon As Long
szTip As String * 128
dwState As Long
dwStateMask As Long
szInfo As String * 256
uTimeout As Long
szInfoTitle As String * 64
dwInfoFlags As Long
guidItem As GUID
End Type
#End If
Public Sub Unhook()
If Hooking = True Then
#If VBA7 Then
SetWindowLongPtr FHandle, GWL_WNDPROC, WndProc
#Else
SetWindowLong FHandle, GWL_WNDPROC, WndProc
#End If
Hooking = False
End If
End Sub
Public Sub RemoveIconFromTray()
Shell_NotifyIcon NIM_DELETE, nfIconData
End Sub
#If VBA7 Then
Function FindWindowd(ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
FindWindowd = FindWindow(lpClassName, lpWindowName)
End Function
Function ExtractIcond(ByVal hInst As LongPtr, ByVal lpszExeFileName As String, ByVal nIconIndex As Long) As LongPtr
ExtractIcond = ExtractIcon(hInst, lpszExeFileName, nIconIndex)
End Function
Public Sub Hook(Lwnd As LongPtr)
If Hooking = False Then
FHandle = Lwnd
WndProc = SetWindowLongPtr(Lwnd, GWL_WNDPROC, AddressOf WindowProc)
Hooking = True
End If
End Sub
Public Function WindowProc(ByVal hw As LongPtr, ByVal uMsg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
If Hooking Then
If lParam = WM_LBUTTONDBL Then
ufDone.Show 1
WindowProc = True
' Unhook
Exit Function
End If
WindowProc = CallWindowProc(WndProc, hw, uMsg, wParam, lParam)
End If
End Function
Public Sub AddIconToTray(MeHwnd As LongPtr, MeIcon As Long, MeIconHandle As LongPtr, Tip As String)
With nfIconData
.hWnd = MeHwnd
.uID = MeIcon
.uFlags = NIF_MESSAGE Or NIF_ICON Or NIF_TIP Or NIF_GUID
.uCallbackMessage = WM_RBUTTONUP
.dwState = NIS_SHAREDICON
.hIcon = MeIconHandle
.szTip = Tip & Chr$(0)
.cbSize = NOTIFYICONDATA_V3_SIZE
End With
Shell_NotifyIcon NIM_ADD, nfIconData
End Sub
Public Sub MacroFinished()
Dim wstate As Long
Dim hwnd2 As LongPtr
wstate = Application.WindowState
hwnd2 = GetForegroundWindow() 'find the current window
AppActivate (ThisWorkbook.Name) 'flash your existing workbook
ufDone.Show 1 'so the notification tray shows
Application.WindowState = wstate
SetForegroundWindow (hwnd2) 'then, bring the original window back to the front
End Sub
#Else
Function FindWindowd(ByVal lpClassName As String, ByVal lpWindowName As String) As Long
FindWindowd = FindWindow(lpClassName, lpWindowName)
End Function
Function ExtractIcond(ByVal hInst As Long, ByVal lpszExeFileName As String, ByVal nIconIndex As Long) As Long
ExtractIcond = ExtractIcon(hInst, lpszExeFileName, nIconIndex)
End Function
Public Sub Hook(Lwnd As Long)
If Hooking = False Then
FHandle = Lwnd
WndProc = SetWindowLong(Lwnd, GWL_WNDPROC, AddressOf WindowProc)
Hooking = True
End If
End Sub
Public Function WindowProc(ByVal hw As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
If Hooking Then
If lParam = WM_LBUTTONDBL Then
ufDone.Show 1
WindowProc = True
' Unhook
Exit Function
End If
WindowProc = CallWindowProc(WndProc, hw, uMsg, wParam, lParam)
End If
End Function
Public Sub AddIconToTray(MeHwnd As Long, MeIcon As Long, MeIconHandle As Long, Tip As String)
With nfIconData
.hWnd = MeHwnd
.uID = MeIcon
.uFlags = NIF_MESSAGE Or NIF_ICON Or NIF_TIP Or NIF_GUID
.uCallbackMessage = WM_RBUTTONUP
.dwState = NIS_SHAREDICON
.hIcon = MeIconHandle
.szTip = Tip & Chr$(0)
.cbSize = NOTIFYICONDATA_V3_SIZE
End With
Shell_NotifyIcon NIM_ADD, nfIconData
End Sub
Public Sub MacroFinished()
Dim wstate As Long
Dim hwnd2 As Long
wstate = Application.WindowState
hwnd2 = GetForegroundWindow() 'find the current window
AppActivate (ThisWorkbook.Name) 'flash your existing workbook
ufDone.Show 1 'so the notification tray shows
Application.WindowState = wstate
SetForegroundWindow (hwnd2) 'then, bring the original window back to the front
End Sub
#End If
Public Sub BalloonPopUp_1()
With nfIconData
.dwInfoFlags = vbInformation
.uFlags = NIF_INFO
.szInfoTitle = ActiveWorkbook.Name & vbNullChar
.szInfo = "Your Macro Has Finished." & vbNullChar
End With
Shell_NotifyIcon NIM_MODIFY, nfIconData
End Sub
'********************************************
Make powerful macros with our free VBA Developer Kit Tutorials like this can be complicated. That’s why we created our free VBA Developer Kit and our Big Book of Excel VBA Macros to supplement this tutorial. Grab them below and you’ll be writing powerful macros in no time.
That’s it! Now for the fun part. It’s time to test out your notification tray balloons!
Note: The macros above have been enhanced based on comments from wellsr.com readers, Johan, Jeff and Ed. Thanks, guys!
If you’re running a 64-bit version of Excel, you’ll need to uncomment the line below #If Win64 Then
near the top of the standard module. It’ll work just fine once you do that!
If you’re still having trouble or getting a Runtime Error 5 - Invalid Procedure Call or Argument message, try commenting out:
AppActivate (ThisWorkbook.Name)
And replace it with:
AppActivate Workbooks(ThisWorkbook.Name).Application.Caption
How to Display Notification when Macro is Finished
I’ve made it really easy to display a notification when your macro is done. All you have to do is call the procedure
For example, let’s say I have a really long code running. When I want to notify myself that my macro is done, I would call the
Sub ReallyLongMacro()
'-----
' your
' really
' long
' code
' goes
' here
'-----
MacroFinished
End Sub
You literally just type that one phrase “MacroFinished” right before your End Sub statement in your VBA macro and you’ll get notified in your System Tray. VBA is great, isn’t it?
Here’s what the notification balloon looks like on Windows 10:
And here’s what it looks like on Windows 7:
Notifications show up in your start menu, just like any other notification! On Windows 10, you’ll even see it queued up in your Action Center.
The macro is designed to work on 32-bit and 64-bit Windows operating systems.
I hope you enjoyed this tutorial. This is one of the more creative VBA solutions I’ve presented in a while.
I want to thank all my readers who have already subscribed to my free wellsrPRO VBA Training Program and I encourage you to go ahead and subscribe using the form below if you haven’t done so. You’ll love the fun VBA content (and freebies) I send your way!