这些示例演示如何选择已使用的区域(包括不包含数据的带格式单元格),以及如何选择数据区域(包括包含实际数据的单元格)。
示例代码提供者: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 在业务管理和 Microsoft Office 应用程序开发方面拥有 25 年以上的经验,与他人合著过“Holy Macro! It's 2,500 Excel VBA Examples”(Holy Macro! 2,500 个 Excel VBA 示例)。
支持和反馈
有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。