can you delete cells within a Macro?


Posted by Mitchell Fox on July 10, 2001 7:18 AM

I am new to Macros, but would like to create to a Macro, that after sorting the data in a certain way (which I know how to do), then deletes all data in a certain column that is a less (or possibly more ) than a particular value. I have found out how to use the IF
statement in a Function, but the most I can do with that is to blank the cells (using " ") found not meeting the condition. I want to delete the entire row
of the entriy that has a value that doesn't meet the
condition, not just blank the cell and leave the rest of the offending row intact. also, I know how to paste the function, but how do I actually make it Run in the
Macro? sorry for the complexity and length of the question.

Posted by Damon Ostrander on July 10, 2001 8:34 AM


Hi Mitchell,

Deleting a row from VBA is easy. The Delete method applies to rows (as well as lots of other objects). The VBA to delete a row is just

row.Delete

where row is the entire row Range object. For example, to delete row 5:

Rows(5).Delete

The row number (in this example 5) can be a variable, so

For i = 10 To 1 Step -2
Rows(i).Delete
Next i

would delete every even row between rows 1 and 10 (the loop runs backwards because each deletion causes all the rows after the deleted row to be renumbered).

To delete the entire row containing the cell that is currently selected:

Selection.EntireRow.Delete

where EntireRow returns the row object that is the entire row containing the selection.

Likewise, to delete the entire row containing cell D27:

[D27].EntireRow.Delete

The same thing applies to columns.

Happy computing.

Damon


Posted by Mitchell Fox on July 10, 2001 11:06 AM

I don't know if anyone has the patience to do this, but I pasted in the code I wrote. I can't get it to delete the rows that have cells in Column H that are less than 75%. I don't even know if I am in the ballpark with this code.
Thanks
Workbooks.Open FileName:="C:\WINDOWS\Desktop\regionalfunnel.xls"
ActiveCell.Offset(9, 2).Range("A1").Select
Selection.EntireRow.Insert
Selection.EntireRow.Insert
Selection.EntireRow.Insert
ActiveWindow.SmallScroll Down:=291
ActiveWindow.ScrollRow = 1
ActiveCell.Offset(2, -2).Range("A1:AK8375").Select
Selection.Sort Key1:=ActiveCell.Offset(0, 7).Range("A1"), Order1:= _
xlAscending, Header:=xlYes, OrderCustom:=1, MatchCase:=False, _
Orientation:=xlTopToBottom
ActiveWindow.SmallScroll Down:=82
ActiveWindow.ScrollRow = 576
ActiveWindow.ScrollRow = 930
ActiveWindow.ScrollRow = 1380
ActiveWindow.ScrollRow = 1712
ActiveWindow.ScrollRow = 2031
ActiveWindow.ScrollRow = 2350
For i = 2000 To 1
If H < 75 Then
Selection.EntireRow.Delete
End If
Next i
End Sub Hi Mitchell, Deleting a row from VBA is easy. The Delete method applies to rows (as well as lots of other objects). The VBA to delete a row is just row.Delete where row is the entire row Range object. For example, to delete row 5: Rows(5).Delete The row number (in this example 5) can be a variable, so For i = 10 To 1 Step -2

Posted by Damon Ostrander on July 10, 2001 12:38 PM

Mitchell,

Here's a simple macro that does it. I am assuming that when you say the values are in percent, that they are really just formatted as percentages, i.e., the underlying values are fractions (75% = 0.75 underlying value). If you are not using percent formatting, then change the 0.75 in the code below to 75.

This code will look in every row from the end of the used range on the worksheet to row 1. If you have headers, and, say, only want to look at row 5 to the end of the range, set the For loop end index to 5 instead of 1.

Note that I declared iRow as Long so that the code can handle row numbers larger than 32767 (just in case your worksheet has lots of rows).

I hope this example helps. As you can see, coding directly in VBA is much easier than what one might expect based on the voluminous and unwieldy code that Excel generates when one records a macro.

Happy computing.

Damon

Sub DelCertainRows()
' Deletes all rows that have a value in column H less than 75% on the active worksheet

Dim iRow As Long

For iRow = ActiveSheet.UsedRange.Rows.Count To 1 Step -1
If Cells(iRow, 8) < 0.75 Then
Rows(iRow).Delete
End If
Next iRow
End Sub

Posted by Mitchell Fox on July 11, 2001 8:22 AM

Here's a macro--thanks, still having problems

Thanks for your Macro. unfortunately, I am still having problems. It is opening the Worksheet i need to work with, but it doesn't seem to be deleting any of the rows that have values less than 75% in column H. I tried formatting Column H
as a true percentage or not, and neither way worked. don't know whether you have the time or energy to continue working with a total novice like me, but below is your code that I modified and that is still not doing what I need it to do.
Thanks

Sub Regional()
Workbooks.Open FileName:="C:\WINDOWS\Desktop\regionalfunnel.xls"
End Sub
Sub DelCertainRows()
' Deletes all rows that have a value in column H less than 75% on the active worksheet

Dim iRow As Long

For iRow = ActiveSheet.UsedRange.Rows.Count To 1 Step -1
If Cells(iRow, 8) < 0.75 Then
Rows(iRow).Delete
End If
Next iRow
End Sub Mitchell, Here's a simple macro that does it. I am assuming that when you say the values are in percent, that they are really just formatted as percentages, i.e., the underlying values are fractions (75% = 0.75 underlying value). If you are not using percent formatting, then change the 0.75 in the code below to 75. This code will look in every row from the end of the used range on the worksheet to row 1. If you have headers, and, say, only want to look at row 5 to the end of the range, set the For loop end index to 5 instead of 1. Note that I declared iRow as Long so that the code can handle row numbers larger than 32767 (just in case your worksheet has lots of rows). I hope this example helps. As you can see, coding directly in VBA is much easier than what one might expect based on the voluminous and unwieldy code that Excel generates when one records a macro. Happy computing. Damon Sub DelCertainRows()

Posted by Damon Ostrander on July 11, 2001 10:32 PM

Re: Here's a macro--thanks, still having problems

Hi again Mitchell,

Apparently you are running the macro Regional to open the file you want to run my macro on. Mine is a separate macro and you have to run it separately after the appropriate worksheet has been activated. If you want it to run automatically when Regional runs, you have to call it from inside the Regional procedure:

Sub Regional()
Workbooks.Open "C:\WINDOWS\Desktop\regionalfunnel.xls"
DelCertainRows
End Sub

Sub DelCertainRows
...

End Sub

One word of caution regarding your code. Since you do not explicitly activate the worksheet you want to operate on, the worksheet that will be active will be the one that was active last time the regionalfunnel workbook was saved. So the routine will not operate properly if the workbook was not last saved properly. It would be best to add a statement to explicitly activate the desired worksheet. For example:

Worksheets("Data").Activate

will active worksheet with tab name "Data".

Happy computing.

Damon Thanks for your Macro. unfortunately, I am still having problems. It is opening the Worksheet i need to work with, but it doesn't seem to be deleting any of the rows that have values less than 75% in column H. I tried formatting Column H For iRow = ActiveSheet.UsedRange.Rows.Count To 1 Step -1 If Cells(iRow, 8) < 0.75 Then Rows(iRow).Delete End If Next iRow

Posted by Mitchell Fox on July 12, 2001 6:30 AM

Re: Here's a macro--thanks, still having problems

Below is my revised code. Still not deleting any rows that have value in Column H less than 75%. It seems to stop and highlight a row that has a value of 70% (it's actually row 85), but doesn't delete anything.
Thanks for your help

Sub Regional()
Workbooks.Open "C:\WINDOWS\Desktop\regionalfunnel.xls"
End Sub


Sub DelCertainRows()
Worksheets("Sheet1").Activate
' Deletes all rows that have a value in column H less than 75% on the active worksheet

Dim iRow As Long

For iRow = ActiveSheet.UsedRange.Rows.Count To 1 Step -1
If Cells(iRow, 8) < 75 Then
Rows(iRow).Delete
End If
Next iRow
End Sub

For iRow = ActiveSheet.UsedRange.Rows.Count To 1 Step -1 If Cells(iRow, 8) < 0.75 Then Rows(iRow).Delete End If Next iRow




Posted by Damon Ostrander on July 16, 2001 7:58 AM

Re: still having problems???

Mitchell,

I can see no way this macro can fail, other than that your data are formatted as percent, in which case the test should be for 0.75, not 75. If this does not solve the problem, feel free to send me the workbook and I will troubleshoot it for you.

Damon

mailto:VBAexpert@piadamon.com

: Hi again Mitchell, : Apparently you are running the macro Regional to open the file you want to run my macro on. Mine is a separate macro and you have to run it separately after the appropriate worksheet has been activated. If you want it to run automatically when Regional runs, you have to call it from inside the Regional procedure