共用方式為


Range.FindNext 方法 (Excel)

繼續使用 Find 方法開始的搜尋。 本方法尋找相符合同一條件的下儲存格,並傳回代表該儲存格的 Range 物件。 本方法不影響選定範圍或目前儲存格。

語法

運算式FindNext (之後)

expression 代表 Range 物件的變數。

參數

名稱 必要/選用 資料類型 描述
After 選用 Variant 要在其後進行搜尋的儲存格。 這個儲存格對應於從使用者介面執行搜尋時的作用中儲存格位置。 請注意,After 必須是搜尋範圍中的單一儲存格。
請記住,搜尋是從這個儲存格之後開始的,必須等到該方法循環回到這個儲存格時,才會搜尋其內容。 如果未指定這個引數,則搜尋會在範圍左上角的儲存格之後開始。

傳回值

範圍

備註

當搜尋到達所指定搜尋範圍的結尾時,它會折回至範圍的開始。 若要在發生折回時停止搜尋,請儲存第一個找到之儲存格的地址,然後測試每個後續找到的儲存格位址是否與這個儲存的地址相等。

範例

本範例會在包含值 2 的工作表上尋找範圍 A1:A500 中的所有儲存格,並將整個儲存格值變更為 5。 也就是說,值 1234 和 99299 都包含 2,而這兩個儲存格的值都會變成 5。

Sub FindValue()
    
    Dim c As Range
    Dim firstAddress As String
    
    With Worksheets(1).Range("A1:A500") 
        Set c = .Find(2, lookin:=xlValues) 
        If Not c Is Nothing Then 
            firstAddress = c.Address 
            Do 
                c.Value = 5 
                Set c = .FindNext(c) 
            Loop While Not c Is Nothing
        End If 
    End With
    
End Sub

本範例會尋找包含常數 X 的前四個數據行中的所有儲存格,並隱藏包含 X 的資料行。

Sub Hide_Columns()

    'Excel objects.
    Dim m_wbBook As Workbook
    Dim m_wsSheet As Worksheet
    Dim m_rnCheck As Range
    Dim m_rnFind As Range
    Dim m_stAddress As String

    'Initialize the Excel objects.
    Set m_wbBook = ThisWorkbook
    Set m_wsSheet = m_wbBook.Worksheets("Sheet1")
    
    'Search the four columns for any constants.
    Set m_rnCheck = m_wsSheet.Range("A1:D1").SpecialCells(xlCellTypeConstants)
    
    'Retrieve all columns that contain an X. If there is at least one, begin the DO/WHILE loop.
    With m_rnCheck
        Set m_rnFind = .Find(What:="X")
        If Not m_rnFind Is Nothing Then
            m_stAddress = m_rnFind.Address
             
            'Hide the column, and then find the next X.
            Do
                m_rnFind.EntireColumn.Hidden = True
                Set m_rnFind = .FindNext(m_rnFind)
            Loop While Not m_rnFind Is Nothing And m_rnFind.Address <> m_stAddress
        End If
    End With

End Sub

本範例會尋找前四個數據行中包含常數 X 的所有儲存格,並取消隱藏包含 X 的資料行。

Sub Unhide_Columns()
    'Excel objects.
    Dim m_wbBook As Workbook
    Dim m_wsSheet As Worksheet
    Dim m_rnCheck As Range
    Dim m_rnFind As Range
    Dim m_stAddress As String
    
    'Initialize the Excel objects.
    Set m_wbBook = ThisWorkbook
    Set m_wsSheet = m_wbBook.Worksheets("Sheet1")
    
    'Search the four columns for any constants.
    Set m_rnCheck = m_wsSheet.Range("A1:D1").SpecialCells(xlCellTypeConstants)
    
    'Retrieve all columns that contain X. If there is at least one, begin the DO/WHILE loop.
    With m_rnCheck
        Set m_rnFind = .Find(What:="X", LookIn:=xlFormulas)
        If Not m_rnFind Is Nothing Then
            m_stAddress = m_rnFind.Address
            
            'Unhide the column, and then find the next X.
            Do
                m_rnFind.EntireColumn.Hidden = False
                Set m_rnFind = .FindNext(m_rnFind)
            Loop While Not m_rnFind Is Nothing And m_rnFind.Address <> m_stAddress
        End If
    End With

End Sub

支援和意見反應

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