将列 Headers 转换为 VBA/Excel 中 ComboBox 的列表条目

Convert Column Headers to List Entries of a ComboBox in VBA/Excel

我在用户窗体上有一个组合框,我想用值列表填充它。

这些值位于一系列列的中间,可以将其视为列 headers,因为每个值都在自己的列中。随着时间的推移,列列表将 扩展 并且应该在每次初始化用户表单时更新。我已经能够从单列创建一个列表,我也可以从多列创建一个列表,但是当我这样做时,值仍然在列方向上,我无法让它们 transpose 到行列表中。列中的数据如下所示:

|--|--A--+--B--+--C--+--D--+ ... +
|--|-----+-----+-----+-----+
|1 |     |     |     |     |
|--|-----+-----+-----+-----+
|2 |  << other data here >>|        
|--|     +-----+-----+-----+
|3 |  "  |  a  |  b  |  c  | ...    <~~ row 3 data (needed as 2nd element in combobox)
|--|     +-----+-----+-----+
|4 |  "  |  d  |  e  |  f  | ...    <~~ row 4 data (needed as 1st element in combobox)
|--|     +-----+-----+-----+
|5 |  "  |  1  |  2  |  3  |
|--|     +-----+-----+-----+
|6 |  "  |  4  |  5  |  6  |
|--|-----+-----+-----+-----+
|7 |  "  |  7  |  8  |  9  |
|--|-----+-----+-----+-----+

我希望组合框列表条目显示如下:

d   a
e   b
f   c

此用户表单由另一个用户表单初始化,该用户表单从多个选项中进行选择,然后从多个具有相似信息的工作表中激活正确的工作表。当第二个用户窗体初始化时,它应该使用上面示例中的数据填充组合框。我使用以下方法从单个列创建了一个值列表:

Private Sub UserForm_Initialize()

    'ReferenceCombo.ColumnCount = 2
    'Range("B4", Range("B" & Rows.Count).End(xlUp)).Name = "Dynamic"
    'Me.ReferenceCombo.RowSource = "Dynamic"

End Sub

我还可以使用以下方法获取一行中所有值的列表:

Dim sht As Worksheet
Set sht = ActiveSheet

    ReferenceCombo.ColumnCount = 2
    sht.Range(Sheet7.Cells(4, 2), Sheet7.Cells(4, Columns.Count).End(xlToLeft)).Name = "Dynamic"
    sht.Range(Sheet7.Cells(4, 2), Sheet7.Cells(4, Columns.Count).End(xlToLeft)).Select
    Me.ReferenceCombo.RowSource = "Dynamic"

但这只选择了我想要的两行之一,并没有将值列表转换为正确的格式。

我试过 here but this does not seem to apply to userforms. Information here was helpful in selecting the row correctly. This was helpful in selecting a dynamic field. Here I found information on transposing a list but I'm not sure I understood it completely. This relates to a listfill range but I'm not sure this applies to comboboxes on userforms either. This 中有关插入转置函数的信息,但它对我不起作用。

如有任何帮助,我们将不胜感激。

将第 4 行和第 3 行中的 header 信息分配给 Combobox

据我了解你的 post,你想提取你的 header 信息,从单元格 B3 第 4 行的最后一列 ,但要在组合框中 反转行顺序 显示数据。

您可以将这些数据分配给变体 2-dim 数组,使用 Application.Index 函数的高级可能性对其进行重组 *) 并将数组分配给组合框 .Column 属性 在一行中(为了避免通过最常用的 .List 属性 进一步重新转置)。

*) 参见 Advanced possibilities of the Application.Index function

Option Explicit                     ' declaration head of Userform code module

Private Sub UserForm_Initialize()
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' [1] assign data to variant 1-based 2-dim array v
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  Dim v As Variant, nCols As Long
  nCols = Sheet7.Range(Sheet7.Cells(4, 2), Sheet7.Cells(4, Columns.Count).End(xlToLeft)).Columns.Count
  v = Sheet7.Range("B1").Resize(4, nCols).Value2          ' e.g. B1:X4 (if X4 is last column)
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' [2] restructure array by filtering rows 4,3 and all columns Array(1,2,3,...)
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  v = Application.Index(v, Application.Transpose(Array(4, 3)), allCols(nCols))
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' [3] assign data to combobox via .Column property
'      (instead of assigning the transposed array to the .List property)
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  Me.ReferenceCombo.Column = v
End Sub

Private Sub UserForm_Layout()
  Me.ReferenceCombo.ColumnCount = 2
End Sub

Private Function allCols(ByVal ColNum As Long) As Variant()
' Purpose: return array with column numbers from 1,2, to ...ColNum
  ReDim temp(0 To ColNum - 1)
  Dim i As Long
  For i = LBound(temp) To UBound(temp)
      temp(i) = i + 1
  Next i
  allCols = temp
  End Function