枚举日历视图中的活动文件夹
在 Microsoft Outlook 中,可以使用 NavigationGroups 和 NavigationFolders 集合遍历导航窗格中模块的组和文件夹层次结构。 NavigationModule 对象的 NavigationGroups 集合包含导航模块中显示的每个导航组,而 NavigationGroup 对象的 NavigationFolders 集合包含导航组中显示的每个导航文件夹。
通过组合使用这些集合,您可以枚举显示在导航窗格中的导航模块的每个导航文件夹。
下面的示例计数选定的导航文件夹,这些文件夹将显示在导航窗格的“日历”导航模块中。 本示例执行下列操作:
首先为活动浏览器获取 NavigationPane 对象的引用。
然后,它使用 NavigationModules 集合的 GetNavigationModule 方法从 NavigationPane 对象获取对 CalendarModule 对象的引用。
然后,该示例通过 CalendarModule 对象的 NavigationGroups 集合进行枚举。 然后,对于集合中的每个 NavigationGroup ,该示例将枚举 NavigationFolders 集合。
如果 NavigationFolders 集合中包含的 NavigationFolder 对象的 IsSelected 属性设置为 True,则变量
intCounter
将递增。最后,该示例显示包含 值的
intCounter
对话框。
Dim WithEvents objPane As NavigationPane
Private Sub EnumerateActiveCalendarFolders()
Dim objModule As CalendarModule
Dim objGroup As NavigationGroup
Dim objFolder As NavigationFolder
Dim intCounter As Integer
On Error GoTo ErrRoutine
' Get the NavigationPane object for the
' currently displayed Explorer object.
Set objPane = Application.ActiveExplorer.NavigationPane
' Get the CalendarModule object, if one exists,
' for the current Navigation Pane.
Set objModule = objPane.Modules.GetNavigationModule(olModuleCalendar)
' Iterate through each NavigationGroup contained
' by the CalendarModule.
For Each objGroup In objModule.NavigationGroups
' Iterate through each NavigationFolder contained
' by the NavigationGroup.
For Each objFolder In objGroup.NavigationFolders
' Check if the folder is selected.
If objFolder.IsSelected Then
intCounter = intCounter + 1
End If
Next
Next
' Display the results.
MsgBox "There are " & intCounter & " selected calendars in the Calendar module."
EndRoutine:
On Error GoTo 0
Set objFolder = Nothing
Set objGroup = Nothing
Set objModule = Nothing
Set objPane = Nothing
intCounter = 0
Exit Sub
ErrRoutine:
MsgBox Err.Number & " - " & Err.Description, _
vbOKOnly Or vbCritical, _
"EnumerateActiveCalendarFolders"
End Sub
支持和反馈
有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。