Objeto CalendarSharing (Outlook)
Representa un conjunto de utilidades para compartir información del calendario.
Comentarios
Use el método GetCalendarExporter de un objeto Folder que representa una carpeta de calendario para crear un objeto CalendarSharing . El método GetCalendarExporter sólo puede utilizarse en carpetas de calendario. Se produce un error si utiliza el método en objetos Folder que representan otros tipos de carpetas.
Use el método SaveAsICal para guardar la información del calendario en un archivo iCalendar (.ics) para compartir un calendario como dirección URL, o bien use el método ForwardAsICal para crear un objeto MailItem para compartir un calendario como una carga.
Nota:
[!NOTA] El objeto CalendarSharing sólo permite exportar el formato iCalendar.
Ejemplo:
El ejemplo siguiente Visual Basic para aplicaciones (VBA) se crea un objeto CalendarSharing para la carpeta Calendario, a continuación, se exporta el contenido de toda la carpeta (incluidos los datos adjuntos y los elementos privados) a un archivo 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
Métodos
Nombre |
---|
ForwardAsICal |
SaveAsICal |
Propiedades
Nombre |
---|
Application |
CalendarDetail |
Class |
EndDate |
Folder |
IncludeAttachments |
IncludePrivateDetails |
IncludeWholeCalendar |
Parent |
RestrictToWorkingHours |
Session |
StartDate |
Consulte también
Referencia del modelo de objetos de Outlook
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.