共用方式為


傳送 RSS 摘要的共用邀請

共用訊息,包括共用邀請、共用要求和共用回應,會在 Microsoft Outlook 中由 SharingItem] (。。/../../api/Outlook.SharingItem.md) 物件。 NameSpace物件的CreateSharingItem方法可用來建立共用邀請和共用要求的SharingItem物件。 當呼叫代表共用邀請或共用要求之SharingItemReplyReplyAll方法時,Outlook 會自動建立共用回應。

本範例會使用 OpenSharingItem 方法來建立 SharingItem,以代表真正簡易新聞訂閱方式 (RSS) 摘要的共用邀請。 共用之後,收件者就可以使用NameSpace物件的OpenSharedFolder方法或SharingItem物件的OpenSharedFolder方法來開啟 RSS 摘要。

  1. 此範例會先建立 MAPI 命名 空間的 ameSpace 物件參考。

  2. 然後,它會使用 CreateSharingItem 方法來建立新的 SharingItem 物件,並使用 RSS 摘要的 URI 來建立 SharingItem 所用的共用內容。

  3. 最後,會呼叫新建立之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 支援與意見反應