3 Ways to Delete Entire Blank Rows in Excel + Video Tutorial

Bottom line: Learn a few ways to delete blank rows in Excel from a data set or table. Includes video tutorial and VBA macro.

Skill level: Beginner

Video Tutorial

Watch on YouTube & Subscribe to our Channel

Download the File

Download the example Excel file to follow along.  The file also contains the Select Blank Rows macro.

3 Ways to Find & Delete Blank Rows

If you are exporting reports from any type of system then there is a good chance the data contains blank rows.  One very common task we do in Excel is to delete these blank rows from the worksheet, especially if you are preparing your data for use with a pivot table.

How do we find and delete entire blank rows

In this case we want to delete rows that are entirely blank.  If a row contains a few blank cells, we still want to keep that row of data.

There are several ways to accomplish this task.  Let's look at some ways to save time and make this process easy.

#1 – Filter for Blanks

If our data set contains a column that ONLY has blank cells in the blank rows, then we can filter for blanks on that column.

Filter a column for blanks

In our example file we can filter the Customer column for blanks.  We can see that rows 4 & 9 still contain data in the other columns.  Therefore we do NOT want to delete these rows.

Filter for Blanks in a column leaves some data rows visible

You can continue to filter other columns for blanks until all cells in the range or Table are blank.  However, this can be time consuming if you have a lot of columns in your data set.

Once you have a filter applied that makes only the entire blank rows visible, then select and delete the rows.  The rows can be deleted by pressing the Delete button on the Home tab of the ribbon (keyboard shortcut: Ctrl+-)

Delete Filtered Blank Rows

Checkout my 3-part video series on Excel Filters to learn more time saving shortcuts.

#2 – Use a Formula to Identify Entire Blank Rows

Another approach is to use a formula with the COUNTA function.  The COUNTA function returns the count of cells that are NOT empty in a range.

We can add this formula to the right of the table, and copy down to each row in the table.

This will give us a column of values that returns the number of empty or non-blank cells in the row.  If the formula returns a 0 (zero) then all the cells in that row are blank.

COUNTA Formula to Count Cells that are NOT Empty or Blank

We then filter the new column for 0 (zero).  This will show all of the entire blank rows, and hide all non-blank rows.

Filter for Zero in the COUNTA column to View All Blank Rows

Next we just select and delete the visible rows.

Select and Delete Blank Rows based on COUNTA formula column

To recap, the steps to delete entire blank rows are:

  1. Add a column with the COUNTA formula to count non-blank cells.
  2. Filter the column for 0 (zero).
  3. Select all visible rows in the filter range.
  4. Delete the rows with the Ctrl+- keyboard shortcut.
  5. Clear the filter to view all rows.

I use an Excel Table (Beginner's Guide to Tables) in this example, and highly recommend using Tables.  You can turn off the Table Formulas (structured references) if you don't like them.

#3 – Use a Macro to Select or Delete Entire Blank Rows

The fastest approach to deleting blank rows is to use a macro.  This allows us to perform the entire task with a click of a button.

The following macro will select all the entire blank rows in the selected range.  If you only have a single cell selected, the macro finds all blank rows in the UsedRange of the active sheet.

Macro to Select All Entire Blank Rows to Delete
Sub Select_Blank_Rows()
'Select all entire blank rows in selected range
'Source: https://www.excelcampus.com/tips/delete-entire-blank-rows/

Dim rRow As Range
Dim rSelect As Range
Dim rSelection As Range
 
  'Check that a range is selected
  If TypeName(Selection) <> "Range" Then
    MsgBox "Please select a range first.", vbOKOnly, "Select Blank Rows Macro"
    Exit Sub
  End If
  
  'Check that multiple cells are selected
  If Selection.Cells.Count = 1 Then
    Set rSelection = ActiveSheet.UsedRange
  Else
    Set rSelection = Selection
  End If
 
  'Loop through each row and add blank rows to rSelect range
  For Each rRow In rSelection.Rows
    If WorksheetFunction.CountA(rRow) = 0 Then
      If rSelect Is Nothing Then
        Set rSelect = rRow
      Else
        Set rSelect = Union(rSelect, rRow)
      End If
    End If
  Next rRow
  
  'Select blank rows
  If rSelect Is Nothing Then
    MsgBox "No blank rows were found.", vbOKOnly, "Select Blank Rows Macro"
    Exit Sub
  Else
    rSelect.Select
  End If
  
End Sub

The macro only selects the blank rows. We can then manually delete the rows with the Ctrl+- keyboard shortcut or pressing the Delete button on the Home tab of the Ribbon.

You can replace the following line of code:

rSelect.Select

with this line of code if you would rather have the macro delete the blank rows.

rSelect.Rows.Delete Shift:=xlShiftUp

It's important to note that you will NOT be able to undo the delete action. So I prefer to have the macro just select the blank rows, and then delete them manually. That way I can undo the action if needed.

If you do add the code to delete the row, I'd recommend adding a Yes/No Message Box to the macro to prevent you from running it accidentally.

The macro can also be modified to select blank columns instead of rows.

Change the following line of code:

For Each rRow In rSelection.Rows</pre>

To:
For Each rRow In rSelection.Columns

The macro will loop through all the columns and select the blank columns in the selected or used range.  Thanks to Sandy for suggesting this!

The Select Blank Rows macro can be added to your Personal Macro Workbook (video guide to creating your Personal Macro Workbook).  We can also add a custom macro button to the ribbon to quickly run the macro on any open workbook.

Other Methods to Delete Blank Rows?

One other method is to use the Go To Special window to select blanks.  We can use this instead of filtering a column for blanks.

Go To Special Menu Select Blank Cells

Here are the steps to use the Go To Special window to select and delete blank rows:

  1. Select an entire column in the worksheet.  The column must ONLY contain blank cells where the entire row is blank.
  2. On the Home tab, click the Find & Select button, then choose Go To Special… (keyboard shortcut: F5, Alt+S)
  3. Select the Blanks radio button on the Go To Special window. (keyboard shortcut: k, Enter)
  4. Delete the entire row.  Home tab > Delete (keyboard shortcut: Ctrl+-)

It's important to note that this method suffers from the same potential as solution #1.  If the column contains blank cells where the entire row is NOT blank, then this will not work.

What other methods do you use for deleting blank rows?  Please share by leaving a comment below.  Thank you! 🙂

42 comments

Your email address will not be published. Required fields are marked *

  • Dear Jon,
    Thus was very helpfull. I used the filter method, but now I learned two more ways. Thanks.

    K.R.
    Edil

  • Hi Jon!

    Two other methods I frequently employ just for removing dup rows are very simple and depend on what I’m doing with the workbook after:

    1. If having populated data rows with *exact* duplicates are a desired part of the set, this won’t work for you, otherwise: Select the entire dataset, go to the Data tab, select “Remove Duplicates”, leave all of the boxes checked to only delete exact dup rows, you will be left with one blank row to delete.

    2. If I’m going to paste the data into another workbook anyway, I sort the blanks to the bottom, then just copy the populated rows to the final workbook.

    Hope those are helpful as well as your suggestions! As always with Excel, there are at least 20 feasible ways to accomplish anything. 🙂

    Kim

    • Hi Kim,

      Thank you for the suggestions! Those are great! You are so right about there being 20 ways to accomplish the same task in Excel. It’s always fun to learn new methods. Thanks again for sharing. 🙂

  • Hi! Use the function IsBlank with Ctrl+Shift in new column. If the answer is True, then those rows may be deleted.

    • Thanks Peter! The ISBLANK array formula is a great way to accomplish the same basic outcome as COUNTA.

      For anyone else reading this, you have to hit Ctrl+Shift+Enter instead of pressing Enter to complete the formula. This makes it an array formula with curly brackets around the formula.

      {=ISBLANK(A2:F2)}

      The array formula evaluates all the cells in the referenced range (A2:F2), and returns TRUE in rows where all cells are blank. If you don’t use an array formula then the formula just returns a FALSE.

      If you are sending your workbook to other users you will want to make sure they also know how to use array formulas.

      Another way to achieve the TRUE/FALSE outcome is to set the COUNTA function equal to zero.

      =COUNTA(A2:F2)=0

      That will return a TRUE value when the range contains all blank cells, and a FALSE value when any of the cells on not blank.

      Thanks again for the great suggestion Peter! 🙂

      • Jon:
        Maybe I am doing something wrong but this does not work for me if the first cell in a row is blank. If the first cell in the row is blank it appears that the formula does not look at the remaining cells in the row.
        I am using the the sample spreadsheet “Deleting-Blank-Rows” downloaded from this page.

        When using {=ISBLANK(A9:F9)} the result is “True” although cells B9:F9 contain data.

        If I use =Counta(A9:F9)=0 the result is “False” as expected.

          • Jon:
            I went back and reviewed the requirements in the original question and found the COUNTA solution to be lacking. As Jan Malis correctly pointed out, COUNTA does not recognize Zero Length Text created by a formula (i.e. =IF(B11=””,””,”Hello”) ). This formula placed in A11 simply says that if B11 is empty to place a zero length text string in A11 or otherwise place Hello in A11.
            With that said we need to find a function such as Countblanks that does not recognize a zero length text as an occupied cell.
            =IF(COUNTBLANK(A12:F12)=6,”Empty”,”Occupied”) or

            =COUNTBLANK(A12:F12)=6 or

            =IF(SUMPRODUCT(LEN(A11:F11))=0,”Empty”,”Occupied”) or

            =SUMPRODUCT(LEN(A19:F19))=0

            {=IF(SUM(LEN(A11:F11))=0,”Empty”,”Occupied”)} Note this is an Array formula

            {=SUM(LEN(A13:F13))=0} Note this is an Array formula

            NOTE: The core ( =SUM(LEN(A2:F2)) ) of those last 4 formulas came from Meni Porat’s contribution up above. I added window dressing to make the output either Empty or Occupied.

            It is worth mentioning that “blank” has more than one definition in EXCEL.

  • I typically start by sorting on a column such as date, then look at the bottom of the range. Pretty quick and effective.

  • I usually insert a blank column and using FILL, SERIES number all rows 1 to last row. Sort whole sheet on a column that has data in every cell except the blank ones.

    Then sort on the column with the row numbers to put data back in original order. Delete the row numbers column. Blanks are gone.

    • Hey Lillian,

      Awesome! Setting up that Index column with sequential numbers first is a great technique for sorting. As you said, it allows you to sort the Index column to get the data back to the original sort order at any time.

      I also teach that method in my Filters 101 Course. I also have a post on Fill Handle Hacks that shows some shortcuts for using the fill handle to fill dates and numbers.

      Thank you for the suggestion! 🙂

  • Sometimes I just sort the range by the most important columns. All the blanks come to the top and then I Delete the rows.

  • Hello Jon

    I had another way to do it.
    First I insert a column at the right with numbers ordered from lowest to highest, then I select the whole table including the new column inserted. After that I go to the sort option, then in the order by I select the first column. Now I go to the end of the ordered table and there will be all the empty rows, I only select and delete them, then I select again all the table and now sort it order by the column of numbers that I introduced. Now the table is sorted in the original way, then I only select the column the numbers that I inserted and delete them.

    Jon thanks for your tutorials and tips, I have learned many tricks

    Have a nice day

    Alfonso Aguilar

  • Hi,
    You can use an Array Formula to identify empty rows (similar to method #2)

    If your data are arranged as a table, you’d use this formula:
    =SUM(LEN(Table1[@[Date]:[Revenue]]))

    If it’s just as a range, use this formula:
    =SUM(LEN(A2:F2))

    The formula calculates the number of characters in each row,
    as opposed to COUNTA which just counts non-empty cells.
    So, if the formula returns 0, it means that the whole row is blank.

    P.S.
    Press: Ctrl+Shift+Enter instead of: Enter, when you finish typing the formula,
    otherwise Excel won’t recognize the formula and mark it with a #VALUE error.

    In a table, Excel automatically fills in the whole column of data.
    In a range, drag the formula downwards to apply it to all the rows in the range.

    Best Regards,
    Meni Porat

    • Hi Meni,

      Thanks for sharing an alternate solution. I’m not sure I understand when the outcome would be different from COUNTA. Is there a scenario where the character count would be different from a non-empty cell?

      Thanks again and have a nice weekend! 🙂

  • Dear Jon,
    This lesson is very pleasant. I often use Counta function to delete blank row, but to know other ways to have the same results is very useful.
    Have a nice weekend!

  • Hi John,

    Thanks for that.

    Well well, I never saw the expression TypeName(Selection) = … before. And I thought I saw quite some code before. That is a great validation tool.

    I also think it was a good visual teaching technique to get the Sub to finish by simply selecting the empty rows THEN show how to get rid of them.

    Can I use this exercise in my class and (as I often do) point the participants to your Web site?

    Again thanks.

  • I tend to sort then do a quick check I’m not picking up any unintentional data using ctrl + shft + arrows combined with the count functionality in the bottom right. Suits my data but I really like the versatility of your solutions.

    And as usual very easy to follow and excellently explained.

  • Hi ,
    my situation was that there were empy cells containing formulas though.
    I needed to get rid of those as well. COUNTA didn´t work for me as it didn´t consider the cell empty when containg formula. And I don´t know anything about “array formulas” so couldn´t check the COUNTBLANK or others ….
    Finaly I came up with a primitive VBA code that works fine too. Here the loop code that makes the bulk work:

    For i = i To k
    If Cells(i, j).Value = “” And Cells(i, j + 7).Value = “” And Cells(i, j + 9).Value = “” And Cells(i, j + 11).Value = “” Then
    If rSelect Is Nothing Then
    Set rSelect = Range(Cells(i, j), Cells(i, j + 11))
    Else
    Set rSelect = Union(rSelect, Range(Cells(i, j), Cells(i, j + 11)))
    End If
    End If
    Next i

    ( my “j” increments are so irregular because I had merged cells , just not to confuse )
    Hope this is contributing.
    Thanks for the lesson !

  • Hi Jon,

    Very nice article. I made a very minor change in code like hide rows instead of delete.

    rSelect.Rows.Hidden = True

    Thank you so much Jon. You are champion.

    Cheers!!!

  • Thanks for the Macro for deleting empty rows. I’ve added to my Custom Ribbon now, along with the other Macros.

    Going to save more time now 🙂

    Thanks Again.

  • Hi Jon
    When I run the macro it bugs for about 30 seconds, whos the page in blank and the message of ‘excel not responding’.Is it normal?
    Thanks in advance!

  • This is excellent is the way to delete an entire if a cell (in column A) is formatted as a date? Thank you.

  • Jon your videos are excellent. I’m very new to macros and I watched your 4 part videos on creating macros, finding where they save, building ‘my macros tab” and yes/no command. I’d like to download your macro for deleting blank rows but can’t seem to get it to save under my personal macro tab and I tried to add the yes/no command with no help. Any simple directions a newbie?

Generic filters
Exact matches only

Excel Shortcuts List

keyboard shortcuts list banner

Learn over 270 Excel keyboard & mouse shortcuts for Windows & Mac.

Excel Shortcuts List

Join Our Weekly Newsletter

The Excel Pro Tips Newsletter is packed with tips & techniques to help you master Excel.

Join Our Free Newsletter