Here's my solution. For the find to work, you have to use the wild cards like "*abc*". As is, it searches the whole drawing. If you wanted to select the text to search, substitute the GetSS_TextFilter function with the GetSS_TextFilter_SOS function.
Public Sub ReplaceText()
Dim ss As AcadSelectionSet
Set ss = GetSS_TextFilter()
Dim sFind As String
Dim sReplace As String
sFind = ThisDrawing.Utility.GetString(1, "Enter the string to search for:> ")
sReplace = ThisDrawing.Utility.GetString(1, "Enter the replacement string:> ")
Dim oEnt As AcadEntity
Dim oTxt As AcadText
Dim oMtxt As AcadMText
For Each oEnt In ss
Select Case oEnt.ObjectName
Case Is = "AcDbText"
Set oTxt = oEnt
If oTxt.TextString Like sFind Then oTxt.TextString = sReplace
Case Is = "AcDbMText"
Set oMtxt = oEnt
If oMtxt.TextString Like sFind Then oMtxt.TextString = sReplace
End Select
Next oEnt
End Sub
Public Function GetSS_TextFilter() As AcadSelectionSet
'creates an ss of Text only
Dim s1 As AcadSelectionSet 'for filtered ss
'filter is needed if there's no pfss
Dim intFtyp(0) As Integer ' setup for the filter
Dim varFval(0) As Variant
Dim varFilter1, varFilter2 As Variant
intFtyp(0) = 0: varFval(0) = "TEXT,MTEXT" ' get only text and mtext
varFilter1 = intFtyp: varFilter2 = varFval
Set s1 = AddSelectionSet("ssTextFilter") ' create or get the set
s1.Clear ' clear the set
s1.Select acSelectionSetAll, , , varFilter1, varFilter2 ' do it
Set GetSS_TextFilter = s1
End Function
Public Function AddSelectionSet(SetName As String) As AcadSelectionSet
' This routine does the error trapping neccessary for when you want to create a
' selectin set. It takes the proposed name and either adds it to the selectionsets
' collection or sets it.
On Error Resume Next
Set AddSelectionSet = ThisDrawing.SelectionSets.Add(SetName)
If Err.Number <> 0 Then
Set AddSelectionSet = ThisDrawing.SelectionSets.Item(SetName)
AddSelectionSet.Clear
End If
End Function
Public Function GetSS_TextFilter_SOS() As AcadSelectionSet
'creates an ss of Text only using SelectOnScreen
Dim s1 As AcadSelectionSet 'for filtered ss
'filter is needed if there's no pfss
Dim intFtyp(0) As Integer ' setup for the filter
Dim varFval(0) As Variant
Dim varFilter1, varFilter2 As Variant
intFtyp(0) = 0: varFval(0) = "TEXT,MTEXT" ' get only text and mtext
varFilter1 = intFtyp: varFilter2 = varFval
Set s1 = AddSelectionSet("ssTextFilter") ' create or get the set
s1.Clear ' clear the set
s1.SelectOnScreen varFilter1, varFilter2 ' do it
Set GetSS_TextFilter_SOS = s1
End Function
Ed
Did you find this post helpful? Feel free to Like this post.
Did your question get successfully answered? Then click on the ACCEPT SOLUTION button.
How to
post your code.data:image/s3,"s3://crabby-images/495e6/495e633166c1c37ea66ebc77cb2908f6e8dd1f02" alt="EESignature EESignature"