Debug.Print and Debugging

Maintained on

When developing VBA programs, finding and fixing bugs is an unavoidable part of the process. Mastering proper debugging techniques will dramatically improve your development efficiency.

This article covers various VBA debugging methods, from basics to advanced techniques.

Situations Requiring Debugging

During program development, you may encounter these issues:

  • Unexpected behavior: Wrong calculation results, incorrect data processing
  • Errors: Runtime errors that stop the program
  • Infinite loops: Programs that never terminate
  • Performance issues: Extremely slow processing
  • Unknown variable values: Not knowing where or how values change

VBA provides powerful debugging tools to solve these problems.

VBA Debugging Tools Overview

VBA offers these debugging tools:

ToolPurposeShortcut
Debug.PrintOutput to Immediate Window-
Immediate WindowCheck results, evaluate expressionsCtrl + G
BreakpointPause execution at specified lineF9
Step IntoExecute one line (enter procedures)F8
Step OverExecute one line (skip procedures)Shift + F8
Step OutExit current procedureCtrl + Shift + F8
Watch WindowMonitor variable values-
Locals WindowDisplay local variables-

Debug.Print: The Fundamental Technique

What Is Debug.Print?

Debug.Print outputs values to the Immediate Window. It’s one of the simplest yet most powerful debugging techniques.

Basic Usage

debug_print_basic.bas
Sub DebugPrintBasic()
    Dim name As String
    Dim age As Integer

    name = "John Smith"
    age = 30

    ' Output a string
    Debug.Print "Program started"

    ' Output variable values
    Debug.Print "Name: " & name
    Debug.Print "Age: " & age

    ' Output expression results
    Debug.Print "Age in 10 years: " & (age + 10)
End Sub
チェック
To open the Immediate Window, press Ctrl + G in the VBE (Visual Basic Editor).

Tracking Program Flow

debug_print_flow.bas
Sub TrackProcessFlow()
    Debug.Print "=== Program Start ==="

    Dim i As Integer
    For i = 1 To 5
        Debug.Print "Loop iteration " & i

        If i Mod 2 = 0 Then
            Debug.Print "  -> Even number"
        Else
            Debug.Print "  -> Odd number"
        End If
    Next i

    Debug.Print "=== Program End ==="
End Sub

Checking Variable Types and Values

debug_print_type.bas
Sub CheckVariableType()
    Dim value As Variant

    value = "text"
    Debug.Print "Value: " & value & ", Type: " & TypeName(value)

    value = 123
    Debug.Print "Value: " & value & ", Type: " & TypeName(value)

    value = True
    Debug.Print "Value: " & value & ", Type: " & TypeName(value)

    value = #10/20/2025#
    Debug.Print "Value: " & value & ", Type: " & TypeName(value)
End Sub
チェック

The TypeName function returns a variable’s type. It’s useful for identifying when Variant variables unexpectedly contain the wrong type.

Inspecting Array Contents

debug_print_array.bas
Sub DebugPrintArray()
    Dim fruits() As Variant
    Dim i As Integer

    fruits = Array("apple", "banana", "orange", "grape")

    Debug.Print "=== Array Contents ==="
    For i = LBound(fruits) To UBound(fruits)
        Debug.Print "fruits(" & i & ") = " & fruits(i)
    Next i
End Sub

Outputting Object Properties

debug_print_object.bas
Sub DebugPrintObject()
    Dim ws As Worksheet
    Set ws = ActiveSheet

    Debug.Print "=== Worksheet Info ==="
    Debug.Print "Name: " & ws.Name
    Debug.Print "Index: " & ws.Index
    Debug.Print "Visible: " & ws.Visible
    Debug.Print "Used Range: " & ws.UsedRange.Address
End Sub

Immediate Window: Interactive Debugging

The Immediate Window isn’t just for viewing Debug.Print output—you can also execute code directly.

Evaluating Expressions

' Type directly in Immediate Window
? 1 + 2 + 3
' Output: 6

? Range("A1").Value
' Output: (cell A1's value)

? ActiveSheet.Name
' Output: (active sheet name)
チェック

? is shorthand for Debug.Print. Typing ? expression outputs the expression’s value.

Executing Statements

' Set values directly
Range("A1").Value = "Test"

' Call procedures
Call MyProcedure

' Change variable values (during break mode)
x = 100

Checking Variables During Execution

check_variables.bas
Sub CheckVariables()
    Dim total As Long
    Dim items(1 To 5) As Long
    Dim i As Integer

    For i = 1 To 5
        items(i) = i * 10
        total = total + items(i)
    Next i

    ' Set breakpoint here, then type in Immediate Window:
    ' ? total
    ' ? items(3)

    Debug.Print "Total: " & total
End Sub

Breakpoints: Pausing Execution

Setting Breakpoints

Click the gray margin to the left of a code line, or press F9 to set a breakpoint. Execution pauses when it reaches that line.

breakpoint_example.bas
Sub BreakpointExample()
    Dim i As Integer
    Dim total As Long

    For i = 1 To 100
        total = total + i

        ' Set breakpoint on this line to check values during loop
        Debug.Print "i=" & i & ", total=" & total
    Next i
End Sub

Conditional Breakpoints

For loops or frequently called code, you may want to break only under certain conditions:

conditional_break.bas
Sub ConditionalBreakExample()
    Dim i As Integer

    For i = 1 To 1000
        ' Add this condition and set breakpoint on the Stop line
        If i = 500 Then
            Stop  ' Execution pauses here when i reaches 500
        End If

        ' Normal processing
        Debug.Print i
    Next i
End Sub
チェック

The Stop statement pauses execution like a breakpoint. It’s useful for conditional pausing.

Step Execution: Line-by-Line Debugging

Step Into (F8)

Executes one line at a time. When encountering a procedure call, enters that procedure.

Step Over (Shift + F8)

Executes one line at a time. When encountering a procedure call, executes it entirely without entering.

Step Out (Ctrl + Shift + F8)

Continues execution until the current procedure ends, then pauses.

step_execution.bas
Sub MainProcedure()
    Dim result As Long

    Debug.Print "Start of main procedure"

    result = CalculateValue(10)  ' Step Into enters this procedure
                                  ' Step Over executes it completely

    Debug.Print "Result: " & result
    Debug.Print "End of main procedure"
End Sub

Function CalculateValue(x As Long) As Long
    Dim temp As Long

    temp = x * 2
    temp = temp + 10
    temp = temp * 3

    CalculateValue = temp
End Function

Watch Window: Monitoring Variables

The Watch Window lets you monitor specific variables or expressions in real-time.

Adding a Watch

  1. Go to Debug menu → Add Watch
  2. Enter the expression to watch
  3. Select watch type

Watch Types

TypeDescription
Watch ExpressionDisplay value (default)
Break When Value Is TrueBreak when expression becomes True
Break When Value ChangesBreak when value changes
watch_example.bas
Sub WatchExample()
    Dim counter As Long
    Dim flag As Boolean

    ' Add watches for "counter" and "counter > 50"

    For counter = 1 To 100
        If counter > 50 Then
            flag = True
        End If

        ' Check Watch Window to see value changes in real-time
        DoEvents
    Next counter
End Sub

Locals Window: Viewing Local Variables

The Locals Window automatically displays all local variables in the current scope with their values—no manual setup required.

How to Use

  1. Go to View menu → Locals Window
  2. Start debugging (F8 or set breakpoint)
  3. Locals Window shows all variables

Error Handling and Debugging

Using On Error for Debugging

error_debugging.bas
Sub ErrorDebugging()
    On Error GoTo ErrorHandler

    Dim x As Long
    Dim y As Long
    Dim result As Double

    x = 10
    y = 0

    result = x / y  ' Division by zero error

    Debug.Print "Result: " & result
    Exit Sub

ErrorHandler:
    Debug.Print "=== Error Occurred ==="
    Debug.Print "Error Number: " & Err.Number
    Debug.Print "Error Description: " & Err.Description
    Debug.Print "Error Source: " & Err.Source

    ' For detailed investigation during debugging
    Stop  ' Pause here to check variable values
End Sub

Temporarily Disabling Error Handling

During development, you may want errors to stop execution immediately:

disable_error_handling.bas
Sub TemporaryDebug()
    ' Comment out during debugging to see where errors occur
    ' On Error Resume Next

    ' Your code here
    Dim result As Double
    result = 1 / 0  ' Error occurs here

    Debug.Print result
End Sub

Debugging Best Practices

1. Add Systematic Debug Output

systematic_debug.bas
Sub ProcessData()
    Const PROC_NAME As String = "ProcessData"

    Debug.Print ">>> " & PROC_NAME & " Start"

    ' Processing
    Dim step As Integer

    step = 1
    Debug.Print PROC_NAME & " - Step " & step & ": Loading data"
    ' Data loading process

    step = 2
    Debug.Print PROC_NAME & " - Step " & step & ": Validating data"
    ' Validation process

    step = 3
    Debug.Print PROC_NAME & " - Step " & step & ": Saving results"
    ' Save process

    Debug.Print "<<< " & PROC_NAME & " End"
End Sub

2. Create Reusable Debug Functions

debug_utility.bas
' Debug output control flag
Public Const DEBUG_MODE As Boolean = True

Sub DebugLog(message As String)
    If DEBUG_MODE Then
        Debug.Print Format(Now, "yyyy-mm-dd hh:nn:ss") & " | " & message
    End If
End Sub

Sub TestDebugLog()
    DebugLog "Processing started"
    DebugLog "Step 1 complete"
    DebugLog "Step 2 complete"
    DebugLog "Processing finished"
End Sub

3. Efficiently Use Breakpoints

  • Set breakpoints before and after problem areas
  • Check variable values at each breakpoint
  • Remove breakpoints after resolving issues

Summary

VBA debugging tools help you efficiently identify and fix problems:

ToolPrimary Use
Debug.PrintOutput values and track flow
Immediate WindowInteractive evaluation
BreakpointsPause at specific locations
Step ExecutionLine-by-line code verification
Watch WindowMonitor specific variables
Locals WindowView all local variables

Master these debugging techniques to develop more efficiently and create more reliable VBA programs.

#VBA #Debugging #Debug.Print #Immediate Window #Breakpoints