VBA Error Handling

Write robust VBA code with proper error trapping and handling techniques

Quick Reference

On Error Resume Next: Continue after errors (use cautiously)

On Error GoTo Label: Jump to error handler

On Error GoTo 0: Disable error handler

Err Object: Contains error information (Number, Description, Source)

Why Error Handling Matters

Without error handling, VBA code stops immediately when an error occurs, showing cryptic error messages to users. Proper error handling:

  • Prevents code crashes and Excel freezes
  • Provides user-friendly error messages
  • Logs errors for debugging
  • Allows graceful recovery or cleanup
  • Makes code production-ready

❌ Without Error Handling

Code stops, shows "Run-time error 1004", leaves data in inconsistent state

✓ With Error Handling

Catches error, shows "File not found. Please check path", cleans up resources

On Error Resume Next

Continues execution on the next line after an error occurs. Use sparingly!

Basic Example:

Sub ResumeNextExample()
On Error Resume Next ' Enable error ignoring
Range("NonExistent").Value = 100 ' This fails silently
Range("A1").Value = "Success" ' This runs anyway
On Error GoTo 0 ' Disable error handler
End Sub

Check for Errors After:

Sub CheckErrors()
On Error Resume Next
' Try risky operation
Workbooks.Open "C:\NonExistent.xlsx"
' Check if it failed
If Err.Number <> 0 Then
MsgBox "Error: " & Err.Description
Err.Clear ' Clear error
End If
On Error GoTo 0
End Sub

Warning: On Error Resume Next hides ALL errors, even unexpected ones. Always check Err.Number immediately after risky operations!

On Error GoTo (Recommended)

Jumps to a labeled error handler when an error occurs. This is the professional approach.

Basic Structure:

Sub ProperErrorHandling()
On Error GoTo ErrorHandler
' Your main code here
Range("A1").Value = 100
' More code...
Exit Sub ' Exit before error handler
ErrorHandler:
MsgBox "Error: " & Err.Description
End Sub

Complete Example with Cleanup:

Sub CompleteErrorHandling()
Dim wb As Workbook
On Error GoTo ErrorHandler
' Main code
Application.ScreenUpdating = False
Set wb = Workbooks.Open("C:\Data.xlsx")
' Process workbook...
wb.Close SaveChanges:=True
' Cleanup
Application.ScreenUpdating = True
Exit Sub
ErrorHandler:
' Cleanup even on error
Application.ScreenUpdating = True
If Not wb Is Nothing Then wb.Close False
' Show error
MsgBox "An error occurred: " & Err.Description, vbCritical
End Sub

Resume Statements:

Resume ' Retry same line that caused error
Resume Next ' Continue on next line
Resume LineLabel ' Jump to specific line

The Err Object

VBA's built-in error object containing information about the last error.

Key Properties:

PropertyDescriptionExample
NumberError code1004
DescriptionError message"File not found"
SourceSource of error"VBAProject"
HelpFileHelp file pathC:\Help.chm
HelpContextHelp topic ID1000

Key Methods:

Err.Clear ' Reset error object (Number = 0)
Err.Raise Number:=1000, Description:="Custom error"

Detailed Error Logging:

Sub LogError()
On Error GoTo ErrorHandler
' Your code...
Exit Sub
ErrorHandler:
Dim errorMsg As String
errorMsg = "Error " & Err.Number & ": " & Err.Description
errorMsg = errorMsg & vbCrLf & "Source: " & Err.Source
Debug.Print errorMsg ' Or write to log file
MsgBox errorMsg, vbCritical, "Error Details"
End Sub

Common VBA Error Numbers

Error #DescriptionCommon Cause
5Invalid procedure callBad argument value
6OverflowNumber too large for data type
7Out of memoryToo many objects/variables
9Subscript out of rangeArray index invalid
11Division by zeroDividing by 0
13Type mismatchWrong data type
53File not foundFile path invalid
91Object variable not setForgot Set keyword
1004Application-defined errorExcel object model error

Handling Specific Errors:

Sub HandleSpecificErrors()
On Error GoTo ErrorHandler
' Your code...
Exit Sub
ErrorHandler:
Select Case Err.Number
Case 53 ' File not found
MsgBox "File doesn't exist. Check path."
Case 91 ' Object not set
MsgBox "Object reference error."
Case 1004 ' Excel error
MsgBox "Excel operation failed."
Case Else
MsgBox "Unexpected error: " & Err.Description
End Select
End Sub

Raising Custom Errors

Use Err.Raise to create your own errors for validation and flow control.

Basic Custom Error:

Sub ValidateInput(value As Integer)
If value < 0 Then
Err.Raise vbObjectError + 1000, _
Description:="Value cannot be negative"
End If
End Sub

Use vbObjectError + your number to avoid conflicts with VBA error numbers

Complete Example with Custom Errors:

Sub ProcessData()
On Error GoTo ErrorHandler
Dim age As Integer
age = Range("A1").Value
' Validation
If age < 0 Then
Err.Raise vbObjectError + 1001, _
Description:="Age must be positive"
ElseIf age > 150 Then
Err.Raise vbObjectError + 1002, _
Description:="Age seems unrealistic"
End If
MsgBox "Valid age: " & age
Exit Sub
ErrorHandler:
If Err.Number >= vbObjectError + 1000 And _
Err.Number <= vbObjectError + 1999 Then
MsgBox "Validation Error: " & Err.Description
Else
MsgBox "System Error: " & Err.Description
End If
End Sub

Debugging Techniques

Debug.Print for Tracing:

Sub TraceExecution()
Debug.Print "Starting process..."
Debug.Print "Value of X: " & x
Debug.Print "Completed at " & Now
End Sub

View output in Immediate Window (Ctrl+G)

Breakpoints:

  • Click left margin or press F9 to set breakpoint
  • Code pauses at breakpoint - inspect variables
  • F8 to step through line by line
  • F5 to continue running

Stop Statement:

If suspiciousCondition Then
Stop ' Pause execution here
End If

Assert for Testing:

Debug.Assert x > 0 ' Breaks if condition false

Error Handling Best Practices

Always use error handling in production code: Every Sub/Function should have error handler
Prefer On Error GoTo over Resume Next: More control and better debugging
Always include Exit Sub before error handler: Prevents falling through to error handler on success
Clean up resources in error handler: Close files, reset ScreenUpdating, release objects
Log errors for debugging: Write to file or Debug.Print with timestamp
Provide user-friendly messages: Don't show technical error codes to end users
Use Option Explicit: Catch undeclared variables at compile time
Test error handlers: Deliberately cause errors to verify handling works

Production-Ready Template

Sub ProductionTemplate()
' ===== Setup =====
Const PROCEDURE_NAME As String = "ProductionTemplate"
On Error GoTo ErrorHandler
' ===== Main Code =====
Application.ScreenUpdating = False
Application.EnableEvents = False
' Your business logic here...
' ===== Cleanup =====
CleanUp:
Application.ScreenUpdating = True
Application.EnableEvents = True
Exit Sub
' ===== Error Handler =====
ErrorHandler:
' Log error
Debug.Print Now & " - " & PROCEDURE_NAME & ": " & _
"Error " & Err.Number & " - " & Err.Description
' Show user message
MsgBox "An error occurred. Please contact support.", _
vbCritical, PROCEDURE_NAME
' Cleanup and exit
Resume CleanUp
End Sub

Related VBA Tutorials

Generate Error-Free VBA Code

AI-generated VBA code with built-in error handling and best practices

✓ No credit card required ✓ 5 free generations