Application.Explorers property (Outlook)

Returns an Explorers collection object that contains the Explorer objects representing all open explorers. Read-only.

Syntax

expression. Explorers

expression A variable that represents an Application object.

Example

The following Microsoft Visual Basic for Applications (VBA) example displays the number of explorer windows that are open.

Private Sub CountExplorers() 
 
 MsgBox "There are " & _ 
 
 Application.Explorers.Count & " Explorers." 
 
End Sub

The following VBA example uses the Count property and Item method of the Selection collection returned by the Selection property to display the senders of all mail items selected in the explorer that displays the Inbox. To run this example, you need to have at least one mail item selected in the explorer displaying the Inbox. You might receive an error if you select items other than a mail item such as task request as the SenderName property does not exist for a TaskRequestItem object.

Sub GetSelectedItems() 
 
 Dim myOlExp As Outlook.Explorer 
 
 Dim myOlSel As Outlook.Selection 
 
 Dim MsgTxt As String 
 
 Dim x As Integer 
 
 
 
 MsgTxt = "You have selected items from: " 
 
 Set myOlExp = Application.Explorers.Item(1) 
 
 If myOlExp = "Inbox" Then 
 
 Set myOlSel = myOlExp.Selection 
 
 For x = 1 To myOlSel.Count 
 
 MsgTxt = MsgTxt & myOlSel.Item(x).SenderName & ";" 
 
 Next x 
 
 MsgBox MsgTxt 
 
End If 
 
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.