MailItem.ReceivedOnBehalfOfEntryID property (Outlook)

Returns a String representing the EntryID of the user delegated to represent the recipient for the mail message. Read-only.

Syntax

expression. ReceivedOnBehalfOfEntryID

expression A variable that represents a MailItem object.

Remarks

This property corresponds to the MAPI property PidTagReceivedRepresentingEntryId.

If you are getting this property in a Microsoft Visual Basic or Microsoft Visual Basic for Applications (VBA) solution, owing to some type issues, instead of directly referencing ReceivedOnBehalfOfEntryID, you should get the property through the PropertyAccessor object returned by the MailItem.PropertyAccessor property, specifying the MAPI property PidTagReceivedRepresentingEntryId property and its MAPI proptag namespace. The following code sample in VBA shows the workaround.

Public Sub GetReceiverEntryID() 
 
 Dim objInbox As Outlook.Folder 
 
 Dim objMail As Outlook.MailItem 
 
 Dim oPA As Outlook.PropertyAccessor 
 
 Dim strEntryID As String 
 
 Const PidTagReceivedRepresentingEntryId As String = "http://schemas.microsoft.com/mapi/proptag/0x00430102" 
 
 
 
 Set objInbox = Application.Session.GetDefaultFolder(olFolderInbox) 
 
 Set objMail = objInbox.Items(1) 
 
 Set oPA = objMail.PropertyAccessor 
 
 strEntryID = oPA.BinaryToString(oPA.GetProperty(PidTagReceivedRepresentingEntryId)) 
 
 Debug.Print strEntryID 
 
 
 
 Set objInbox = Nothing 
 
 Set objMail = Nothing 
 
End Sub

See also

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