Compartir vía


Objeto Names (Excel)

Colección de todos los objetos Name de la aplicación o del libro.

Comentarios

Cada objeto Name representa un nombre definido para un rango de celdas. Los nombres pueden ser nombres integrados(como base de datos, Print_Area y Auto_Open) o nombres personalizados.

El argumento RefersTo debe especificarse en notación de estilo A1, incluidos signos de dólar ($) donde corresponda. Por ejemplo, si la celda A10 está seleccionada en Sheet1 y se define un nombre mediante el argumento RefersTo "=sheet1!A1:B1", el nuevo nombre en realidad hará referencia a las celdas A10:B10 (puesto que se ha especificado una referencia relativa). Para especificar una referencia absoluta, use "=sheet1!$A$1:$B$1".

Ejemplo:

Utilice la propiedad Names del objeto Workbook para devolver la colección Names . En el ejemplo siguiente se crea una lista de todos los nombres del libro activo, además de las direcciones a las que hacen referencia.

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

Use el método Add para crear un nombre y agregarlo a la colección. En el ejemplo siguiente se crea un nuevo nombre que hace referencia a las celdas A1:C20 de la hoja de cálculo denominada Sheet1.

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

Use Names (index), donde index es el número de índice de nombre o el nombre definido, para devolver un único objeto Name . En el ejemplo siguiente se elimina el nombre mySortRange del libro activo.

ActiveWorkbook.Names("mySortRange").Delete

En este ejemplo se usa un rango con nombre como la fórmula de validación de datos. En este ejemplo se requiere que la validación de datos sea en la Hoja 2 en el rango A2:A100. Estos datos de validación se usan para validar los datos especificados en Sheet1 en el intervalo 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

Métodos

Propiedades

Vea también

Soporte técnico y comentarios

¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.