スピンボタンの使い方:Excel VBA入門 |
スポンサードリンク | |
値を増減する | 日付を増減する |
Private Sub SpinButton1_SpinUp() TextBox1.Value = TextBox1.Value + 1 End Sub |
Private Sub SpinButton1_SpinDown() TextBox1.Value = TextBox1.Value - 1 End Sub |
Sub myform5() UserForm5.Show End Sub |
Private Sub UserForm_Initialize() Dim lRow As Long, myRange UserForm1.Caption = "商品名の選択" With Worksheets("Sheet1") myRange = Range(.Range("A2"), .Range("C" & Rows.Count).End(xlUp)) End With With ComboBox1 .ColumnCount = 3 .ColumnWidths = "50;50;50" .List = myRange End With TextBox1.Value = 0 TextBox1.IMEMode = fmIMEModeOff OptionButton1.Value = True End Sub |
Private Sub CommandButton1_Click() Dim lRow As Long, i As Long Dim ListNo As Long ListNo = ComboBox1.ListIndex If ListNo < 0 Then MsgBox "いずれかの行を選択してください" Exit Sub End If With Worksheets("Sheet2") lRow = .Range("B" & Rows.Count).End(xlUp).Row .Range("B1").Offset(lRow, 0).Resize(1, 3).Value = _ Worksheets("Sheet1").Range("A2").Offset(ListNo, 0).Resize(1, 3).Value .Cells(lRow + 1, 5).Value = TextBox1.Value .Cells(lRow + 1, 6).Value = _ .Cells(lRow + 1, 4).Value * .Cells(lRow + 1, 5).Value '---オプションボタンの状態を取得 If OptionButton1 = True Then .Cells(lRow + 1, 7).Value = OptionButton1.Caption ElseIf OptionButton2 = True Then .Cells(lRow + 1, 7).Value = OptionButton2.Caption ElseIf OptionButton3 = True Then .Cells(lRow + 1, 7).Value = OptionButton3.Caption End If '---チェックボタンの状態を取得 If CheckBox1 = True Then .Cells(lRow + 1, 8).Value = "○" If CheckBox2 = True Then .Cells(lRow + 1, 9).Value = "○" If CheckBox3 = True Then .Cells(lRow + 1, 10).Value = "○" End With TextBox1.Value = 0 CheckBox1 = False CheckBox2 = False CheckBox3 = False End Sub |
Private Sub CommandButton2_Click() Unload Me End Sub |
Private Sub SpinButton1_SpinUp() TextBox1.Value = TextBox1.Value + 1 End Sub |
Private Sub CommandButton1_Click() Dim lRow As Long With Worksheets("Sheet3") lRow = .Range("A" & Rows.Count).End(xlUp).Row .Range("A" & lRow + 1).Value = DateValue(TextBox1.Value) .Range("A" & lRow + 1).NumberFormatLocal = "yyyy""年""mm""月""dd""日""" End With TextBox1.SetFocus End Sub |
Private Sub CommandButton2_Click() Unload Me End Sub |
Private Sub SpinButton1_SpinDown() TextBox1.Value = Format(DateValue(TextBox1.Value) - 1, "yyyy年mm月dd日") End Sub |
Private Sub SpinButton1_SpinUp() TextBox1.Value = Format(DateValue(TextBox1.Value) + 1, "yyyy年mm月dd日") End Sub |
Private Sub UserForm_Initialize() UserForm1.Caption = "日付の入力" With TextBox1 .Value = Format(Date, "yyyy年mm月dd日") .SetFocus End With End Sub |
スポンサードリンク
PageViewCounter
Since2006/2/27