Consulting

Results 1 to 13 of 13

Thread: Solved: VLOOKUP in VBA not working

  1. #1
    VBAX Expert
    Joined
    Dec 2007
    Posts
    522
    Location

    Solved: VLOOKUP in VBA not working

    HI All,

    I have a worksheet userform which I am developing using VBA.

    In this particular case, I would like when the user runs a macro to do a VLOOKUP in VBA and place the value in a specified cell in the macro.

    Currently, If I run the following code to evaluate the VLOOKUP value in VBA and place it in the target range i.e. 2 rows below Range("Section7_a"):

    [vba]Sub Pensioner_Data_Autofill(rngSrcPensioner As Range)

    rngSrcPensioner.Offset(2, 0).Value = _
    Application.Evaluate(Application.VLookup(rngSrcPensioner.Value, _
    Range("SECTION7_Autofill_Data"), 5, False))

    End Sub[/vba]

    and call this macro as follows:

    [vba]Sub Pensioner1_Autofill()

    Call Pensioner_Data_Autofill(Range("Section7_a"))
    End Sub[/vba]
    It displays a #NAME? value in the cell 2 rows down from Range("Section7_a"), as specified.

    However, as a means of debugging, I tried the following to display the full VLOOKUP Formula as follows:

    [vba]Sub Pensioner_Data_Autofill(rngSrcPensioner As Range)

    rngSrcPensioner.Offset(2, 0).Formula = _
    "=VLookup(Section7_a, SECTION7_Autofill_Data, 5, False)"

    End Sub[/vba]
    It prints the full formula in the cell 2 rows below Range("Section7_a") as
    "=VLOOKUP(Section7_a, SECTION7_Autofill_Data, 5, FALSE)" and prints the correct value as "M".

    I don't understand why the first approach to evaluate the vlookup value (i.e. not display the formula) in VBA is not working? Could anyone please suggest how to make it work, as I woould not like to print a formula for the client?

    As the form is confidential, it's difficult for me to post it online.

    Any help appreciated.

  2. #2
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,844
    would this work? (not tested):
    [VBA]rngSrcPensioner.Offset(2, 0).Value = Application.WorksheetFunction.VLookup(rngSrcPensioner.Value, Range("SECTION7_Autofill_Data"), 5, False)
    [/VBA]

    There's a good article on the Evaluate Method on this site at:
    http://vbaexpress.com/forum/showthread.php?t=10311
    which will probalby answer your question.

    p45cal
    p45cal
    Everyone: If I've helped and you can't be bothered to acknowledge it, I can't be bothered to look at further posts from you.

  3. #3
    VBAX Expert
    Joined
    Dec 2007
    Posts
    522
    Location
    Quote Originally Posted by p45cal
    would this work? (not tested):
    [vba]rngSrcPensioner.Offset(2, 0).Value = Application.WorksheetFunction.VLookup(rngSrcPensioner.Value, Range("SECTION7_Autofill_Data"), 5, False)
    [/vba]
    There's a good article on the Evaluate Method on this site at:
    http://vbaexpress.com/forum/showthread.php?t=10311
    which will probalby answer your question.

    p45cal
    p45cal, works really well - thank you!

    Just to extend this slightly, I have a question - as I understand the main difference between:

    [vba]Application.WorksheetFunction.VLookup(rngSrcPensioner.Value, Range("SECTION7_Autofill_Data"), 5, False)[/vba]
    and:

    [vba]Application.VLookup(rngSrcPensioner.Value, Range("SECTION7_Autofill_Data"), 5, False)[/vba]
    is error handling. I have been told that the second approach is usually more robust than the first. Do you agree with this?

    Also with either approach, could you please suggest any error-handling techniques I could apply to this simple macro?

    Kind regards and thanks again.

  4. #4
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,443
    Location
    There are two ways to invoke worksheet functions in VBA, either using the function as a property of the WorksheetFunction property, or as property of the Application object.

    As an example, the SUM function can be called with Application.SUM, or with Worksheetfunction.SUM.

    Application was how worksheet functions were invoked prior to Excel 97, and has been retained for compatibility. Although both work, there are some nuances in the way in which they work.

    • WorksheetFunction,and Application.WorksheetFunction, supports the "auto list members" option, whereas Application alone does not.
    • Not all worksheet functions are exposed to VBA. Functions not exposed by the WorksheetFunction object usually have a VBA equivalent (e.g., Left, Year), but they do not necessarily work in exactly the same way.
    • Functions within Add-ins, such as the Analysis Toolpak, cannot be called with Application or WorksheetFunction.
    • WorksheetFunction is faster than Application, by an order of circa 20%.
    • Errors are handled differently. When a function is called directly using Application, such as Application.VLookup, the result is a variant containing an error. When called directly using WorksheetFunction, for example WorksheetFunction.VLookup, the function will raise an error. Both can be managed, but in different ways

    [vba]

    Dim res As Variant
    res = Application.VLookup(1, Range("A1:B10"), 2, False)

    res = WorksheetFunction.VLookup(1, Range("A1:B10"), 2, False)
    [/vba]

    Here, the VLOOKUP function is being invoked to lookup a value that does not exist in the range A1:B10. The first method, Application.Vlookup, returns an error to the variable, whereas the second method raises an error.

    Application calls can also be trapped using the IsError statement

    [vba]

    If IsError(Application.VLookup(1, Range("A1:B10"), 2, False)) Then
    Debug.Print "error"
    End If
    [/vba]

    In a similar manner, WorksheetFunction calls can be wrapped in error handling code to trap the errors.

    [vba]

    On Error Resume Next
    res = WorksheetFunction.VLookup(1, Range("A1:B10"), 2, False)
    On Error GoTo 0
    Debug.Print res
    [/vba]

    In this instance, res will be an empty variable.
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  5. #5
    VBAX Tutor david000's Avatar
    Joined
    Mar 2007
    Location
    Chicago
    Posts
    276
    Location
    Thanks xld,
    That's a very nice explanation. I've been wondering that for ages. I even had a sheet set up to ask that very question one day!

    [vba]
    Public Sub ProcessData()
    Dim i As Long
    Dim iLastRow As Long
    With ActiveSheet

    iLastRow = .Cells(.Rows.Count, "A").End(xlUp).Row
    For i = iLastRow To 5 Step -1

    If IsError(Application.Match(.Cells(i, "A").Value, Range("d1:d3"), 0)) Then

    .Rows(i).Delete
    End If
    Next i

    End With
    End Sub

    Public Sub ProcessData2()
    Dim i As Long
    Dim iLastRow As Long
    With ActiveSheet

    iLastRow = .Cells(.Rows.Count, "A").End(xlUp).Row
    For i = iLastRow To 5 Step -1
    On Error Resume Next
    If IsError(Application.WorksheetFunction.Match(.Cells(i, "A").Value, Range("d1:d3"), 0)) Then
    On Error GoTo 0
    .Rows(i).Delete
    End If
    Next i

    End With
    End Sub



    [/vba]

  6. #6
    VBAX Expert
    Joined
    Dec 2007
    Posts
    522
    Location
    Quote Originally Posted by xld
    There are two ways to invoke worksheet functions in VBA, either using the function as a property of the WorksheetFunction property, or as property of the Application object.

    As an example, the SUM function can be called with Application.SUM, or with Worksheetfunction.SUM.

    Application was how worksheet functions were invoked prior to Excel 97, and has been retained for compatibility. Although both work, there are some nuances in the way in which they work.

    • WorksheetFunction,and Application.WorksheetFunction, supports the "auto list members" option, whereas Application alone does not.
    • Not all worksheet functions are exposed to VBA. Functions not exposed by the WorksheetFunction object usually have a VBA equivalent (e.g., Left, Year), but they do not necessarily work in exactly the same way.
    • Functions within Add-ins, such as the Analysis Toolpak, cannot be called with Application or WorksheetFunction.
    • WorksheetFunction is faster than Application, by an order of circa 20%.
    • Errors are handled differently. When a function is called directly using Application, such as Application.VLookup, the result is a variant containing an error. When called directly using WorksheetFunction, for example WorksheetFunction.VLookup, the function will raise an error. Both can be managed, but in different ways

    [vba]

    Dim res As Variant
    res = Application.VLookup(1, Range("A1:B10"), 2, False)

    res = WorksheetFunction.VLookup(1, Range("A1:B10"), 2, False)
    [/vba]
    Here, the VLOOKUP function is being invoked to lookup a value that does not exist in the range A1:B10. The first method, Application.Vlookup, returns an error to the variable, whereas the second method raises an error.

    Application calls can also be trapped using the IsError statement

    [vba]

    If IsError(Application.VLookup(1, Range("A1:B10"), 2, False)) Then
    Debug.Print "error"
    End If
    [/vba]
    In a similar manner, WorksheetFunction calls can be wrapped in error handling code to trap the errors.

    [vba]

    On Error Resume Next
    res = WorksheetFunction.VLookup(1, Range("A1:B10"), 2, False)
    On Error GoTo 0
    Debug.Print res
    [/vba]
    In this instance, res will be an empty variable.
    Bob that is a fantastic explanation (to reiterate david000's compliments). I had hit the sack by the time your response came through yesterday.

    My code at the moment looks like this:

    [vba]Option Explicit

    Sub Pensioner_Data_Autofill(rngSrcPensioner As Range)

    With rngSrcPensioner

    .Offset(1, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 4, False)

    .Offset(2, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 5, False)

    .Offset(3, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 6, False)

    .Offset(4, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 7, False)

    .Offset(5, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 8, False)

    .Offset(7, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 9, False)

    .Offset(8, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 10, False)

    .Offset(9, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 11, False)

    .Offset(10, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 12, False)

    .Offset(11, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 13, False)

    .Offset(15, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 14, False)

    .Offset(16, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 15, False)

    .Offset(17, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 16, False)

    .Offset(21, 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), 17, False)

    End With

    End Sub[/vba]

    I can't quite loop it very effectively as the offset rows and the VLOOKUP columns don't match incrementally.

    Would I have to wrap the error handling you suggested around each of these Application.WorksheetFunction.VLookup calls, or is there a more efficient way to go about this?

    Sincere thanks for your great help.

  7. #7
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,844
    One, albeit not elegant, solution to the non-incremental looping could be:
    [vba]Sub Pensioner_Data_Autofill(rngSrcPensioner As Range)
    Dim Map, i
    Map = Array("1", "4", "2", "5", "3", "6", "4", "7", "5", "8", "7", "9", "8", "10", "9", "11", "10", "12", "11", "13", "15", "14", "16", "15", "17", "16", "21", "17")
    With rngSrcPensioner
    For i = LBound(Map) To UBound(Map) Step 2
    'Debug.Print "zz" & Map(i) & "zz,xx" & Map(i + 1) & "xx"
    .Offset(CLng(Map(i)), 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), CLng(Map(i + 1)), False)
    Next i
    End With
    End Sub
    [/vba]I've not tested this beyond ensuring the numbers are used in the right order (commented-out debug statement); the CLng conversion may not be necessary. I leave you to put the error handling in.
    p45cal
    ps. to edit more easily and visualise the paired values you can do the likes of this:[vba]Map = Array("1", "4", _
    "2", "5", _
    "3", "6", _
    "4", "7", _
    "5", "8", _
    "7", "9", _
    "8", "10", _
    "9", "11", _
    "10", "12", _
    "11", "13", _
    "15", "14", _
    "16", "15", _
    "17", "16", _
    "21", "17")
    [/vba]
    p45cal
    Everyone: If I've helped and you can't be bothered to acknowledge it, I can't be bothered to look at further posts from you.

  8. #8
    VBAX Expert
    Joined
    Dec 2007
    Posts
    522
    Location
    Quote Originally Posted by p45cal
    One, albeit not elegant, solution to the non-incremental looping could be:
    [vba]Sub Pensioner_Data_Autofill(rngSrcPensioner As Range)
    Dim Map, i
    Map = Array("1", "4", "2", "5", "3", "6", "4", "7", "5", "8", "7", "9", "8", "10", "9", "11", "10", "12", "11", "13", "15", "14", "16", "15", "17", "16", "21", "17")
    With rngSrcPensioner
    For i = LBound(Map) To UBound(Map) Step 2
    'Debug.Print "zz" & Map(i) & "zz,xx" & Map(i + 1) & "xx"
    .Offset(CLng(Map(i)), 0).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), CLng(Map(i + 1)), False)
    Next i
    End With
    End Sub
    [/vba]I've not tested this beyond ensuring the numbers are used in the right order (commented-out debug statement); the CLng conversion may not be necessary. I leave you to put the error handling in.
    p45cal
    ps. to edit more easily and visualise the paired values you can do the likes of this:[vba]Map = Array("1", "4", _
    "2", "5", _
    "3", "6", _
    "4", "7", _
    "5", "8", _
    "7", "9", _
    "8", "10", _
    "9", "11", _
    "10", "12", _
    "11", "13", _
    "15", "14", _
    "16", "15", _
    "17", "16", _
    "21", "17")
    [/vba]
    p45cal, that works wonderfully. Thank you very much.

    Great to learn these cool VBA tricks for use in future projects.

    Kind regards

  9. #9
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,844
    I've been utterly stupid.. why did I use strings and convert them back??[vba]Sub Pensioner_Data_Autofill(rngSrcPensioner As Range)
    Dim Map, i
    Map = Array(1, 4, 2, 5, 3, 6, 4, 7, 5, 8, 7, 9, 8, 10, 9, 11, 10, 12, 11, 13, 15, 14, 16, 15, 17, 16, 21, 17)
    With rngSrcPensioner
    For i = LBound(Map) To UBound(Map) Step 2
    .Offset(Map(i)).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), Map(i + 1), False)
    Next i
    End With
    End Sub
    [/vba]Not tested. Incidentally you don't need the ",0" in the offset statement.
    p45cal
    Everyone: If I've helped and you can't be bothered to acknowledge it, I can't be bothered to look at further posts from you.

  10. #10
    VBAX Expert
    Joined
    Dec 2007
    Posts
    522
    Location
    Quote Originally Posted by p45cal
    I've been utterly stupid.. why did I use strings and convert them back??[vba]Sub Pensioner_Data_Autofill(rngSrcPensioner As Range)
    Dim Map, i
    Map = Array(1, 4, 2, 5, 3, 6, 4, 7, 5, 8, 7, 9, 8, 10, 9, 11, 10, 12, 11, 13, 15, 14, 16, 15, 17, 16, 21, 17)
    With rngSrcPensioner
    For i = LBound(Map) To UBound(Map) Step 2
    .Offset(Map(i)).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), Map(i + 1), False)
    Next i
    End With
    End Sub
    [/vba]Not tested. Incidentally you don't need the ",0" in the offset statement.
    Even slicker mate!

    Thank you very much for your help.

  11. #11
    Administrator
    VP-Knowledge Base
    VBAX Grand Master mdmackillop's Avatar
    Joined
    May 2004
    Location
    Scotland
    Posts
    14,489
    Location
    Hi p45cal
    I would be more inclined to go along with your paired values, but keeping them in 2 arrays. The Step 2 could be confusing to someone maintaining the code and it keeps the source>target arrangements clearer.
    Regards
    MD

    [VBA] Map = Array(1, 2, 3, 4, 5, 7, 8, 9, 10, 11, 15, 16, 17, 21)
    Arr = Array(4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17)
    With rngSrcPensioner
    For i = LBound(Map) To UBound(Map)
    .Offset(Map(i)).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), Arr(i), False)
    [/VBA]
    MVP (Excel 2008-2010)

    Post a workbook with sample data and layout if you want a quicker solution.


    To help indent your macros try Smart Indent

    Please remember to mark threads 'Solved'

  12. #12
    VBAX Expert
    Joined
    Dec 2007
    Posts
    522
    Location
    Quote Originally Posted by mdmackillop
    Hi p45cal
    I would be more inclined to go along with your paired values, but keeping them in 2 arrays. The Step 2 could be confusing to someone maintaining the code and it keeps the source>target arrangements clearer.
    Regards
    MD

    [vba] Map = Array(1, 2, 3, 4, 5, 7, 8, 9, 10, 11, 15, 16, 17, 21)
    Arr = Array(4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17)
    With rngSrcPensioner
    For i = LBound(Map) To UBound(Map)
    .Offset(Map(i)).Value = Application.WorksheetFunction.VLookup(.Value, Range("SECTION7_Autofill_Data"), Arr(i), False)
    [/vba]
    The collaborative responses for this thread just keep adding to the great tips and tricks shared.

    Thanks malcolm for your contrib.

  13. #13
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,844
    Quote Originally Posted by mdmackillop
    Hi p45cal
    I would be more inclined to go along with your paired values, but keeping them in 2 arrays. The Step 2 could be confusing to someone maintaining the code and it keeps the source>target arrangements clearer.
    Regards
    MD
    Quite so!
    p45cal
    Everyone: If I've helped and you can't be bothered to acknowledge it, I can't be bothered to look at further posts from you.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •