Search code examples
excelvbalistboxuserform

VBA Userform Listbox Conditional Logic Not Working as Intended


I have a Userform with a listbox for which I am using conditional logic to determine output values to the sheet of selected or non-selected items in the listbox. The issue is that when the Textbox (Tbl_AliasName) is blank, the code executes this:

ElseIf .Selected(k) = True And Tbl_AliasName = vbNullString Then
            lstbxRow = lstbxRow + 1

                Worksheets("New TRAX").Cells(lstbxRow, 3) = Trim(Cells(2, 1).Value2) & "." & .Column(1, k)

But if Tbl_AliasName is not blank then the code does nothing, but it is supposed to do this:

 ElseIf .Selected(k) = True And Tbl_AliasName <> vbNullString Then
            lstbxRow = lstbxRow + 1

                Worksheets("New TRAX").Cells(lstbxRow, 3) = Tbl_AliasName & "." & .Column(1, k)

I have used several variations of If statements, and non of which have worked.
Below is My Code:

Option Explicit
Public Tbl_AliasName As String
Tbl_AliasName = Trim(UserForm_Finder.txtConcat.Value)

Private Sub BtnConcat_Click()
Dim k As Long, lstbxRow As Long, LR As Long

lstbxRow = 1

 '****************
'This if statement works perfectly
If (Cells(2, 1).Value2 = vbNullString Or Cells(2, 2).Value2 = vbNullString) _
        And Tbl_AliasName = vbNullString Then

        MsgBox "You must Search for a Table or Column first.", _
        vbExclamation, "Error Encountered"

        Exit Sub

ElseIf (UserForm_Finder.ListBx_TblsCols.ListCount = 0 And Tbl_AliasName <> vbNullString) Then
        MsgBox "You must Search for a Table or Column first.", _
        vbExclamation, "Error Encountered"
        '(Cells(2, 1).Value2 = vbNullString Or Cells(2, 2).Value2 = vbNullString) And _

        Exit Sub

End If


With UserForm_Finder.ListBx_TblsCols
    For k = 0 To .ListCount - 1
        '****************
         This is where the problems begin
    If .Selected(k) = False Then
            MsgBox "You must Select 1 or more items from the list box.", _
            vbExclamation, "Error Encountered"
            Exit Sub

        ElseIf .Selected(k) = True And Tbl_AliasName <> vbNullString Then
            lstbxRow = lstbxRow + 1

                Worksheets("New TRAX").Cells(lstbxRow, 3) = Tbl_AliasName & "." & .Column(1, k)

        ElseIf .Selected(k) = True And Tbl_AliasName = vbNullString Then
            lstbxRow = lstbxRow + 1

                Worksheets("New TRAX").Cells(lstbxRow, 3) = Trim(Cells(2, 1).Value2) & "." & .Column(1, k)

        End If
    Next k
  End With
End Sub

My goal is to do the following:

  1. If a Textbox (Tbl_AliasName) is not blank and the user has selected one or more items in the listbox (ListBx_TbleCols) then concatenate the Tbl_AliasName to the selected items in the listbox
  2. If Tbl_AliasName is blank, then use the value in Cells(2,1) to concatenate to the selected Items in the list box.

I have tried the following additions:

Dim LstBxItemSelected As Boolean

'This was placed in the for loop
LstBxItemSelected = True

'this was placed outside the for loop
If LstBxItemSelected = False Then
      MsgBox "You must Select 1 or more items from the list box.", _
             vbExclamation, "Error Encountered"
      Exit Sub       
End If

Is there a better way to tell if items are selected, because I feel that the way I have it structured in my loop, the code will throw the error if everything isn't selected? Thank you in advance for any ideas, answers, or suggestions!

Note: The Listbox is populated by the click of another button on the userform which calls the following sub:

Sub FillLstBxCols()  

    Dim ListBx_Target As MSForms.ListBox
    Dim rngSource As Range
    Dim LR As Long

    If Cells(2, 1).Value2 <> vbNullString Then
        LR = Worksheets("New TRAX").Cells(Rows.Count, 2).End(xlUp).Row


        'Set reference to the range of data to be filled
        Set rngSource = Worksheets("New Trax").Range("A" & 2 & ":" & "B" & LR)

        'Fill the listbox
        Set ListBx_Target = UserForm_Finder.ListBx_TblsCols
        With ListBx_Target
            .RowSource = rngSource.Address
        End With
    End If
End Sub

Solution

  • Hard to say without sample data and expected results, but I think this is what you're looking for:

    Private Sub btnConcat_Click()
    
        Dim ws As Worksheet
        Dim bSelected As Boolean
        Dim sConcat As String
        Dim i As Long, lRowIndex As Long
    
        Set ws = ActiveWorkbook.Sheets("New TRAX")
        lRowIndex = 1
        bSelected = False
        sConcat = Trim(Me.txtConcat.Text)
        If Len(sConcat) = 0 Then sConcat = Trim(ws.Cells(2, "A").Value)
        If Len(sConcat) = 0 Then
            MsgBox "You must Search for a Table or Column first.", vbExclamation, "Error Encountered"
            Exit Sub
        End If
    
        For i = 0 To Me.ListBx_TblsCols.ListCount - 1
            If Me.ListBx_TblsCols.Selected(i) Then
                If bSelected = False Then
                    bSelected = True
                    ws.Range("C2", ws.Cells(ws.Rows.Count, "C")).Clear  'clear previous concat results (delete this line if not needed)
                End If
                lRowIndex = lRowIndex + 1
                ws.Cells(lRowIndex, "C").Value = sConcat & "." & Me.ListBx_TblsCols.List(i)
            End If
        Next i
    
        If bSelected = False Then MsgBox "Must select at least one item from the list"
    
    End Sub