Range object (Excel)

Represents a cell, a row, a column, a selection of cells containing one or more contiguous blocks of cells, or a 3D range.

Note

Interested in developing solutions that extend the Office experience across multiple platforms? Check out the new Office Add-ins model. Office Add-ins have a small footprint compared to VSTO Add-ins and solutions, and you can build them by using almost any web programming technology, such as HTML5, JavaScript, CSS3, and XML.

Remarks

The default member of Range forwards calls without parameters to the Value property and calls with parameters to the Item member. Accordingly, someRange = someOtherRange is equivalent to someRange.Value = someOtherRange.Value, someRange(1) to someRange.Item(1) and someRange(1,1) to someRange.Item(1,1).

The following properties and methods for returning a Range object are described in the Example section:

  • Range and Cells properties of the Worksheet object
  • Range and Cells properties of the Range object
  • Rows and Columns properties of the Worksheet object
  • Rows and Columns properties of the Range object
  • Offset property of the Range object
  • Union method of the Application object

Example

Use Range (arg), where arg names the range, to return a Range object that represents a single cell or a range of cells. The following example places the value of cell A1 in cell A5.

Worksheets("Sheet1").Range("A5").Value = _ 
    Worksheets("Sheet1").Range("A1").Value

The following example fills the range A1:H8 with random numbers by setting the formula for each cell in the range. When it's used without an object qualifier (an object to the left of the period), the Range property returns a range on the active sheet. If the active sheet isn't a worksheet, the method fails.

Use the Activate method of the Worksheet object to activate a worksheet before you use the Range property without an explicit object qualifier.

Worksheets("Sheet1").Activate 
Range("A1:H8").Formula = "=Rand()"    'Range is on the active sheet

The following example clears the contents of the range named Criteria.

Note

If you use a text argument for the range address, you must specify the address in A1-style notation (you cannot use R1C1-style notation).

Worksheets(1).Range("Criteria").ClearContents

Use Cells on a worksheet to obtain a range consisting all single cells on the worksheet. You can access single cells via Item(row, column), where row is the row index and column is the column index. Item can be omitted since the call is forwarded to it by the default member of Range. The following example sets the value of cell A1 to 24 and of cell B1 to 42 on the first sheet of the active workbook.

Worksheets(1).Cells(1, 1).Value = 24
Worksheets(1).Cells.Item(1, 2).Value = 42

The following example sets the formula for cell A2.

ActiveSheet.Cells(2, 1).Formula = "=Sum(B1:B5)"

Although you can also use Range("A1") to return cell A1, there may be times when the Cells property is more convenient because you can use a variable for the row or column. The following example creates column and row headings on Sheet1. Be aware that after the worksheet has been activated, the Cells property can be used without an explicit sheet declaration (it returns a cell on the active sheet).

Note

Although you could use Visual Basic string functions to alter A1-style references, it is easier (and better programming practice) to use the Cells(1, 1) notation.

Sub SetUpTable() 
Worksheets("Sheet1").Activate 
For TheYear = 1 To 5 
    Cells(1, TheYear + 1).Value = 1990 + TheYear 
Next TheYear 
For TheQuarter = 1 To 4 
    Cells(TheQuarter + 1, 1).Value = "Q" & TheQuarter 
Next TheQuarter 
End Sub

Use_expression_.Cells, where expression is an expression that returns a Range object, to obtain a range with the same address consisting of single cells. On such a range, you access single cells via Item(row, column), where are relative to the upper-left corner of the first area of the range. Item can be omitted since the call is forwarded to it by the default member of Range. The following example sets the formula for cell C5 and D5 of the first sheet of the active workbook.

Worksheets(1).Range("C5:C10").Cells(1, 1).Formula = "=Rand()"
Worksheets(1).Range("C5:C10").Cells.Item(1, 2).Formula = "=Rand()"

Use Range (cell1, cell2), where cell1 and cell2 are Range objects that specify the start and end cells, to return a Range object. The following example sets the border line style for cells A1:J10.

Note

Be aware that the period in front of each occurrence of the Cells property is required if the result of the preceding With statement is to be applied to the Cells property. In this case, it indicates that the cells are on worksheet one (without the period, the Cells property would return cells on the active sheet).

With Worksheets(1) 
    .Range(.Cells(1, 1), _ 
        .Cells(10, 10)).Borders.LineStyle = xlThick 
End With

Use Rows on a worksheet to obtain a range consisting all rows on the worksheet. You can access single rows via Item(row), where row is the row index. Item can be omitted since the call is forwarded to it by the default member of Range.

Note

It's not legal to provide the second parameter of Item for ranges consisting of rows. You first have to convert it to single cells via Cells.

The following example deletes row 5 and 10 of the first sheet of the active workbook.

Worksheets(1).Rows(10).Delete
Worksheets(1).Rows.Item(5).Delete

Use Columns on a worksheet to obtain a range consisting all columns on the worksheet. You can access single columns via Item(row) [sic], where row is the column index given as a number or as an A1-style column address. Item can be omitted since the call is forwarded to it by the default member of Range.

Note

It's not legal to provide the second parameter of Item for ranges consisting of columns. You first have to convert it to single cells via Cells.

The following example deletes column "B", "C", "E", and "J" of the first sheet of the active workbook.

Worksheets(1).Columns(10).Delete
Worksheets(1).Columns.Item(5).Delete
Worksheets(1).Columns("C").Delete
Worksheets(1).Columns.Item("B").Delete

Use_expression_.Rows, where expression is an expression that returns a Range object, to obtain a range consisting of the rows in the first area of the range. You can access single rows via Item(row), where row is the relative row index from the top of the first area of the range. Item can be omitted since the call is forwarded to it by the default member of Range.

Note

It's not legal to provide the second parameter of Item for ranges consisting of rows. You first have to convert it to single cells via Cells.

The following example deletes the ranges C8:D8 and C6:D6 of the first sheet of the active workbook.

Worksheets(1).Range("C5:D10").Rows(4).Delete
Worksheets(1).Range("C5:D10").Rows.Item(2).Delete

Use_expression_.Columns, where expression is an expression that returns a Range object, to obtain a range consisting of the columns in the first area of the range. You can access single columns via Item(row) [sic], where row is the relative column index from the left of the first area of the range given as a number or as an A1-style column address. Item can be omitted since the call is forwarded to it by the default member of Range.

Note

It's not legal to provide the second parameter of Item for ranges consisting of columns. You first have to convert it to single cells via Cells.

The following example deletes the ranges L2:L10, G2:G10, F2:F10 and D2:D10 of the first sheet of the active workbook.

Worksheets(1).Range("C5:Z10").Columns(10).Delete
Worksheets(1).Range("C5:Z10").Columns.Item(5).Delete
Worksheets(1).Range("C5:Z10").Columns("D").Delete
Worksheets(1).Range("C5:Z10").Columns.Item("B").Delete

Use Offset (row, column), where row and column are the row and column offsets, to return a range at a specified offset to another range. The following example selects the cell three rows down from and one column to the right of the cell in the upper-left corner of the current selection. You cannot select a cell that is not on the active sheet, so you must first activate the worksheet.

Worksheets("Sheet1").Activate 
  'Can't select unless the sheet is active 
Selection.Offset(3, 1).Range("A1").Select

Use Union (range1, range2, ...) to return multiple-area ranges—that is, ranges composed of two or more contiguous blocks of cells. The following example creates an object defined as the union of ranges A1:B2 and C3:D4, and then selects the defined range.

Dim r1 As Range, r2 As Range, myMultiAreaRange As Range 
Worksheets("sheet1").Activate 
Set r1 = Range("A1:B2") 
Set r2 = Range("C3:D4") 
Set myMultiAreaRange = Union(r1, r2) 
myMultiAreaRange.Select

If you work with selections that contain more than one area, the Areas property is useful. It divides a multiple-area selection into individual Range objects and then returns the objects as a collection. Use the Count property on the returned collection to verify a selection that contains more than one area, as shown in the following example.

Sub NoMultiAreaSelection() 
    NumberOfSelectedAreas = Selection.Areas.Count 
    If NumberOfSelectedAreas > 1 Then 
        MsgBox "You cannot carry out this command " & _ 
            "on multi-area selections" 
    End If 
End Sub

This example uses the AdvancedFilter method of the Range object to create a list of the unique values, and the number of times those unique values occur, in the range of column A.

Sub Create_Unique_List_Count()
    'Excel workbook, the source and target worksheets, and the source and target ranges.
    Dim wbBook As Workbook
    Dim wsSource As Worksheet
    Dim wsTarget As Worksheet
    Dim rnSource As Range
    Dim rnTarget As Range
    Dim rnUnique As Range
    'Variant to hold the unique data
    Dim vaUnique As Variant
    'Number of unique values in the data
    Dim lnCount As Long
    
    'Initialize the Excel objects
    Set wbBook = ThisWorkbook
    With wbBook
        Set wsSource = .Worksheets("Sheet1")
        Set wsTarget = .Worksheets("Sheet2")
    End With
    
    'On the source worksheet, set the range to the data stored in column A
    With wsSource
        Set rnSource = .Range(.Range("A1"), .Range("A100").End(xlDown))
    End With
    
    'On the target worksheet, set the range as column A.
    Set rnTarget = wsTarget.Range("A1")
    
    'Use AdvancedFilter to copy the data from the source to the target,
    'while filtering for duplicate values.
    rnSource.AdvancedFilter Action:=xlFilterCopy, _
                            CopyToRange:=rnTarget, _
                            Unique:=True
                            
    'On the target worksheet, set the unique range on Column A, excluding the first cell
    '(which will contain the "List" header for the column).
    With wsTarget
        Set rnUnique = .Range(.Range("A2"), .Range("A100").End(xlUp))
    End With
    
    'Assign all the values of the Unique range into the Unique variant.
    vaUnique = rnUnique.Value
    
    'Count the number of occurrences of every unique value in the source data,
    'and list it next to its relevant value.
    For lnCount = 1 To UBound(vaUnique)
        rnUnique(lnCount, 1).Offset(0, 1).Value = _
            Application.Evaluate("COUNTIF(" & _
            rnSource.Address(External:=True) & _
            ",""" & rnUnique(lnCount, 1).Text & """)")
    Next lnCount
    
    'Label the column of occurrences with "Occurrences"
    With rnTarget.Offset(0, 1)
        .Value = "Occurrences"
        .Font.Bold = True
    End With

End Sub

Methods

Properties

See also

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.