CalendarSharing.SaveAsICal 方法 (Outlook)
将日历信息作为 iCalendar 日历 (.ics) 文件从 CalendarSharing 对象的父 Folder 导出。
语法
expression。 SaveAsICal
( _Path_
)
表达 返回 CalendarSharing 对象的表达式。
参数
名称 | 必需/可选 | 数据类型 | 说明 |
---|---|---|---|
Path | 必需 | String | iCalendar 文件的路径和文件名。 |
备注
ICalendar 文件中提供的详细程度取决于在下面的 CalendarSharing 属性的值的组合:
可以将 IncludeWholeCalendar 属性设置为 True 可导出包含在文件夹中的所有项,或者可以设置 开始日期 和 结束日期 属性,分别结束日期,并限制对指定的开始日期之间的日期范围的导出的项。
示例
下面的 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
.IncludeWholeCalendar = True
.IncludeAttachments = True
.IncludePrivateDetails = True
.RestrictToWorkingHours = False
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
另请参阅
支持和反馈
有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。