這些範例示範如何選取已使用的範圍,其中包含不包含資料的格式化儲存格,以及如何選取包含實際資料的資料格資料範圍。
範例程式碼提供者: Tom Urtis,Atlas Programming Management
選取已使用的範圍
此範例示範如何使用Worksheet物件的UsedRange屬性和Range物件的Select方法,選取目前工作表上的已使用範圍,其中包含不包含資料的格式化儲存格。 然後它會向使用者顯示範圍的位址。
Sub SelectUsedRange()
ActiveSheet.UsedRange.Select
MsgBox "The used range address is " & ActiveSheet.UsedRange.Address(0, 0) & ".", 64, "Used range address:"
End Sub
從儲存格 A1 開始選取資料範圍
此範例示範如何選取目前工作表上的資料範圍,從儲存格 A1 開始,然後向使用者顯示範圍的位址。 資料範圍不包含格式化且不包含資料的儲存格。 若要取得資料範圍,這個範例會使用Range物件的Find方法,尋找包含實際資料的最後一個資料列和最後一個資料行。
Sub SelectDataRange()
Dim LastRow As Long, LastColumn As Long
LastRow = Cells.Find(What:="*", After:=Range("A1"), SearchOrder:=xlByRows, SearchDirection:=xlPrevious).Row
LastColumn = Cells.Find(What:="*", After:=Range("A1"), SearchOrder:=xlByColumns, SearchDirection:=xlPrevious).Column
Range("A1").Resize(LastRow, LastColumn).Select
MsgBox "The data range address is " & Selection.Address(0, 0) & ".", 64, "Data-containing range address:"
End Sub
選取未知起始位置的資料範圍
此範例示範當您不知道開始位置時,如何選取目前工作表上的資料範圍,並將範圍的位址顯示給使用者。 資料範圍不包含格式化且不包含資料的儲存格。 若要取得資料範圍,此範例會使用Range物件的Find方法,尋找包含實際資料的第一個和最後一個資料列和資料行。
Sub UnknownRange()
If WorksheetFunction.CountA(Cells) = 0 Then
MsgBox "There is no range to be selected.", , "No cells contain any values."
Exit Sub
Else
Dim FirstRow&, FirstCol&, LastRow&, LastCol&
Dim myUsedRange As Range
FirstRow = Cells.Find(What:="*", SearchDirection:=xlNext, SearchOrder:=xlByRows).Row
On Error Resume Next
FirstCol = Cells.Find(What:="*", SearchDirection:=xlNext, SearchOrder:=xlByColumns).Column
If Err.Number <> 0 Then
Err.Clear
MsgBox _
"There are horizontally merged cells on the sheet" & vbCrLf & _
"that should be removed in order to locate the range.", 64, "Please unmerge all cells."
Exit Sub
End If
LastRow = Cells.Find(What:="*", SearchDirection:=xlPrevious, SearchOrder:=xlByRows).Row
LastCol = Cells.Find(What:="*", SearchDirection:=xlPrevious, SearchOrder:=xlByColumns).Column
Set myUsedRange = Range(Cells(FirstRow, FirstCol), Cells(LastRow, LastCol))
myUsedRange.Select
MsgBox "The data range on this worksheet is " & myUsedRange.Address(0, 0) & ".", 64, "Range address:"
End If
End Sub
關於參與者
MVP Tom Urtis 是 Atlas Programming Management 的創辦人,這家公司位於矽谷,專門提供 Microsoft Office 和 Excel 商務解決方案全套服務。 Tom 擁有 25 年的業務管理和開發 Microsoft Office 應用程式的經驗,並共同編寫了《Holy Macro! It's 2,500 Excel VBA Examples》。
支援和意見反應
有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應。