Rules.Create-Methode (Outlook)

Erstellt ein Rule-Objekt mit dem durch Name angegebenen Namen und dem von RuleType angegebenen Regeltyp.

Syntax

Ausdruck. Create( _Name_ , _RuleType_ )

Ausdruck Eine Variable, die ein Rules-Objekt darstellt.

Parameter

Name Erforderlich/Optional Datentyp Beschreibung
Name Erforderlich String A string identifier for the rule, which will be represented by Rule.Name after rule creation. Names of rules in a collection are not unique.
RuleType Erforderlich OlRuleType Eine Konstante in der OlRuleType -Aufzählung, die bestimmt, ob die Regel auf das Senden oder Empfangen einer Nachricht angewendet wird.

Rückgabewert

Ein Rule -Objekt, das die neu erstellte Regel darstellt.

HinwBemerkungeneise

Der RuleType-Parameter der hinzugefügten Regel bestimmt gültige Regelaktionen, Regelbedingungen und Regel-Ausnahmebedingungen, die dem Rule-Objekt zugeordnet werden können.

Wenn eine Regel zur Auflistung hinzugefügt wird, ist die Rule.ExecutionOrder der neuen Regel 1. Die ExecutionOrder der anderen Regeln in der Auflistung wird um 1 erhöht.

Beispiel

Im folgenden Codebeispiel in Visual Basic for Applications (VBA) wird das Rules-Objektmodell verwendet, um eine Regel zu erstellen. In dem Codebeispiel wird mit den Objekten RuleAction und RuleCondition eine Regel angegeben, mit der Nachrichten eines bestimmten Absenders in einen bestimmten Ordner verschoben werden, es sei denn, in der Betreffzeile sind gewisse Begriffe enthalten. Beachten Sie, dass in dem Codebeispiel davon ausgegangen wird, dass der Posteingang bereits einen Unterordner "Dan" hat.

Sub CreateRule() 
 
 Dim colRules As Outlook.Rules 
 
 Dim oRule As Outlook.Rule 
 
 Dim colRuleActions As Outlook.RuleActions 
 
 Dim oMoveRuleAction As Outlook.MoveOrCopyRuleAction 
 
 Dim oFromCondition As Outlook.ToOrFromRuleCondition 
 
 Dim oExceptSubject As Outlook.TextRuleCondition 
 
 Dim oInbox As Outlook.Folder 
 
 Dim oMoveTarget As Outlook.Folder 
 
 
 
 'Specify target folder for rule move action 
 
 Set oInbox = Application.Session.GetDefaultFolder(olFolderInbox) 
 
 'Assume that target folder already exists 
 
 Set oMoveTarget = oInbox.Folders("Dan") 
 
 
 
 'Get Rules from Session.DefaultStore object 
 
 Set colRules = Application.Session.DefaultStore.GetRules() 
 
 
 
 'Create the rule by adding a Receive Rule to Rules collection 
 
 Set oRule = colRules.Create("Dan's rule", olRuleReceive) 
 
 
 
 'Specify the condition in a ToOrFromRuleCondition object 
 
 'Condition is if the message is sent by "DanWilson" 
 
 Set oFromCondition = oRule.Conditions.From 
 
 With oFromCondition 
 
 .Enabled = True 
 
 .Recipients.Add ("DanWilson") 
 
 .Recipients.ResolveAll 
 
 End With 
 
 
 
 'Specify the action in a MoveOrCopyRuleAction object 
 
 'Action is to move the message to the target folder 
 
 Set oMoveRuleAction = oRule.Actions.MoveToFolder 
 
 With oMoveRuleAction 
 
 .Enabled = True 
 
 .Folder = oMoveTarget 
 
 End With 
 
 
 
 'Specify the exception condition for the subject in a TextRuleCondition object 
 
 'Exception condition is if the subject contains "fun" or "chat" 
 
 Set oExceptSubject = _ 
 
 oRule.Exceptions.Subject 
 
 With oExceptSubject 
 
 .Enabled = True 
 
 .Text = Array("fun", "chat") 
 
 End With 
 
 
 
 'Update the server and display progress dialog 
 
 colRules.Save 
 
End Sub

Siehe auch

Rules-Objekt

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.