![]() |
入力したデータをまとめて転記する:Excel VBA プログラミング入門 |
スポンサードリンク | |
Dim lastRow as Long lastRow1 = Worksheets("入力").Range("A" & Rows.Count).End(xlUp).Row If lastRow1 = 1 Then Exit Sub |
Dim i as Long For i = 2 To lastRow1 Worksheets("データ").Range("A2:D2").Value =Worksheets("入力").Range("A" & i & ":D" & i).Value Next i |
Dim lastRow2 as Long lastRow2 = Worksheets("データ").Range("A" & Rows.Count).End(xlUp).Row |
Dim i as Long For i = 2 To lastRow1 lastRow2 = Worksheets("データ").Range("A" & Rows.Count).End(xlUp).Row Worksheets("データ").Range("A" & lastRow2 + 1 & ":D" & lastRow2 + 1).Value =Worksheets("入力").Range("A" & i & ":D" & i).Value Next i |
Dim lastRow as Long Dim lastRow2 as Long Dim i as Long lastRow1 = Worksheets("入力").Range("A" & Rows.Count).End(xlUp).Row For i = 2 To lastRow1 lastRow2 = Worksheets("データ").Range("A" & Rows.Count).End(xlUp).Row Worksheets("データ").Range("A" & lastRow2 + 1 & ":D" & lastRow2 + 1).Value = Worksheets("入力").Range("A" & i & ":D" & i).Value Next i |
Sub prog21() Dim Sh1 As Worksheet, Sh2 As Worksheet Dim lastRow1 As Long, lastRow2 As Long Dim i As Long Set Sh1 = Worksheets("入力") Set Sh2 = Worksheets("データ") '入力データの最下行を求める lastRow1 = Sh1.Range("A" & Rows.Count).End(xlUp).Row If lastRow1 = 1 Then Exit Sub With Sh2 For i = 2 To lastRow1 '転記先の最下行を求める lastRow2 = .Range("A" & Rows.Count).End(xlUp).Row 'データを転記する .Range("A" & lastRow2 + 1 & ":D" & lastRow2 + 1).Value = sh1.Range("A" & i & ":D" & i).Value Next i End With End Sub |
Sub prog21() Dim Sh1 As Worksheet, Sh2 As Worksheet Dim lastRow1 As Long, lastRow2 As Long Dim i As Long Set Sh1 = Worksheets("入力") Set Sh2 = Worksheets("データ") For i = 2 To lastRow1 lastRow2 = .Range("A" & Rows.Count).End(xlUp).Row '金額の計算 .Range("E" & lastRow2 + 1).Value = Sh1.Range("C" & i).Value * Sh1.Range("D" & i).Value Next i End With End Sub |
Worksheets("入力").Range("A2:D" & lastRow1).ClearContents |
Sub prog21() Dim Sh1 As Worksheet, Sh2 As Worksheet Dim lastRow1 As Long, lastRow2 As Long Dim i As Long Set Sh1 = Worksheets("入力") Set Sh2 = Worksheets("データ") '入力データの最下行を求める lastRow1 = Sh1.Range("A" & Rows.Count).End(xlUp).Row If lastRow1 = 1 Then Exit Sub With Sh2 For i = 2 To lastRow1 '転記先の最下行を求める lastRow2 = .Range("A" & Rows.Count).End(xlUp).Row 'データを転記する .Range(.Range("A" & lastRow2 + 1), .Range("D" & lastRow2 + 1)).Value = _ Sh1.Range(Sh1.Range("A" & i), Sh1.Range("D" & i)).Value '金額の計算 .Range("E" & lastRow2 + 1).Value = Sh1.Range("C" & i).Value * Sh1.Range("D" & i).Value Next i End With '入力データをクリアする With Sh1 .Range("A2:D" & lastRow1).ClearContents End With End Sub |
Sub prog22() Dim Sh1 As Worksheet, Sh2 As Worksheet Dim lastRow1 As Long, lastRow2 As Long Dim i As Long Dim myData As Variant Set Sh1 = Worksheets("入力") Set Sh2 = Worksheets("データ") With Sh1 lastRow1 = .Range("A" & Rows.Count).End(xlUp).Row If lastRow1 = 1 Then Exit Sub '配列に入力データを読み込む myData = .Range("A2:D" & lastRow1).Value '配列の要素数を変更 ReDim Preserve myData(1 To lastRow1 - 1, 1 To 5) '金額の計算 For i = LBound(myData) To UBound(myData) myData(i, 5) = myData(i, 3) * myData(i, 4) Next i '入力データをクリアする .Range("A2:D" & lastRow1).ClearContents End With With Sh2 lastRow2 = .Range("A" & Rows.Count).End(xlUp).Row + 1 'データシートへ配列を書き出す .Range("A" & lastRow2).Resize(UBound(myData), UBound(myData, 2)).Value = myData End With End Sub |
スポンサードリンク
PageViewCounter
Since2006/2/27