Outlook) (的 Selection.Item 方法
從選取範圍傳回 Microsoft Outlook 專案或交談標頭。
語法
運算式。專案 (索引)
表達 代表 'Selection' 物件的變數。
參數
名稱 | 必要/選用 | 資料類型 | 描述 |
---|---|---|---|
Index | 必要 | Variant | 物件的索引編號或是用來比對集合中物件之預設屬性的值。 |
傳回值
Object,表示指定的專案或交談標頭。
註解
請勿對 Item 方法傳回類型進行任何假設;您的程式碼應該能夠處理多個專案類型或 ConversationHeader 物件。 例如,Item方法可以根據Selection.Location屬性的值,傳回 [收件匣] 資料夾中的AppointmentItem、MailItem、MeetingItem或TaskItem。
只有當您在Selection物件的GetSelection方法中指定olConversationHeaders時,Selection集合才會包含ConversationHeader物件。
範例
下列 Microsoft Visual Basic for Applications (VBA) 範例會顯示使用中檔案總管內每個選取項目的寄件者。 它會使用Explorer.Selection屬性所傳回之Selection物件的Count屬性和Item方法,來顯示在使用中總管中選取之所有訊息的寄件者。
Sub GetSelectedItems()
Dim myOlExp As Outlook.Explorer
Dim myOlSel As Outlook.Selection
Dim mySender As Outlook.AddressEntry
Dim oMail As Outlook.MailItem
Dim oAppt As Outlook.AppointmentItem
Dim oPA As Outlook.PropertyAccessor
Dim strSenderID As String
Const PR_SENT_REPRESENTING_ENTRYID As String = _
"http://schemas.microsoft.com/mapi/proptag/0x00410102"
Dim MsgTxt As String
Dim x As Long
MsgTxt = "Senders of selected items:"
Set myOlExp = Application.ActiveExplorer
Set myOlSel = myOlExp.Selection
For x = 1 To myOlSel.Count
If myOlSel.Item(x).Class = OlObjectClass.olMail Then
' For mail item, use the SenderName property.
Set oMail = myOlSel.Item(x)
MsgTxt = MsgTxt & oMail.SenderName & ";"
ElseIf myOlSel.Item(x).Class = OlObjectClass.olAppointment Then
' For appointment item, use the Organizer property.
Set oAppt = myOlSel.Item(x)
MsgTxt = MsgTxt & oAppt.Organizer & ";"
Else
' For other items, use the property accessor to get sender ID,
' then get the address entry to display the sender name.
Set oPA = myOlSel.Item(x).PropertyAccessor
strSenderID = oPA.GetProperty(PR_SENT_REPRESENTING_ENTRYID)
Set mySender = Application.Session.GetAddressEntryFromID(strSenderID)
MsgTxt = MsgTxt & mySender.Name & ";"
End If
Next x
Debug.Print MsgTxt
End Sub
另請參閱
支援和意見反應
有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應。