Enviar um convite de compartilhamento para um Feed do RSS
O compartilhamento de mensagens, incluindo convites de compartilhamento, solicitações de compartilhamento e respostas de compartilhamento, são representados no Microsoft Outlook pelo SharingItem](.. /.. /.. Objeto /api/Outlook.SharingItem.md). O método CreateSharingItem do objeto NameSpace é usado para criar objetos SharingItem para compartilhamento de convites e solicitações de compartilhamento. As respostas de compartilhamento são criadas automaticamente pelo Outlook quando os métodos Reply ou ReplyAll de um SharingItem que representa um convite de compartilhamento ou solicitação de compartilhamento são chamados.
Este exemplo usa o método OpenSharingItem para criar um SharingItem que representa um convite de compartilhamento de um Really Simple Syndication (RSS) feed. Depois de compartilhado, o destinatário poderá usar o método OpenSharedFolder do objeto NameSpace ou o método OpenSharedFolder do objeto SharingItem para abrir o feed do RSS.
O exemplo primeiro cria uma referência de objeto ameSpace ao namespace MAPI.
Em seguida, ele usa o método CreateSharingItem para criar um novo objeto SharingItem, usando a URL do RSS feed para estabelecer o contexto de compartilhamento usado por um SharingItem.
Por fim, o método Add para a coleção Destinatários do objeto SharingItem recém-criado é chamado para adicionar o destinatário especificado e o método Enviar é usado para enviar o 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
Suporte e comentários
Tem dúvidas ou quer enviar comentários sobre o VBA para Office ou sobre esta documentação? Confira Suporte e comentários sobre o VBA para Office a fim de obter orientação sobre as maneiras pelas quais você pode receber suporte e fornecer comentários.