(Excel) 命名对象

应用程序或工作簿中所有 Name 对象的集合。

备注

每一个 Name 对象都代表一个单元格区域的定义名称。 名称可以是内置名称(例如 Database、Print_Area 和 Auto_Open),也可以是自定义名称。

RefersTo 参数必须以 A1 样式表示法指定,包括必要时使用的美元符 ($)。 例如,如果在 Sheet1 上选定了单元格 A10,并且通过将 RefersTo 参数“=Sheet1!A1:B1”而定义了一个名称,那么该新名称实际上指向单元格区域 A10:B10(因为指定的是相对引用)。 若要指定绝对引用,请使用“=Sheet1!$A$1:$B$1”。

示例

使用 Workbook 对象的 Names 属性可返回 Names 集合。 以下示例创建活动工作簿中所有名称及其引用的地址的列表。

Set nms = ActiveWorkbook.Names 
Set wks = Worksheets(1) 
For r = 1 To nms.Count 
    wks.Cells(r, 2).Value = nms(r).Name 
    wks.Cells(r, 3).Value = nms(r).RefersToRange.Address 
Next

使用 Add 方法创建名称并将其添加到集合。 以下示例创建一个新名称,该名称引用名为 Sheet1 的工作表上的单元格 A1:C20。

Names.Add Name:="test", RefersTo:="=sheet1!$a$1:$c$20"

使用 名称 (索引) (其中 index 是名称索引号或定义的名称)可返回单个 Name 对象。 以下示例从活动工作簿中删除名称 mySortRange。

ActiveWorkbook.Names("mySortRange").Delete

此示例使用命名区域作为公式来进行数据验证。 此示例要求验证数据位于 Sheet2 上的区域 A2:A100 中。 此验证数据用于验证 D2:D10 范围内的 Sheet1 上输入的数据。

Sub Add_Data_Validation_From_Other_Worksheet()
'The current Excel workbook and worksheet, a range to define the data to be validated, and the target range
'to place the data in.
Dim wbBook As Workbook
Dim wsTarget As Worksheet
Dim wsSource As Worksheet
Dim rnTarget As Range
Dim rnSource As Range

'Initialize the Excel objects and delete any artifacts from the last time the macro was run.
Set wbBook = ThisWorkbook
With wbBook
    Set wsSource = .Worksheets("Sheet2")
    Set wsTarget = .Worksheets("Sheet1")
    On Error Resume Next
    .Names("Source").Delete
    On Error GoTo 0
End With

'On the source worksheet, create a range in column A of up to 98 cells long, and name it "Source".
With wsSource
    .Range(.Range("A2"), .Range("A100").End(xlUp)).Name = "Source"
End With

'On the target worksheet, create a range 8 cells long in column D.
Set rnTarget = wsTarget.Range("D2:D10")

'Clear out any artifacts from previous macro runs, then set up the target range with the validation data.
With rnTarget
    .ClearContents
    With .Validation
        .Delete
        .Add Type:=xlValidateList, _
             AlertStyle:=xlValidAlertStop, _
             Formula1:="=Source"
        
'Set up the Error dialog with the appropriate title and message
        .ErrorTitle = "Value Error"
        .ErrorMessage = "You can only choose from the list."
    End With
End With

End Sub

方法

属性

另请参阅

支持和反馈

有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。