CalendarModule.Position property (Outlook)

Returns or sets a Long value that represents the ordinal position of the CalendarModule object when it is displayed in the navigation pane. Read/write.

Syntax

expression.Position

expression A variable that represents a CalendarModule object.

Remarks

This property can only be set to a value between 1 and 9. An error occurs if you attempt to set it to a value outside of that range.

Changing the value of this property for a given CalendarModule object changes the Position values of other navigation modules in a NavigationModules collection, depending on the relative change between the new value and the original value.

  • If the new value is less than the original value, the specified CalendarModule object moves up to the new position and the other navigation modules that are already at or below that new position move down.

  • If the new value is greater than the original value, the specified CalendarModule object moves down to the new position and the other navigation modules that are between the old position and the new position move up, filling the old position.

Example

The following Visual Basic for Applications (VBA) sample code attempts to retrieve the Calendar navigation module from the navigation pane. If it successfully retrieves the module, the code sets the Position property of the CalendarModule object to '1,' which moves it to the top of the navigation pane. Finally, the code sets the CurrentModule property of the NavigationPane object to the retrieved Calendar module, which selects it in the navigation pane.

Sub MoveCalendarModuleFirst() 
 
 Dim objPane As NavigationPane 
 
 Dim objModule As CalendarModule 
 
 
 
 On Error GoTo ErrRoutine 
 
 
 
 ' Get the current NavigationPane object. 
 
 Set objPane = Application.ActiveExplorer.NavigationPane 
 
 
 
 ' Get the Calendar navigation module 
 
 ' from the navigation pane. 
 
 Set objModule = objPane.Modules.GetNavigationModule( _ 
 
 olModuleCalendar) 
 
 
 
 ' If a CalendarModule object is present, 
 
 ' make it the first navigation module displayed in the 
 
 ' Navigation Pane. 
 
 If Not (objModule Is Nothing) Then 
 
 objModule.Position = 1 
 
 End If 
 
 
 
 ' Select the Calendar navigation module in the 
 
 ' Navigation Pane. 
 
 Set objPane.CurrentModule = objModule 
 
 
 
EndRoutine: 
 
 On Error GoTo 0 
 
 Set objModule = Nothing 
 
 Set objPane = Nothing 
 
 Exit Sub 
 
 
 
ErrRoutine: 
 
 Debug.Print Err.Number & " (&H" & Hex(Err.Number) & ")" 
 
 Select Case Err.Number 
 
 Case -2147024809 '&H80070057 
 
 ' Typically occurs if you set the Position 
 
 ' property less than 1 or greater than 9. 
 
 MsgBox Err.Number & " - " & Err.Description, _ 
 
 vbOKOnly Or vbCritical, _ 
 
 "MoveCalendarModuleFirst" 
 
 End Select 
 
 GoTo EndRoutine 
 
End Sub

See also

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