VBA On Error – Error Handling Best Practices

Written by

Editorial Team

Reviewed by

Steve Rynearson

Last updated on December 15, 2021

VBA Errors Cheat Sheet

Errors

Description
VBA Code
On Error – Stop code and display error
On Error Goto 0
On Error – Skip error and continue running
On Error Resume Next
On Error – Go to a line of code [Label]
On Error Goto [Label]
Clears (Resets) Error
On Error GoTo1
Show Error number
MsgBox Err.Number
Show Description of error
MsgBox Err.Description
Function to generate own error
Err.Raise

See more VBA “Cheat Sheets” and free PDF Downloads

VBA Error Handling

VBA Error Handling refers to the process of anticipating, detecting, and resolving VBA Runtime Errors. The VBA Error Handling process occurs when writing code, before any errors actually occur.

VBA Runtime Errors are errors that occur during code execution. Examples of runtime errors include:

VBA On Error Statement

Most VBA error handling is done with the On Error Statement. The On Error statement tells VBA what to do if it encounters an error. There are three On Error Statements:

  • On Error GoTo 0
  • On Error Resume Next
  • On Error GoTo Line

On Error GoTo 0

On Error GoTo 0 is VBA’s default setting. You can restore this default setting by adding the following line of code:

On Error GoTo 0

When an error occurs with On Error GoTo 0, VBA will stop executing code and display its standard error message box.

vba runtime error 13

Often you will add an On Error GoTo 0 after adding On Error Resume Next error handling (next section):

Sub ErrorGoTo0()

On Error Resume Next
    ActiveSheet.Shapes("Start_Button").Delete
On Error GoTo 0

'Run More Code

End Sub

On Error Resume Next

On Error Resume Next tells VBA to skip any lines of code containing errors and proceed to the next line.

On Error Resume Next

Note: On Error Resume Next does not fix an error, or otherwise resolve it. It simply tells VBA to proceed as if the line of code containing the error did not exist. Improper use of On Error Resume Next can result in unintended consequences.

A great time to use On Error Resume Next is when working with objects that may or may not exist. For example, you want to write some code that will delete a shape, but if you run the code when the shape is already deleted, VBA will throw an error. Instead you can use On Error Resume Next to tell VBA to delete the shape if it exists.

On Error Resume Next
    ActiveSheet.Shapes("Start_Button").Delete
On Error GoTo 0

Notice we added On Error GoTo 0 after the line of code containing the potential error. This resets the error handling.

In the next section we’ll show you how to test if an error occurred using Err.Number, giving you more advanced error handling options.

Err.Number, Err.Clear, and Catching Errors

Instead of simply skipping over a line containing an error, we can catch the error by using On Error Resume Next and Err.Number.

Err.Number returns an error number corresponding with the type of error detected. If there is no error, Err.Number = 0.

For example, this procedure will return “11” because the error that occurs is Run-time error ’11’.

Sub ErrorNumber_ex()

On Error Resume Next
ActiveCell.Value = 2 / 0
MsgBox Err.Number

End Sub

vba run-time error 11 err.number

Error Handling with Err.Number

The true power of Err.Number lies in the ability to detect if an error occurred (Err.Number <> 0).  In the example below, we’ve created a function that will test if a sheet exists by using Err.Number.

Sub TestWS()
    MsgBox DoesWSExist("test")
End Sub

Function DoesWSExist(wsName As String) As Boolean
    Dim ws As Worksheet
    
    On Error Resume Next
    Set ws = Sheets(wsName)
    
    'If Error WS Does not exist
    If Err.Number <> 0 Then
        DoesWSExist = False
    Else
        DoesWSExist = True
    End If

    On Error GoTo -1
End Function

Note: We’ve added a On Error GoTo -1 to the end which resets Err.Number to 0 (see two sections down).

With On Error Resume Next and Err.Number, you can replicate the “Try” & “Catch” functionality of other programming languages.

On Error GoTo Line

On Error GoTo Line tells VBA to “go to” a labeled line of code when an error is encountered.  You declare the Go To statement like this (where errHandler is the line label to go to):

On Error GoTo errHandler

and create a line label like this:

errHandler:

Note: This is the same label that you’d use with a regular VBA GoTo Statement.

Below we will demonstrate using On Error GoTo Line to Exit a procedure.

On Error Exit Sub

You can use On Error GoTo Line to exit a sub when an error occurs.

You can do this by placing the error handler line label at the end of your procedure:

Sub ErrGoToEnd()

On Error GoTo endProc

'Some Code
    
endProc:
End Sub

or by using the Exit Sub command:

Sub ErrGoToEnd()

On Error GoTo endProc

'Some Code
GoTo skipExit
    
endProc:
Exit Sub

skipExit:

'Some More Code

End Sub

Err.Clear, On Error GoTo -1,  and Resetting Err.Number

After an error is handled, you should generally clear the error to prevent future issues with error handling.

After an error occurs, both Err.Clear and On Error GoTo -1 can be used to reset Err.Number to 0. But there is one very important difference: Err.Clear does not reset the actual error itself, it only resets the Err.Number.

What does that mean?  Using Err.Clear, you will not be able to change the error handling setting. To see the difference, test out this code and replace On Error GoTo -1 with Err.Clear:

Sub ErrExamples()

    On Error GoTo errHandler:
        
    '"Application-defined" error
    Error (13)
    
Exit Sub
errHandler:
    ' Clear Error
    On Error GoTo -1
    
    On Error GoTo errHandler2:
    
    '"Type mismatch" error
    Error (1034)
    
Exit Sub
errHandler2:
    Debug.Print Err.Description
End Sub

Typically, I recommend always using On Error GoTo -1, unless you have a good reason to use Err.Clear instead.

VBA On Error MsgBox

You might also want to display a Message Box on error.  This example will display different message boxes depending on where the error occurs:

Sub ErrorMessageEx()
 
Dim errMsg As String
On Error GoTo errHandler

    'Stage 1
    errMsg = "An error occured during the Copy & Paste stage."
    'Err.Raise (11)
    
    'Stage 2
    errMsg = "An error occured during the Data Validation stage."
    'Err.Raise (11)
     
    'Stage 3
    errMsg = "An error occured during the P&L-Building and Copy-Over stage."
    Err.Raise (11)
     
    'Stage 4
    errMsg = "An error occured while attempting to log the Import on the Setup Page"
    'Err.Raise (11)

    GoTo endProc
    
errHandler:
    MsgBox errMsg
   
endProc:
End Sub

Here you would replace Err.Raise(11) with your actual code.

VBA IsError

Another way to handle errors is to test for them with the VBA ISERROR Function. The ISERROR Function tests an expression for errors, returning TRUE or FALSE if an error occurs.

Sub IsErrorEx()
    MsgBox IsError(Range("a7").Value)
End Sub

VBA Programming | Code Generator does work for you!

If Error VBA

You can also handle errors in VBA with the Excel IFERROR Function.  The IFERROR Function must be accessed by using the WorksheetFunction Class:

Sub IfErrorEx()

Dim n As Long
n = WorksheetFunction.IfError(Range("a10").Value, 0)

MsgBox n
End Sub

This will output the value of Range A10, if the value is an error, it will output 0 instead.

VBA Error Types

Runtime Errors

As stated above:

VBA Runtime Errors are errors that occur during code execution. Examples of runtime errors include:

  • Referencing a non-existent workbook, worksheet, or other object
  • Invalid data ex. referencing an Excel cell containing an error
  • Attempting to divide by zero

vba runtime error 13

You can “error handle” runtime errors using the methods discussed above.

Syntax Errors

VBA Syntax Errors are errors with code writing. Examples of syntax errors include:

  • Mispelling
  • Missing or incorrect punctuation

The VBA Editor identifies many syntax errors with red highlighting:

vba syntax error example

The VBA Editor also has an option to “Auto Syntax Check”:

vba syntax error option

When this is checked, the VBA Editor will generate a message box alerting you syntax errors after you enter a line of code:

vba syntax compile error

I personally find this extremely annoying and disable the feature.

Compile Errors

Before attempting to run a procedure, VBA will “compile” the procedure. Compiling transforms the program from source code (that you can see) into executable form (you can’t see).

VBA Compile Errors are errors that prevent the code from compiling.

A good example of a compile error is a missing variable declaration:

vba compile error variable

Other examples include:

  • For without Next
  • Select without End Select
  • If without End If
  • Calling a procedure that does not exist

Syntax Errors (previous section) are a subset of Compile Errors.

AutoMacro | Ultimate VBA Add-in | Click for Free Trial!

Debug > Compile

Compile errors will appear when you attempt to run a Procedure. But ideally, you would identify compile errors prior to attempting to run the procedure.

You can do this by compiling the project ahead of time. To do so, go to Debug > Compile VBA Project.

vba debug compile

The compiler will “go to” the first error. Once you fix that error, compile the project again. Repeat until all errors are fixed.

You can tell that all errors are fixed because Compile VBA Project will be grayed out:

vba compile vbaproject

OverFlow Error

The VBA OverFlow Error occurs when you attempt to put a value into a variable that is too large. For example, Integer Variables can only contain values between -32,768 to 32,768. If you enter a larger value, you’ll receive an Overflow error:

vba overflow error

Instead, you should use the Long Variable to store the larger number.

Other VBA Error Terms

VBA Catch Error

Unlike other programming languages, In VBA there is no Catch Statement. However, you can replicate a Catch Statement by using On Error Resume Next and If Err.Number <> 0 Then. This is covered above in Error Handling with Err.Number.

AutoMacro | Ultimate VBA Add-in | Click for Free Trial!

VBA Ignore Error

To ignore errors in VBA, simply use the On Error Resume Next statement:

On Error Resume Next

However, as mentioned above, you should be careful using this statement as it doesn’t fix an error, it just simply ignores the line of code containing the error.

VBA Throw Error / Err.Raise

To through an error in VBA, you use the Err.Raise method.

This line of code will raise Run-time error ’13’: Type mismatch:

Err.Raise (13)

vba runtime error 13

VBA Error Trapping

VBA Error Trapping is just another term for VBA Error Handling.

VBA Error Message

A VBA Error Message looks like this:

vba runtime error 13

When you click ‘Debug’, you’ll see the line of code that is throwing the error:

vba raise error

AutoMacro | Ultimate VBA Add-in | Click for Free Trial!

VBA Error Handling in a Loop

The best way to error handle within a Loop is by using On Error Resume Next along with Err.Number to detect if an error has occurred (Remember to use Err.Clear to clear the error after each occurrence).

The example below will divide two numbers (Column A by Column B) and output the result into Column C. If there’s an error, the result will be 0.

Sub test()
Dim cell As Range

On Error Resume Next
For Each cell In Range("a1:a10")

    'Set Cell Value
    cell.Offset(0, 2).Value = cell.Value / cell.Offset(0, 1).Value
    
    'If Cell.Value is Error then Default to 0
    If Err.Number <> 0 Then
         cell.Offset(0, 2).Value = 0
         Err.Clear
    End If
 Next
End Sub

VBA Error Handling in Access

All of the above examples work exactly the same in Access VBA as in Excel VBA.

Function DelRecord(frm As Form)
'this function is used to delete a record in a table from a form
   On Error GoTo ending
   With frm
      If .NewRecord Then
         .Undo
         Exit Function
      End If
   End With
   With frm.RecordsetClone
      .Bookmark = frm.Bookmark
      .Delete
      frm.Requery
   End With
   Exit Function
   ending:
   End
End Function

vba-free-addin

VBA Code Examples Add-in

Easily access all of the code examples found on our site.

Simply navigate to the menu, click, and the code will be inserted directly into your module. .xlam add-in.

(No installation required!)

Free Download

Return to VBA Code Examples