Range.FindNext 方法 (Excel)

继续使用 Find 方法开始的搜索。 查找匹配相同条件的下一个单元格,并返回表示该单元格的 Range 对象。 该操作不影响选定内容和活动单元格。

语法

表达式。) 后的FindNext (

expression 一个表示 Range 对象的变量。

参数

名称 必需/可选 数据类型 说明
After 可选 Variant 指定一个单元格,查找将从该单元格之后开始。 从用户界面搜索时,这对应于活动单元格的位置。 注意,After 必须是查找区域中的单个单元格。
注意,搜索是从该单元格之后开始的;直到本方法环绕到此单元格时,才会搜索指定单元格。 如果未指定此参数,则在区域左上角的单元格之后开始搜索。

返回值

Range

备注

当搜索到达指定的搜索区域末尾时,它会绕到该区域的开头位置。 若要在发生此绕回时停止搜索,请保存第一个找到的单元格的地址,然后针对此保存的地址测试每个连续找到的单元格地址。

示例

本示例在包含值 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 支持和反馈,获取有关如何接收支持和提供反馈的指南。