Método NameSpace.CompareEntryIDs (Outlook)
Devuelve un valor booleano que indica si dos valores de identificador de entrada hacen referencia al mismo elemento de Outlook.
Sintaxis
expresión. CompareEntryIDs
( _FirstEntryID_
, _SecondEntryID_
)
Expresión Expresión que devuelve un objeto NameSpace .
Parameters
Nombre | Obligatorio/opcional | Tipo de datos | Descripción |
---|---|---|---|
FirstEntryID | Obligatorio | String | Primer Id. de entrada que se desea comparar. |
SecondEntryID | Obligatorio | String | Segundo Id. de entrada que se desea comparar. |
Valor devuelto
True si los valores de identificador de entrada hacen referencia al mismo elemento de Outlook; de lo contrario, False.
Comentarios
Los identificadores de entrada no pueden compararse directamente porque un objeto puede estar representado por dos valores binarios distintos. Use este método para determinar si dos identificadores de entrada representan el mismo objeto.
Ejemplo:
El ejemplo siguiente Visual Basic para aplicaciones (VBA) se compara el identificador de entrada asociado al organizador de un objeto AppointmentItem especificado con el identificador de entrada de un objeto Recipient especificado, utilizando el método CompareEntryIDs y devuelve True si el organizador y el destinatario especificado representan el mismo usuario.
Function IsRecipientTheOrganizer( _
ByVal Appt As Outlook.AppointmentItem, _
ByVal Recipient As Outlook.Recipient) As Boolean
Dim objAddrEntry As Outlook.AddressEntry
Dim objPropAc As Outlook.PropertyAccessor
Dim strOrganizerEntryId As String
Dim bytResult() As Byte
Dim objRecipientUser As Outlook.ExchangeUser
Dim objOrganizerUser As Outlook.ExchangeUser
Dim blnReturn As Boolean
'Property tag for Organizer EntryID
Const PR_SENT_REPRESENTING_ENTRYID As String = _
"http://schemas.microsoft.com/mapi/proptag/0x00410102"
' Retrieve an AddressEntry object reference for the
' specified recipient.
Set objAddrEntry = Recipient.AddressEntry
' If the address entry represents an Exchange user
' or Exchange remote user, retrieve an
' ExchangeUser object reference for the sender and
' compare the EntryID value of that object with
' the EntryID of the specified recipient.
If objAddrEntry.AddressEntryUserType = _
OlAddressEntryUserType.olExchangeUserAddressEntry _
Or objAddrEntry.AddressEntryUserType = _
OlAddressEntryUserType.olExchangeRemoteUserAddressEntry Then
' Attempt to retrieve an ExchangeUser
' object reference for the specified
' recipient.
Set objRecipientUser = objAddrEntry.GetExchangeUser()
If objRecipientUser Is Nothing Then
' An Exchange user could not be retrieved
' for the specified recipient.
blnReturn = False
Else
' Retrieve the EntryID property value of the organizer.
' The Organizer property of the AppointmentItem object only
' contains a string representation of the name of the
' organizer, so the PR_SENT_REPRESENTING_ENTRYID property value
' is instead retrieved, using the PropertyAccessor object
' associated with the appointment item.
Set objPropAc = Appt.PropertyAccessor
bytResult = objPropAc.GetProperty( _
PR_SENT_REPRESENTING_ENTRYID)
If Not IsEmpty(bytResult) Then
' Convert the binary value retrieved from the
' PR_SENT_REPRESENTING_ENTRYID property into
' a string value for comparison.
strOrganizerEntryId = _
objPropAc.BinaryToString(bytResult)
' Attempt to retrieve an ExchangeUser
' object reference for the organizer.
Set objOrganizerUser = Appt.Application.Session. _
GetAddressEntryFromID(strOrganizerEntryId).GetExchangeUser()
If objOrganizerUser Is Nothing Then
' An Exchange user could not be retrieved
' for the organizer.
blnReturn = False
Else
' Compare the EntryIDs of the organizer
' and the specified recipient.
blnReturn = Appt.Application.Session. _
CompareEntryIDs( _
objRecipientUser.ID, _
objOrganizerUser.ID)
End If
End If
End If
End If
EndRoutine:
' Clean up
Set objOrganizerUser = Nothing
Set objRecipientUser = Nothing
Set objAddrEntry = Nothing
Set objPropAc = Nothing
' Return the results.
IsRecipientTheOrganizer = blnReturn
Exit Function
ErrRoutine:
Debug.Print Err.Number & " - " & Err.Description, _
vbOKOnly Or vbCritical, _
"IsRecipientTheOrganizer"
GoTo EndRoutine
End Function
Consulte también
Soporte técnico y comentarios
¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.