Share via


使用 For Each...Next 陳述式

For Each...Next 陳述式會對集合中的每個物件陣列中的每個元素重複一個區塊的陳述式。 Visual Basic 會在每次執行迴圈時自動設定變數。 例如,下列 程式 會將 10 加入至範圍 A1 到 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 類別

每個...下一個 迴圈不只會逐一查看 Collection 物件的陣列和實例。 For Each...Next 迴圈還可以查看您編寫的 VBA 類別。

以下的範例示範如何執行此動作。

  1. 在 VBE (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] 您也可以從 [檔案] 功能表上選擇移除項目,從 VBE 移除某個類別模組。
[cc4] 您可以啟動匯入檔案對話方塊 (在 [檔案] 功能表上選擇匯入檔案),藉此匯入外部類別模組檔案。

另請參閱

支援和意見反應

有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應