Recipient.Resolved property (Outlook)

Returns a Boolean that indicates True if the recipient has been validated against the Address Book. Read-only.

Syntax

expression. Resolved

expression A variable that represents a 'Recipient' object.

Remarks

If similar names exist for a recipient in an Address Book, you can resolve the recipient by specifying the recipient's full SMTP email address.

Example

This Visual Basic for Applications (VBA) example uses the Resolve method to resolve the Recipient object representing Dan Wilson, and then returns Dan's shared default Calendar folder.

Sub ResolveName() 
 
 Dim myNamespace As Outlook.NameSpace 
 
 Dim myRecipient As Outlook.Recipient 
 
 Dim CalendarFolder As Outlook.Folder 
 
 
 
 Set myNamespace = Application.GetNamespace("MAPI") 
 
 Set myRecipient = myNamespace.CreateRecipient("Dan Wilson") 
 
 myRecipient.Resolve 
 
 If myRecipient.Resolved Then 
 
 Call ShowCalendar(myNamespace, myRecipient) 
 
 End If 
 
End Sub 
 
 
 
Sub ShowCalendar(myNamespace, myRecipient) 
 
 Dim CalendarFolder As Outlook.Folder 
 
 Set CalendarFolder = _ 
 
 myNamespace.GetSharedDefaultFolder _ 
 
 (myRecipient, olFolderCalendar) 
 
 CalendarFolder.Display 
 
End Sub

See also

Recipient 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.