Compartir a través de


Enviar una invitación de uso compartido para un calendario

Los mensajes para compartir, como invitaciones, solicitudes y respuestas para compartir, se representan en Microsoft Outlook mediante el objeto SharingItem. Se usa el método CreateSharingItem del objeto NameSpace con el fin de crear objetos SharingItem para invitaciones y solicitudes para compartir.

En este ejemplo se usa el método OpenSharingItem para crear un objeto SharingItem que represente una invitación a compartir para la carpeta predeterminada Calendar (Calendario). Una vez compartida, el destinatario puede usar el método OpenSharedFolder o GetSharedDefaultFolder del objeto NameSpace, o bien, el método OpenSharedFolder del objeto SharingItem para abrir la carpeta compartida.

  1. En el ejemplo se obtiene una referencia de objeto Folder de la carpeta predeterminada Calendar (Calendario) para el actual usuario mediante el método GetDefaultFolder del objeto NameSpace.

  2. Se usa el método CreateSharingItem para crear un nuevo objeto SharingItem, usando el objeto Folder para establecer el contexto de uso compartido usado por el objeto SharingItem.

  3. Por último, se llama al método Add de la colección Recipients del nuevo objeto SharingItem para agregar el destinatario especificado, y se usa el método Send para enviar el objeto SharingItem.

Public Sub ShareCalendarByInvitation() 
 Dim oNamespace As NameSpace 
 Dim oFolder As Folder 
 Dim oSharingItem As SharingItem 
 
 On Error GoTo ErrRoutine 
 
 ' Get a reference to the Calendar default folder 
 Set oNamespace = Application.GetNamespace("MAPI") 
 Set oFolder = oNamespace.GetDefaultFolder(olFolderCalendar) 
 
 ' Create a new sharing invitation, using the Calendar 
 ' default folder to establish sharing context. 
 Set oSharingItem = oNamespace.CreateSharingItem(oFolder) 
 
 ' 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 of a SharingItem 
 ' to True when sharing 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

Soporte técnico y comentarios

¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.