Consulting

Page 1 of 2 1 2 LastLast
Results 1 to 20 of 22

Thread: VBA ListBox List - Want only selected columns to be displayed

  1. #1

    VBA ListBox List - Want only selected columns to be displayed

    Hi All,

    ListBox1.ColumnCount = 4
    ListBox1.ColumnWidths = "25;120;60;80"
    Me.ListBox1.list = Sheets("Sheet1").Range("A2:AF100").Value

    My data range is ("A2:BB100)
    Here in this list box, I want only 2 columns (Column A and Column AF)
    Can anybody help me to solve this,

    Thanks - Jamshad

  2. #2
    VBAX Guru mancubus's Avatar
    Joined
    Dec 2010
    Location
    "Where I lay my head is home" :D
    Posts
    2,644
    Col A's index is 1 and Col AF's index is 32
    A2:BB100 is a 99-rows table

    Private Sub UserForm_Initialize()
    
        sn = Range("A2:BB100").Value
        sp = Application.Index(sn, [Row(1:99)], Array(1, 32))
        'http://www.snb-vba.eu/VBA_Arrays_en.html#L_0
        'Title 6.7.1
        
        With ListBox1
            .ColumnCount = 4
            .ColumnWidths = "25;120;60;80"
            .List = sp
        End With
    
    End Sub
    PLS DO NOT PM; OPEN A THREAD INSTEAD!!!

    1) Posting Code
    [CODE]PasteYourCodeHere[/CODE]
    (or paste your code, select it, click # button)

    2) Uploading File(s)
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) (multiple files can be selected while holding Ctrl key) / Upload Files / Done
    Replace company specific / sensitive / confidential data. Include so many rows and sheets etc in the uploaded workbook to enable the helpers visualize the data and table structure. Helpers do not need the entire workbook.

    3) Testing the Codes
    always back up your files before testing the codes.

    4) Marking the Thread as Solved
    from Thread Tools (on the top right corner, above the first message)

  3. #3
    Woow.. Thanks. Its working

  4. #4
    VBAX Tutor MINCUS1308's Avatar
    Joined
    Jun 2014
    Location
    UNDER MY DESK
    Posts
    254
    woow is right. mancubus and other Masters do some truly amazing things with code.
    Welcome to the forum vmjamshad!
    If you could, would you please mark this thread as solved for us?
    I believe at the upper right corner of the thread there is a 'Thread Tools' drop down.
    There should be a 'Mark as Solved' option.
    - I HAVE NO IDEA WHAT I'M DOING

  5. #5
    VBAX Guru mancubus's Avatar
    Joined
    Dec 2010
    Location
    "Where I lay my head is home" :D
    Posts
    2,644
    your are welcome.

    credits go to snb... the link to the source is included in the code.


    @jamshad
    pls mark the thread as solved (see my signature) for future references...
    PLS DO NOT PM; OPEN A THREAD INSTEAD!!!

    1) Posting Code
    [CODE]PasteYourCodeHere[/CODE]
    (or paste your code, select it, click # button)

    2) Uploading File(s)
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) (multiple files can be selected while holding Ctrl key) / Upload Files / Done
    Replace company specific / sensitive / confidential data. Include so many rows and sheets etc in the uploaded workbook to enable the helpers visualize the data and table structure. Helpers do not need the entire workbook.

    3) Testing the Codes
    always back up your files before testing the codes.

    4) Marking the Thread as Solved
    from Thread Tools (on the top right corner, above the first message)

  6. #6
    Dear - I have one more doubt. Can i apply variable to the row. [Row(1:99)] - [Row(1:a)] and a will be the last row of the column. The reason behind that is there will be addition and deletion to the file. So the row end number will keep changing.

    Hope that my question is clear

    Thanks

  7. #7
    VBAX Tutor MINCUS1308's Avatar
    Joined
    Jun 2014
    Location
    UNDER MY DESK
    Posts
    254
    Seems to work. Go for it.
    Sub testing()
         a = 99
         sp = Application.Index(sn, [Row(1:a)], Array(1, 32))
    End Sub
    - I HAVE NO IDEA WHAT I'M DOING

  8. #8
    VBAX Tutor MINCUS1308's Avatar
    Joined
    Jun 2014
    Location
    UNDER MY DESK
    Posts
    254
    if you want to set the variable to the last used column you can use
    a =ActiveSheet.UsedRange.Columns.Count
    but it is prone to error. maybe someone else has a better method
    - I HAVE NO IDEA WHAT I'M DOING

  9. #9
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,724
    Location
    @MINCUS1308 -- you need to change your sig - it's obviously wrong, since you do know what you're doing -- don't be humble
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  10. #10
    VBAX Tutor MINCUS1308's Avatar
    Joined
    Jun 2014
    Location
    UNDER MY DESK
    Posts
    254
    Yeah.. I maxed out my post number at 999,999. so I had to reset my user account. Now I have to climb my way back through the ranks

    I fumble my way through a lot of code. But thank you Paul_Hossler
    - I HAVE NO IDEA WHAT I'M DOING

  11. #11
    Thanks MINCUS1308 .. I tried that, but got some error. Thanks Jamshad

  12. #12
    VBAX Tutor MINCUS1308's Avatar
    Joined
    Jun 2014
    Location
    UNDER MY DESK
    Posts
    254
    that's unfortunate. can you describe the error or post a screen shot ? maybe post your file?
    - I HAVE NO IDEA WHAT I'M DOING

  13. #13

    VBA ListBox List - Want only selected columns to be displayed - WITH ATTACHMENT

    I have attached the file.
    Attached Files Attached Files

  14. #14
    VBAX Guru mancubus's Avatar
    Joined
    Dec 2010
    Location
    "Where I lay my head is home" :D
    Posts
    2,644
    Private Sub UserForm_Initialize()
           
        With Worksheets("Sheet1")
            With .Range("B6:MX" & .Cells(Rows.Count, 1).End(xlUp).Row - 1)
                sn = .Value
                sp = Application.Index(sn, Evaluate("Row(" & .Offset(-5).Address & ")"), Array(1, 2))
            End With
        End With
            
        With ListBox1
            .ColumnCount = 7
            .ColumnWidths = "180;180;160;0;25;0;30"
            .list = sp
        End With
    
    End Sub


    1) think about Offset(-5). (why did i add that bit?)

    2) homework: VBA Evaluate Method (Google it. there are many valuable online resources.)
    PLS DO NOT PM; OPEN A THREAD INSTEAD!!!

    1) Posting Code
    [CODE]PasteYourCodeHere[/CODE]
    (or paste your code, select it, click # button)

    2) Uploading File(s)
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) (multiple files can be selected while holding Ctrl key) / Upload Files / Done
    Replace company specific / sensitive / confidential data. Include so many rows and sheets etc in the uploaded workbook to enable the helpers visualize the data and table structure. Helpers do not need the entire workbook.

    3) Testing the Codes
    always back up your files before testing the codes.

    4) Marking the Thread as Solved
    from Thread Tools (on the top right corner, above the first message)

  15. #15
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,638
    What's the use reading many columns if you only need the first 2 ? :array(1,2)

    Private Sub UserForm_Initialize()
      With ListBox1
        .list = Sheet1.Cells(1).CurrentRegion.Offset(5, 1).Resize(, 1).SpecialCells(2).Resize(, 2).Value
        .ColumnCount = 2
        .ColumnWidths = "180;180"
      End With
    End sub
    If you want the first and the last column of a certain range to be part of - and to be shown in- a ListBox, you could use:

    Private Sub Userform_initialize()
      With ListBox1
        .list = Sheet1.Cells(1).CurrentRegion.Offset(5, 1).Resize(, 1).SpecialCells(2).Resize(, 4).Value
        .list = Application.Index(.list, Evaluate("row(1:" & .ListCount & ")"), Array(1, UBound(.list, 2)))
        .ColumnCount = 2
        .ColumnWidths = "180;180"
      End With
    End Sub

  16. #16
    Thanks. actually my file has more than 400 columns. From that i will select maximum of 10-12 columns which i will show in the list box.that is the reason why i am looking for array

  17. #17
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,638
    Adapt to your needs

    For Example: if you want columns 1,11,21,31,41,51,61,71,81,91 to be displayed:

    Private Sub Userform_initialize() 
      With ListBox1 
        .list = Sheet1.Cells(1).CurrentRegion.Offset(5, 1).Resize(, 1).SpecialCells(2).Resize(, 400).Value 
        .list = Application.Index(.list, Evaluate("row(1:" & .ListCount & ")"), Array(1,11,21,31,41,51,61,71,81,91)) 
        .ColumnCount = ubound(.list,2)+1 
        .ColumnWidths = mid(replace(space(.columncount)," ",";180"),2)
      End With 
    End Sub

  18. #18
    Hi, I used the below code:

    Private Sub UserForm_Initialize()
    With ListBox1
    .ColumnCount = 4
    .ColumnWidths = "130;30;30;130"
    End With


    LstRow = Cells(Rows.Count, 1).End(xlUp).Row
    For a = 0 To LstRow - 2
    b = a + 2
    ListBox1.AddItem
    ListBox1.list(a, 0) = Cells(b, 4)
    ListBox1.list(a, 1) = Cells(b, 1)
    ListBox1.list(a, 2) = Cells(b, 3)
    ListBox1.list(a, 3) = Cells(b, 2)


    Next a


    End Sub
    Please suggest if any changes to be made.
    Thanks.

  19. #19
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,638
    Please use code tags !!

  20. #20
    You meant for the column and cell numbers, Right?
    Quote Originally Posted by snb View Post
    Please use code tags !!

Tags for this Thread

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •