-
Excel VBA - Verify A Named Range Exists
I found this piece of code on the web to verify whether or not a named range exists.
Code:
Function NameExists(TheName As String) As Boolean
On Error Resume Next
NameExists = Len(ThisWorkbook.Names(TheName).Name) <> 0
End Function
I use it like this
Code:
If NameExists("PYAcuteBase") = True Then
Wkb1.Sheets("HFR Setting").Range(pyactuebase).PasteSpecial Paste:=xlPasteValues, Operation:=xlNone, SkipBlanks:= _
False, Transpose:=False
Else
Wkb1.Sheets("HFR Setting").Range("E16").PasteSpecial Paste:=xlPasteValues, Operation:=xlNone, SkipBlanks:= _
False, Transpose:=False
End If
But, it always returns False even when the range does exist.
I just need to know if a range name exists...if it does, then I want to use it. If it doesn't, not big deal, I will just hard code the cell location I want.
-
I use a Function almost identical to yours, and it works fine.
Code:
Public Function IsRangeName(RangeName As String) As Boolean
On Error Resume Next
IsRangeName = Len(Names(RangeName).Name) <> 0
End Function
-
Ok...maybe it is how I'm calling it.
What code do you use to call your IsRangeName function? Is it similiar to my If/Else statement?
-
After much playing around I came up with this which seems to work just fine. Any of you Excel gurus see a potential problem that I don't see with using this?
Code:
Function NamedRangeExists(strName As String, Optional wkbName As String) As Boolean
Dim rngRangeNameToFind As Range
Dim i As Long
On Error Resume Next 'because we will be going through all ranges, all non matches
'will generate an error that we can avoid
If wkbName = vbNullString Then wkbName = ActiveWorkbook.Name
With Workbooks(wkbName)
For i = 1 To .Sheets.Count Step 1
Set rngRangeNameToFind = .Sheets(i).Range(strName)
Select Case Err.Number
Case 0
NamedRangeExists = True
Exit Function
Case 1004 '"Application defined or Object Defined error" - this is what
'we will get if the range name does not exist so just
'clear it out and move on
Err.Clear
Case Else
MsgBox Err.Number & " " & Err.Description
End Select
Next
End With
On Error GoTo 0
End Function
-
Corrected function
Hi,
You both had the same error in the function.
It has to be "Len(.Range(RangeName).Name"
And also make sure, the function has a false value first. If then an object error occurs because the name does not exist, it stays false; if the name exist, it gets true:
Code:
Public Function IsRangeName(mySh As Worksheet, RangeName As String) As Boolean
On Error Resume Next
IsRangeName = False
IsRangeName = Len(mySh.Range(RangeName).Name) <> 0
End Function
-
Why the "On Error Resume Next" (basically I would rather have a double root canal than ever use that - if there is an error I want to correct it, or handle it, not ignore it.)
-
 Originally Posted by Hack
Why the "On Error Resume Next" (basically I would rather have a double root canal than ever use that - if there is an error I want to correct it, or handle it, not ignore it.)
As there is no method to check for if the name exists, the ERROR raised when accessing a non-existing name is what we need to detect if it exists or not.
So there is no complicated error-handling necessary because the method only does exactly this and we know that the error can only come from this event because that's what we're actually testing. Therefore the error itself can be ignored.
-
A version wihout messages
 Originally Posted by KerryXEX
Hi,
You both had the same error in the function.
It has to be "Len( .Range(RangeName).Name"
And also make sure, the function has a false value first. If then an object error occurs because the name does not exist, it stays false; if the name exist, it gets true:
Code:
Public Function IsRangeName(mySh As Worksheet, RangeName As String) As Boolean
On Error Resume Next
IsRangeName = False
IsRangeName = Len(mySh.Range(RangeName).Name) <> 0
End Function
Here's a simple version that excludes messages:
Code:
Function RangeNameExists(RangeName As String, Optional Wkbk As Workbook) As Boolean
' Returns TRUE if the range name exists.
Dim i As Long, RangeToFind As Range
Dim S As String
RangeNameExists = False
If Wkbk Is Nothing Then
Set Wkbk = ActiveWorkbook
End If
Err.Clear
On Error Resume Next
With Wkbk
For i = 1 To .Sheets.Count
' S = .Sheets(i).Name 'For test purposes.
Set RangeToFind = .Sheets(i).Range(RangeName)
If Err.Number = 0 Then
RangeNameExists = True
Exit For
Else
Err.Clear
End If
Next i
End With
On Error GoTo 0
Err.Clear
End Function
Last edited by Hack; 11-25-2013 at 08:53 AM.
Reason: added code tags
-
 Originally Posted by KerryXEX
Hi,
You both had the same error in the function.
It has to be "Len( .Range(RangeName).Name"
And also make sure, the function has a false value first. If then an object error occurs because the name does not exist, it stays false; if the name exist, it gets true:
Code:
Public Function IsRangeName(mySh As Worksheet, RangeName As String) As Boolean
On Error Resume Next
IsRangeName = False
IsRangeName = Len(mySh.Range(RangeName).Name) <> 0
End Function
ALL VBA Variables are automatically initialized by VBA Including retrun values
Therefore IsRangeName = False is redundant
Then default RANGE object in EXCEL is the Workbook.Range, therefore only RANGE(RangeName).Name is required to return the name of the specified range.
FYI: a Boolean data type internally is considered a numeric data type with the values of 0 or -1
where 0 is false and -1 is true. Since all numeric variables initialize to zero, a boolean variable's
initialization to 0 is automatically FALSE...
The only error you will get with this is when the RangeName does not exsist
So simply ignoring the error and allowing the function to return its's default value of zero
which as a boolean data type means False, is the correct responce.
Similar Threads
-
By Hack in forum VB Classic
Replies: 4
Last Post: 09-24-2008, 09:02 AM
-
By Tord in forum VB Classic
Replies: 3
Last Post: 09-15-2008, 01:26 PM
-
By slimasian in forum .NET
Replies: 0
Last Post: 05-15-2008, 04:24 PM
-
Replies: 1
Last Post: 01-02-2007, 09:58 AM
-
By blayne in forum VB Classic
Replies: 1
Last Post: 11-17-2005, 07:14 PM
Posting Permissions
- You may not post new threads
- You may not post replies
- You may not post attachments
- You may not edit your posts
-
Forum Rules
|
Development Centers
-- Android Development Center
-- Cloud Development Project Center
-- HTML5 Development Center
-- Windows Mobile Development Center
|