ペイロード共有を使用して予定表をエクスポートする
Microsoft Outlook には、 MailItem に添付された iCalendar (.ics) ファイルを使用して、予定表情報を他のユーザーと共有する機能が含まれています。 CalendarSharing オブジェクトは、予定表アイテムを含むフォルダーから iCalendar ファイルを生成し、iCalendar ファイルが添付されている MailItem を生成するために使用されます。
この例では CalendarSharing アイテムを使用して、次のような手順で 7 日後までの空き時間情報を 1 人の受信者と共有します。
NameSpace オブジェクトの GetDefaultFolder メソッドを使用して、現在のユーザーの既定の 予定表フォルダーの Folder オブジェクト参照を取得します。
Folder オブジェクトの GetCalendarExporter メソッドを使用して、フォルダーの CalendarSharing オブジェクト参照を作成します。
CalendarSharing オブジェクトに対して以下のプロパティを設定し、オブジェクトからエクスポートされる情報の範囲とレベルを制限します。
CalendarDetail プロパティを設定し、各予定表アイテムの情報を空き時間情報のみに制限します。
StartDate プロパティと EndDate プロパティを設定し、ファイルに含まれる予定表アイテムを 7 日後までに制限します。
RestrictToWorkingHours プロパティを設定し、予定表アイテムを稼働時間内のアイテムに制限します。
IncludeAttachments プロパティを設定し、オブジェクトからエクスポートされる予定表アイテムの添付ファイルを除外します。
IncludePrivateDetails プロパティを設定し、オブジェクトからエクスポートされる個人用の予定表アイテムの詳細を除外します。
次に、CalendarSharing オブジェクトの ForwardAsICal メソッドを呼び出して予定表アイテムを iCalendar ファイルにエクスポートし、iCalendar ファイルを添付ファイルとして MailItem オブジェクトを作成します。 olCalendarMailFormatDailySchedule 列挙型の olCalendarMailFormatSchedule 定数は、ForwardAsICal メソッドと共に使用され、MailItem の本文に次の 7 日間の空き時間情報を HTML 形式で含める必要があることを示します。
最後に、新しく作成された 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 のサポートおよびフィードバックを参照してください。