Results 1 to 8 of 8

Thread: Excel Find Method in Excel VBA (Any version of Excel)

Threaded View

  1. #1

    Thread Starter
    Discovering Life Siddharth Rout's Avatar
    Join Date
    Feb 2005
    Location
    Mumbai, India
    Posts
    12,001

    Excel Find Method in Excel VBA (Any version of Excel)

    I have been contemplating on writing this tutorial for a long time as I have found a lot of questions revolving around this topic. However due to the tight schedule that I am in, I was not getting the time for it. Surprisingly today I have no work and I am absolutely free. So the first thing that I did was open my pending work list (Old habits die hard) and saw that I had to write a tutorial on .Find so here it is…

    Most of us use loops in case we wanted to find something in Excel.

    For Example, Let’s say

    Our data is in sheet1 (Workbook Attached) from Cell A1 to A65000 and the data is like this

    A1 ~~> 1
    A2 ~~> 2
    A3 ~~> 3
    A4 ~~> 4
    A5 ~~> 5



    A65000 ~~> 65000
    Now suppose we want to find which cell has say 10000. The primitive way was to loop through each cell and find which cell had that value. For Example

    Code:
    Sub Sample()
        Dim oSht As Worksheet
        Dim lastRow As Long, i As Long
        Dim strSearch As String
        Dim t As Long
        
        t = GetTickCount
        
        On Error GoTo Err
        
        Set oSht = Sheets("Sheet1")
        
        lastRow = oSht.Range("A" & Rows.Count).End(xlUp).Row
        
        strSearch = "10000"
        
        For i = 1 To lastRow
            If oSht.Range("A" & i).Value = strSearch Then
                MsgBox "Value Found in Cell " & oSht.Range("A" & i).Address & vbCrLf & _
                "and it took " & GetTickCount - t & " milliseconds"
                Exit Sub
            End If
        Next i
      
        Exit Sub
    Err:
        MsgBox Err.Description
    End Sub
    This method of looping is not ‘wrong’ but yes it is very slow as compared to Excel’s inbuilt “.Find” Tool. The above sub executed in 109 milliseconds on my laptop.

    In this tutorial, I will stress on how to use .Find to make your search faster.

    The syntax of .Find is

    expression.Find(What, After, LookIn, LookAt, SearchOrder, SearchDirection, MatchCase, MatchByte, SearchFormat)

    Where

    Expression (Required): is any valid range Object. So if we take the above example then the range would be Range(“A1:A” & lastRow)
    What (Optional Variant): is the “Search value”
    After (Optional Variant): The cell after which you want the search to begin.
    LookIn (Optional Variant): The type of information. (xlValues or xlFormulas)
    LookAt (Optional Variant): Can be one of the following XlLookAt constants: xlWhole or xlPart.
    SearchOrder (Optional Variant): Can be one of the following XlSearchOrder constants: xlByRows or xlByColumns.
    SearchDirection: Can be one of these XlSearchDirection constants. xlNext default xlPrevious
    MatchCase (Optional Variant): True to make the search case sensitive. The default value is False.
    MatchByte (Optional Variant): Used only if you've selected or installed double-byte language support. True to have double-byte characters match only double-byte characters. False to have double-byte characters match their single-byte equivalents.
    SearchFormat (Optional Variant): The search format.

    Now let’s try and incorporate .Find to find the data that we want.

    Code:
    Sub Sample1()
        Dim oSht As Worksheet
        Dim lastRow As Long, i As Long
        Dim strSearch As String
        Dim t As Long
        Dim aCell As Range
        
        t = GetTickCount
        
        On Error GoTo Err
        
        Set oSht = Sheets("Sheet1")
        
        lastRow = oSht.Range("A" & Rows.Count).End(xlUp).Row
        
        strSearch = "10000"
        
        Set aCell = oSht.Range("A1:A" & lastRow).Find(What:=strSearch, LookIn:=xlValues, _
        LookAt:=xlPart, SearchOrder:=xlByRows, SearchDirection:=xlNext, _
        MatchCase:=False, SearchFormat:=False)
        
        If Not aCell Is Nothing Then
            MsgBox "Value Found in Cell " & aCell.Address & vbCrLf & _
            "and it took " & GetTickCount - t & "milliseconds"
        End If
        
        Exit Sub
    Err:
        MsgBox Err.Description
    End Sub
    The above sub took 6 milliseconds as compared to 109 milliseconds on the ‘looping’ sub !!!

    Let’s now take different scenarios on how to work with ".Find"

    The other scenarios that we will work on are as follows…

    1) Find Values in Cell Value (Covered above. Example in Sheet1)
    2) Find Values in Cell Formula (Example in Sheet2)
    3) .FindNext (Example in Sheet3)
    4) Making .Find work as Vlookup() formula (Example in Sheet4)

    If there are any other scenarios that you are finding difficulty with then simply create a new thread in Office Development and I will try to help you if I can
    Attached Files Attached Files
    Last edited by Siddharth Rout; Dec 4th, 2010 at 07:28 AM.
    A good exercise for the Heart is to bend down and help another up...
    Please Mark your Thread "Resolved", if the query is solved


    MyGear:
    ★ CPU ★ Ryzen 5 5800X
    ★ GPU ★ NVIDIA GeForce RTX 3080 TI Founder Edition
    ★ RAM ★ G. Skill Trident Z RGB 32GB 3600MHz
    ★ MB ★ ASUS TUF GAMING X570 (WI-FI) ATX Gaming
    ★ Storage ★ SSD SB-ROCKET-1TB + SEAGATE 2TB Barracuda IHD
    ★ Cooling ★ NOCTUA NH-D15 CHROMAX BLACK 140mm + 10 of Noctua NF-F12 PWM
    ★ PSU ★ ANTEC HCG-1000-EXTREME 1000 Watt 80 Plus Gold Fully Modular PSU
    ★ Case ★ LIAN LI PC-O11 DYNAMIC XL ROG (BLACK) (G99.O11DXL-X)
    ★ Monitor ★ LG Ultragear 27" 240Hz Gaming Monitor
    ★ Keyboard ★ TVS Electronics Gold Keyboard
    ★ Mouse ★ Logitech G502 Hero

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •  



Click Here to Expand Forum to Full Width