ListBox (lsb)

microsoft excel docsListBox - This control allows the user to select from a list of possible choices.

microsoft excel docs

ListBox vs ComboBox

A listbox only lets you choose from a pre-defined list. You cannot type/enter a different value.
A combobox allows the user to either select an item from a drop-down list or to enter a different value into the textbox.


Adding to single column

You can use the "AddItem" method when you have a single column listbox.
If you try to add items to a listbox that has a non empty RowSource property you will get a "permission denied" error.

lsbListBox1.AddItem "Item 1" 
lsbListBox1.AddItem "Item 2"

Currently Selected Item

Obtaining the currently selected item in a single selection list box

Call MsgBox (lsbListBox1.Value) 
Call MsgBox (lsbListBox1.List(lsbListBox1.ListIndex))

Multiple Columns

A listbox can contain multiple columns by using the ColumnCount property.
You can use the "AddItem" combined with the List property when you have multiple columns.
All list entries start with a row number of 0, and a column number of 0, ie List(0,0) = "text"
If you want to add items to a multi column listbox, you need to use "AddItem" to add a new row and then either "List" or "Column" to add the specific items past the first column.

Dim iCount As Integer 
lsbListBox1.ColumnCount = 3
lsbListBox1.ColumnWidths = "50,50,50"
For icount = 1 to 25
   lsbListBox1.AddItem
   lsbListBox1.List(iCount - 1, 0) = "Item " & iCount
   lsbListBox1.List(iCount - 1, 1) = "Item " & iCount
   lsbListBox1.List(iCount - 1, 2) = "Item " & iCount
Next iCount

Both column and row numbers in a listbox start at 0 by default and not 1.
The only way to obtain the selected items in a multiple selection list box is to cycle through the whole list.

Dim iCount As Integer 
For iCount = 0 To lsbListBox1.ListCount - 1
   If (lsbListBox1.Selected(iCount) = True) Then
      Call MsgBox(lsbListBox1.List(iCount))
   End If
Next icount

Adding using an Array

If you data is stored in a one-dimensional array you can assign the array directly using the List property.

Dim iCount As Integer 
Dim vDataArray1(100)
For iCount = 0 to 100
   vDataArray1(iCount) = iCount
Next iCount
lsbListBox1.List = vDataArray1

If you data is stored in a two-dimensional array you can assign the array directly using the List property.

lsbListBox1.ColumnCount = 2 
lsbListBox1.ColumnWidths = "50,50"
Dim iCount As Integer
Dim vDataArray2(1 To 50, 1 To 2)
For iCount = 1 to 50
   vDataArray2(iCount, 1) = iCount
   vDataArray2(iCount, 2) = iCount & "b"
Next iCount
lsbListBox1.List = vDataArray2

Removing Selected

This will remove the currently selected item

lsbListBox1.Remove(lsbListBox.ListIndex) 

More than 10 Columns

If you want to have more than 10 columns in your listbox then you must use the List Property.

microsoft excel docs
Private Sub UserForm_Initialize() 
Dim myArray() As String
Dim iRow As Integer
Dim iCol As Integer
    ReDim myArray(1 To 5, 1 To 13)
    iRow = 1
    While (iRow < 6)
         lsbListBox1.AddItem
         For iCol = 1 To 13
             myArray(iRow, iCol) = "Col" & iCol
         Next iCol
         iRow = iRow + 1
    Wend
    lsbListBox1.ColumnHeads = True
    lsbListBox1.ColumnCount = 13
    lsbListBox1.ColumnWidths = "50,50,50,50,50,50,50,50,50,50,50,50,50"
    lsbListBox1.List = myArray
End Sub

TextColumn

This property allows you to display one set of values to the user but return a different value when selection has been made.
Use the Text property to return the column specified in the TextBound column.
If you use the Value property you will always get the item in the first column.


BoundColumn

The BoundColumn property identifies which column is referenced when you refer to the Value property of a listbox entry.


No items selected

It is possible to display a listbox with no items selected (when the listindex = -1).
Although once an item is selected it is not possible to unselect all the items.


Multiple selections

By default only a single item can be selected although this can be changed by changing the MultiSelect property.
You can only make multiple selections with a listbox - not a combo box.

lsbListBox1.MultiSelect = fmMultiSelectMulti 

RowSource

The items in a Listbox can be retrieved from an Excel range of cells by using the RowSource property.
Make sure you include the worksheet name otherwise the active sheet will be used.

lsbListBox1.RowSource = "Sheet1!A1:A12" 

If you populate a listbox using the RowSource method you then can't populate a second listbox using the "List" method.
If you populate a listbox using the RowSource method you cannot use the RemoveItem method.


Adding Column Headers

You can only display column headers when you use the RowSource property, not when you use an array or add items individually.
To display column headers set the ColumnHeads property to True.
Do not include the column headings on the worksheet in the range defined for RowSource.
The row directly above the first row of the RowSource will be automatically used.


Adding Unique Items

You should add all the items to a collection ensuring that only unique items get added and then add all the items from the collection to the listbox.

Dim objCell As Range 
Dim colNoDuplicates As New Collection
Dim vItem As Variant

On Error Resume Next
For Each objCell In Range("A1:A12")
   colNoDuplicates.Add objCell.Value, CStr(objCell.Value)
Next objCell
For Each vItem In colNoDuplicates
   UserForm1.lsbListBox1.AddItem vItem
Next vItem
UserForm1.Show

It might also be worth sorting the collection before you add it to the listbox.


lsbListBox1.Top 
lsbListBox1.TakeFocusOnClick = False

Change the Integral Height to False and a line is roughly 13.42
Arial, 10, Regular
It is possible to have a drop-down listbox - change the property - doesn't have to be a combo box !!
It is possible to display equally spaced items in a list box by using a monospaced font such as Courier New. A better approach is to use multiple columns.
Do you have to populate a listbox with data to be able to assign an array to it ???? I DON'T THINK YOU DO !!
The vertical height of a listbox in design mode may not be the same height when the userform is actually displayed.


Properties

BackColorSpecifies the background color of the object.
BorderColorSpecifies the color of an object's border.
BorderStyleSpecifies the type of border used.
BoundColumnIdentifies the source of data in a multicolumn ListBox.
Cancel(excluded from Properties window)
ColumnProvides a reference to a specific column when you have a multiple column listbox.
ColumnCountSpecifies the number of columns to display in a list box.
ColumnHeadsDisplays a single row of column headings for list boxes.
ColumnWidthsSpecifies the width of each column in a multicolumn list box. Including the "pt" is optional.
ControlSourceIdentifies the data location used to set or store the Value property of a control. The ControlSource property accepts worksheet ranges from Microsoft Excel.
ControlTipTextSpecifies text that appears when the user briefly holds the mouse pointer over a control without clicking.
Default(excluded from Properties window)
EnabledSpecifies whether a control can receive the focus and respond to user-generated events.
FontDefines the characteristics of the text used by a control.
ForeColorSpecifies the foreground color of an object
Height 
IMEModeSpecifies the default run time mode of the Input Method Editor (IME) for a control. This property applies only to applications written for the Far East and is ignored in other applications.
IntegralHeightIndicates whether a ListBox or TextBox displays full lines of text in a list or partial lines.
LayoutEffect(excluded from Properties window)
Left 
List(excluded from Properties window)
ListCount(excluded from Properties window) (read-only) Returns the number of items in the listbox.
ListIndex(excluded from Properties window) Specifies which item is selected in the listbox. This is an integer from 0 to the total number of items minus 1.
ListStyleSpecifies the visual appearance of the list in a ListBox , either frmListStylePlain or fmListStyleOption. If you have a listbox which has its liststyle set to option, then to remove the horizontal scrollbar, change to columnwidths property to the width - 16.
LockedSpecifies whether a control can be edited.
MatchEntryReturns or sets a value indicating how a ListBox searches its list as the user types, either fmMatchEntryFirstLetter, fmMatchEntryComplete or fmMatchEntryNone
MouseIconAssigns a custom icon to an object.
MousePointerSpecifies the type of pointer displayed when the user positions the mouse over a particular object. Can be any of the fmMousePointer constants.
MultiSelectIndicates whether the object permits multiple selections.
RowSourceLinks the control to a range of cells on a worksheet. Avoid using
RowSourceType 
Selected(excluded from Properties window)
SpecialEffectSpecifies the visual appearance of an object. Can be any of the fmSpecialEffect constants.
TabIndex 
TabStop 
TextChanges the selected row in a ListBox.
TextAlignSpecifies how text is aligned in a control. Can be any of the fmTextAlign constants.
TextColumnIdentifies the column in a ListBox to store in the Text property when the user selects a row.
TopIndex 
ValueSpecifies the state or content of a given control. This is the value in the BoundColumn.
Width 

Methods

AddItem 
Clear 
Move 
RemoveItem 
SetFocus 
ZOrder 

Events

AfterUpdateFires each time the listbox selection changes. This does not fire unless the listbox has its Multi-Select set to Single.
BeforeDragOver 
BeforeDropOrPaste 
BeforeUpdate 
Change 
ClickThis does not fire unless the list box has its MultiSelect set to Single. In VB.NET this has been replaced with the SelectedIndexChanged and CheckStateChanged events.
DblClickIn VB.NET this has been replaced with the SelectionIndexChanged and TextChanged events.
Enter 
Error 
Exit 
KeyDown 
KeyPress 
KeyUp 
Layout 
MouseDown 
MouseMove 
MouseUp 
ValidateIn VB.NET this has been replaced with the Validating event.

© 2024 Better Solutions Limited. All Rights Reserved. © 2024 Better Solutions Limited TopPrevNext