Prev: Conditional formating using VBA
Next: Syntax help
From: OssieMac on 8 Apr 2010 16:51 Try this. It will leave a blank for any not found. However, if running the code on the same range as has been previously used then need to clear the range first otherwise it will leave the old value. Note that a space and an underscore at the end of a line is a line break in an otherwise single line of code. Worksheets("MarketList") _ .Range("C2:C" & lRow).Offset(0, -1) _ .ClearContents For Each c In Worksheets("MarketList") _ .Range("C2:C" & lRow).Cells On Error Resume Next c.Offset(0, -1) = Application.WorksheetFunction _ .VLookup(c, VendorTable, 2, False) On Error GoTo 0 'Reset error trapping ASAP Next c -- Regards, OssieMac
From: Chip Pearson on 8 Apr 2010 16:53 There are two ways to handle an error from a worksheet function used in VBA. If you include the WorksheetFunction reference in the line of code, you need to use On Error Resume Next, call the function, and test the Err.Number value: Dim V As Variant On Error Resume Next Err.Clear V = Application.WorksheetFunction.VLookup(123, Range("A1:C10"), 3, False) If Err.Number <> 0 Then Debug.Print "error with VLOOKUP" End If You can omit the WorksheetFunction from the call. In this case, the Variant V will contain an error subtype value indicating the error. No On Error Resume Next is required. Dim V As Variant V = Application.VLookup(123, Range("A1:C10"), 3, False) If IsError(V) Then Debug.Print "error with VLOOKUP" End If Cordially, Chip Pearson Microsoft Most Valuable Professional, Excel, 1998 - 2010 Pearson Software Consulting, LLC www.cpearson.com On Thu, 8 Apr 2010 13:16:01 -0700, Ayo <Ayo(a)discussions.microsoft.com> wrote: >Thanks Mac. >Now how do I account for the occassion when >Application.WorksheetFunction.VLookup(c, VendorTable, 2,False) IsNA?. > How do I write that in code. > > > >"OssieMac" wrote: > >> Also there is no need to activate/select worksheets or ranges. The following >> code >> >> Worksheets("MarketList").Activate >> lRow = ActiveSheet.UsedRange.Rows.Count >> >> can be replaced with this >> >> With Worksheets("MarketList") >> lRow = .UsedRange.Rows.Count >> End With >> >> or with this >> lRow = Worksheets("MarketList").UsedRange.Rows.Count >> >> -- >> Regards, >> >> OssieMac >> >>
From: Ayo on 8 Apr 2010 17:07 The same error "Unable to get VLookup property of WorksheetFunction class" is back. Run-time error '1004': "OssieMac" wrote: > > Try this. It will leave a blank for any not found. However, if running the > code on the same range as has been previously used then need to clear the > range first otherwise it will leave the old value. > > Note that a space and an underscore at the end of a line is a line break in > an otherwise single line of code. > > Worksheets("MarketList") _ > .Range("C2:C" & lRow).Offset(0, -1) _ > .ClearContents > > For Each c In Worksheets("MarketList") _ > .Range("C2:C" & lRow).Cells > On Error Resume Next > c.Offset(0, -1) = Application.WorksheetFunction _ > .VLookup(c, VendorTable, 2, False) > On Error GoTo 0 'Reset error trapping ASAP > Next c > > -- > Regards, > > OssieMac > >
From: Ayo on 8 Apr 2010 17:35 Thanks Chip. I know what the error is, I just want to ignore it. The error is because the lookup_value is not in the range. When this occurs, I what the macro to ignore the error and move on to the next cell. That is what I am trying to get to. "Chip Pearson" wrote: > There are two ways to handle an error from a worksheet function used > in VBA. If you include the WorksheetFunction reference in the line of > code, you need to use On Error Resume Next, call the function, and > test the Err.Number value: > > Dim V As Variant > On Error Resume Next > Err.Clear > V = Application.WorksheetFunction.VLookup(123, Range("A1:C10"), 3, > False) > If Err.Number <> 0 Then > Debug.Print "error with VLOOKUP" > End If > > > You can omit the WorksheetFunction from the call. In this case, the > Variant V will contain an error subtype value indicating the error. No > On Error Resume Next is required. > > Dim V As Variant > V = Application.VLookup(123, Range("A1:C10"), 3, False) > If IsError(V) Then > Debug.Print "error with VLOOKUP" > End If > > > Cordially, > Chip Pearson > Microsoft Most Valuable Professional, > Excel, 1998 - 2010 > Pearson Software Consulting, LLC > www.cpearson.com > > > > > > > On Thu, 8 Apr 2010 13:16:01 -0700, Ayo <Ayo(a)discussions.microsoft.com> > wrote: > > >Thanks Mac. > >Now how do I account for the occassion when > >Application.WorksheetFunction.VLookup(c, VendorTable, 2,False) IsNA?. > > How do I write that in code. > > > > > > > >"OssieMac" wrote: > > > >> Also there is no need to activate/select worksheets or ranges. The following > >> code > >> > >> Worksheets("MarketList").Activate > >> lRow = ActiveSheet.UsedRange.Rows.Count > >> > >> can be replaced with this > >> > >> With Worksheets("MarketList") > >> lRow = .UsedRange.Rows.Count > >> End With > >> > >> or with this > >> lRow = Worksheets("MarketList").UsedRange.Rows.Count > >> > >> -- > >> Regards, > >> > >> OssieMac > >> > >> > . >
From: OssieMac on 9 Apr 2010 00:54
Did you change anything in the code? The following is the entire sub that I used to test and it works fine. Sub test() Dim c As Range Dim lRow As Long Dim BOReport_lastRow Dim VendorTable As Range lRow = Worksheets("MarketList").UsedRange.Rows.Count With Worksheets("AAV_Table") BOReport_lastRow = .UsedRange.Rows.Count Set VendorTable = .Range("B2:C" & BOReport_lastRow) End With Worksheets("MarketList") _ .Range("C2:C" & lRow).Offset(0, -1) _ .ClearContents For Each c In Worksheets("MarketList") _ .Range("C2:C" & lRow).Cells On Error Resume Next c.Offset(0, -1) = Application.WorksheetFunction _ .VLookup(c, VendorTable, 2, False) On Error GoTo 0 'Reset error trapping ASAP Next c End Sub -- Regards, OssieMac |