MeetingItem.GetAssociatedAppointment method (Outlook)

Returns an AppointmentItem object that represents the appointment associated with the meeting request.

Syntax

expression. GetAssociatedAppointment( _AddToCalendar_ )

expression A variable that represents a MeetingItem object.

Parameters

Name Required/Optional Data type Description
AddToCalendar Required Boolean True to add the meeting to the default Calendar folder.

Return value

An AppointmentItem object that represents the associated appointment.

Example

This Visual Basic for Applications (VBA) example finds a MeetingItem in the default Inbox folder that has not been responded to yet and adds the associated appointment to the Calendar folder. It then responds to the sender by accepting the meeting.

Sub AcceptMeeting() 
 
 Dim myNameSpace As Outlook.NameSpace 
 
 Dim myFolder As Outlook.Folder 
 
 Dim myMtgReq As Outlook.MeetingItem 
 
 Dim myAppt As Outlook.AppointmentItem 
 
 Dim myMtg As Outlook.MeetingItem 
 
 
 
 Set myNameSpace = Application.GetNamespace("MAPI") 
 
 Set myFolder = myNameSpace.GetDefaultFolder(olFolderInbox) 
 
 Set myMtgReq = myFolder.Items.Find("[MessageClass] = 'IPM.Schedule.Meeting.Request'") 
 
 If TypeName(myMtgReq) <> "Nothing" Then 
 
 Set myAppt = myMtgReq.GetAssociatedAppointment(True) 
 
 Set myMtg = myAppt.Respond(olResponseAccepted, True) 
 
 myMtg.Send 
 
 End If 
 
End Sub

See also

MeetingItem Object

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.