We have published many tutorials showing how to create your own VBA macros and procedures. Often the VBA MsgBox
function is used to communicate information. For example, our Create Your First Macro tutorial illustrates the ubiquitous MsgBox("Hello World")
macro. We even taught you how to change the text color of a MsgBox. Even though we’ve shown some neat MsgBox tricks, most of our previous tutorials have not discussed the use of MsgBox
buttons to provide choices for directing a procedure.
VBA’s MsgBox
function displays a message in a dialog box with 1, 2, or 3 standard buttons labeled OK, Cancel, Abort, Retry, Ignore, Yes, or No. (We will ignore the possible addition of another button labeled Help because it can only be used to open a Windows Help file.) The function waits until the user clicks a button then returns an
- Using VBA’s MsgBox Function
- Introducing the MsgBoxCustom Module
- Using the MsgBoxCustom Procedures
- Final Thoughts
Using VBA's MsgBox Function
The VBA MsgBox function syntax is
MsgBox(prompt, [buttons,] [title,] [helpfile, context])
Only the
For this tutorial we are primarily concerned with the number and arrangement of buttons and the function’s return value (a whole number from 1 to 7) identifying which button was clicked. (As stated earlier, the function supports a Help button that can only be used to open an optional Windows Help file; the Help button will be ignored here.)
All of the possible settings for the
VB Constant | Value | Description |
---|---|---|
vbOKOnly | 0 | OK button only |
vbOKCancel | 1 | OK and Cancel buttons |
vbAbortRetryIgnore | 2 | Abort, Retry, and Ignore buttons |
vbYesNoCancel | 3 | Yes, No, and Cancel buttons |
vbYesNo | 4 | Yes and No buttons |
vbRetryCancel | 5 | Retry and Cancel buttons |
The function’s return value indicates which button was clicked.
VB Constant | Value | Description |
---|---|---|
vbOK | 1 | OK button clicked |
vbCancel | 2 | Cancel button clicked |
vbAbort | 3 | Abort button clicked |
vbRetry | 4 | Retry button clicked |
vbIgnore | 5 | Ignore button clicked |
vbYes | 6 | Yes button clicked |
vbNo | 7 | No button clicked |
So the following VBA statements
ans = MsgBox("Click a button.", vbOKCancel)
ans = MsgBox("Click a button.", (vbYesNo + vbQuestion))
will produce the following dialog boxes
The first
Notice the first dialog box has an X in its upper-right corner, which is disabled in the second. This is the standard Close Window button and is always enabled for the three MsgBox
configurations that include a Cancel button; in this case, MsgBox
will return
The second dialog box includes a Question icon associated with the sum of
Introducing the MsgBoxCustom Module
So what can we do if the 7 standard MsgBox
buttons do not satisfy our requirements? What if we want to add custom button labels to a VBA MsgBox? The solution is to interrupt the process of creating the dialog box and change its button labels before its window is activated. The method is discussed in Microsoft’s CBTProc reference and requires setting a Windows Hook for Computer Based Training (WH_CBT) that specifies a callback procedure to monitor preparation of the window and update the button labels when the HCBT_ACTIVATE message is received.
We must supply the callback procedure, but the following Windows functions enable its implementation: GetCurrentThreadId
, SetWindowsHookEx
, SetDlgItemText
, CallNextHookEx
, and UnhookWindowsHookEx
. These functions are available in dynamic-link libraries (DLLs); therefore, we must use Declare
statements along with module level global constants and variables before any Sub
or Function
statement in our VBAProject’s module. You may recognize some of these functions from our tutorial on masking your password with the VBA InputBox, which also required hooking.
Here is the complete code for our module:
' This module includes Private declarations for GetCurrentThreadId, SetWindowsHookEx, SetDlgItemText, CallNextHookEx, UnhookWindowsHookEx
' plus code for Public Sub MsgBoxCustom, Public Sub MsgBoxCustom_Set, Public Sub MsgBoxCustom_Reset
' plus code for Private Sub MsgBoxCustom_Init, Private Function MsgBoxCustom_Proc
' DEVELOPER: J. Woolley (for wellsr.com)
#If VBA7 Then
Private Declare PtrSafe Function GetCurrentThreadId Lib "kernel32" _
() As Long
Private Declare PtrSafe Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" _
(ByVal idHook As Long, ByVal lpfn As LongPtr, ByVal hmod As LongPtr, ByVal dwThreadId As Long) As LongPtr
Private Declare PtrSafe Function SetDlgItemText Lib "user32" Alias "SetDlgItemTextA" _
(ByVal hDlg As LongPtr, ByVal nIDDlgItem As Long, ByVal lpString As String) As Long
Private Declare PtrSafe Function CallNextHookEx Lib "user32" _
(ByVal hHook As LongPtr, ByVal ncode As Long, ByVal wParam As LongPtr, lParam As Any) As LongPtr
Private Declare PtrSafe Function UnhookWindowsHookEx Lib "user32" _
(ByVal hHook As LongPtr) As Long
Private hHook As LongPtr ' handle to the Hook procedure (global variable)
#Else
Private Declare Function GetCurrentThreadId Lib "kernel32" _
() As Long
Private Declare Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" _
(ByVal idHook As Long, ByVal lpfn As Long, ByVal hmod As Long, ByVal dwThreadId As Long) As Long
Private Declare Function SetDlgItemText Lib "user32" Alias "SetDlgItemTextA" _
(ByVal hDlg As Long, ByVal nIDDlgItem As Long, ByVal lpString As String) As Long
Private Declare Function CallNextHookEx Lib "user32" _
(ByVal hHook As Long, ByVal ncode As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function UnhookWindowsHookEx Lib "user32" _
(ByVal hHook As Long) As Long
Private hHook As Long ' handle to the Hook procedure (global variable)
#End If
' Hook flags (Computer Based Training)
Private Const WH_CBT = 5 ' hook type
Private Const HCBT_ACTIVATE = 5 ' activate window
' MsgBox constants (these are enumerated by VBA)
' vbOK = 1, vbCancel = 2, vbAbort = 3, vbRetry = 4, vbIgnore = 5, vbYes = 6, vbNo = 7 (these are button IDs)
' for 1 button, use vbOKOnly = 0 (OK button with ID vbOK returned)
' for 2 buttons, use vbOKCancel = 1 (vbOK, vbCancel) or vbYesNo = 4 (vbYes, vbNo) or vbRetryCancel = 5 (vbRetry, vbCancel)
' for 3 buttons, use vbAbortRetryIgnore = 2 (vbAbort, vbRetry, vbIgnore) or vbYesNoCancel = 3 (vbYes, vbNo, vbCancel)
' Module level global variables
Private sMsgBoxDefaultLabel(1 To 7) As String
Private sMsgBoxCustomLabel(1 To 7) As String
Private bMsgBoxCustomInit As Boolean
Private Sub MsgBoxCustom_Init()
' Initialize default button labels for Public Sub MsgBoxCustom
Dim nID As Integer
Dim vA As Variant ' base 0 array populated by Array function (must be Variant)
vA = VBA.Array(vbNullString, "OK", "Cancel", "Abort", "Retry", "Ignore", "Yes", "No")
For nID = 1 To 7
sMsgBoxDefaultLabel(nID) = vA(nID)
sMsgBoxCustomLabel(nID) = sMsgBoxDefaultLabel(nID)
Next nID
bMsgBoxCustomInit = True
End Sub
Public Sub MsgBoxCustom_Set(ByVal nID As Integer, Optional ByVal vLabel As Variant)
' Set button nID label to CStr(vLabel) for Public Sub MsgBoxCustom
' vbOK = 1, vbCancel = 2, vbAbort = 3, vbRetry = 4, vbIgnore = 5, vbYes = 6, vbNo = 7
' If nID is zero, all button labels will be set to default
' If vLabel is missing, button nID label will be set to default
' vLabel should not have more than 10 characters (approximately)
If nID = 0 Then Call MsgBoxCustom_Init
If nID < 1 Or nID > 7 Then Exit Sub
If Not bMsgBoxCustomInit Then Call MsgBoxCustom_Init
If IsMissing(vLabel) Then
sMsgBoxCustomLabel(nID) = sMsgBoxDefaultLabel(nID)
Else
sMsgBoxCustomLabel(nID) = CStr(vLabel)
End If
End Sub
Public Sub MsgBoxCustom_Reset(ByVal nID As Integer)
' Reset button nID to default label for Public Sub MsgBoxCustom
' vbOK = 1, vbCancel = 2, vbAbort = 3, vbRetry = 4, vbIgnore = 5, vbYes = 6, vbNo = 7
' If nID is zero, all button labels will be set to default
Call MsgBoxCustom_Set(nID)
End Sub
#If VBA7 Then
Private Function MsgBoxCustom_Proc(ByVal lMsg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
#Else
Private Function MsgBoxCustom_Proc(ByVal lMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
#End If
' Hook callback function for Public Function MsgBoxCustom
Dim nID As Integer
If lMsg = HCBT_ACTIVATE And bMsgBoxCustomInit Then
For nID = 1 To 7
SetDlgItemText wParam, nID, sMsgBoxCustomLabel(nID)
Next nID
End If
MsgBoxCustom_Proc = CallNextHookEx(hHook, lMsg, wParam, lParam)
End Function
Public Sub MsgBoxCustom( _
ByRef vID As Variant, _
ByVal sPrompt As String, _
Optional ByVal vButtons As Variant = 0, _
Optional ByVal vTitle As Variant, _
Optional ByVal vHelpfile As Variant, _
Optional ByVal vContext As Variant = 0)
' Display standard VBA MsgBox with custom button labels
' Return vID as result from MsgBox corresponding to clicked button (ByRef...Variant is compatible with any type)
' vbOK = 1, vbCancel = 2, vbAbort = 3, vbRetry = 4, vbIgnore = 5, vbYes = 6, vbNo = 7
' Arguments sPrompt, vButtons, vTitle, vHelpfile, and vContext match arguments of standard VBA MsgBox function
' This is Public Sub instead of Public Function so it will not be listed as a user-defined function (UDF)
hHook = SetWindowsHookEx(WH_CBT, AddressOf MsgBoxCustom_Proc, 0, GetCurrentThreadId)
If IsMissing(vHelpfile) And IsMissing(vTitle) Then
vID = MsgBox(sPrompt, vButtons)
ElseIf IsMissing(vHelpfile) Then
vID = MsgBox(sPrompt, vButtons, vTitle)
ElseIf IsMissing(vTitle) Then
vID = MsgBox(sPrompt, vButtons, , vHelpfile, vContext)
Else
vID = MsgBox(sPrompt, vButtons, vTitle, vHelpfile, vContext)
End If
If hHook <> 0 Then UnhookWindowsHookEx hHook
End Sub
Make powerful macros with our free VBA Developer Kit This is actually pretty neat. If you have trouble understanding or remembering it, our free VBA Developer Kit can help. It’s loaded with VBA shortcuts to help you make your own macros like this one - we’ll send a copy, along with our Big Book of Excel VBA Macros, to your email address below.
Notice everything in our VBA module is declared Private
except MsgBoxCustom
, MsgBoxCustom_Set
, and MsgBoxCustom_Reset
. Only those three Sub
procedures may be accessed outside the module; they will be discussed later under Using the MsgBoxCustom Procedures.
MsgBoxCustom_Init
initializes the default (standard) button labels and sets each custom label to the default. It is called when appropriate by MsgBoxCustom_Set
. VBA’s Array function is qualified as VBA.Array
to insure it is unaffected by Option Base
.
The MsgBoxCustom_Proc
function is the hook callback procedure set by MsgBoxCustom
to monitor preparation of the dialog box window and update button labels before activation. In this case, SetDlgItemText
is used to change the text of button (control) MsgBoxCustom_Set
. Finally, MsgBoxCustom_Proc
uses CallNextHookEx
to pass the hook information to the next hook procedure in the current hook chain and return the result. The definition of MsgBoxCustom_Proc
must be different for VBA7 (which supports
I know that was complicated, but in a nutshell, all we’re doing is hooking our window and changing the button labels before they’re shown on the screen.
Using the MsgBoxCustom Procedures
When you want to customize the MsgBox button labels for your project, you’ll first use MsgBoxCustom_Set
to define each label. Then you’ll use MsgBoxCustom
to create the final message box. For example, the following VBA will create a MsgBox with 2 buttons labeled Open and Close instead of OK and Cancel:
Sub Custom_MsgBox_Demo1()
MsgBoxCustom_Set vbOK, "Open"
MsgBoxCustom_Set vbCancel, "Close"
MsgBoxCustom ans, "Click a button.", vbOKCancel
End Sub
Notice the MsgBoxCustom
sub specifies the vbOKCancel
button combination since those are the buttons we redefined with our MsgBoxCustom_Set
function. The button ID returned in variable
To make a MsgBox
with a Question icon and 2 buttons labeled Start and Stop instead of Yes and No, use the following macro:
Sub Custom_MsgBox_Demo2()
MsgBoxCustom_Set vbYes, "Start"
MsgBoxCustom_Set vbNo, "Stop"
MsgBoxCustom ans, "Click a button.", (vbYesNo + vbQuestion)
End Sub
In this case,
These two examples are illustrated in the following screen shots:
It should be noted that VBA’s actual MsgBox
function will not be altered; it will continue to have buttons with standard labels. The two examples presented in Using VBA’s MsgBox Function were
ans = MsgBox("Click a button.", vbOKCancel)
ans = MsgBox("Click a button.", (vbYesNo + vbQuestion))
These will always have standard buttons labeled OK, Cancel, Yes, and No. The labels only change when you use the three MsgBoxCustom
procedures as described above.
After using MsgBoxCustom_Set
to change a label, each new use of MsgBoxCustom
will reflect that change until the button’s default label is restored by calling the MsgBoxCustom_Reset
function (or by calling MsgBoxCustom_Set
without specifying a label). For example, if the two demo macros illustrated in the screen shots above are followed by this code
Sub Custom_MsgBox_Demo3()
MsgBoxCustom_Reset vbOK
MsgBoxCustom ans, "OK reset.", (vbOKCancel + vbInformation), "MsgBoxCustom"
MsgBoxCustom_Reset vbYes
MsgBoxCustom_Set vbNo
MsgBoxCustom ans, "Yes/No reset.", vbYesNoCancel, "MsgBoxCustom"
End Sub
the results will look like
Notice the MsgBoxCustom
and displayed in each title bar.
If either MsgBoxCustom_Reset
or MsgBoxCustom_Set
is called with a zero argument, then all button labels will be set to default values. Therefore, the following four statements are equivalent. (Notice the use of Call
in VBA is optional; if used, all arguments must be within one set of parentheses.)
'Each of these statements are equivalent
MsgBoxCustom_Reset 0 ' reset all labels
MsgBoxCustom_Set 0 ' reset all labels
Call MsgBoxCustom_Reset(0) ' reset all labels
Call MsgBoxCustom_Set(0) ' reset all labels
When MsgBoxCustom
is called, it uses SetWindowsHookEx
to set a Windows Hook for Computer Based Training (WH_CBT) specifying the callback procedure MsgBoxCustom_Proc
(described above). Then it uses VBA’s MsgBox
function to prepare a dialog box in the usual way (except for changes made by MsgBoxCustom_Proc
). MsgBoxCustom
’s first argument will receive the value returned by MsgBox
identifying the clicked button’s ID. MsgBoxCustom
’s remaining arguments will be passed directly to MsgBox
. Finally, the WH_CBT hook will be removed.
Final Thoughts
-
MsgBoxCustom_Reset
is superfluous (because it simply callsMsgBoxCustom_Set
without a label), but its name describes its purpose. -
Custom labels defined using
MsgBoxCustom_Set
should not be longer than 10 characters (approximately). -
MsgBoxCustom_Set
andMsgBoxCustom
use the VBAIsMissing
function to determine whether anOptional
argument (which must beVariant
) was passed to the procedure. -
MsgBoxCustom
is made a Sub instead of a Function so it will not be considered a user-defined function (UDF) in Excel’s Insert Function dialog. Therefore, its first argument is declaredByRef
to receive the clicked button’s ID fromMsgBox
. This also helps to visually distinguish code referencingMsgBoxCustom
from code referencingMsgBox
. Plus, callingMsgBoxCustom_Set
followed byMsgBoxCustom
followed byMsgBoxCustom_Reset
has a certain appealing symmetry. -
If desired,
MsgBoxCustom
could easily be made aFunction
to matchMsgBox
, but this would allow it to be referenced in a cell formula like the following example, which might be awkward. If you do this, you will probably want to makeMsgBoxCustom_Set
aFunction
, too.
=MsgBoxCustom(IF(WEEKDAY(TODAY(),2)>5,"Weekend","Workday"),,"Today is a")
Although we have referred to Excel throughout this tutorial, MsgBoxCustom
applies to any Windows application of VBA.
If you’re serious about writing macros, subscribe for more VBA tips. Simply fill out the form below and we’ll share our best time-saving VBA tips.