使用 For Each...Next 语句

For Each...Next 语句会为集合中的每个 对象并为数组中的每个元素重复语句块。 在每次循环运行时,Visual Basic 会自动设置一个变量。 例如,以下 过程 将 10 添加到 A10 范围中每个单元格的值。

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

下面的代码将循环访问数组中的每个元素,并将每个元素的值设置为索引变量 I 的值。

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

循环读取一系列单元格

使用 For Each...Next 循环来循环访问范围中的单元格。 下面的过程将循环访问 Sheet1 上的范围 A1:D10,并将其绝对值小于 0.01 的任何数字设置为 0(零)。

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

在 For Each...Next 循环完成前退出该循环

可使用 Exit For 语句退出 For Each...Next 循环。 例如,发生错误时,可使用 If...Then...Else 语句或 Select Case 语句的 True 语句块中的 Exit For 语句,它专用于检查错误。 如果未发生错误,则 If…Then…Else 语句为 False,且循环继续如期运行。

下面的示例测试范围 A1:B5 中不包含数字的第一个单元格。 如果找到此类单元格,则显示一条消息并且 Exit For 将退出循环。

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

使用“For Each...Next”循环来循环访问 VBA 类

对于每个...下一个 循环不仅循环访问 集合 对象的数组和实例。 For Each...Next 循环还可以循环访问你已编写的 VBA 类。

下面的示例显示了如何完成此操作。

  1. 在 VBA(Visual Basic 编辑器)中创建一个类模块,并将其重命名为 CustomCollectioncc1

  2. 将以下代码置于新建模块中。

    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. 将此模块导出为文件并将其存储在本地。cc2

  4. 导出模块之后,使用文本编辑器(Windows 的记事本软件应该足够了)打开已导出的文件。 文件内容类似于以下所示。

    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. 使用文本编辑器,删除文件的 Property Get NewEnum() As IUnknown 文本下的第一行中的 ' 字符。 保存修改的文件。

  6. 返回 VBE,删除通过 VBA 项目创建的类,系统提示时不要选择将其导出。cc3

  7. 将你从其中删除 ' 字符的文件导入回 VBE。cc4

  8. 运行以下代码,以查看你现在是否可以循环访问使用 VBE 和文本编辑器编写的自定义 VBA 类。

    Dim Element
    Dim MyCustomCollection As New CustomCollection
    For Each Element In MyCustomCollection
    MsgBox Element
    Next
    
脚注 说明
[cc1] 可以通过选择插入菜单上的“类模块”创建“类模块”。 可以通过在“属性”窗口中修改其属性来重命名类模块。
[cc2] 可以通过在文件菜单上的导出文件来激活导出文件对话框。
[cc3] 可以通过在“文件”菜单中选择删除项来从 VBA 中删除类模块。
[cc4] 可以通过激活导入文件对话框(在“文件”菜单上选择导入文件)来导入外部类模块文件。

另请参阅

支持和反馈

有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。