NavigationPane.IsCollapsed-Eigenschaft (Outlook)

Gibt einen booleschen Wert zurück, der bestimmt, ob der Navigationsbereich reduziert ist, oder legt diesen wert fest. Lese-/Schreibzugriff.

Syntax

Ausdruck. IsCollapsed

Ausdruck Eine Variable, die ein NavigationPane-Objekt darstellt.

Beispiel

Im folgenden beispiel für Visual Basic for Applications (VBA) wird der Navigationsbereich reduziert, nachdem alle darin enthaltenen Module ausgeblendet wurden.

Sub CollapseAndHideAllModules() 
 
 Dim objPane As NavigationPane 
 
 
 
 ' Get the NavigationPane object for the 
 
 ' currently displayed Explorer object. 
 
 Set objPane = Application.ActiveExplorer.NavigationPane 
 
 
 
 ' Set the DisplayedModuleCount property to 
 
 ' hide all modules contained by the 
 
 ' Navigation Pane. 
 
 objPane.DisplayedModuleCount = 0 
 
 
 
 ' Set the IsCollapsed property to 
 
 ' collapse the navigation pane. 
 
 objPane.IsCollapsed = True 
 
 
 
End Sub

Siehe auch

NavigationPane-Objekt

Support und Feedback

Haben Sie Fragen oder Feedback zu Office VBA oder zu dieser Dokumentation? Unter Office VBA-Support und Feedback finden Sie Hilfestellung zu den Möglichkeiten, wie Sie Support erhalten und Feedback abgeben können.