MailItem.GetInspector property (Outlook)

Returns an Inspector object that represents an inspector initialized to contain the specified item. Read-only.

Syntax

expression. GetInspector

expression A variable that represents a MailItem object.

Remarks

This property is useful for returning an Inspector object in which to display the item, as opposed to using the Application.ActiveInspector method and setting the Inspector.CurrentItem property. If an Inspector object already exists for the item, the GetInspector property will return that Inspector object instead of creating a new one.

Example

This Visual Basic for Applications (VBA) example shows a function InsertBodyTextInWordEditor that creates a mail item, assigns it a title and adds text for the body. The function sets the Subject property to assign the title "Testing...". It then calls the Display method to open the mail item in an inspector. To insert text in a Word editor as the body of the mail item, the function uses the Document object and Range object in the Word object model. The function uses the item's GetInspector property to get the existing Inspector object, and then uses the Inspector.WordEditor property to obtain a Word.Document object for the item. Using the Word.Document object, the function accesses the Word.Range object and inserts text into the body of the item.

Since this example accesses the Word object model, you must first add a reference to the Microsoft Word Object Library to compile the example successfully.

Sub InsertBodyTextInWordEditor() 
 Dim myItem As Outlook.MailItem 
 Dim myInspector As Outlook.Inspector 
 'You must add a reference to the Microsoft Word Object Library 
 'before this sample will compile 
 Dim wdDoc As Word.Document 
 Dim wdRange As Word.Range 
 
 On Error Resume Next 
 Set myItem = Application.CreateItem(olMailItem) 
 myItem.Subject = "Testing..." 
 myItem.Display 
 'GetInspector property returns Inspector 
 Set myInspector = myItem.GetInspector 
 'Obtain the Word.Document for the Inspector 
 Set wdDoc = myInspector.WordEditor 
 If Not (wdDoc Is Nothing) Then 
 'Use the Range object to insert text 
 Set wdRange = wdDoc.Range(0, wdDoc.Characters.Count) 
 wdRange.InsertAfter ("Hello world!") 
 End If 
End Sub

See also

MailItem 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.