Word VBA Macros – Find, Find & Replace

Written by

Editorial Team

Reviewed by

Steve Rynearson

Last updated on July 8, 2022

Word VBA Find

This example is a simple word macro find the text “a”:

Sub SimpleFind()

    Selection.Find.ClearFormatting
    With Selection.Find
        .Text = "a"
        .Replacement.Text = ""
        .Forward = True
        .Wrap = wdFindAsk
        .Format = False
        .MatchCase = False
        .MatchWholeWord = False
        .MatchWildcards = False
        .MatchSoundsLike = False
        .MatchAllWordForms = False
    End With
    Selection.Find.Execute
End Sub

Find and Replace

This simple macro will search for the word “their” and replace it with “there”:

Sub SimpleReplace()

    Selection.Find.ClearFormatting
    Selection.Find.Replacement.ClearFormatting
    With Selection.Find
        .Text = "their"
        .Replacement.Text = "there"
        .Forward = True
        .Wrap = wdFindContinue
        .Format = False
        .MatchCase = False
        .MatchWholeWord = False
        .MatchWildcards = False
        .MatchSoundsLike = False
        .MatchAllWordForms = False
    End With
    Selection.Find.Execute Replace:=wdReplaceAll
End Sub

 

Find and Replace Only in Selection

This VBA macro will find and replace text in a selection. It will also italicize the replaced text.

Sub ReplaceInSelection()
'replaces text JUST in selection . in adittion it makes replaced text italic
    Selection.Find.ClearFormatting
    Selection.Find.Replacement.ClearFormatting
    With Selection.Find
        .Text = "their"

        With .Replacement
            .Font.Italic = True
            .Text = "there"
        End With

        .Forward = True
        .Wrap = wdFindStop    'this prevents Word from continuing to the end of doc
        .Format = True 'we want to replace formatting of text as well
        .MatchCase = False
        .MatchWholeWord = True
        .MatchWildcards = False
        .MatchSoundsLike = False
        .MatchAllWordForms = False
    End With
    Selection.Find.Execute Replace:=wdReplaceAll
End Sub

This line of code prevents VBA from continuing to the end of the Word document:

.Wrap = wdFindStop    'this prevents Word from continuing to the end of doc

This line of code indicates to replace the formatting of the text as well:

.Format = True 'we want to replace formatting of text as well

 

Find and Replace Only In Range

Instead of replacing text throughout the entire document, or in a selection, we can tell VBA to find and replace only in range.  In this example we defined the range as the first paragraph:

Dim oRange As Range
Set oRange = ActiveDocument.Paragraphs(1).Range

 

Sub ReplaceInRange()
'replaces text JUST in range [in this example just in the first paragraph]
Dim oRange As Range
Set oRange = ActiveDocument.Paragraphs(1).Range
 oRange.Find.ClearFormatting
    oRange.Find.Replacement.ClearFormatting
    With oRange.Find
        .Text = "their"
        .Replacement.Text = "there"
        .Forward = True
        .Wrap = wdFindStop 'this prevent Word to continue to the end of doc
        .Format = False
        .MatchCase = False
        .MatchWholeWord = False
        .MatchWildcards = False
        .MatchSoundsLike = False
        .MatchAllWordForms = False
    End With
    oRange.Find.Execute Replace:=wdReplaceAll
End Sub