共用方式為


使用承載共用匯出行事曆

Microsoft Outlook 包含使用附加至 MailItem的 iCalendar (.ics) 檔案與其他使用者共用行事曆資訊的能力。 CalendarSharing物件可用來從包含行事曆專案的資料夾產生 iCalendar 檔案,以及產生附加 iCalendar 檔案的MailItem

這則範例會使用 CalendarSharing 項目與單一收件者共用今後 7 日間的空閒/忙碌資訊:

  1. 此範例會使用 NameSpace 物件的 GetDefaultFolder 方法,取得目前使用者之 [行事曆] 預設資料夾的 Folder 物件參照。

  2. 它會使用Folder物件的GetCalendarExporter方法來建立資料夾的CalendarSharing物件參照。

  3. 然後,它會在 CalendarSharing 物件上設定下列屬性,以便限制物件匯出的資訊範圍和層級:

    • 設定 CalendarDetail 屬性,以便將每個行事曆項目的資訊限制為只有空閒/忙碌資訊。

    • 設定 StartDateEndDate 屬性,以便將檔案內包含的行事曆項目限制為今後 7 日間。

    • 設定 RestrictToWorkingHours 屬性,以便將行事曆項目限制為上班時間內的行事曆項目。

    • 設定 IncludeAttachments 屬性,以便排除物件匯出之行事曆項目的任何附件。

    • 設定 IncludePrivateDetails 屬性,以便排除物件匯出之任何私人行事曆項目的詳細資料。

  4. 然後,它會呼叫CalendarSharing物件的ForwardAsICal方法,將行事曆專案匯出至 iCalendar 檔案,並使用 iCalendar 檔案作為附件來建立MailItem物件。 olCalendarMailFormat列舉的olCalendarMailFormat 常數會與ForwardAsICal方法搭配使用,以指出MailItem的主體應該包含未來七天的 HTML 格式空閒/忙碌資訊。

  5. 最後,會呼叫新建立之 MailItem物件之Recipients集合的Add方法來新增指定的收件者,並使用Send方法來傳送MailItem

Public Sub ShareWorkCalendarByPayload() 
 
 Dim oNamespace As NameSpace 
 Dim oFolder As Folder 
 Dim oCalendarSharing As CalendarSharing 
 Dim oMailItem As MailItem 
 
 On Error GoTo ErrRoutine 
 ' Get a reference to the Calendar default folder 
 Set oNamespace = Application.GetNamespace("MAPI") 
 Set oFolder = oNamespace.GetDefaultFolder(olFolderCalendar) 
 
 ' Get a reference to a CalendarSharing object for that 
 ' folder. 
 Set oCalendarSharing = oFolder.GetCalendarExporter 
 
 ' Set the CalendarSharing object to restrict 
 ' the information shared in the iCalendar file. 
 With oCalendarSharing 
 ' Send free/busy information only. 
 .CalendarDetail = olFreeBusyOnly 
 
 ' Send information for the next seven days. 
 .startDate = Now 
 .endDate = DateAdd("d", 7, Now) 
 
 ' Restrict information to working hours only. 
 .RestrictToWorkingHours = True 
 
 ' Exclude attachments and private information. 
 .IncludeAttachments = False 
 .IncludePrivateDetails = False 
 End With 
 
 ' Get the mail item containing the iCalendar file 
 ' and calendar information. 
 Set oMailItem = oCalendarSharing.ForwardAsICal( _ 
 olCalendarMailFormatDailySchedule) 
 
 ' Send the mail item to the specified recipient. 
 With oMailItem 
 .Recipients.Add "someone@example.com" 
 .Send 
 End With 
 
EndRoutine: 
 On Error GoTo 0 
 Set oMailItem = Nothing 
 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 支援與意見反應