WebListBox.MultiSelect property (Publisher)

Specifies whether a user may select more than one item in a web list box control. Read/write.

Syntax

expression.MultiSelect

expression A variable that represents a WebListBox object.

Return value

MsoTriState

Remarks

The MultiSelect property value can be one of the MsoTriState constants declared in the Microsoft Office type library and shown in the following table.

Constant Description
msoFalse Indicates that a user may only select one item in a web list box control.
msoTrue Indicates that a user may select more than one item in a web list box control.

Example

This example adds a web list box control to the active publication, adds items to it, and specifies that a user may select more than one item.

Sub NewListBoxItems() 
 Dim intCount As Integer 
 With ActiveDocument.Pages(1).Shapes.AddWebControl _ 
 (Type:=pbWebControlListBox, Left:=100, _ 
 Top:=100, Width:=150, Height:=100).WebListBox 
 .MultiSelect = msoTrue 
 With .ListBoxItems 
 For intCount = 1 To .Count 
 .Delete (1) 
 Next 
 .AddItem Item:="Yellow" 
 .AddItem Item:="Red" 
 .AddItem Item:="Blue" 
 .AddItem Item:="Green" 
 .AddItem Item:="Black" 
 End With 
 End With 
End Sub

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.