Inspector.SetCurrentFormPage method (Outlook)

Displays the specified form page or form region in the inspector.

Syntax

expression. SetCurrentFormPage( _PageName_ )

expression A variable that represents an Inspector object.

Parameters

Name Required/Optional Data type Description
PageName Required String The display name of the form page, or the internal name of a form region.

Remarks

Use SetCurrentFormPage to display a form region by specifying the InternalName property of the form region, if the form region is an a separate, replace, or replace-all form region.

Example

This Visual Basic for Applications (VBA) example uses the SetCurrentFormPage method to show the All Fields page of the currently open item. If an error occurs, Outlook will display a message box to the user.

Sub ShowAllFieldsPage() 
 
 On Error GoTo ErrorHandler 
 
 Dim myInspector As Inspector 
 
 Dim myItem As Object 
 
 
 
 Set myInspector = Application.ActiveInspector 
 
 myInspector.SetCurrentFormPage ("All Fields") 
 
 Set myItem = myInspector.CurrentItem 
 
 myItem.Display 
 
Exit Sub 
 
 
 
ErrorHandler: 
 
 MsgBox Err.Description, vbInformation 
 
End Sub

See also

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