Sei sulla pagina 1di 4

Creating a Name Report in Excel

If you use lots of named cells and ranges in your workbook, you may be surprised to discover that
Excel provides no way to list the details for each name. Useful information appears in the Name
Manager dialog box, but there is no way to display this information in a manner that can be printed.
The VBA code below generates a useful report that describes the names defined in any workbook.

Example Name Report


The figure below shows an example of a Name Report.

The report, which is created on a new worksheet, includes the following information for each name:
Name: The name.
RefersTo: The definition for the name. Usually, this will be a cell or range, but a name can also
define formula.
Cells: The number of cells contained in the named range. For named formulas, this field
displays #N/A.

Wiley, the Wiley logo, For Dummies and all related trademarks, logos, and trade dress are trademarks or registered trademarks of John Wiley & Sons, Inc. and/or its affiliates.

Creating a Name Report in Excel

Scope: The scope of the name, either Workbook, or the name of the specific worksheet on which
the name is valid.
Hidden: True if the name is hidden. Hidden names are created by some add-ins (such as Solver),
and do not appear in the Name Manager dialog box.
Error: True if the name contains an erroneous reference.
Link: A hyperlink that, when clicked, activates the named range. Only names that refer to cells or
ranges include a link.
Comment: The comment for the name, if any.

The VBA Code


To use this code, press Alt+F11 to activate Visual Basic Editor. Then choose Insert -> Module to
insert a new VBA module. Copy the code and paste it into the new module.
Sub GenerateNameReport()
'
Generates a report for all names in the workbook
'
(Does not include Table names)
Dim n As Name
Dim Row As Long
Dim CellCount As Variant
'

Exit if no names
If ActiveWorkbook.Names.Count = 0 Then
MsgBox "The active workbook has no defined names."
Exit Sub
End If

'

Exit if workbook is protected


If ActiveWorkbook.ProtectStructure Then
MsgBox "A new sheet cannot be added because the workbook is protected."
Exit Sub
End If

'

Insert a new sheet for the report


ActiveWorkbook.Worksheets.Add
ActiveSheet.Move After:=Sheets(ActiveWorkbook.Sheets.Count)
ActiveWindow.DisplayGridlines = False

'

Add first line of title


Range("A1:H1").Merge
With Range("A1")
.Value = "Name Report for: " & ActiveWorkbook.Name
.Font.Size = 14
.Font.Bold = True
.HorizontalAlignment = xlCenter
End With

Wiley, the Wiley logo, For Dummies and all related trademarks, logos, and trade dress are trademarks or registered trademarks of John Wiley & Sons, Inc. and/or its affiliates.

Creating a Name Report in Excel


'

Add second line of title


Range("A2:H2").Merge
With Range("A2")
.Value = "Generated " & Now
.HorizontalAlignment = xlCenter
End With

'

Add the headers


Range("A4:H4") = Array("Name", "RefersTo", "Cells", _
"Scope", "Hidden", "Error", "Link", "Comment")

'

Loop through the names


Row = 4
On Error Resume Next
For Each n In ActiveWorkbook.Names
Row = Row + 1
'Column A: Name
If n.Name Like "*!*" Then
Cells(Row, 1) = Split(n.Name, "!")(1) ' Remove sheet name
Else
Cells(Row, 1) = n.Name
End If
'Column B: RefersTo
Cells(Row, 2) = "'" & n.RefersTo
'Column C: Number of cells
CellCount = CVErr(xlErrNA) ' Return value for named formula
CellCount = n.RefersToRange.CountLarge
Cells(Row, 3) = CellCount
' Column D: Scope
If n.Name Like "*!*" Then
Cells(Row, 4) = Split(n.Name, "!")(0) ' extract sheet name
Cells(Row, 4) = Replace(Cells(Row, 4), "'", "") 'remove apostrophes
Else
Cells(Row, 4) = "Workbook"
End If
'Column E: Hidden status
Cells(Row, 5) = Not n.Visible
'Column F: Erroroneous name
Cells(Row, 6) = n.RefersTo Like "*[#]REF!*"

'Column G: Hyperlink
If Not Application.IsNA(Cells(Row, 3)) Then
ActiveSheet.Hyperlinks.Add _
Anchor:=Cells(Row, 7), _
Address:="", _
SubAddress:=n.Name, _
TextToDisplay:=n.Name
End If

Wiley, the Wiley logo, For Dummies and all related trademarks, logos, and trade dress are trademarks or registered trademarks of John Wiley & Sons, Inc. and/or its affiliates.

Creating a Name Report in Excel


'Column H: Comment
Cells(Row, 8) = n.Comment
Next n
'

Convert it to a table
ActiveSheet.ListObjects.Add _
SourceType:=xlSrcRange, _
Source:=Range("A4").CurrentRegion

'

Adjust the column widths


Columns("A:H").EntireColumn.AutoFit
End Sub

Generating a Report
Execute the GenerateNameReport procedure, and the report is generated on a new worksheet in
the active workbook. The code doesn't have to be in the workbook that contains the names for the
report.

If you find this code useful, you might want to store it in your Personal Macro Workbook,
or create an add-in.

About the Author


John Walkenbach, known to his fans as Mr.
Spreadsheet, has written some 50 books and
around 300 articles on computer topics,
predominantly Excel. He created the awardwinning Power Utitlity Pak and several other
versatile Excel add-ons. John also maintains
the popular Spreadsheet Page website, where
users can find free tips, downloads, and other
Excel tools.

978-1-118-49037-2
Wiley, the Wiley logo, For Dummies and all related trademarks, logos, and trade dress are trademarks or registered trademarks of John Wiley & Sons, Inc. and/or its affiliates.

Potrebbero piacerti anche