CalendarSharing オブジェクト (Outlook)

予定表の情報を共有するためのユーティリティの集合を表します。

注釈

予定表フォルダーを表す Folder オブジェクトの GetCalendarExporter メソッドを使用して、CalendarSharing オブジェクトを作成します。 GetCalendarExporter メソッドは、予定表フォルダーでのみ使用できます。 エラーは、他の種類のフォルダーを表す Folder オブジェクトでメソッドを使用する場合に発生します。

予定表を URL として共有するために iCalendar (.ics) ファイルに予定表情報を保存するには 、SaveAsICal メソッドを使用するか、 ForwardAsICal メソッドを使用して、予定表をペイロードとして共有するための MailItem を作成します。

注:

[!メモ] エクスポート オブジェクトには、iCalendar 形式のエクスポートのみサポートしています。

次の Visual Basic for Applications (VBA) の例は、予定表フォルダーの エクスポート オブジェクトを作成し、全体のフォルダーを (添付ファイルやプライベートなアイテムを含む) の内容を 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 のサポートおよびフィードバックを参照してください。