Consulting

Page 1 of 2 1 2 LastLast
Results 1 to 20 of 26

Thread: Find and replace within VBA modules

  1. #1
    VBAX Tutor
    Joined
    Mar 2010
    Posts
    287
    Location

    Question Find and replace within VBA modules

    Hi all...

    I was wondering what code I use to programmatically do a find/replace all within the VBA modules.

    I have several references that need changing within the VBA code.

    I can build a For Next loop for each VBE environment, but need the code to do a find/replace all for all items in the Project.

    Any help appreciated.

  2. #2
    Knowledge Base Approver VBAX Guru GTO's Avatar
    Joined
    Sep 2008
    Posts
    3,368
    Location
    What is the "all" and what is the "reference"?

    Quite frankly, I have stayed way too busy since January and do not get to spend as much time learning as I would be fond of. Could you provide a couple of sample (zipped) Before and After workbooks (.xls) so that we could see what exactly we are piling through?

    Thank you so much,

    Mark

  3. #3
    VBAX Tutor
    Joined
    Mar 2010
    Posts
    287
    Location

    Question

    I have this to start with. Might adjust the 'String' arguments to be actual object, and change to a function.

    Doesn't include the replace functionality that I desire....

    [vba]
    Public Sub SearchCodeModule(wkb As String, vbModule As String, vbFind As String)
    Dim VBProj As VBIDE.VBProject
    Dim VBComp As VBIDE.VBComponent
    Dim CodeMod As VBIDE.CodeModule
    Dim FindWhat As String
    Dim SL As Long ' start line
    Dim EL As Long ' end line
    Dim SC As Long ' start column
    Dim EC As Long ' end column
    Dim Found As Boolean

    Set VBProj = Workbooks(wkb).VBProject
    Set VBComp = VBProj.VBComponents(vbModule)
    Set CodeMod = VBComp.CodeModule

    FindWhat = vbFind

    With CodeMod
    SL = 1
    EL = .CountOfLines
    SC = 1
    EC = 255
    Found = .Find(Target:=FindWhat, StartLine:=SL, StartColumn:=SC, _
    EndLine:=EL, EndColumn:=EC, _
    wholeword:=True, MatchCase:=False, patternsearch:=False)
    Do Until Found = False
    Debug.Print "Found at: Line: " & CStr(SL) & " Column: " & CStr(SC)
    EL = .CountOfLines
    SC = EC + 1
    EC = 255
    Found = .Find(Target:=FindWhat, StartLine:=SL, StartColumn:=SC, _
    EndLine:=EL, EndColumn:=EC, _
    wholeword:=True, MatchCase:=False, patternsearch:=False)
    Loop
    End With
    End Sub
    [/vba]

  4. #4
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    rather straightforward:

    [VBA]
    Sub tst()
    For Each vbc In ThisWorkbook.VBProject.VBComponents
    c01 = Replace(vbc.codemodule.Lines(1, vbc.codemodule.countoflines), "xxx", "yyy")
    vbc.codemodule.deletelines
    vbc.codemodule.addfromstring c01
    Next
    End Sub
    [/VBA]

  5. #5
    VBAX Tutor
    Joined
    Mar 2010
    Posts
    287
    Location
    Thanks snb.

    Different approach to the one I was thinking of. You physically delete the line and replace it with an adjusted line.

    What should I 'Dim' vbc as? I assume it means VB Components?

  6. #6
    VBAX Master Aflatoon's Avatar
    Joined
    Sep 2009
    Location
    UK
    Posts
    1,720
    Location
    I think I can guess what the answer to that will be...
    Be as you wish to seem

  7. #7
    VBAX Regular
    Joined
    Oct 2012
    Posts
    10
    Location
    Yeap....

  8. #8
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    The code doesn't replace line by line, but by whole codemodule.

  9. #9
    VBAX Tutor
    Joined
    Mar 2010
    Posts
    287
    Location

    Question

    Any major issues with this? I am going to loop through two ranges "rngOld" and "rngNew" on Worksheets("index") and feed these to the "xxx" , "yyy" so that I can do bulk changes...

    [vba]
    For Each vbaProj In Application.VBE.VBProjects

    Set Application.VBE.ActiveVBProject = vbaProj

    For Each vbc In vbaProj.VBComponents
    c01 = Replace(vbc.codemodule.Lines(1, vbc.codemodule.countoflines), "xxx", "yyy")
    vbc.codemodule.deletelines
    vbc.codemodule.addfromstring c01
    Next vbc

    Next vbaProj
    [/vba]

  10. #10
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Quote Originally Posted by theta
    What should I 'Dim' vbc as? I assume it means VB Components?
    Same as your VBComp.
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  11. #11
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Quote Originally Posted by theta
    Any major issues with this? I am going to loop through two ranges "rngOld" and "rngNew" on Worksheets("index") and feed these to the "xxx" , "yyy" so that I can do bulk changes...

    [vba]
    For Each vbaProj In Application.VBE.VBProjects

    Set Application.VBE.ActiveVBProject = vbaProj

    For Each vbc In vbaProj.VBComponents
    c01 = Replace(vbc.codemodule.Lines(1, vbc.codemodule.countoflines), "xxx", "yyy")
    vbc.codemodule.deletelines
    vbc.codemodule.addfromstring c01
    Next vbc

    Next vbaProj
    [/vba]
    Why do you loop through all projects if you are only interested in the activeproject, or vice versa?
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  12. #12
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Also be aware that snb rarely gives working code, there is invariably logic or syntax errors which you are left to sort out yourself. This code snippet is no exception.
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  13. #13
    VBAX Tutor
    Joined
    Mar 2010
    Posts
    287
    Location
    Sorry typo. [vba]ActiveWorkbook[/vba] should not be in there...

  14. #14
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    [vba]Sub snb()
    For Each vbc In ThisWorkbook.VBProject.VBComponents
    With vbc.codemodule
    If .countoflines > 0 Then
    c01 = Replace(.Lines(1, .countoflines), "xxx", "yyy")
    .deletelines 1, .countoflines
    .addfromstring c01
    End If
    End If
    Next
    End Sub[/vba]

  15. #15
    VBAX Tutor
    Joined
    Mar 2010
    Posts
    287
    Location
    Thanks SNB...I was working on the following (very close)

    The only problem I am having is that it is trying to access the calling module. I need a way of saying for each vbaProj, then testing that vbaProj <> thisvbaProj ?

    [vba]
    Public Sub FindReplaceAll(sMatch As String)

    For Each vbaProj In Application.VBE.VBProjects
    If (UCase(vbaProj.Name) Like (sMatch)) Then
    'Set Application.VBE.ActiveVBProject = vbaProj
    'Check if Project is unlocked
    If vbaProj.Protection <> 1 Then
    'Set Application.VBE.ActiveVBProject = vbaProj
    For Each vbc In vbaProj.VBComponents
    If vbc.codemodule.countoflines <> 0 Then
    c01 = Replace(vbc.codemodule.Lines(1, vbc.codemodule.countoflines), "xxx", "yyy")
    vbc.codemodule.deletelines
    vbc.codemodule.addfromstring c01
    End If
    Next vbc
    End If
    End If
    Next vbaProj

    End Sub
    [/vba]

    Also (just for my own knowledge) - is there a clear way to distinguish between vbc types in code i.e. workbook vs module vs userform.

  16. #16
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    look at the vbcomponents(j).type property

    macromodule: 1
    class: 2
    Userform:3
    workbook: 100
    worksheet: 100

    To distinguish between worksheet and workbook use .properties.count:

    worksheet.properties.count=66
    workbook.properties.count<>66

  17. #17
    VBAX Tutor
    Joined
    Mar 2010
    Posts
    287
    Location
    I am *almost* there. I just need a way to prevent the code from running on the current module. It tried to overwrite itself as causes a 450 error.

    Where I have put "Hello" I would need application.vbe.thisvbproject but I cannot find a control to reference "this" vbproject (as you can with worksheets etc)

    ?

    EDIT : This seems to do the trick, any other input welcome

    [vba]
    Public Sub FindReplaceAll(sMatch As String)

    Set vbaActive = Application.VBE.ActiveVBProject

    For Each vbaProj In Application.VBE.VBProjects
    If (UCase(vbaProj.Name) Like UCase((sMatch))) And (vbaProj.Name <> vbaActive.Name) Then
    If vbaProj.Protection <> 1 Then
    For Each vbc In vbaProj.VBComponents
    With vbc.CodeModule
    If .countoflines > 0 Then
    c01 = Replace(.Lines(1, .countoflines), "xxx", "yyy")
    .deletelines 1, .countoflines
    .addfromstring c01
    End If
    End With
    Next vbc
    End If
    End If
    Next vbaProj

    Set vbaActive = Nothing

    End Sub
    [/vba]
    Last edited by theta; 11-02-2012 at 07:35 AM.

  18. #18
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    [VBA]
    Public Sub FindReplaceAll(sMatch As String)
    For Each vbaProj In Application.VBE.VBProjects
    if vbaProj.filename<>thisworkfbook.fullname then
    If vbaProj.Protection <> 1 Then
    For Each vbc In vbaProj.VBComponents
    With vbc.CodeModule
    If .countoflines > 0 Then
    c01 = Replace(.Lines(1, .countoflines), "xxx", "yyy")
    .deletelines 1, .countoflines
    .addfromstring c01
    End If
    End With
    Next vbc
    End If
    End If
    Next

    End Sub
    [/VBA]

  19. #19
    VBAX Tutor
    Joined
    Mar 2010
    Posts
    287
    Location
    Quote Originally Posted by snb
    [VBA]
    Public Sub FindReplaceAll(sMatch As String)
    For Each vbaProj In Application.VBE.VBProjects
    if vbaProj.filename<>thisworkfbook.fullname then
    If vbaProj.Protection <> 1 Then
    For Each vbc In vbaProj.VBComponents
    With vbc.CodeModule
    If .countoflines > 0 Then
    c01 = Replace(.Lines(1, .countoflines), "xxx", "yyy")
    .deletelines 1, .countoflines
    .addfromstring c01
    End If
    End With
    Next vbc
    End If
    End If
    Next

    End Sub
    [/VBA]
    Whenever I run this on my projects I keep getting an automation error :/ prevent it from running any further. And to make it worse, it happens in the first module. These projects contain on event code etc, would that be causing it - and how can I get round it?

    Run-time error '-2147417848 (80010108)
    Method 'AddFromString' of object 'CodeModule' failed

  20. #20
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    From where do you call this macro.

    Are you sure you have access to all addins ?

    What workbook causes the problem ?

    Why do you want to replace text in codemodules from the start ?

Posting Permissions

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