发送日历的共享邀请
共享邮件(包括共享邀请、共享请求和共享响应)在 Microsoft Outlook 中由 SharingItem 对象表示。 NameSpace 对象的 CreateSharingItem 方法用于创建 SharingItem 对象,用于共享邀请和共享请求。
本示例将使用 OpenSharingItem 方法来创建一个 SharingItem,该对象代表您的“日历”默认文件夹的共享邀请。 共享后,收件人可以使用 NameSpace 对象的 OpenSharedFolder 或 GetSharedDefaultFolder 方法或 SharingItem 对象的 OpenSharedFolder 方法打开共享文件夹。
该示例通过使用 NameSpace 对象的 GetDefaultFolder 方法获取当前用户的 Calendar 默认文件夹的 Folder 对象引用。
之后,本示例使用 CreateSharingItem 方法创建一个新的 SharingItem 对象,并使用 Folder 对象建立该 SharingItem 使用的共享上下文。
最后,调用新创建的 SharingItem 对象的 Recipients 集合的 Add 方法以添加指定的收件人,并使用 Send 方法发送 SharingItem。
Public Sub ShareCalendarByInvitation()
Dim oNamespace As NameSpace
Dim oFolder As Folder
Dim oSharingItem As SharingItem
On Error GoTo ErrRoutine
' Get a reference to the Calendar default folder
Set oNamespace = Application.GetNamespace("MAPI")
Set oFolder = oNamespace.GetDefaultFolder(olFolderCalendar)
' Create a new sharing invitation, using the Calendar
' default folder to establish sharing context.
Set oSharingItem = oNamespace.CreateSharingItem(oFolder)
' Add a recipient to the Recipients collection of
' the sharing invitation.
oSharingItem.Recipients.Add "someone@example.com"
' Send the sharing invitation.
oSharingItem.Send
EndRoutine:
On Error GoTo 0
Set oSharingItem = 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 -313393143 ' &HED520009
' This error typically occurs if you set the
' AllowWriteAccess property of a SharingItem
' to True when sharing a default folder.
MsgBox Err.Description, _
vbOKOnly, _
Err.Number & " - " & Err.Source
Case -2147467259 ' &H80004005
' This error typically occurs if the SharingItem
' cannot be sent because of incorrect or
' conflicting property settings.
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
支持和反馈
有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。