With Statement

Maintained on

When programming in VBA, you often need to access multiple properties or methods of the same object repeatedly. The With statement makes this much easier. This article explains everything from basics to advanced usage with concrete examples.

When You Need the With Statement

When working with Excel cells, worksheets, charts, and other objects in VBA, it’s common to set multiple properties or execute multiple methods on the same object.

Consider the following code that applies various settings to a cell:

Sub WithoutWithExample()
    ActiveSheet.Range("A1").Value = "Title"
    ActiveSheet.Range("A1").Font.Bold = True
    ActiveSheet.Range("A1").Font.Size = 14
    ActiveSheet.Range("A1").Font.Color = RGB(0, 0, 255)
    ActiveSheet.Range("A1").Interior.Color = RGB(255, 255, 200)
    ActiveSheet.Range("A1").HorizontalAlignment = xlCenter
End Sub

This code repeats ActiveSheet.Range("A1") multiple times, causing several problems:

  • Verbose code that’s harder to read
  • Increased risk of typos
  • Performance degradation (object reference resolution happens every time)
  • Poor maintainability (changing the target cell requires modifying every line)

The With statement solves these problems.

What Is the With Statement?

The With statement lets you write multiple operations on the same object together. Once you specify the object reference after With, you can use abbreviated notation starting with a period (.) within the With...End With block.

Basic Syntax

With object
    .Property1 = Value1
    .Property2 = Value2
    .Method1
End With

Specify the target object after With, then access its members by starting with . (period) inside the block.

チェック

Using the With statement means object reference resolution happens only once at the beginning, which can improve performance. However, for large-scale data processing, other optimization techniques may be more effective.

Practical With Statement Examples

Basic Usage

Let’s rewrite the earlier example using the With statement:

Sub WithExample()
    With ActiveSheet.Range("A1")
        .Value = "Title"
        .Font.Bold = True
        .Font.Size = 14
        .Font.Color = RGB(0, 0, 255)
        .Interior.Color = RGB(255, 255, 200)
        .HorizontalAlignment = xlCenter
    End With
End Sub

The ActiveSheet.Range("A1") reference now appears only once, making the code much cleaner. Each line starting with a period clearly indicates an operation on the object specified in the With statement.

Nested With Statements

With statements can be nested. For example, you can use separate With statements for a cell and its Font object:

Sub NestedWithExample()
    With ActiveSheet.Range("A1")
        .Value = "Important Notice"
        .HorizontalAlignment = xlCenter

        With .Font
            .Name = "Arial"
            .Size = 16
            .Bold = True
            .Color = RGB(255, 0, 0)
        End With

        With .Interior
            .Color = RGB(255, 255, 200)
            .Pattern = xlSolid
        End With
    End With
End Sub

Nesting makes hierarchical object configurations clearer.

チェック

Nesting With statements too deeply can reduce readability. Generally, 2-3 levels of nesting is recommended.

Batch Settings for Multiple Cells

Combine With statements with loops to efficiently configure multiple cells:

Sub MultipleRangeWithExample()
    Dim i As Long

    ' Header row settings
    With ActiveSheet.Range("A1:E1")
        .Value = Array("Name", "Age", "Department", "Title", "Salary")
        .Font.Bold = True
        .Font.Size = 11
        .Interior.Color = RGB(200, 200, 255)
        .HorizontalAlignment = xlCenter
        .VerticalAlignment = xlCenter
    End With

    ' Data row formatting
    For i = 2 To 10
        With ActiveSheet.Rows(i)
            .Font.Size = 10
            .RowHeight = 20

            ' Alternating background colors
            If i Mod 2 = 0 Then
                .Interior.Color = RGB(240, 240, 240)
            End If
        End With
    Next i
End Sub

Combining with Worksheet Objects

The With statement is also convenient for worksheet-level settings:

Sub WorksheetWithExample()
    ' Add and configure a new worksheet
    With Worksheets.Add
        .Name = "MonthlyReport_" & Format(Date, "yyyymm")

        ' Page setup
        With .PageSetup
            .Orientation = xlLandscape
            .PaperSize = xlPaperA4
            .PrintTitleRows = "$1:$1"
            .LeftMargin = Application.InchesToPoints(0.5)
            .RightMargin = Application.InchesToPoints(0.5)
        End With

        ' Set tab color
        .Tab.Color = RGB(100, 200, 100)
    End With
End Sub

Using with Object Variables

Combine the With statement with object variables for more flexible usage:

Sub ObjectVariableWithExample()
    Dim targetRange As Range
    Dim ws As Worksheet

    Set ws = ThisWorkbook.Worksheets("Sheet1")
    Set targetRange = ws.Range("B2:D10")

    ' Format the range
    With targetRange
        .Font.Name = "Calibri"
        .Font.Size = 11
        .Borders.LineStyle = xlContinuous
        .Interior.Color = RGB(255, 255, 230)
    End With
End Sub

Chart Configuration

The With statement is particularly useful for configuring charts, which have many settings:

Sub ConfigureChartWithWith()
    Dim chartObj As ChartObject
    Set chartObj = ActiveSheet.ChartObjects.Add(100, 100, 400, 300)

    With chartObj.Chart
        .ChartType = xlColumnClustered
        .SetSourceData Source:=Range("A1:B10")

        With .ChartTitle
            .Text = "Monthly Sales"
            .Font.Size = 14
            .Font.Bold = True
        End With

        With .Axes(xlCategory)
            .HasTitle = True
            .AxisTitle.Text = "Month"
        End With

        With .Axes(xlValue)
            .HasTitle = True
            .AxisTitle.Text = "Sales ($)"
            .MajorGridlines.Format.Line.Visible = True
        End With

        .Legend.Position = xlLegendPositionBottom
    End With
End Sub

Important Considerations

Don’t Mix External References Inside With Blocks

Inside a With block, any . that doesn’t start the line refers to the With object. Be careful with this:

Sub WithCautionExample()
    Dim otherSheet As Worksheet
    Set otherSheet = Worksheets("Sheet2")

    With ActiveSheet.Range("A1")
        .Value = "Main Value"

        ' This is fine - using a different object explicitly
        otherSheet.Range("A1").Value = "Other Value"

        ' This references the With object
        .Font.Bold = True
    End With
End Sub

Avoid Excessive Nesting

While nesting is powerful, too many levels make code hard to follow:

' Avoid this - too deeply nested
Sub TooMuchNesting()
    With Workbooks("Book1")
        With .Worksheets("Sheet1")
            With .Range("A1")
                With .Font
                    With .Border
                        ' Hard to track which object we're working with
                    End With
                End With
            End With
        End With
    End With
End Sub

' Better - use variables to break up complexity
Sub BetterApproach()
    Dim targetCell As Range
    Set targetCell = Workbooks("Book1").Worksheets("Sheet1").Range("A1")

    With targetCell
        .Value = "Value"
        .Font.Bold = True
    End With
End Sub

Performance Considerations

Using With can improve performance by reducing object resolution overhead:

Sub PerformanceComparison()
    Dim startTime As Double
    Dim i As Long

    ' Without With
    startTime = Timer
    For i = 1 To 10000
        ActiveSheet.Range("A1").Value = i
        ActiveSheet.Range("A1").Font.Bold = True
    Next i
    Debug.Print "Without With: " & Timer - startTime & " seconds"

    ' With With statement
    startTime = Timer
    For i = 1 To 10000
        With ActiveSheet.Range("A1")
            .Value = i
            .Font.Bold = True
        End With
    Next i
    Debug.Print "With With: " & Timer - startTime & " seconds"
End Sub

Summary

The With statement is an essential VBA feature that:

  • Reduces repetition: Write object references only once
  • Improves readability: Makes code easier to understand
  • Enhances maintainability: Changes require editing only one location
  • Can improve performance: Reduces object resolution overhead

Master the With statement to write cleaner, more efficient VBA code.

#VBA #With Statement #Basic Syntax #Coding