If you have not modified Excel’s Quick Access toolbar, it probably includes the Undo and Redo buttons. Here is a screenshot of my Quick Access toolbar, where I have added the Back button to the left of Undo and the Repeat button to the right of Redo. The screenshot includes my Custom ribbon, where I have duplicated these four buttons for better illustration of this discussion. (The Back button can be ignored for the remainder.)

Undo, Redo, and Repeat Buttons

You might have noticed the Undo (Ctrl+Z) and Redo (Ctrl+Y) buttons usually lose their previous “stack” of choices whenever you run an Excel macro. You might subsequently notice the Repeat button (also Ctrl+Y) repeats the Excel macro that was recently run. But did you know you can program the behavior of the Undo and Repeat buttons using VBA? If done carefully, this lets you simulate undoing a macro after it was executed. In this tutorial, we’re going to incrementally develop a series of macros to demonstrate this behavior.

Now before you ask, why do Redo and Repeat share the same keyboard shortcut (Ctrl+Y)? I wish I knew. In fact the Repeat button frequently “becomes” the Redo button, including sharing its icon. As we will learn, there is no way to program the Redo button in VBA; only the Undo and Repeat buttons offer that feature. For these reasons, I normally remove the Redo button from my Quick Access toolbar, but let us keep Undo, Redo, and Repeat for now. We will also learn that programming the Repeat button is not recommended because it upsets the Redo button’s normal function.

Basic AddOneMonth Macro

I have a spreadsheet to keep track of monthly bills including date received and date due. I noticed that several of the bills are received and/or due on the same day each month. Therefore, I created a macro to add one month if a selected cell contains a date literal (not a formula), and I made the macro easy to run by giving it a keyboard shortcut (Ctrl+Shift+M).

Public Sub AddOneMonth1()
'
'   If Selection is a single cell (ActiveCell) containing a date literal (not a date formula), then increment its value by one month
'
    If Selection.Cells.Count = 1 And Not ActiveCell.HasFormula And IsDate(ActiveCell.Value) Then
        ActiveCell.Value = DateAdd("m", 1, ActiveCell.Value)
    Else
        Beep
    End If
End Sub

Make powerful macros with our free VBA Developer Kit

It’s easy to copy and paste a macro like this, but it’s harder make one on your own. To help you make macros like this, we built a free VBA Developer Kit and wrote the Big Book of Excel VBA Macros full of hundreds of pre-built macros to help you master file I/O, arrays, strings and more - grab your free copy below.

I'll take a free VBA Developer Kit

If Selection is a single cell, then it will also be the ActiveCell. If the cell does not contain a formula and its value is a date, then one month will be added to the date in the cell. Otherwise, the VBA statement Beep will signal the macro completed without changing anything. You may recognize the VBA Beep statement from our tutorial on providing an audial cue when an error is received. DateAdd is a VBA function used to add a specified amount of time to an existing date. We used the same function when scheduling a macro in our VBA OnTime tutorial.

The following screenshots illustrate my spreadsheet with the Undo, Redo, and Repeat buttons before and after selecting the Cable bill’s date and running AddOneMonth1. Before the macro, Undo and Redo had their usual stacks and Repeat duplicated the top of the Redo stack. After the macro, the Undo and Redo stacks are empty and Repeat says it will Repeat Macros.

Note: The repeat button should say Repeat Macro (singular) because it will only repeat the most recent macro that was run by the user (or by Excel). In particular, the term Repeat Macro does not apply to a Sub that was activated by a VBA statement (for example, Call MySub).

Before and After AddOneMonth1

AddOneMonth Macro With Undo

In the following macro named AddOneMonth2, we will program the Undo button after a cell’s date has been incremented to enable restoration of its original value. The magic is done by Application.OnUndo. Since this is an Application method, it applies to all cells, sheets, and workbooks currently opened by Excel. That means that before we can restore the date, we must recall which cell was incremented, which worksheet contains that cell, and which workbook contains that sheet.

This is convenient if we do both the incrementing and the restoring in a single Sub AddOneMonth2_Do procedure that includes an Undo argument telling us which action to perform. When Undo is zero, the date in the ActiveCell will be incremented and the Undo button will be programmed to enable restoration of the original date. Sub AddOneMonth2_Do is declared Private because it is only expected to be useful within the current VBA Module. Let’s look at the code before further discussion.

Public Sub AddOneMonth2()
'
'   If Selection is a single cell (ActiveCell) containing a date literal (not a date formula), then increment its value by one month
'   Undo is supported
'
    If Selection.Cells.Count = 1 And Not ActiveCell.HasFormula And IsDate(ActiveCell.Value) Then
        Call AddOneMonth2_Do(0)
    Else
        Beep
    End If
End Sub

Private Sub AddOneMonth2_Do(ByVal Undo As Integer)
    Static xBook As Workbook, xSheet As Worksheet, xCell As Range, xValue As Date
    Const sName As String = "AddOneMonth2"
    Const sUndo As String = "Undo Month+1 in "
    If Undo = 0 Then
        Set xBook = ActiveWorkbook
        Set xSheet = ActiveSheet
        Set xCell = ActiveCell
        xValue = xCell.Value
        xCell.Show
        xCell.ClearContents
        DoEvents
        xCell.Value = DateAdd("m", 1, xValue)
        Application.OnUndo (sUndo + xCell.Address(False, False)), (ThisWorkbook.Name + "!" + sName + "_Undo")
    ElseIf xCell Is Nothing Then
        Beep
    Else
        xBook.Activate
        xSheet.Activate
        xCell.Select
        xCell.Show
        xCell.ClearContents
        DoEvents
        xCell.Value = xValue
        Set xCell = Nothing
    End If
End Sub

Private Sub AddOneMonth2_Undo()
    Call AddOneMonth2_Do(-1)
End Sub

A procedure’s local variables (for example, those declared using the Dim statement) normally lose their value when the procedure has completed, but variables declared Static retain their value until the workbook containing that procedure is closed. Because of their increased variable lifetime, we have used Static variables to remember which workbook, worksheet, and cell was incremented and to remember the date’s original value. We also use Const to define items that cannot be changed within the procedure; defining these constants near the top of the procedure makes them convenient to update if you wish to modify the code later.

When the AddOneMonth2 macro is run, it calls AddOneMonth2_Do(0) to increment the selected date. When the Undo argument is zero, AddOneMonth2_Do initializes its Static variables, then uses the Show method to make sure ActiveCell is in view within Excel’s window. The ClearContents method makes the cell blank without disturbing its format. The DoEvents VBA function is simply used to introduce a pause or “wink” so the user might notice the cell has changed. After the date has been incremented, the Application.OnUndo method programs the Undo button to enable restoration of the cell’s original value.

The Application.OnUndo method accepts two String parameters.

  1. The first parameter defines a screen tip for the Undo button; in our case it will include the cell’s relative address. This is the text that will appear when you hover over the Undo button.
  2. The second parameter identifies a procedure that Excel will run when the Undo button is clicked; that procedure must be a Sub with no arguments. In our case the procedure is AddOneMonth2_Undo, a Private Sub that simply calls AddOneMonth2_Do(-1).

Notice the -1 argument when calling the AddOneMonth2_Do macro. When the Undo argument is not zero, AddOneMonth2_Do recalls the retained values of its Static variables to restore the workbook, worksheet, and cell to their original view and the cell’s date to its original value. Finally, the Range object xCell is set to Nothing so that AddOneMonth2_Undo will simply produce a Beep signal if it is repeated before the user runs the AddOneMonth2 macro again.

Notice the Undo button will perform appropriately even if the original workbook, worksheet, or cell are no longer displayed in Excel’s window; however, we have assumed the workbook remains open and the worksheet has not been deleted. If these assumptions are troublesome, we could introduce some VBA On Error… error handling to address this situation.

The following screenshots illustrate the Undo, Redo, and Repeat buttons before and after selecting the Cable bill’s date and running AddOneMonth2. Before the macro, Undo and Redo had their usual stacks and Repeat duplicated the top of the Redo stack. After the macro, the middle screenshot indicates the Undo button will restore the date in cell B4, the Redo stack is empty, and Repeat will rerun AddOneMonth2. When the Undo button was clicked, Excel ran AddOneMonth2_Undo to restore the Cable bill’s original date. This nullified the Undo and Redo buttons, but the Repeat button was set to rerun the last macro AddOneMonth2_Undo, producing a Beep signal.

Before and After AddOneMonth2

AddOneMonth Macro With Undo and Repeat

Excel’s object model does not provide an OnRedo method, but we can try to use Application.OnRepeat to simulate a Redo function in the following macro named AddOneMonth3.

Public Sub AddOneMonth3()
'
'   If Selection is a single cell (ActiveCell) containing a date literal (not a date formula), then increment its value by one month
'   Undo and Repeat (Redo) are supported
'
    If Selection.Cells.Count = 1 And Not ActiveCell.HasFormula And IsDate(ActiveCell.Value) Then
        Call AddOneMonth3_Do(0)
    Else
        Beep
    End If
End Sub

Private Sub AddOneMonth3_Do(ByVal Undo As Integer)
    Static xBook As Workbook, xSheet As Worksheet, xCell As Range, xValue As Date
    Const sName As String = "AddOneMonth3"
    Const sUndo As String = "Undo Month+1 in "
    Const sRedo As String = "Redo Month+1 in "
    If Undo = 0 Then
        Set xBook = ActiveWorkbook
        Set xSheet = ActiveSheet
        Set xCell = ActiveCell
        xValue = xCell.Value
        xCell.Show
        xCell.ClearContents
        DoEvents
        xCell.Value = DateAdd("m", 1, xValue)
        Application.OnUndo (sUndo + xCell.Address(False, False)), (ThisWorkbook.Name + "!" + sName + "_Undo")
    ElseIf xCell Is Nothing Then
        Beep
    Else
        xBook.Activate
        xSheet.Activate
        xCell.Select
        xCell.Show
        xCell.ClearContents
        DoEvents
        If Undo < 0 Then
            xCell.Value = xValue
            Application.OnRepeat (sRedo + xCell.Address(False, False)), (ThisWorkbook.Name + "!" + sName + "_Redo")
        Else
            xCell.Value = DateAdd("m", 1, xValue)
            Set xCell = Nothing
        End If
    End If
End Sub

Private Sub AddOneMonth3_Undo()
    Call AddOneMonth3_Do(-1)
End Sub

Private Sub AddOneMonth3_Redo()
    Call AddOneMonth3_Do(1)
End Sub

The AddOneMonth3_Do procedure in similar to the previous AddOneMonth2_Do except when its Undo argument is negative (i.e., after AddOneMonth3_Undo) the OnRepeat method programs the Repeat button to run AddOneMonth3_Redo, which simply calls AddOneMonth3_Do(1). In this case the Undo argument will be greater than zero so the original date value (i.e., the value before running AddOneMonth3) will be incremented again (redone). Finally, xCell is set to Nothing so that AddOneMonth3_Redo will simply produce a Beep signal if it is repeated before the AddOneMonth3 macro is rerun by the user.

The following screenshots illustrate the Undo, Redo, and Repeat buttons after selecting the Cable bill’s date and running AddOneMonth3. When the Undo button was clicked, the middle screenshot indicates the Repeat button will “Redo Month+1 in B4.” But before capturing the middle screenshot I had typed a new date in cell C7, then clicked the Undo button to make C7 blank again, then clicked the Redo button to “Redo Typing ‘4/22’ in C7….” As we can see, the Redo button has no effect when the Repeat button has been programmed by use of the OnRepeat method.

After AddOneMonth3

The final screenshot shows the result after clicking the Repeat button to “Redo Month+1 in B4.” In this case, Excel ran AddOneMonth3_Redo to increment the Cable bill’s date again. This nullified the Undo and Redo buttons, but the Repeat button was set to rerun the last macro AddOneMonth3_Redo, producing a Beep signal.

Conclusions

This tutorial demonstrates how easy it is to program the Undo button with the Application.OnUndo method. The supporting VBA code must be carefully designed, though. Unfortunately, Excel’s object model does not provide an OnRedo method to customize operation of the Redo button. Although it’s possible to simulate Redo with Repeat, use of the OnRepeat method is discouraged because of apparent interference with the Redo button’s normal function.

I hope you’ll take a minute to subscribe for more VBA tips. Simply fill out the form below and we’ll share our best time-saving VBA tips.