Método CalendarSharing.SaveAsICal (Outlook)
Exporta la información del calendario del objeto primario Folder del objeto CalendarSharing como archivo de calendario iCalendar (.ics).
Sintaxis
expresión. SaveAsICal
( _Path_
)
Expresión Expresión que devuelve un objeto CalendarSharing .
Parameters
Nombre | Obligatorio/opcional | Tipo de datos | Descripción |
---|---|---|---|
Path | Obligatorio | String | Ruta de acceso y nombre del archivo iCalendar. |
Comentarios
El nivel de detalle proporcionada en el archivo de iCalendar se determina mediante una combinación de los valores de las siguientes propiedades CalendarSharing:
Puede establecer la propiedad IncludeWholeCalendar en True para exportar todos los elementos contenidos en la carpeta, o puede establecer las propiedades StartDate y EndDate para limitar los elementos exportados a un intervalo de fechas entre una fecha de inicio especificada y fecha de finalización, respectivamente.
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
.IncludeWholeCalendar = True
.IncludeAttachments = True
.IncludePrivateDetails = True
.RestrictToWorkingHours = False
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
Consulte también
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.