Name.RefersToLocal property (Excel)

Returns or sets the formula that the name refers to. The formula is in the language of the user, and it's in A1-style notation, beginning with an equal sign. Read/write String.

Syntax

expression.RefersToLocal

expression A variable that represents a Name object.

Example

This example creates a new worksheet and then inserts a list of all the names in the active workbook, including their formulas (in A1-style notation and in the language of the user).

Set newSheet = ActiveWorkbook.Worksheets.Add 
i = 1 
For Each nm In ActiveWorkbook.Names 
 newSheet.Cells(i, 1).Value = nm.NameLocal 
 newSheet.Cells(i, 2).Value = "'" & nm.RefersToLocal 
 i = i + 1 
Next

Known issues

This property has a bug. Assigning a localized formula to this property fails. The property expects the same formula syntax as the RefersTo property: US format and list separators. Example:

Sub Example()
    Dim Nm As Name
    Set Nm = ThisWorkbook.Names("test")
    'If Windows is set to use ; as listseparator, this fails:
    Nm.RefersToLocal = "=SUM(Sheet1!$A$1,Sheet1!$A$3)"
    'If Windows is set to use ; as listseparator, this works:
    Nm.RefersToLocal = "=SUM(Sheet1!$A$1;Sheet1!$A$3)"
End Sub

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.