Outlook) (CalendarModule.Position 屬性
會傳回或設定 Long 值,代表 CalendarModule 物件在流覽窗格中顯示時的序數位置。 可讀寫。
語法
運算式。位置
表達 代表 CalendarModule 物件的 變數。
註解
這個屬性只能設定成介於 1 到 9 之間的值。 如果嘗試將其設定成超出該範圍的值,則會發生錯誤。
如果變更指定之 CalendarModule 物件的這個屬性值,將會變更 NavigationModules 集合中其他瀏覽模組的 Position 值,這會取決於新值與原始值之間的相對變更。
如果新值小於原始值,則所指定的 CalendarModule 物件會向上移動到新的位置,而已在該位置或位於該位置下方的另一個瀏覽模組則會向下移動。
如果新值大於原始值,則指定的 CalendarModule 物件會向下移至新位置,而位於舊位置與新位置之間的其他流覽模組則會向上移動,填滿舊的位置。
範例
下列 Visual Basic for Applications (VBA) 範例程式碼會嘗試從流覽窗格擷取 行事曆 流覽模組。 如果成功擷取模組,程式碼會將CalendarModule物件的Position屬性設定為 '1',這會將它移至流覽窗格的頂端。 最後,程式碼會將NavigationPane物件的CurrentModule屬性設定為擷取的Calendar模組,該模組會在流覽窗格中選取它。
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
另請參閱
支援和意見反應
有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應。