Using For Each...Next statements

For Each...Next statements repeat a block of statements for each object in a collection or each element in an array. Visual Basic automatically sets a variable each time the loop runs. For example, the following procedure adds 10 to the value of every cell in the range A1 to A10.

Sub Add10ToAllCellsInRange()
    Dim rng As Range
    For Each rng In Range("A1:A10")
        rng.Value = rng.Value + 10
    Next
End Sub

The following code loops through each element in an array and sets the value of each to the value of the index variable I.

Dim TestArray(10) As Integer, I As Variant 
For Each I In TestArray 
 TestArray(I) = I 
Next I 

Looping through a range of cells

Use a For Each...Next loop to loop through the cells in a range. The following procedure loops through the range A1:D10 on Sheet1 and sets any number whose absolute value is less than 0.01 to 0 (zero).

Sub RoundToZero() 
 For Each rng in Range("A1:D10") 
 If Abs(rng.Value) < 0.01 Then rng.Value = 0 
 Next 
End Sub

Exiting a For Each...Next loop before it is finished

You can exit a For Each...Next loop by using the Exit For statement. For example, when an error occurs, use the Exit For statement in the True statement block of either an If...Then...Else statement or a Select Case statement that specifically checks for the error. If the error does not occur, the If…Then…Else statement is False and the loop continues to run as expected.

The following example tests for the first cell in the range A1:B5 that does not contain a number. If such a cell is found, a message is displayed and Exit For exits the loop.

Sub TestForNumbers() 
 For Each rng In Range("A1:B5") 
  If IsNumeric(rng.Value) = False Then 
   MsgBox "Cell " & rng.Address & " contains a non-numeric value." 
   Exit For 
  End If 
 Next rng 
End Sub

Using a For Each...Next loop to iterate over a VBA class

For Each...Next loops don't only iterate over arrays and instances of the Collection object. For Each...Next loops can also iterate over a VBA class that you have written.

Following is an example demonstrating how you can do this.

  1. Create a class module in the VBE (Visual Basic Editor), and rename it CustomCollection.cc1

  2. Place the following code in the newly created module.

    Private MyCollection As New Collection
    
    ' The Initialize event automatically gets triggered
    ' when instances of this class are created.
    ' It then triggers the execution of this procedure.
    Private Sub Class_Initialize()
        With MyCollection
            .Add "First Item"
            .Add "Second Item"
            .Add "Third Item"
        End With
    End Sub
    
    ' Property Get procedure for the setting up of
    ' this class so that it works with 'For Each...'
    ' constructs.
    Property Get NewEnum() As IUnknown
    ' Attribute NewEnum.VB_UserMemId = -4
    
    Set NewEnum = MyCollection.[_NewEnum]
    End Property
    
  3. Export this module to a file and store it locally.cc2

  4. After you export the module, open the exported file by using a text editor (Window's Notepad software should be sufficient). The file contents should look like the following.

    VERSION 1.0 CLASS
    BEGIN
    MultiUse = -1  'True
    END
    Attribute VB_Name = "CustomCollection"
    Attribute VB_GlobalNameSpace = False
    Attribute VB_Creatable = False
    Attribute VB_PredeclaredId = False
    Attribute VB_Exposed = False
    Private MyCollection As New Collection
    
    ' The Initialize event automatically gets triggered
    ' when instances of this class are created.
    ' It then triggers the execution of this procedure.
    Private Sub Class_Initialize()
        With MyCollection
            .Add "First Item"
            .Add "Second Item"
            .Add "Third Item"
        End With
    End Sub
    
    ' Property Get procedure for the setting up of
    ' this class so that it works with 'For Each...'
    ' constructs.
    Property Get NewEnum() As IUnknown
    ' Attribute NewEnum.VB_UserMemId = -4
    
    Set NewEnum = MyCollection.[_NewEnum]
    End Property
    
  5. Using the text editor, remove the ' character from the first line under the Property Get NewEnum() As IUnknown text in the file. Save the modified file.

  6. Back in the VBE, remove the class that you created from your VBA project and don't choose to export it when prompted.cc3

  7. Import the file that you removed the ' character from back into the VBE.cc4

  8. Run the following code to see that you can now iterate over your custom VBA class that you have written by using both the VBE and a text editor.

    Dim Element
    Dim MyCustomCollection As New CustomCollection
    For Each Element In MyCustomCollection
    MsgBox Element
    Next
    
Footnotes Description
[cc1] You can create a class module by choosing Class Module on the Insert menu. You can rename a class module by modifying its properties in the Properties window.
[cc2] You can activate the Export File dialog box by choosing Export File on the File menu.
[cc3] You can remove a class module from the VBE by choosing Remove Item on the File menu.
[cc4] You can import an external class-module file by activating the Import File dialog box (choose Import File on the File menu).

See also

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.