Partager via


Objet CalendarSharing (Outlook)

Représente un ensemble d’utilitaires pour le partage d’informations de calendrier.

Remarques

Utilisez la méthode GetCalendarExporter d’un objet Folder qui représente un dossier de calendrier pour créer un objet CalendarSharing . La méthode GetCalendarExporter peut être utilisée uniquement avec les dossiers de calendrier. Si vous utilisez cette méthode avec des objets Folder représentant d’autres types de dossiers, une erreur est générée.

Utilisez la méthode SaveAsICal pour enregistrer les informations de calendrier dans un fichier iCalendar (.ics) afin de partager un calendrier en tant qu’URL, ou utilisez la méthode ForwardAsICal pour créer un objet MailItem permettant de partager un calendrier en tant que charge utile.

Remarque

L’objet CalendarSharing prend uniquement en charge l’exportation du format de fichier iCalendar.

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 
 
 .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éthodes

Nom
ForwardAsICal
SaveAsICal

Propriétés

Nom
Application
CalendarDetail
Class
EndDate
Folder
IncludeAttachments
IncludePrivateDetails
IncludeWholeCalendar
Parent
RestrictToWorkingHours
Session
StartDate

Voir aussi

Référence du modèle objet Outlook

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.