Application.AdvancedSearch method (Outlook)

Performs a search based on a specified DAV Searching and Locating (DASL) search string.

Syntax

expression. AdvancedSearch( _Scope_ , _Filter_ , _SearchSubFolders_ , _Tag_ )

expression A variable that represents an Application object.

Parameters

Name Required/Optional Data type Description
Scope Required String The scope of the search. For example, the folder path of a folder. It's recommended that the folder path is enclosed within single quotes. Otherwise, the search might not return correct results if the folder path contains special characters including Unicode characters. To specify multiple folder paths, enclose each folder path in single quotes and separate the single quoted folder paths with a comma.
Filter Optional Variant The DASL search filter that defines the parameters of the search.
SearchSubFolders Optional Variant Determines if the search will include any of the folder's subfolders.
Tag Optional Variant The name given as an identifier for the search.

Return value

A Search object that represents the results of the search.

Remarks

You can run multiple searches simultaneously by calling the AdvancedSearch method in successive lines of code. However, you should be aware that programmatically creating a large number of search folders can result in significant simultaneous search activity that would affect the performance of Outlook, especially if Outlook conducts the search in online Exchange mode.

The AdvancedSearch method and related features in the Outlook object model don't create a Search Folder that will appear in the Outlook user interface. However, you can use the Save method of the Search object that is returned to create a Search Folder that will appear in the Search Folders list in the Outlook user interface.

Using the Scope parameter, you can specify one or more folders in the same store, but you may not specify multiple folders in multiple stores. To specify multiple folders in the same store for the Scope parameter, use a comma character between each folder path and enclose each folder path in single quotes. For default folders such as Inbox or Sent Items, you can use the simple folder name instead of the full folder path. For example, the following two lines of code represent valid Scope parameters:

Scope = "'Inbox', 'Sent Items'"
Scope = "'" & Application.Session.GetDefaultFolder(olFolderInbox).FolderPath _  
    & "','" & Application.Session.GetDefaultFolder(olFolderSentMail).FolderPath & "'"

The Filter parameter can be any valid DASL query. For additional information on DASL queries, see Filtering Items and Referencing Properties by Namespace. Note that you cannot use a JET query for the Filter parameter of Advanced Search. If Instant Search is enabled on a store that contains a folder specified in the Scope parameter, you can use Instant Search keywords to improve the performance of your search. If you use Instant Search keywords and Instant Search is not enabled, Outlook will return an error and your search will fail.

Example

The following Visual Basic for Applications (VBA) example searches the Inbox for items with subject equal to Test and displays the names of the senders of the email items returned by the search. The AdvancedSearchComplete event procedure sets the boolean blnSearchComp to True when the search is complete. This boolean variable is used by the TestAdvancedSearchComplete() procedure to determine when the search is complete. The sample code must be placed in a class module such as ThisOutlookSession, and the TestAdvancedSearchComplete() procedure must be called before the event procedure can be called by Outlook.

Public blnSearchComp As Boolean  
  
Private Sub Application_AdvancedSearchComplete(ByVal SearchObject As Search)  
    Debug.Print "The AdvancedSearchComplete Event fired"  
    If SearchObject.Tag = "Test" Then  
        m_SearchComplete = True  
    End If  
  
End Sub  
  
Sub TestAdvancedSearchComplete()  
    Dim sch As Outlook.Search  
    Dim rsts As Outlook.Results  
    Dim i As Integer  
    blnSearchComp = False  
    Const strF As String = "urn:schemas:mailheader:subject = 'Test'"  
    Const strS As String = "Inbox"     
    Set sch = Application.AdvancedSearch(strS, strF, "Test")   
    While blnSearchComp = False  
        DoEvents  
    Wend   
    Set rsts = sch.Results  
    For i = 1 To rsts.Count  
        Debug.Print rsts.Item(i).SenderName  
    Next  
End Sub

The following Microsoft Visual Basic for Applications example uses the AdvancedSearch method to create a new search. The parameters of the search, as specified by the Filter argument of the AdvancedSearch method, will return all items in the Inbox and Sent Items folders where the Subject phrase-matches or contains "Office". The user's Inbox and Sent Items folders are specified as the scope of the search and the SearchSubFolders property is set to True. When the search is complete, the GetTable method is called on the Search object for performant enumeration of search results.

Public m_SearchComplete As Boolean  
  
Private Sub Application_AdvancedSearchComplete(ByVal SearchObject As Search)  
    If SearchObject.Tag = "MySearch" Then  
        m_SearchComplete = True  
    End If  
End Sub  
  
Sub TestSearchForMultipleFolders()  
    Dim Scope As String  
    Dim Filter As String  
    Dim MySearch As Outlook.Search  
    Dim MyTable As Outlook.Table  
    Dim nextRow As Outlook.Row  
    m_SearchComplete = False  
    'Establish scope for multiple folders  
    Scope = "'" & Application.Session.GetDefaultFolder( _  
    olFolderInbox).FolderPath _  
    & "','" & Application.Session.GetDefaultFolder( _  
    olFolderSentMail).FolderPath & "'"  
    'Establish filter  
    If Application.Session.DefaultStore.IsInstantSearchEnabled Then  
        Filter = Chr(34) & "urn:schemas:httpmail:subject" _  
        & Chr(34) & " ci_phrasematch 'Office'"  
    Else  
        Filter = Chr(34) & "urn:schemas:httpmail:subject" _  
        & Chr(34) & " like '%Office%'"  
    End If  
    Set MySearch = Application.AdvancedSearch( _  
    Scope, Filter, True, "MySearch")  
    While m_SearchComplete <> True  
        DoEvents  
    Wend  
    Set MyTable = MySearch.GetTable  
    Do Until MyTable.EndOfTable  
        Set nextRow = MyTable.GetNextRow()  
        Debug.Print nextRow("Subject")  
    Loop  
End Sub

See also

Application Object

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.