Category.ShortcutKey-Eigenschaft (Outlook)
Gibt eine OlCategoryShortcutKey -Konstante zurück, die die vom Category -Objekt verwendete Tastenkombination angibt, oder legt die Konstante fest. Lese-/Schreibzugriff.
Syntax
Ausdruck. ShortcutKey
Ausdruck Eine Variable, die ein Category-Objekt darstellt.
Hinweise
Eine beliebige andere OlCategoryShortcutKeyNoneOlCategoryShortcutKey -Konstante kann nur durch ein Category -Objekt zu einem bestimmten Zeitpunkt verwendet werden. Festlegen des Werts dieser Eigenschaft auf eine Konstante OlCategoryShortcutKey bereits in Verwendung legt die ShortcutKey -Eigenschaft des Category -Objekts, das den angegebenen Wert in OlCategoryShortcutKeyNone bereits verwendet.
Beispiel
Im folgende Visual Basic für Applikationen (VBA) zeigt ein Dialogfeld mit Zuweisungen der Tastenkombination für jedes Category -Objekts in der NameSpace -Standardobjekt zugeordnet Categories -Auflistung enthalten sind.
Private Sub ListShortcutKeys()
Dim objNameSpace As NameSpace
Dim objCategory As Category
Dim strOutput As String
' Obtain a NameSpace object reference.
Set objNameSpace = Application.GetNamespace("MAPI")
' Check if the Categories collection for the Namespace
' contains one or more Category objects.
If objNameSpace.Categories.Count > 0 Then
' Enumerate the Categories collection, checking
' the value of the ShortcutKey property for
' each Category object.
For Each objCategory In objNameSpace.Categories
' Add the name of the Category object to
' the output string.
strOutput = strOutput & objCategory.Name
' Add information about the assigned shortcut key
' to the output string.
Select Case objCategory.ShortcutKey
Case OlCategoryShortcutKey.olCategoryShortcutKeyNone
strOutput = strOutput & ": No shortcut key" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF2
strOutput = strOutput & ": Ctrl+F2" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF3
strOutput = strOutput & ": Ctrl+F3" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF4
strOutput = strOutput & ": Ctrl+F4" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF5
strOutput = strOutput & ": Ctrl+F5" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF6
strOutput = strOutput & ": Ctrl+F6" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF7
strOutput = strOutput & ": Ctrl+F7" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF8
strOutput = strOutput & ": Ctrl+F8" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF9
strOutput = strOutput & ": Ctrl+F9" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF10
strOutput = strOutput & ": Ctrl+F10" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF11
strOutput = strOutput & ": Ctrl+F11" & vbCrLf
Case OlCategoryShortcutKey.olCategoryShortcutKeyCtrlF12
strOutput = strOutput & ": Ctrl+F12" & vbCrLf
Case Else
strOutput = strOutput & ": Unknown" & vbCrLf
End Select
Next
End If
' Display the output string.
MsgBox strOutput
' Clean up.
Set objCategory = Nothing
Set objNameSpace = Nothing
End Sub
Siehe auch
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.