Consulting

Results 1 to 10 of 10

Thread: Excel VBA Find macro fails to find a string even when the string is present in sheet!

  1. #1
    VBAX Regular
    Joined
    Jan 2021
    Posts
    10
    Location

    Excel VBA Find macro fails to find a string even when the string is present in sheet!

    Hi,

    I'd be very grateful to anyone who could explain the problem with the following Excel VBA macro. I created it with Macro Record and then edited it. The macro should search through three sheets looking for a string (e.g. 'author'). Once it finds a match the macro should stop and ask if it should continue.

    Problem is, even when the string is present in the sheets the Find code in the macro fails to find the string. I've checked for spelling errors etc by using the Excel search function (ctrl F) to find the string. Every time ctrl F finds the string (e.g. 'author') that the macro search code fails to find.

    A futher question I have is that sometimes I want to search for a whole match (LookAt:=xlWhole) and other times for a partial match (I Googled the web and looked at several Excel VBA books, but failed to find the equivalent to xlWhole for a partial search - anyone know?). Can I create a string variable which I could substitute for xlWhole in the LookAt parameter e.g. Lookat:=PartialMatchOnly?

    My thanks in advance for your help and suggestions.

    Here is my macro:

    Sub SearchForTagsx()
    'SearchForTags Macro
    ' Searches for a tag in each of the tag sheets in sequence
    Dim Rng As Range
    Dim TagToBeFound As String
    Dim InputIfToContinue As String
    Sheets("Tags Insert").Select
    Range("F6").Select
    TagToBeFound = ActiveCell.Value
    Sheets("Tags I").Select
    Set Rng = ActiveSheet.Range("A1:M56").Find(What:=TagToBeFound, After:=ActiveCell, LookIn:=xlFormulas, _
    LookAt:=xlWhole, SearchOrder:=xlByRows, SearchDirection:=xlNext, _
    MatchCase:=False, SearchFormat:=False)
    If Not Rng Is Nothing Then
        InputIfToContinue = InputBox("Continue searching? 'Y' or 'N'")
        If InputIfToContinue = "n" Then
            GoTo EndSubNow
        End If
    End If
    Sheets("Tags II").Select
    Set Rng = ActiveSheet.Range("A1:M56").Find(What:=TagToBeFound, After:=ActiveCell, LookIn:=xlFormulas, _
    LookAt:=xlWhole, SearchOrder:=xlByRows, SearchDirection:=xlNext, _
    MatchCase:=False, SearchFormat:=False)
    If Not Rng Is Nothing Then
         InputIfToContinue = InputBox("Continue searching? 'Y' or 'N'")
         If InputIfToContinue = "n" Then
            GoTo EndSubNow
        End If
    End If
    Sheets("Tags III").Select
    Set Rng = ActiveSheet.Range("A1:M56").Find(What:=TagToBeFound, After:=ActiveCell, LookIn:=xlFormulas, _
    LookAt:=xlWhole, SearchOrder:=xlByRows, SearchDirection:=xlNext, _
    MatchCase:=False, SearchFormat:=False)
    If Not Rng Is Nothing Then
        InputIfToContinue = InputBox("Continue searching? 'Y' or 'N'")
        If InputIfToContinue = "n" Then
            GoTo EndSubNow
        End If
    End If
    Sheets("Tags Insert").Select
    EndSubNow:
    End Sub
    Last edited by Aussiebear; 03-10-2024 at 02:00 PM. Reason: Added code tags to supplied code

  2. #2
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,198
    Location
    Hi Divadog,

    This will only find the first instance of the search string on a sheet and then move on to the next sheet. Is that what you want or do you wish to search every instance on each sheet?

    I also noticed that when the search string is found, the code does not select nor display the found cell in any way. Did you intend to select the cell containing the search string?

    (I Googled the web and looked at several Excel VBA books, but failed to find the equivalent to xlWhole for a partial search - anyone know?)
    In answer to this question, You are looking for: xlPart

    If you are happy with only finding one instance from each sheet and want to select the found cell then perhaps the below will be another option to look at:
    Sub SearchForTagsx()
        Dim TagToBeFound As String, ws As Worksheet, mb As Variant, fRng As Range
        Dim wsVar As Variant
        
        TagToBeFound = Sheets("Tags Insert").Range("F6").Value ' search string
        wsVar = Array("Tags I", "Tags II", "Tags III") ' sheets to search
        
        For Each ws In Sheets(wsVar) ' loop through the worksheets
            Set fRng = ws.Range("A1:M56").Find(TagToBeFound, , , xlPart) ' set fRng to the cell containing the search string
            If Not fRng Is Nothing Then ' check if fRng is not empty
                Application.Goto fRng ' go to fRng (select sheet and cell)
                If ws.Name <> wsVar(UBound(wsVar)) Then ' check if we are on the last sheet, if we are then don't ask to continue
                    mb = MsgBox("Continue searching?", vbYesNo)
                    If mb = vbNo Then Exit Sub
                End If
                Set fRng = Nothing ' reset fRng after each search
            End If
        Next ws ' next ws in the loop
    End Sub
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved
    Click here for a guide on how to upload a file with your post

    Excel 365, Version 2403, Build 17425.20146

  3. #3
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    Sub M_snb()
      c00= Sheets("Tags Insert").cells(6,6)
      
      for each it in sheets
        if it.name<> "Tags Insert") then 
          If Not it.UsedRange.Find(c00, , , 1) Is Nothing Then MsgBox "continue ?", vbYesNoCancel, it.UsedRange.Find(c00, , , 1).Address(, , , True)
        end if
      Next
    End Sub

  4. #4
    VBAX Regular
    Joined
    Jan 2021
    Posts
    10
    Location
    Hi georgiboy,

    Thanks so much for your effort. I very much appreciate your help. Unfortunately, the macro still fails to activate the cell containing the search string.

    In some cases I have the same string in two of the three sheets being searched. If the string is in 'Tags I' and 'Tags III', the macro will first stop in 'Tags I' and ask if it should continue. The active cell will be the cell that was last active in 'Tags I'. It will not have activated the cell that contains the search string.

    Once it is told to continue it will skip sheet 'Tags II', which does not contain the search string and move on to sheet 'Tags III'. Again, the active cell will be the last cell that was active in that sheet. It will not have activated the cell that contains the search string. The macro asks it should continue and when so instructed it returns to sheeet 'Tags Insert'.

    Once the macro has finished I can go to the two sheets ('Tags I' and 'Tags III') which contain the search string, hit ctrl F in both. In both sheets ctrl F activates the cells containing the search string.

    I wonder if the problem is that my VBA search command lacks an 'activate' or the macro lacks an 'activate' line. However, when I add 'activate' to the search command as in:


    Set Rng = ActiveSheet.Range("A1:M56").Find(What:=TagToBeFound, After:=ActiveCell, LookIn:=xlFormulas, _
    LookAt:=xlWhole, SearchOrder:=xlByRows, SearchDirection:=xlNext, _
    MatchCase:=False, SearchFormat:=False).Activate
    I get 'Run-time error 424 Object required'. Oddly, when I research this error with Google I fail to find very much of anything. Any suggestions?

    Thanks again for your help. I very much appreciate it.

    P.S. I like how much more concise your macro is than mine!

  5. #5
    VBAX Regular
    Joined
    Jan 2021
    Posts
    10
    Location
    Hi SNB,

    Thanks for the suggested revision. I very much appreciate it. Unfortunately, when run it gives a Compile Error Syntax Error for:

    if it.name<> "Tags Insert") then

    Unfortunately, your code is way above my pay grade. I’m not sure how I should correct this error so I’d appreciate any further suggestions you could provide.

    Also, as I read your revisions, the macro will now search every sheet in the workbook. However, I only want it to search three of the workbook sheets: ‘Tags I’, ‘Tags II’ and ‘Tags III’. The search strings I am using are in other sheets of the workbook, but I do not want to search these sheets. How should the macro be changed to have it search only ‘Tags I’, ‘Tags II’ and ‘Tags III’?

    Thanks again for your revision. I very much appreciate your help.

  6. #6
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    a typo:

    Sub M_snb()
      c00= Sheets("Tags Insert").cells(6,6)
      
      for j=1 to 3
         If Not sheets("Tags " & string(j,"I")).usedrange.Find(c00, , , 1) Is Nothing Then MsgBox "continue ?", vbYesNoCancel, sheets("Tags " & string(j,"I")).usedrange.Find(c00, , , 1).Address(, , , True)
      Next
    End Sub

  7. #7
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,198
    Location
    See if this attachment helps.

    I have edited the code to the below:
    Sub SearchForTagsx()
        Dim TagToBeFound As String, ws As Worksheet, fRng As Range
        
        TagToBeFound = Sheets("Tags Insert").Range("F6").Value ' search string
        
        For Each ws In Sheets(Array("Tags I", "Tags II", "Tags III")) ' loop through the worksheets
            Set fRng = ws.Range("A1:M56").Find(TagToBeFound, , , xlPart) ' set fRng to the cell containing the search string
            If Not fRng Is Nothing Then ' check if fRng is not empty
                Application.Goto fRng ' go to fRng (select sheet and cell)
                If MsgBox("Continue searching?", vbYesNo) = vbNo Then Exit For
                Set fRng = Nothing ' reset fRng after each search
            End If
        Next ws ' next ws in the loop
        
        Sheets("Tags Insert").Activate
    End Sub
    Attached Files Attached Files
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved
    Click here for a guide on how to upload a file with your post

    Excel 365, Version 2403, Build 17425.20146

  8. #8
    VBAX Regular
    Joined
    Jan 2021
    Posts
    10
    Location
    Hi Georgiboy,

    It runs great now. Thanks a million. I very much appreciate your efforst. I just wish I could write such concise code as you do.

    The only change I would like to add is to run it in two version:

    1) With 'Match entire cell contents' on
    2) With 'Match entire cell Contents' off

    So I've edited the macro as follows:

    Sub M_snbx()
    Dim MatchEntireCell As String
    TagToBeFound = Sheets("Tags Insert").Range("F6").Value ' search string
    MatchEntireCell = InputBox("Match Entire Cell Contents? 'y' or 'n'")
    If MatchEntireCell = "n" Then
        For Each ws In Sheets(Array("Tags I", "Tags II", "Tags III")) ' loop through the worksheets
            Set fRng = ws.Range("A1:M56").Find(TagToBeFound, , , xlPart) ' set fRng to the cell containing the search string
            If Not fRng Is Nothing Then ' check if fRng is not empty
                Application.Goto fRng ' go to fRng (select sheet and cell)
                If MsgBox("Continue searching?", vbYesNo) = vbNo Then Exit For
                Set fRng = Nothing ' reset fRng after each search
            End If
        Next ws ' next ws in the loop
    Else
        For Each ws In Sheets(Array("Tags I", "Tags II", "Tags III")) ' loop through the worksheets
            Set fRng = ws.Range("A1:M56").Find(TagToBeFound, , , xlWhole) ' set fRng to the cell containing the search string
            If Not fRng Is Nothing Then ' check if fRng is not empty
                Application.Goto fRng ' go to fRng (select sheet and cell)
                If MsgBox("Continue searching?", vbYesNo) = vbNo Then Exit For
                Set fRng = Nothing ' reset fRng after each search
            End If
        Next ws ' next ws in the loop
    End If
    End Sub
    These changes run. I just wonder if there is a more precise and elegent to do this.

    Anyway, thanks so much for your help. Your macro works wonderfully.
    Last edited by Aussiebear; 03-14-2024 at 12:24 PM. Reason: Added code tags to supplied code

  9. #9
    VBAX Expert Dave's Avatar
    Joined
    Mar 2005
    Posts
    835
    Location
    In the absence of other suggestions, maybe...
    Sub M_snbx(WholeSearch As Boolean)
    Dim MatchEntireCell As String
    TagToBeFound = Sheets("Tags Insert").Range("F6").Value ' search string
    If WholeSearch Then
    MatchEntireCell = "xlwhole"
    Else
    MatchEntireCell = "xlpart"
    End If
        
    For Each ws In Sheets(Array("Tags I", "Tags II", "Tags III")) ' loop through the worksheets
        ' set fRng to the cell containing the search string
        Set fRng = ws.Range("A1:M56").Find(TagToBeFound, , , MatchEntireCell)
        If Not fRng Is Nothing Then ' check if fRng is not empty
            Application.Goto fRng ' go to fRng (select sheet and cell)
            If MsgBox("Continue searching?", vbYesNo) = vbNo Then Exit For
            Set fRng = Nothing ' reset fRng after each search
        End If
    Next ws ' next ws in the loop
    End Sub
    To operate...
    Call M_snbx(True) ' whole word search
    Call M_snbx(False) ' partial word search
    HTH. Dave

  10. #10
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,198
    Location
    Hi Divadog,

    When providing code, it's essential to use code tags for clarity. For guidance on this, refer to the first link in my signature.

    If you wanted to stick with the message box idea then I would do it as below:
    Sub SearchForTagsx()
        Dim TagToBeFound As String, ws As Worksheet, fRng As Range, MatchCell As Object, p As Integer
        
        TagToBeFound = Sheets("Tags Insert").Range("F6").Value ' search string
        p = IIf(MsgBox("Match entire cell?", vbYesNo) = vbYes, 1, 2)
        
        For Each ws In Sheets(Array("Tags I", "Tags II", "Tags III")) ' loop through the worksheets
            Set fRng = ws.Range("A1:M56").Find(TagToBeFound, , , p) ' set fRng to the cell containing the search string
            If Not fRng Is Nothing Then ' check if fRng is not empty
                Application.Goto fRng ' go to fRng (select sheet and cell)
                If MsgBox("Continue searching?", vbYesNo) = vbNo Then Exit For
                Set fRng = Nothing ' reset fRng after each search
            End If
        Next ws ' next ws in the loop
        
        Sheets("Tags Insert").Activate
    End Sub
    Last edited by georgiboy; 03-15-2024 at 12:08 AM. Reason: Added note about code tags
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved
    Click here for a guide on how to upload a file with your post

    Excel 365, Version 2403, Build 17425.20146

Tags for this Thread

Posting Permissions

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