Outlook) (CalendarSharing.SaveAsICal 方法
將CalendarSharing物件的父資料夾中的行事曆資訊匯出為 iCalendar 行事曆 (.ics) 檔案。
語法
expression。 SaveAsICal
( _Path_
)
表達 會傳回 CalendarSharing 物件的 運算式。
參數
名稱 | 必要/選用 | 資料類型 | 描述 |
---|---|---|---|
Path | 必要 | 字串 | iCalendar 檔案的路徑和檔案名。 |
註解
iCalendar 檔案中提供的詳細資料層級是由下列 CalendarSharing 屬性中的值組合所決定:
您可以將 IncludeWholeCalendar 屬性設定為 True 以匯出資料夾中包含的所有專案,也可以設定 StartDate 和 EndDate 屬性,將匯出的專案分別限制在指定的開始日期和結束日期之間的日期範圍。
範例
下列 Visual Basic for Applications (VBA) 範例會建立 Calendar 資料夾的 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 支援與意見反應。