共用方式為


Excel) (Names 物件

應用程式或活頁簿中所有 Name 物件的集合。

註解

每個 Name 物件都代表某個儲存格範圍的已定義名稱。 名稱可以是內建名稱,例如資料庫、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

此範例使用具名範圍做為資料驗證的公式。 此範例需要驗證資料位在 Sheet 2 上的範圍 A2:A100 中。 此驗證資料是用來驗證在 Sheet1 上輸入 D2:D10 範圍中的資料。

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 支援與意見反應