Méthode CalendarSharing.SaveAsICal (Outlook)
Exporte les informations de calendrier à partir du dossier parent de l’objet CalendarSharing sous la forme d’un fichier de calendrier iCalendar (.ics).
Syntaxe
expression. SaveAsICal
( _Path_
)
Expression Expression qui renvoie un objet CalendarSharing .
Parameters
Nom | Requis/Facultatif | Type de données | Description |
---|---|---|---|
Path | Obligatoire | String | Chemin d’accès et nom de fichier du fichier iCalendar. |
Remarques
Le niveau de détail fourni dans le fichier iCalendar est déterminé par une combinaison de valeurs dans les propriétés CalendarSharing suivantes :
Vous pouvez définir la propriété IncludeWholeCalendar sur True pour exporter tous les éléments contenus dans le dossier, ou vous pouvez définir les propriétés StartDate et EndDate pour limiter les éléments exportés à une plage de dates comprise entre une date de début et une date de fin spécifiées, respectivement.
Exemple
L’exemple Visual Basic pour Applications (VBA) suivant crée un objet CalendarSharing pour le dossier Calendar, puis exporte le contenu de l’ensemble du dossier (y compris les pièces jointes et les éléments privés) dans un fichier de calendrier 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
Voir aussi
Assistance et commentaires
Avez-vous des questions ou des commentaires sur Office VBA ou sur cette documentation ? Consultez la rubrique concernant l’assistance pour Office VBA et l’envoi de commentaires afin d’obtenir des instructions pour recevoir une assistance et envoyer vos commentaires.