Método CalendarSharing.SaveAsICal (Outlook)
Exporta informações do calendário do objeto Folder pai do objeto CalendarSharing como um arquivo de calendário iCalendar (.ics).
Sintaxe
expression. SaveAsICal
( _Path_
)
Expressão Uma expressão que retorna um objeto CalendarSharing .
Parâmetros
Nome | Obrigatório/Opcional | Tipo de dados | Descrição |
---|---|---|---|
Path | Obrigatório | String | O caminho e o nome do arquivo iCalendar. |
Comentários
O nível de detalhes fornecidos no arquivo iCalendar é determinado por uma combinação dos valores na seguintes propriedades de CalendarSharing:
Você pode definir a propriedade IncludeWholeCalendar como True para exportar todos os itens contidos na pasta, ou você pode definir as propriedades StartDate e EndDate para limitar os itens exportados para um intervalo de datas entre uma data de início especificada e a data final, respectivamente.
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
.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
Confira também
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.