Consulting

Results 1 to 17 of 17

Thread: Multi Find and Replace VBA Script Macro Not Working

  1. #1
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location

    Multi Find and Replace VBA Script Macro Not Working

    I am struggling with the code below - and frankly not sure if I am using the right code for my purpose. I have a file, named test.xlsm. The file has two columns, A and B. I want to run the script in other files of my choice, and hoping that will mean that any cells that have text from A, will have such text replaced with content from B. Am I doing this wrong? Thank you for your help.


    Sub Multi_FindReplace()'PURPOSE: Find & Replace a list of text/values throughout entire workbook
    'ORIGINAL SOURCE: www.TheSpreadsheetGuru.com/the-code-vault
    'Adapted for external data
    
    
    
    
    Dim sht As Worksheet
    Dim fndList As Variant
    Dim x As Long
    Dim Source As Workbook
    Dim Target As Workbook
    
    
    
    
    Set Target = ThisWorkbook
    Set Source = Workbooks.Open("C:\Users\NAME\Desktop\test.xlsm")
    
    
    
    
    fndList = Source.Sheets(1).Range("A:B").SpecialCells(2).Value
    Source.Close False
    
    
    
    
    'Loop through each item in Array lists
      For x = LBound(fndList) To UBound(fndList)
        'Loop through each worksheet in ActiveWorkbook
          For Each sht In Target.Worksheets
            sht.Cells.Replace What:=fndList(x, 1), Replacement:=fndList(x, 2), _
              LookAt:=xlPart, SearchOrder:=xlByRows, MatchCase:=False, _
              SearchFormat:=False, ReplaceFormat:=False
          Next sht
      Next x
    End Sub

  2. #2
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,726
    Location
    Well, since you asked

    I'd turn it around a little

    In the WB#1 with the lists, I'd have the macro below. It uses a list in the WB#1 with the From-To pairs

    It opens a second WB#2 and replaces From-To pairs in WB#1 on all sheets in that WB#2

    If then saves and closes WB#2

    Seems to me musch easier than having the macro in many WBs and the From-To pairs in a 'database' WB



    Option Explicit
    
    'ORIGINAL SOURCE: www.TheSpreadsheetGuru.com/the-code-vault
    'Adapted for external data
    
    Sub Multi_FindReplace()
     'PURPOSE: Find & Replace a list of text/values throughout entire workbook
        Dim wbReplaceList As Workbook
        Dim wbReplaceIn As Workbook
        Dim ws As Worksheet
        Dim sReplaceIn As String
        Dim rReplaceList As Range
        Dim iReplace As Long
        
        
        'get WB name to replace in
        sReplaceIn = Application.GetOpenFilename("File to Replace In, *.xls?", 1, "Select File To Replace In")
        If sReplaceIn = "False" Then Exit Sub
        
        Application.ScreenUpdating = False
        
        Set wbReplaceIn = Workbooks.Open(sReplaceIn)
        Set wbReplaceList = ThisWorkbook
        Set rReplaceList = wbReplaceList.Worksheets(1).Cells(1, 1).CurrentRegion
        For Each ws In wbReplaceIn.Worksheets
            With rReplaceList
                For iReplace = 2 To .Rows.Count
                    Call ws.UsedRange.Replace(.Cells(iReplace, 1).Value, .Cells(iReplace, 2).Value, xlWhole, , False)
                Next iReplace
            End With
        Next
        
        wbReplaceIn.Save
        wbReplaceIn.Close
        
        
        Application.ScreenUpdating = False
    End Sub

    MultiFind.xlsm has the macro and the From-To list, and ReplaceInHere.xlsx was my test WB to process
    Attached Files Attached Files
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  3. #3
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    Would it be possible not to specify the workbook where text will be replaced? Instead, having the macro work on the currently open workbook where the macro is run?

  4. #4
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,726
    Location
    Sure, but why do you want to do it that way?

    You'd have to put the macro into each workbook

    That macro could open the 'From-To List' WB and use that to replace

    It just seems easier to have the macro and the From-To list in one WB

    OR

    Did you what the macro to run on all workbooks that are open?
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  5. #5
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    Basically, I download specific updates from our corporate website in excel file form, which has some private health information on it. My goal is to use this macro for replacing patient info with more private versions of it (which is stored in one file). I am curious on whether or not it is possible to download the file and run the macro so that you instantly have a file that is edited to my specifications. Is there a way to isolate the macro action to the file that I just downloaded and opened without editing the code every time?

  6. #6
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    Actually, I was using your version wrong. Now I figured it out. This is wonderful, thank you very much!

  7. #7
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    Small follow-up: is it possible for the macro to detect a portion of the text within a cell, and replace only such a portion. I noticed that the macro only works when the whole cell is the text that I am trying to find and replace.

    Thank you for all of your help.

  8. #8
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,726
    Location
    In this line, replace xlWhole with xlPart and you should be OK


    Call ws.UsedRange.Replace(.Cells(iReplace, 1).Value, .Cells(iReplace, 2).Value, xlWhole, , False)
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  9. #9
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    That last tip worked perfectly as well, thank you!

    Last question (I hope): Is there a way to make sure that the updated cells are adjusted in row height appropriately? Because some additional info is added to the cells, the text does not fit entirely in to the cells, requiring an additional step of resizing the rows. Curious to see if there is anything more automated that could be added to the macro.

  10. #10
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,726
    Location
    Is this what you meant?


     Option Explicit
    'ORIGINAL SOURCE: www.TheSpreadsheetGuru.com/the-code-vault
    'Adapted for external data
    Sub Multi_FindReplace() 'PURPOSE: Find & Replace a list of text/values throughout entire workbook
        Dim wbReplaceList As Workbook
        Dim wbReplaceIn As Workbook
        Dim ws As Worksheet
        Dim sReplaceIn As String
        Dim rReplaceList As Range
        Dim iReplace As Long
        
        
        'get WB name to replace in
        sReplaceIn = Application.GetOpenFilename("File to Replace In, *.xls?", 1, "Select File To Replace In")
        If sReplaceIn = "False" Then Exit Sub
        
        Application.ScreenUpdating = False
        
        Set wbReplaceIn = Workbooks.Open(sReplaceIn)
        Set wbReplaceList = ThisWorkbook
        Set rReplaceList = wbReplaceList.Worksheets(1).Cells(1, 1).CurrentRegion
        For Each ws In wbReplaceIn.Worksheets
            With rReplaceList
                For iReplace = 2 To .Rows.Count
                    Call ws.UsedRange.Replace(.Cells(iReplace, 1).Value, .Cells(iReplace, 2).Value, xlPart, , False)
                Next iReplace
                
                ws.Rows.AutoFit     '   added
                
            End With
        Next
        
        wbReplaceIn.Save
        wbReplaceIn.Close
        
        
        Application.ScreenUpdating = False
    End Sub
    Attached Files Attached Files
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  11. #11
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    One more last question (I think this is it, last question, sorry!). After the last code does its thing, is it possible to have one more code that searches cells in the workbook and deletes text "HHA", "CNA", and "HHAV"? Basically, deletes only that specific text but leaves everything else alone. Thank you very much for your help in advance.

  12. #12
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,726
    Location
    Should just require the 3 new lines below

    Option Explicit
    'ORIGINAL SOURCE: www.TheSpreadsheetGuru.com/the-code-vault
    'Adapted for external data
    Sub Multi_FindReplace() 'PURPOSE: Find & Replace a list of text/values throughout entire workbook
        Dim wbReplaceList As Workbook
        Dim wbReplaceIn As Workbook
        Dim ws As Worksheet
        Dim sReplaceIn As String
        Dim rReplaceList As Range
        Dim iReplace As Long
        
        
        'get WB name to replace in
        sReplaceIn = Application.GetOpenFilename("File to Replace In, *.xls?", 1, "Select File To Replace In")
        If sReplaceIn = "False" Then Exit Sub
        
        Application.ScreenUpdating = False
        
        Set wbReplaceIn = Workbooks.Open(sReplaceIn)
        Set wbReplaceList = ThisWorkbook
        Set rReplaceList = wbReplaceList.Worksheets(1).Cells(1, 1).CurrentRegion
        For Each ws In wbReplaceIn.Worksheets
            With rReplaceList
                For iReplace = 2 To .Rows.Count
                    Call ws.UsedRange.Replace(.Cells(iReplace, 1).Value, .Cells(iReplace, 2).Value, xlPart, , False)
                Next iReplace
                    
                'HHAV has to be before HHA
                Call ws.UsedRange.Replace("HHAV", vbNullString, xlPart, , False)
                Call ws.UsedRange.Replace("HHA", vbNullString, xlPart, , False)
                Call ws.UsedRange.Replace("CNA", vbNullString, xlPart, , False)
                
                ws.Rows.AutoFit     '   added
                
            End With
        Next
        
        wbReplaceIn.Save
        wbReplaceIn.Close
        
        
        Application.ScreenUpdating = False
    End Sub
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  13. #13
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    That works perfectly! Exactly what I needed, thank you.

    One thing I noticed is that the auto row fit code seems to adjust to the first cells in line from the left, and not so much to the cell with the most text in the row. Is there a way to fix this? Not a major issue, but thought I'd check if there is a way around it.

  14. #14
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,726
    Location
    replace that line with these and see if it helps


        ws.Rows.RowHeight = 100
        ws.Rows.EntireRow.AutoFit
    
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  15. #15
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    At this time, based on your instructions, my code is as follows;

    Option Explicit'ORIGINAL SOURCE: www.TheSpreadsheetGuru.com/the-code-vault
    'Adapted for external data
    Sub Multi_FindReplace() 'PURPOSE: Find & Replace a list of text/values throughout entire workbook
        Dim wbReplaceList As Workbook
        Dim wbReplaceIn As Workbook
        Dim ws As Worksheet
        Dim sReplaceIn As String
        Dim rReplaceList As Range
        Dim iReplace As Long
        
        
        'get WB name to replace in
        sReplaceIn = Application.GetOpenFilename("File to Replace In, *.xls?", 1, "Select File To Replace In")
        If sReplaceIn = "False" Then Exit Sub
        
        Application.ScreenUpdating = False
        
        Set wbReplaceIn = Workbooks.Open(sReplaceIn)
        Set wbReplaceList = ThisWorkbook
        Set rReplaceList = wbReplaceList.Worksheets(1).Cells(1, 1).CurrentRegion
        For Each ws In wbReplaceIn.Worksheets
            With rReplaceList
                For iReplace = 2 To .Rows.Count
                    Call ws.UsedRange.Replace(.Cells(iReplace, 1).Value, .Cells(iReplace, 2).Value, xlPart, , False)
                Next iReplace
                    
                'HHAV has to be before HHA
                Call ws.UsedRange.Replace("HHAV", vbNullString, xlPart, , False)
                Call ws.UsedRange.Replace("HHA", vbNullString, xlPart, , False)
                
                ws.Rows.EntireRow.AutoFit
                
            End With
        Next
        
        wbReplaceIn.Save
        
        
        Application.ScreenUpdating = False
    End Sub
    Schedule.xlsx

    I attached a file "Schedule.xlsx" - basically, the file where stuff gets replaced by the aforementioned code. To further streamline our workflow, is it possible to simplify the data in the schedule, as in using the data in the calendar to create a list like so;

    July 31st
    Data from boxes under it
    Data from boxes under it
    Data from boxes under it
    Data from boxes under it

    August 1st
    Data from boxes under it
    Data from boxes under it
    Data from boxes under it
    Data from boxes under it

    All in one column, either in excel, or somehow transitioned to another text document such as Word. The only thing is, when the file (Schedule file) is downloaded, the number of cells under a date varies, depending on how many entries were made.

  16. #16
    VBAX Regular
    Joined
    Jul 2019
    Posts
    10
    Location
    bump

  17. #17
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,726
    Location
    Possilby do-able, but all the merged cells, hidden (or small) rows and columns make it very hard to just get the data

    Could you simplify the format, and only use merged cells in non-event areas?

    Capture.JPG
    Attached Files Attached Files
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

Posting Permissions

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