Use VBA ThisWorkbook event handling to capture a variety of application-level events. The events captured in the VBA ThisWorkbook module can be used to trigger unique actions based on a user’s interaction with Excel.

In this context, an event is an action or occurrence recognized by Excel that may be handled by it. This will make more sense in a few minutes.

Excel events can either be triggered by Excel, by the user or by third-party applications. An event handler, therefore, is a callback subroutine that handles inputs pertaining to an event in a program. This, in turn, allows the programmer to check for certain desired states before either allowing, halting or altering further code execution and/or other events.

Don’t worry if this all sounds a bit abstract and technical to you at this stage. You’ll have a very clear understanding of what Excel events and Excel event handlers are when you’re finished reading this tutorial.

VBA events and their corresponding event handlers can be grouped into three main categories:

  • Workbook events. These events pertain to all the worksheets in the workbook and the objects embedded in them such as charts, pivot tables, etc. This are typically handled using the ThisWorkbook module in your VBA editor.
  • Worksheet events. These events pertain to a particular worksheet and all the objects embedded in it such as charts, pivot tables, etc.
  • Userform events. Userform events only pertain to a particular userform (a form you make from the VBA editor) and the objects embedded in it.

Excel VBA is normally characterized as an event-driven language, as it comes with a huge range of built-in objects and controls capable of handling events. We’ll focus solely on Workbook event handlers in this tutorial, which are handled via the ThisWorkbook module in your VBA editor. We may write about other types of VBA events in future tutorials. Let us know in the comments if you want to hear more about other VBA event handlers!

Let’s start by outlining what a generic VBA event handler (callback subroutine) looks like and how it works!


Typical event handler format

The code below is pseudo-code and only serves to illustrate how a VBA event handler (event callback subroutine) is structured and works:

Private Sub PseudoEventHandler(ByVal Param1 as SomeDataType, ByVal Param2 As SomeOtherDataType )
    '******************************
    ' Insert your code here
    '******************************
End Sub

On the surface, this looks like any other type of subroutine that takes parameters and allows you to execute your own code within it, but it’s not! Since event handlers are predefined by Excel, they only work when certain conditions are made.

If you do not specify the parameters exactly as Excel expects, you’ll get an error message (like the one below) either when the subroutine is executed or when you compile your code (with Debug > Compile VBAProject in the Visual Basic Editor):

VBA Workbook event compile error
VBA Workbook event compile error

Secondly, the parameters passed to the subroutine are passed by Excel and not by some other code you’re using.

Thirdly, you cannot change the name of the event handler without breaking it! If you do change the name, Excel won’t know which event you’re trying to handle, and your subroutine will then simply be treated like any other subroutine, rather than as an event handler. Event handler names are predefined by Excel, so they won’t be recognized if you try to make changes to the names.

Fourthly, the (pseudo-)event handler above is declared as a Private sub. Amongst other things, this ensures that it doesn’t appear in the Macros Dialog Box when you type Alt+F8:

Macros Dialog Box
Macros Dialog Box

Any subroutine with a parameter won’t appear in the Macros Dialog Box, unless the parameter is an Optional Variant type variable. However, not all event handlers come with parameters, so for consistency they are all declared Private by default.

Fifthly, the location of the event handler matters. Depending on which type of event handler you’re dealing with it should be placed in a module pertaining to the scope of the event it handles. More on this in the next section!

Finally, it should be noted that if a parameter to the event handler is not declared as a ByVal (“by value”) variable, it means you can change its value within the scope of the procedure. Event handlers are no different from ordinary subroutines in this respect, except that altering a non-ByVal or ByRef (“by reference”) parameter typically enables you to control whether a specific Excel event is carried out or not. In VBA the name of this parameter is usually Cancel.

You’ll understand exactly what we mean by this when we step through the event handlers of the Workbook object, but before we get to that, let’s show you how to set up an Excel workbook event handler using VBA.


Setting up a Workbook event handler

Open a Workbook, type Alt+F11 and double click on ThisWorkbook in your Project Explorer (Ctrl+R).

VBA ThisWorkbook Excel Object
VBA ThisWorkbook Excel Object

Next, click the dropdown list to the right where it says (General) and select Workbook. The (Declarations) dropdown list to the far right will now display all the event handlers of the Application.WorkBook object!

VBA Workbook event handlers dropdown list
VBA Workbook event handlers dropdown list

It’s important that you do not move the Workbook event handling procedures out of this module as they won’t work if you do so. This is what we meant earlier when we said that all event handling procedures must be placed in modules pertaining to the scope of the events they handle. Workbook events must be placed in the ThisWorkbook module

You’re now ready to start working with all the Excel Workbook events. We’ll give you a rundown of all the Excel workbook event handlers in the next section, each of which can be used to trigger actions in your VBA macros.


List of workbook event handlers

Below is a complete list of Workbook event handlers in Excel. You can use it later as a reference when you’re coding your own event handling procedures, but for now a more cursory reading will do. I encourage you to browse through the list, stop whenever you find a procedure that interests you and then read the info on that specific workbook event.

Name Parameter(s) Description
Activate None Occurs when the workbook is activated, like when someone clicks into your workbook from another application or when they select your workbook in their taskbar.
AddinInstall None Occurs when the workbook is installed as an add-in.
AddinUninstall None Occurs when the workbook is uninstalled as an add-in.
AfterRemoteChange None Occurs after a remote user's edits to the workbook are merged.
AfterSave ByVal Success As Boolean Occurs after the workbook is saved. The Success parameter is a True-False (Boolean) value which indicates whether the Workbook was successfully saved.
AfterXmlExport ByVal Map As XmlMap,
ByVal Url As String,
ByVal Result As XlXmlExportResult
Occurs after Microsoft Office Excel saves or exports data from the workbook to an XML data file. All three parameters are mandatory. Map is the schema map that was used to save or export data. Url is the location of the XML file that was exported. Result indicates the result of the save or export operation (True = successful, False = unsuccessful).
AfterXmlImport ByVal Map As XmlMap,
ByVal IsRefresh As Boolean,
ByVal Result As XlXmlImportResult
Occurs after an existing XML data connection is refreshed or after new XML data is imported into the workbook. All three parameters are mandatory. Map is the XML map that will be used to import data. IsRefresh will be True
if the event was triggered by refreshing an existing connection to XML data and False if the event was triggered by importing from a different data source. Result indicates the results of the refresh or import operation.
BeforeClose Cancel as Boolean Occurs before the workbook closes. If the workbook has been changed, this event occurs before the user is asked to save changes. The parameter Cancel is False by default. If set to True in the callback function, this will cancel the closing of the Workbook. In other words, it will prevent the user from closing the workbook.
BeforePrint Cancel As Boolean Occurs before the workbook (or anything in it) is printed. Cancel is False by default but setting it to True cancels the printing.
BeforeRemoteChange None Occurs before a remote user's edits to the workbook are merged.
BeforeSave ByVal SaveAsUI As Boolean,
Cancel as Boolean
Occurs before the workbook is saved. SaveAsUI True if the Save As dialog box will be displayed when changes made in the workbook are to be saved. The Cancel parameter is False by default but setting it to True cancels the saving of the workbook, so the user won't be able to save the workbook.
BeforeXmlExport ByVal Map As XmlMap,
ByVal Url As String,
Cancel As Boolean
Occurs before Microsoft Office Excel saves or exports data from the workbook to an XML data file. See AfterXmlExport for further explanation of the first two parameters. Cancel</mod> is False by default but setting it to True cancels the XML export.
BeforeXmlImport ByVal Map As XmlMap,
ByVal Url As String,
ByVal IsRefresh As Boolean,
Cancel As Boolean
Occurs before an existing XML data connection is refreshed or before new XML data is imported into the workbook. Please refer to the other BeforeXml subroutines for an explanation of the parameters.
Deactivate None Occurs when the workbook is deactivated.
ModelChange ByVal Changes As ModelChanges Occurs when the data model is updated. A Data Model is an integration of data from multiple tables (list objects), and thus effectively a relational data source inside an Excel workbook. Data models are typically used for PivotTables and PivotCharts. The Changes parameter is an object containing the changes made to the Excel data model in the last transaction.
NewChart ByVal Ch As Chart Occurs when a new chart is created in any open workbook. The Ch parameter is the new chart object.
NewSheet ByVal Sh As Object Occurs when a new sheet is created in the workbook. The event also fires when a new chart is created on a new sheet and in this case the Sh parameter will be a chart object. In all other cases, it will be a worksheet object. This explains why the parameter is declared as a generic object rather than a Worksheet object.
Open None Occurs when a workbook is opened. This is probably the most widely used Workbook event handler of them all.
PivotTableCloseConnection ByVal Target As PivotTable Occurs after a PivotTable report connection has been closed. The Target parameter is the pivot table object which triggered the event.
PivotTableOpenConnection ByVal Target As
PivotTable
Occurs after a PivotTable report connection has been opened. The Target parameter is the pivot table object which triggered the event.
RowsetComplete ByVal Description As String,
ByVal Sheet As String,
ByVal Success As Boolean
Occurs when the user either drills through the recordset or invokes the rowset action on an OLAP PivotTable. OLAP stands for Online Analytical Processing and is used for multi-dimensional analytical queries. The Description parameter contains a brief description of the event. The Sheet parameter contains the name of the worksheet on which the recordset was created. The Success parameter is Boolean type value indicating either success (True) or failure (False).
SheetActivate ByVal Sh as Object Occurs when any sheet is activated. The Sh parameter contains the sheet object which triggered the event.
SheetBeforeDelete ByVal Sh As Object Occurs before any sheet is deleted. The Sh parameter contains the sheet object which triggered the event.
SheetBeforeDoubleClick ByVal Sh As Object,
ByVal Target As Range,
Cancel As Boolean
Occurs when any worksheet is double-clicked, before the default double-click action. The Sh parameter contains the sheet object which triggered the event. The Target parameter is a range object representing the cell nearest to the mouse pointer when the double click occurred. The Cancel parameter is False by default but setting it to True cancels the double-click action.
SheetBeforeRightClick ByVal Sh As Object,
ByVal Target As Range,
Cancel As Boolean
Occurs when any worksheet is right-clicked, before the default right-click action. The event is not triggered on chart sheets. Please refer to SheetBeforeDoubleClick for an explanation for the parameters.
SheetCalculate ByVal Sh As Object Occurs after any worksheet is recalculated or after any changed data is plotted on a chart. Therefore, the Sh parameter can be either a chart or worksheet object.
SheetChange ByVal Sh As Object,
ByVal Source As Range
Occurs when cells in any worksheet are changed by the user or by an external link. The Sh parameter represents the worksheet object in which the event occurred. The Target is the range object of the worksheet in which the change occurred.
SheetDeactivate ByVal Sh As Object Occurs when any sheet is deactivated, including chart sheets. The Sh object can either be a chart or a worksheet object.
SheetFollowHyperlink ByVal Sh as Object,
ByVal Target As Hyperlink
Occurs when you click any hyperlink in any worksheet in Excel. The Sh parameter is the sheet object containing the clicked hyperlinked. The Target parameter is the hyperlink object representing the destination of the hyperlink.
SheetLensGalleryRenderComplete ByVal Sh As Object Occurs when a callout gallery's icons (dynamic & static) have completed rendering. This event pertains only to objects on which you can use data callouts (special data labels, e.g. on charts).
SheetPivotTableAfterValueChange ByVal Sh As Object,
ByVal TargetPivotTable As PivotTable,
ByVal TargetRange As Range
Occurs after a cell or range of cells inside a PivotTable are edited or recalculated (for cells that contain formulas). The Sh parameter represents the worksheet object on which the event occurred. The TargetPivotTable parameter is the pivot table object in which the values were changed or recalculated. The TargetRange is the range of cells in which the values were changed or recalculated.
SheetPivotTableBeforeAllocateChanges ByVal Sh As Object,
ByVal TargetPivotTable As PivotTable,
ByVal ValueChangeStart As Long,
ByVal ValueChangeEnd As Long,
Cancel As Boolean
Occurs before changes are applied to a PivotTable. The ValueChangeStart parameter is the index to the first change in the associated PivotTableChangeList
collection and the ValueChangeEnd is the last index of this collection. The Cancel parameter is False by default but setting it to True cancels the double-click action. Please refer to SheetPivotTableAfterValueChange for an explanation of the rest of the parameters.
SheetPivotTableBeforeCommitChanges ByVal Sh As Object,
ByVal TargetPivotTable As PivotTable,
ByVal ValueChangeStart As Long,
ByVal ValueChangeEnd As Long,
Cancel As Boolean
Occurs before changes are committed against the OLAP data source for a PivotTable and immediately after the user has chosen to save changes for the whole PivotTable. Please refer to the other SheetPivotTable event handlers above for an explanation of the parameters.
SheetPivotBeforeDiscardChanges ByVal Sh As Object,
ByVal TargetPivotTable As PivotTable,
ByVal ValueChangeStart As Long,
ByVal ValueChangeEnd As Long
Occurs before changes to a PivotTable are discarded. Please refer to the other SheetPivotTable event handlers above for an explanation of the parameters.
SheetPivotTableChangeSync ByVal Sh As Target,
Target As PivotTable
Occurs after changes to a PivotTable. Please refer to the other SheetPivotTable event handlers above for an explanation of the parameters.
SheetPivotTableUpdate ByVal Sh As Target,
Target As PivotTable
Occurs after a PivotTable report is updated on a worksheet. Please refer to the other SheetPivotTable event handlers above for an explanation of the parameters.
SheetSelectionChange ByVal Sh As Object,
ByVal Target As Range
Occurs when the selection changes on a worksheet, i.e when you select a new cell. The Sh parameter is the worksheet object in which the new selection was made. The Target parameter is the selected range.
SheetTableUpdate ByVal Sh As Object,
ByVal Target As TableObject
Occurs after a Query table connected to the Data Model is updated on a worksheet. The Sh parameter is the worksheet object in which the updated table is located. The Target parameter is the updated table object.
Sync - This object or member has been deprecated, but it remains part of the object model for backward compatibility. You should not use it in new applications.
WindowsActivate ByVal Wn As Window Occurs when the workbook is activated. Only relevant to use if at least two Workbooks are open at the same time, otherwise the only open Workbook will always be the active Workbook. Only one Workbook can be active at a time and when a Workbook is activated, any other open Workbooks are deactivated. The Wn parameter holds the activated window object.
WindowsDeactivate ByVal Wn As Window Occurs when the workbook is deactivated. For further explanation, please refer to WindowsActivate.
WindowResize ByVal Wn As Window Occurs when any workbook window is resized. The Wn parameter holds the resized window object.

Some of these event handlers are somewhat esoteric and only very rarely used, whereas others are much more common. In the next section, we’ll present some code examples for a couple of the more commonly used event handlers.

Workbook Event Handling Examples

Paste the code below into the ThisWorkbook code module:

' (1) display a message box with the name of the sheet and 
'     the cell address of column A in which a selection change was made
Private Sub Workbook_SheetSelectionChange(ByVal Sh As Object, ByVal Target As Range)
    If Not Intersect(Sh.Range("A1:A10"), Target) Is Nothing Then
        MsgBox "A new selection was made on " & Sh.Name & ", column A at " & Target.Address
    End If
End Sub

' (2) display a message box with the name of the sheet on
'     which a calculation was performed
Private Sub Workbook_SheetCalculate(ByVal Sh As Object)
    MsgBox "A calculation was performed on " & Sh.Name
End Sub

The event handlers above become active immediately after you paste the code into the module, provided Application.EnableEvents is set to True.

Test the first by selecting a cell in range "A1:A10" in column A on any of the worksheets in your workbook.

Anyway, once a new cell is selected in the target range, a message like the one below should then appear:

VBA Selection change message
VBA Selection change message

If it doesn’t, try typing Application.EnableEvents = True in the Immediate window of the Visual Basic Editor and then press Enter.

In the Workbook_SheetSelectionChange event handling procedure above, we’ve narrowed down the handled worksheet area (cell range) with the following piece of code: If Not Intersect(Sh.Range("A1:A10"), Target) Is Nothing Then

This means the code inside the conditional statement above is only executed if range "A1:A10" of the active sheet and the range of the cell in which the selection change was made intersect or “overlap.” In other words, the message box will only appear if the selection change was made in range "A1:A10". A similar code can be placed in many of the other event handler macros to restrict your macro from running unless certain cells are triggered.

In the second code example, we check for calculations performed on any sheet in the workbook. For instance, try entering a simple formula such as “=2+3” into any cell of your workbook and press enter. A message like the one below should now appear:

VBA calculation performed message
VBA calculation performed message

Since the built-in Excel event handler only returns the corresponding sheet object, there is no easy way to determine in which range(s) of the worksheet the calculation(s) occurred, so we simply display a message with the name of the worksheet instead.


Excel Workbook Event Cautions

Even though event handling is a wonderful thing which can make your life a lot easier, improve the user experience and make your applications much more powerful, some words of caution are in order.

  • Use precise coding. Event handlers can lead to a sharp decline in performance, especially if you’re not careful about how you code them! Be as specific as possible when you use them so that they’re only triggered exactly when you need them to be. In other words, you should strive to achieve the goals of your coding with as little code execution as possible!
  • Use the less expensive event handler. If several event handlers can achieve the same goal, you should go for the one who takes the least toll on your system. Don’t use Workbook_SheetSelectionChange if what you really want is to monitor selection changes on only one of your worksheets! In that case, you should use the Worksheet_SelectionChange event handler instead.
  • Turn off event handling when you’re running procedures. There exist valid exceptions to this rule, but you should adhere to it whenever you do not need event handling while your procedure is running. If your procedure triggers event handlers while it’s being executed, the execution time will be considerably longer than it needs to be. Simply set Application.EnableEvents = False at beginning of the procedure and then set it back to True and the end of it.
  • Is event handling the right solution for you? Sometimes the benefits of using event handlers are outweighed by the cost of using them. Workbook event handlers are particularly expensive since they work at the application level and typically monitor many Excel objects at once, rather just a single object, such as a worksheet. If your workbook is slow to work with for no immediately apparent reason, the problem could be that laborious and unnecessary event handling procedures are running in the background. Try turning them off and see if you can spot any performance differences.

That’s all for this tutorial. When you’re ready to take your VBA to the next level, subscribe using the form below.