Outlook) (CalendarSharing 对象

代表用于共享日历信息的一组实用程序。

备注

使用代表日历文件夹的 Folder 对象的 GetCalendarExporter 方法创建 CalendarSharing 对象。 GetCalendarExporter 方法仅可在日历文件夹。 如果在代表其他文件夹类型的 Folder 对象上使用方法,就会出错。

使用 SaveAsICal 方法将日历信息保存在 iCalendar (.ics) 文件中,以便将日历共享为 URL,或使用 ForwardAsICal 方法创建 MailItem 以将日历共享为有效负载。

注意

[!注释] CalendarSharing 对象仅支持导出 iCalendar 格式。

示例

下面的 Visual Basic for Applications (VBA) 示例创建 CalendarSharing 对象的日历文件夹中,然后将整个文件夹 (包括附件和私人性质项目) 中的内容导出到 iCalendar 日历 (.ics) 文件。

Public Sub ExportEntireCalendar() 
 
 
 
 Dim oNamespace As NameSpace 
 
 Dim oFolder As Folder 
 
 Dim oCalendarSharing As CalendarSharing 
 
 
 
 On Error GoTo ErrRoutine 
 
 
 
 ' Get a reference to the Calendar default folder 
 
 Set oNamespace = Application.GetNamespace("MAPI") 
 
 Set oFolder = oNamespace.GetDefaultFolder(olFolderCalendar) 
 
 
 
 ' Get a CalendarSharing object for the Calendar default folder. 
 
 Set oCalendarSharing = oFolder.GetCalendarExporter 
 
 
 
 ' Set the CalendarSharing object to export the contents of 
 
 ' the entire Calendar folder, including attachments and 
 
 ' private items, in full detail. 
 
 With oCalendarSharing 
 
 .CalendarDetail = olFullDetails 
 
 .IncludeAttachments = True 
 
 .IncludePrivateDetails = True 
 
 .IncludeWholeCalendar = True 
 
 End With 
 
 
 
 ' Export calendar to an iCalendar calendar (.ics) file. 
 
 oCalendarSharing.SaveAsICal "C:\SampleCalendar.ics" 
 
 
 
EndRoutine: 
 
 On Error GoTo 0 
 
 Set oCalendarSharing = Nothing 
 
 Set oFolder = Nothing 
 
 Set oNamespace = Nothing 
 
Exit Sub 
 
 
 
ErrRoutine: 
 
 Select Case Err.Number 
 
 Case 287 ' &H0000011F 
 
 ' The user denied access to the Address Book. 
 
 ' This error occurs if the code is run by an 
 
 ' untrusted application, and the user chose not to 
 
 ' allow access. 
 
 MsgBox "Access to Outlook was denied by the user.", _ 
 
 vbOKOnly, _ 
 
 Err.Number & " - " & Err.Source 
 
 Case -2147467259 ' &H80004005 
 
 ' Export failed. 
 
 ' This error typically occurs if the CalendarSharing 
 
 ' method cannot export the calendar information because 
 
 ' of conflicting property settings. 
 
 MsgBox Err.Description, _ 
 
 vbOKOnly, _ 
 
 Err.Number & " - " & Err.Source 
 
 Case -2147221233 ' &H8004010F 
 
 ' Operation failed. 
 
 ' This error typically occurs if the GetCalendarExporter method 
 
 ' is called on a folder that doesn't contain calendar items. 
 
 MsgBox Err.Description, _ 
 
 vbOKOnly, _ 
 
 Err.Number & " - " & Err.Source 
 
 Case Else 
 
 ' Any other error that may occur. 
 
 MsgBox Err.Description, _ 
 
 vbOKOnly, _ 
 
 Err.Number & " - " & Err.Source 
 
 End Select 
 
 
 
 GoTo EndRoutine 
 
End Sub

方法

名称
ForwardAsICal
SaveAsICal

属性

名称
Application
CalendarDetail
EndDate
Folder
IncludeAttachments
IncludePrivateDetails
IncludeWholeCalendar
Parent
RestrictToWorkingHours
Session
StartDate

另请参阅

Outlook 对象模型引用

支持和反馈

有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。