条件を満たす行を削除する:Excel VBA入門 |
スポンサードリンク | |
Sub test01() Dim i As Long For i = 2 To 10 If Cells(i, 2).Value = 0 Then Range(i & ":" & i).Delete End If Next i End Sub |
Sub test01a() Dim lRow As Long Dim i As Long lRow = Cells(Rows.Count, 1).End(xlUp).Row Application.ScreenUpdating = False For i = lRow To 2 Step -1 If Cells(i, 2).Value = 0 Then Range(i & ":" & i).Delete End If Next i Application.ScreenUpdating = True End Sub |
Sub test03() Dim lRow As Long, lCol As Long Dim i As Long, j As Long Dim x, y Dim myCnt As Long lRow = Cells(Rows.Count, 1).End(xlUp).Row lCol = Cells(1, Columns.Count).End(xlToLeft).Column '----データを配列Xに読み込む x = Range(Cells(1, 1), Cells(lRow, lCol)).Value '----データを書き出す配列yを準備する ReDim y(1 To lRow, 1 To lCol) For i = 1 To lRow '----削除しないデータを配列yに書き込む If x(i, 2) <> 0 Then myCnt = myCnt + 1 For j = 1 To lCol y(myCnt, j) = x(i, j) Next j End If Next i '----配列yをシートへ書き出す Range("A1").Resize(lRow, lCol).Value = y End Sub |
Sub test0b() Dim lRow As Long Dim i As Long lRow = Cells(Rows.Count, 1).End(xlUp).Row Application.ScreenUpdating = False For i = lRow To 2 Step -1 If Cells(i, 1).Value ="" Then Range(i & ":" & i).Delete End If Next i Application.ScreenUpdating = True End Sub |
Sub test0c() Dim lRow As Long Dim i As Long lRow = Cells(Rows.Count, 1).End(xlUp).Row Application.ScreenUpdating = False For i = lRow To 2 Step -1 If VarType(Cells(i, 1)) = vbEmpty Then Range(i & ":" & i).Delete End If Next i Application.ScreenUpdating = True End Sub |
スポンサードリンク
PageViewCounter
Since2006/2/27