Working with Ranges in VBA

Master the Range object to read, write, and manipulate Excel data with VBA

Quick Reference

Range("A1"): Reference single cell

Range("A1:C10"): Reference cell range

Cells(row, column): Reference cell by coordinates

ActiveCell: Currently selected cell

Referencing Ranges

Method 1: Range Property

Range("A1") ' Single cell
Range("A1:C10") ' Rectangular range
Range("A1:A10, C1:C10") ' Multiple areas
Range("MyNamedRange") ' Named range

Method 2: Cells Property

Cells(1, 1) ' Row 1, Column 1 = A1
Cells(5, 3) ' Row 5, Column 3 = C5
Cells(i, j) ' Variables for row and column

Best for loops - use numeric row/column instead of letter references

Method 3: Shortcuts

ActiveCell ' Currently selected cell
Selection ' Currently selected range
ActiveSheet.UsedRange ' All used cells
Rows(5) ' Entire row 5
Columns(3) ' Entire column C

Reading Cell Values

Read Single Cell

Sub ReadValue()
Dim cellValue As Variant
cellValue = Range("A1").Value
MsgBox cellValue
End Sub

Value vs Value2 vs Text

  • .Value: Default property. Returns formatted value (dates as Date, numbers as Double)
  • .Value2: Raw value without formatting (dates as numbers, currency without symbol)
  • .Text: Formatted text as displayed (exactly what you see in cell)
  • .Formula: The formula if present, otherwise the value
Debug.Print Range("A1").Value ' Most common
Debug.Print Range("A1").Value2 ' Raw value
Debug.Print Range("A1").Text ' Display text
Debug.Print Range("A1").Formula ' Formula

Read Multiple Cells to Array (Fast!)

Sub ReadToArray()
Dim dataArray As Variant
' Read entire range into memory at once
dataArray = Range("A1:C10").Value
' Access array elements (1-based!)
MsgBox dataArray(1, 1) ' First row, first column
End Sub

Much faster than reading cell-by-cell in loops!

Writing Cell Values

Write Single Cell

Sub WriteValue()
Range("A1").Value = "Hello"
Range("B1").Value = 100
Range("C1").Value = Now ' Current date/time
End Sub

Write Formula

Sub WriteFormula()
Range("D1").Formula = "=SUM(A1:C1)"
Range("E1").FormulaR1C1 = "=SUM(RC[-4]:RC[-2])"
End Sub

Write Array to Range (Fast!)

Sub WriteArrayToRange()
Dim dataArray(1 To 10, 1 To 3) As Variant
Dim i As Integer, j As Integer
' Fill array
For i = 1 To 10
For j = 1 To 3
dataArray(i, j) = i * j
Next j
Next i
' Write all at once - MUCH faster!
Range("A1:C10").Value = dataArray
End Sub

Clear Contents

Range("A1:C10").ClearContents ' Clear values only
Range("A1:C10").Clear ' Clear everything
Range("A1:C10").ClearFormats ' Clear formatting only

Useful Range Properties

Formatting Properties

With Range("A1")
.Font.Bold = True
.Font.Color = RGB(255, 0, 0) ' Red
.Font.Size = 14
.Interior.Color = RGB(255, 255, 0) ' Yellow
.NumberFormat = "$#,##0.00" ' Currency
.HorizontalAlignment = xlCenter
End With

Border Properties

With Range("A1:C10").Borders
.LineStyle = xlContinuous
.Weight = xlThin
.Color = RGB(0, 0, 0)
End With

Information Properties

Debug.Print Range("A1").Address ' "$A$1"
Debug.Print Range("A1:C10").Rows.Count ' 10
Debug.Print Range("A1:C10").Columns.Count ' 3
Debug.Print Range("A1:C10").Cells.Count ' 30

Range Methods

Select & Activate

Range("A1").Select ' Select the range
Range("A1").Activate ' Make it the active cell

Note: Avoid Select/Activate in production code - works directly with ranges instead for better performance.

Copy & Paste

' Method 1: Copy/Paste
Range("A1:C10").Copy
Range("E1").PasteSpecial xlPasteValues
' Method 2: Direct assignment (faster!)
Range("E1:G10").Value = Range("A1:C10").Value

Find & Replace

Sub FindValue()
Dim foundCell As Range
Set foundCell = Range("A:A").Find("Target")
If Not foundCell Is Nothing Then
MsgBox "Found at: " & foundCell.Address
End If
End Sub
' Replace
Range("A:A").Replace "Old", "New"

Sort

Sub SortRange()
Range("A1:C10").Sort _
Key1:=Range("A1"), _
Order1:=xlAscending, _
Header:=xlYes
End Sub

AutoFill

' Fill down from A1 to A10
Range("A1").AutoFill Range("A1:A10")
' Fill series (1, 2, 3...)
Range("B1").Value = 1
Range("B1").AutoFill Range("B1:B10"), xlFillSeries

Dynamic Range References

Find Last Row/Column

Sub FindLastRow()
Dim lastRow As Long
' Find last row in column A
lastRow = Cells(Rows.Count, 1).End(xlUp).Row
MsgBox "Last row: " & lastRow
End Sub
Sub FindLastColumn()
Dim lastCol As Long
' Find last column in row 1
lastCol = Cells(1, Columns.Count).End(xlToLeft).Column
MsgBox "Last column: " & lastCol
End Sub

Resize Range

' Start at A1, make it 10 rows by 5 columns
Range("A1").Resize(10, 5).Value = "Data"
' Dynamic range based on data
Dim lastRow As Long
lastRow = Cells(Rows.Count, 1).End(xlUp).Row
Range("A1").Resize(lastRow).Interior.Color = RGB(200, 200, 200)

Offset Range

' Move 2 rows down, 1 column right from A1
Range("A1").Offset(2, 1).Value = "C3"
' Skip header row
Range("A1").Offset(1, 0).Select ' Selects A2

CurrentRegion

' Select entire contiguous data region around A1
Range("A1").CurrentRegion.Select
' Get row count of data region
MsgBox Range("A1").CurrentRegion.Rows.Count

Looping Through Ranges

For Each Loop

Sub LoopCells()
Dim cell As Range
For Each cell In Range("A1:A10")
If cell.Value > 100 Then
cell.Interior.Color = RGB(255, 0, 0)
End If
Next cell
End Sub

For Next with Cells

Sub LoopWithCells()
Dim i As Long
For i = 1 To 100
Cells(i, 1).Value = i * 10
Cells(i, 2).Value = i * 20
Next i
End Sub

Better performance than For Each for large ranges

Best Practices

Use arrays for bulk operations: Read range to array, process, write back - 100x faster
Avoid Select and Activate: Work directly with range objects
Use With statements: Cleaner code when setting multiple properties
Qualify worksheet references: Worksheets("Sheet1").Range("A1")
Turn off screen updating: Application.ScreenUpdating = False for long operations
Use Long not Integer: Integer maxes at 32,767 - too small for row numbers
Set references to Nothing: Set rng = Nothing when done

Performance Example

❌ Slow (Cell-by-Cell)

For i = 1 To 10000
Cells(i, 1).Value = i
Cells(i, 2).Value = i * 2
Next i

Takes several seconds for 10,000 rows

✓ Fast (Array Method)

Dim arr(1 To 10000, 1 To 2)
For i = 1 To 10000
arr(i, 1) = i
arr(i, 2) = i * 2
Next i
Range("A1:B10000") = arr

Completes in milliseconds!

Related VBA Tutorials

Generate Range Code Automatically

Let AI write your VBA range manipulation code with best practices

✓ No credit card required ✓ 5 free generations