Objeto CalendarSharing (Outlook)

Representa um conjunto de utilitários para compartilhamento de informações do calendário.

Comentários

Use o método GetCalendarExporter de um objeto Folder que representa uma pasta de calendário para criar um objeto CalendarSharing . O método GetCalendarExporter somente pode ser usado em pastas de calendário. Ocorrerá um erro se você usar o método em objetos Folder que representam os outros tipos de pasta.

Use o método SaveAsICal para salvar informações de calendário em um arquivo iCalendar (.ics) para compartilhar um calendário como URL ou usar o método ForwardAsICal para criar um MailItem para compartilhar um calendário como uma carga.

Observação

[!OBSERVAçãO] Objeto CalendarSharing só oferece suporte a exportação no formato iCalendar.

Exemplo

O seguinte exemplo Visual Basic for Applications (VBA) cria um objeto CalendarSharing para a pasta Calendário e exporta o conteúdo da pasta inteira (incluindo anexos e itens particulares) para um arquivo de iCalendar (. ICS) do calendário.

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

Nome
ForwardAsICal
SaveAsICal

Propriedades

Nome
Application
CalendarDetail
Classe
EndDate
Folder
IncludeAttachments
IncludePrivateDetails
IncludeWholeCalendar
Responsável
RestrictToWorkingHours
Sessão
StartDate

Confira também

Referência de modelo de objeto do Outlook

Suporte e comentários

Tem dúvidas ou quer enviar comentários sobre o VBA para Office ou sobre esta documentação? Confira Suporte e comentários sobre o VBA para Office a fim de obter orientação sobre as maneiras pelas quais você pode receber suporte e fornecer comentários.