Search object (Outlook)
Contains information about individual searches performed against Outlook items.
Remarks
The Search object contains properties that define the type of search and the parameters of the search itself.
Use the Application object's AdvancedSearch method to return a Search object.
Use the AdvancedSearchComplete event to determine when a given search has completed.
Example
The following Microsoft Visual Basic for Applications (VBA) example returns a search object named "SubjectSearch" and displays the object's Tag and Filter property values. The Tag property is used to identify a specific search once it has completed.
Sub SearchInboxFolder()
'Searches the Inbox
Dim objSch As Search
Const strF As String = _
"urn:schemas:mailheader:subject = 'Office Christmas Party'"
Const strS As String = "Inbox"
Const strTag As String = "SubjectSearch"
Set objSch = Application.AdvancedSearch(Scope:=strS, _
Filter:=strF, SearchSubFolders:=True, Tag:=strTag)
End Sub
The following VBA example displays information about the search and the results of the search.
Private Sub Application_AdvancedSearchComplete(ByVal SearchObject As Search)
Dim objRsts As Results
MsgBox "The search " & SearchObject.Tag & "has completed.
Set objRsts = SearchObject.Results
'Print out number in Results collection
Debug.Print objRsts.Count
'Print out each member of Results collection
For Each Item In objRsts
Debug.Print Item
Next
End Sub
Methods
Name |
---|
GetTable |
Save |
Stop |
Properties
Name |
---|
Application |
Class |
Filter |
IsSynchronous |
Parent |
Results |
Scope |
SearchSubFolders |
Session |
Tag |
See also
Search Object Members Outlook Object Model Reference
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.