UserDefinedProperties.Add method (Outlook)

Creates a new UserDefinedProperty object and appends it to the collection.

Syntax

expression.Add (Name, Type, DisplayFormat, Formula)

expression A variable that represents a UserDefinedProperties object.

Parameters

Name Required/Optional Data type Description
Name Required String The name of the new user-defined property.
Type Required OlUserPropertyType The type of the new user-defined property.
DisplayFormat Optional Variant The display format of the new user-defined property. This parameter can be set to a value from one of several different enumerations, determined by the OlUserPropertyType constant specified in the Type parameter. For more information on how Type and DisplayFormat interact, see DisplayFormat Property.
Formula Optional Variant The formula used to calculate values for the new user-defined property. This parameter is ignored if the Type parameter is set to any value other than olCombination or olFormula.

Return value

A UserDefinedProperty object that represents the new user-defined property.

Remarks

You can create a property of a type that is defined by the OlUserPropertyType enumeration, except for the following types: olEnumeration, olOutlookInternal, and olSmartFrom.

Example

The following Visual Basic for Applications (VBA) example uses the Add method to create and add several UserDefinedProperty objects to the Inbox default folder.

Sub AddStatusProperties() 
 Dim objNamespace As NameSpace 
 Dim objFolder As Folder 
 Dim objProperty As UserDefinedProperty 
 
 ' Obtain a Folder object reference to the 
 ' Inbox default folder. 
 Set objNamespace = Application.GetNamespace("MAPI") 
 Set objFolder = objNamespace.GetDefaultFolder(olFolderInbox) 
 
 ' Add five user-defined properties, used to identify and 
 ' track customer issues. 
 With objFolder.UserDefinedProperties 
 Set objProperty = .Add("Issue?", olYesNo, olFormatYesNoIcon) 
 Set objProperty = .Add("Issue Research Time", olDuration) 
 Set objProperty = .Add("Issue Resolution Time", olDuration) 
 Set objProperty = .Add("Customer Follow-Up", olYesNo, olFormatYesNoYesNo) 
 Set objProperty = .Add("Issue Closed", olYesNo, olFormatYesNoYesNo) 
 End With 
End Sub

See also

UserDefinedProperties Object

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.