![]() |
リストボックスの使い方:Excel VBA入門 |
スポンサードリンク | |
リストボックスへデータを表示する | リストボックスへセル範囲のデータを表示する |
リストボックスの値をセル範囲へ入力する | リストボックスに列見出しを表示する |
リストの先頭を変更する |
Private Sub UserForm_Initialize() UserForm6.Caption = "商品名の入力" With ListBox1 .AddItem "りんご" .AddItem "みかん" .AddItem "バナナ" End With End Sub |
Private Sub CommandButton1_Click() Dim lastRow As Long With Worksheets("Sheet1") lastRow = .Cells(Rows.Count, 1).End(xlUp).Row + 1 .Cells(lastRow, 1).Value = UserForm6.ListBox1.Value End With End Sub |
Private Sub CommandButton2_Click() Unload Me End Sub |
Sub myform6() UserForm6.Show End Sub |
Private Sub UserForm_Initialize() Dim myData(2, 2) As Variant UserForm6.Caption = "商品名の入力" myData(0, 0) = 1001 myData(0, 1) = 1002 myData(0, 2) = 1003 myData(1, 0) = "りんご" myData(1, 1) = "みかん" myData(1, 2) = "バナナ" myData(2, 0) = 100 myData(2, 1) = 150 myData(2, 2) = 200 With ListBox1 .ColumnCount = 3 .ColumnWidths = "50;50;50" .Column() = myData End With End Sub |
Private Sub CommandButton1_Click() Dim lastRow As Long Dim i As Integer With Worksheets("Sheet4") lastRow = .Cells(Rows.Count, 1).End(xlUp).Row + 1 For i = 1 To 3 .Cells(lastRow, i).Value = ListBox1.List(ListBox1.ListIndex, i - 1) Next i End With End Sub |
Private Sub CommandButton2_Click() Unload Me End Sub |
Sub myform6() UserForm6.Show End Sub |
Private Sub UserForm_Initialize() Dim lastRow As Long With Worksheets("Sheet1") lastRow = .Cells(Rows.Count, 1).End(xlUp).Row End With With ListBox1 .ColumnCount = 3 .ColumnWidths = "50;50;50" .RowSource = "Sheet1!A1:C" & lastRow End With End Sub |
Private Sub UserForm_Initialize() Dim lastRow As Long Dim myData With Worksheets("Sheet1") myData = .Range(.Cells(1, 1), .Cells(Rows.Count, 3).End(xlUp)).Value End With With ListBox1 .ColumnCount = 3 .ColumnWidths = "50;50;50" .List = myData End With End Sub |
Private Sub CommandButton1_Click() Dim lastRow As Long Dim i As Integer With Worksheets("Sheet4") lastRow = .Cells(Rows.Count, 1).End(xlUp).Row + 1 For i = 1 To 3 .Cells(lastRow, i).Value = ListBox1.List(ListBox1.ListIndex, i - 1) Next i End With End Sub |
Private Sub CommandButton2_Click() Unload Me End Sub |
Sub myform6() Load UserForm6 UserForm6.Show End Sub |
Private Sub CommandButton1_Click() Dim lRow As Long, i As Long Dim ListNo As Long ListNo = ListBox1.ListIndex If ListNo < 0 Then MsgBox "いずれかの行を選択してください" Exit Sub End If With Worksheets("Sheet2") lRow = .Range("B" & Rows.Count).End(xlUp).Row For i = 0 To 2 .Cells(lRow + 1, i + 2).Value = ListBox1.List(ListNo, i) Next i .Cells(lRow + 1, 5).Value = TextBox1.Value .Cells(lRow + 1, 6).Value = _ .Cells(lRow + 1, 4).Value * .Cells(lRow + 1, 5).Value End With TextBox1.Value = "" End Sub |
Private Sub UserForm_Initialize() Dim lRow As Long With Worksheets("Sheet1") lRow = .Range("A" & Rows.Count).End(xlUp).Row End With With ListBox1 .ColumnCount = 3 .ColumnWidths = "50;50;50" .RowSource = "Sheet1!A1:C" & lRow End With TextBox1.Value = "" End Sub |
Private Sub UserForm_Initialize() Dim lRow As Long With Worksheets("Sheet1") lRow = .Range("A" & Rows.Count).End(xlUp).Row End With With ListBox1 .ColumnCount = 3 .ColumnWidths = "50;50;50" .RowSource = "Sheet1!A2:C" & lRow .ColumnHeads = True End With TextBox1.Value = "" End Sub |
Private Sub CommandButton1_Click() Dim lRow As Long, i As Long Dim ListNo As Long ListNo = ListBox1.ListIndex If ListNo < 0 Then MsgBox "いずれかの行を選択してください" Exit Sub End If With Worksheets("Sheet2") lRow = .Range("B" & Rows.Count).End(xlUp).Row For i = 0 To 2 .Cells(lRow + 1, i + 2).Value = ListBox1.List(ListNo, i) Next i .Cells(lRow + 1, 5).Value = TextBox1.Value .Cells(lRow + 1, 6).Value = _ .Cells(lRow + 1, 4).Value * .Cells(lRow + 1, 5).Value End With TextBox1.Value = "" ListBox1.TopIndex = ListNo End Sub |
スポンサードリンク
PageViewCounter
Since2006/2/27