PropertyAccessor-Objekt (Outlook)
Bietet die Möglichkeit, Eigenschaften für Objekte zu erstellen, abzurufen, festzulegen und zu löschen.
HinwBemerkungeneise
Verwenden Sie das PropertyAccessor-Objekt , um Eigenschaften auf Elementebene abzurufen und festzulegen, die nicht explizit im Outlook-Objektmodell verfügbar gemacht werden, oder Eigenschaften für die folgenden Nichtelementobjekte: AddressEntry, AddressList, Attachment, ExchangeDistributionList, ExchangeUser, Folder, Recipient und Store.
Um mehrere benutzerdefinierte Eigenschaften abzurufen oder festzulegen, verwenden Sie das PropertyAccessor-Objekt anstelle des UserProperties-Objekts , um die Leistung zu verbessern.
Weitere Informationen zum Verwenden des PropertyAccessor-Objekts finden Sie unter Eigenschaften (Übersicht).
Beispiel
Im folgenden Codebeispiel wird veranschaulicht, wie die PropertyAccessor.GetProperty-Methode verwendet wird, um eine MAPI-Eigenschaft zu lesen, die zu einem MailItem gehört, aber nicht im Outlook-Objektmodell verfügbar gemacht wird , PR_TRANSPORT_MESSAGE_HEADERS.
Sub DemoPropertyAccessorGetProperty()
Dim PropName, Header As String
Dim oMail As Object
Dim oPA As Outlook.PropertyAccessor
'Get first item in the inbox
Set oMail = _
Application.Session.GetDefaultFolder(olFolderInbox).Items(1)
'PR_TRANSPORT_MESSAGE_HEADERS
PropName = "http://schemas.microsoft.com/mapi/proptag/0x007D001E"
'Obtain an instance of PropertyAccessor class
Set oPA = oMail.PropertyAccessor
'Call GetProperty
Header = oPA.GetProperty(PropName)
Debug.Print (Header)
End Sub
Im nächsten Codebeispiel wird veranschaulicht, wie die PropertyAccessor.SetProperties-Methode die Werte mehrerer Eigenschaften festlegt. Wenn eine Eigenschaft nicht vorhanden ist, wird die Eigenschaft durch SetProperties erstellt, solange das übergeordnete Objekt die Erstellung dieser Eigenschaften unterstützt. Wenn das Objekt eine explizite Save -Operation nicht unterstützt, werden die Eigenschaften im Objekt gespeichert, wenn die explizite Save -Operation aufgerufen wird. Wenn das Objekt eine explizite Save-Operation nicht unterstützt, werden die Eigenschaften im Objekt gespeichert, wenn SetProperties aufgerufen wird.
Sub DemoPropertyAccessorSetProperties()
Dim PropNames(), myValues() As Variant
Dim arrErrors As Variant
Dim prop1, prop2, prop3, prop4 As String
Dim i As Integer
Dim oMail As Outlook.MailItem
Dim oPA As Outlook.PropertyAccessor
'Get first item in the inbox
Set oMail = _
Application.Session.GetDefaultFolder(olFolderInbox).Items(1)
'Names for properties using the MAPI string namespace
prop1 = "http://schemas.microsoft.com/mapi/string/" & _
"{FFF40745-D92F-4C11-9E14-92701F001EB3}/mylongprop"
prop2 = "http://schemas.microsoft.com/mapi/string/" & _
"{FFF40745-D92F-4C11-9E14-92701F001EB3}/mystringprop"
prop3 = "http://schemas.microsoft.com/mapi/string/" & _
"{FFF40745-D92F-4C11-9E14-92701F001EB3}/mydateprop"
prop4 = "http://schemas.microsoft.com/mapi/string/" & _
"{FFF40745-D92F-4C11-9E14-92701F001EB3}/myboolprop"
PropNames = Array(prop1, prop2, prop3, prop4)
myValues = Array(1020, "111-222-Kudo", Now(), False)
'Set values with SetProperties call
'If the properties don't exist, then SetProperties
'adds the properties to the object when saved.
'The type of the property is the type of the element
'passed in myValues array.
Set oPA = oMail.PropertyAccessor
arrErrors = oPA.SetProperties(PropNames, myValues)
If Not (IsEmpty(arrErrors)) Then
'Examine the arrErrors array to determine if any
'elements contain errors
For i = LBound(arrErrors) To UBound(arrErrors)
'Examine the type of the element
If IsError(arrErrors(i)) Then
Debug.Print (CVErr(arrErrors(i)))
End If
Next
End If
'Save the item
oMail.Save
End Sub
Methoden
Name |
---|
BinaryToString |
DeleteProperties |
DeleteProperty |
GetProperties |
GetProperty |
LocalTimeToUTC |
SetProperties |
SetProperty |
StringToBinary |
UTCToLocalTime |
Eigenschaften
Name |
---|
Anwendung |
Klasse |
Parent |
Session |
Siehe auch
Outlook-ObjektmodellreferenzPropertyAccessor-Objektelemente
Support und Feedback
Haben Sie Fragen oder Feedback zu Office VBA oder zu dieser Dokumentation? Unter Office VBA-Support und Feedback finden Sie Hilfestellung zu den Möglichkeiten, wie Sie Support erhalten und Feedback abgeben können.