RSS フィードの共有招待を送信する
共有の招待、共有要求、共有応答などのメッセージの共有は、Microsoft Outlook で SharingItem]( によって表されます。/../../api/Outlook.SharingItem.md) オブジェクト。 NameSpace オブジェクトの CreateSharingItem メソッドは、招待と共有要求を共有するための SharingItem オブジェクトを作成するために使用されます。 共有の招待または共有要求を表す SharingItem の Reply メソッドまたは ReplyAll メソッドが呼び出されると、Outlook によって共有応答が自動的に作成されます。
この例では、OpenSharingItem メソッドを使用して、RSS (Really Simple Syndication) フィードの共有への招待を表す SharingItem を作成します。 共有すると、受信者は NameSpace オブジェクトの OpenSharedFolder メソッド、または SharingItem オブジェクトの OpenSharedFolder メソッドを使用して RSS フィードを開くことができます。
このサンプルでは、最初に MAPI 名前空間への ameSpace オブジェクト参照を作成します。
CreateSharingItem メソッドを使用して、新しい SharingItem オブジェクトを作成します。 SharingItem で使われる共有コンテキストを設定するために、RSS フィードの URI を使用します。
最後に、新しく作成された SharingItem オブジェクトの Recipients コレクションの Add メソッドを呼び出して指定した受信者を追加し、Send メソッドを使用して SharingItem を送信します。
Public Sub ShareRSSByInvitation()
Dim oNamespace As NameSpace
Dim sRSSurl As String
Dim oSharingItem As SharingItem
On Error GoTo ErrRoutine
' Specify the RSS feed URL for which sharing is to
' be requested.
sRSSurl = "feed://example.com/rss.xml"
' Get a reference to the MAPI namespace.
Set oNamespace = Application.GetNamespace("MAPI")
' Create a new sharing request, using the RSS feed
' URL to establish sharing context.
Set oSharingItem = oNamespace.CreateSharingItem(sRSSurl)
' Add a recipient to the Recipients collection of
' the sharing invitation.
oSharingItem.Recipients.Add "someone@example.com"
' Send the sharing invitation.
oSharingItem.Send
EndRoutine:
On Error GoTo 0
Set oSharingItem = 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 -313393143 ' &HED520009
' This error typically occurs if you set the
' AllowWriteAccess property to true for a
' default folder.
MsgBox Err.Description, _
vbOKOnly, _
Err.Number & " - " & Err.Source
Case -2147467259 ' &H80004005
' This error typically occurs if the SharingItem
' cannot be sent because of incorrect or
' conflicting property settings.
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 のサポートおよびフィードバックを参照してください。