Consulting

Page 1 of 2 1 2 LastLast
Results 1 to 20 of 34

Thread: Solved: use formula in VBA for vlookup

  1. #1
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location

    Solved: use formula in VBA for vlookup

    I'm trying to remove code from worksheet to elimnate user altering/deleting. I can lock sheets, but want more control over code in sheets.
    I have a chart that uses vlookup and sumproduct, rather than leave the vlookup on the sheet I'm trying to put it in vba

    This is one of the data source cells for the chart
    techchart (a named cell) is the technumber of the formula I'm trying to relocate.
    =SUMPRODUCT(--(item27=scan_item),--(QCDate>=WkStart),--(QCDate<=RangeEnd),--(Techs=techChart))

    This is the cell I pull the pass and fail results.
    ="Pass" & ": "&TechPass &" Fail: "&TechFail

    I have a table of data of pass and fail items,
    using sumproduct within a date range, the chart shows results based on a drop down validation list from range AJ7 to AO67 (the AO67 may change)
    part of controling the code is I want to use a count on the rows down incase I add or remove the total techs so AO67 might go to 68 or 66
    [vba]
    Function FindTechNumber()

    Dim technum As short
    Dim TechPassValue As short
    Dim TechFailValue As short

    With Worksheets("Chart")

    Set technum = "VLookup(AD35, AJ7:AO67, 3)"
    Set TechPassValue = "VLookup(AD35, AJ7:AO67, 5)"
    Set TechFailValue = "VLookup(AD35, AJ7:AO67, 6)"

    ' on change of validation list in AD35 re-calculate these values?

    End Function[/vba]
    The file is working with code on the worksheet, but fails if I add a tech or delete one.
    I supply other offices with this workbook and they have different numbers of techs, so the AO67 value may change, being able to allow vba code to accomidate that will help deployment.

    If I can get the coding in VBA is the best so others can't (are less likely) break it...
    Thanks in advance.

  2. #2
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    I am not sure what the question is, and I have no idea what Short is, but here goes

    [vba]

    Function FindTechNumber()
    Dim technum
    Dim TechPassValue
    Dim TechFailValue

    With Worksheets("Chart")

    technum = Application.VLookup(Range("AD35"), Range("AJ:AO6"), 3)
    TechPassValue = Application.VLookup(Range("AD35"), Range("AJ:AO6"), 5)
    TechFailValue = Application.VLookup(Range("AD35"), Range("AJ:AO6"), 6)
    End With

    End Function
    [/vba]
    ____________________________________________
    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

  3. #3
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location

    How to evaluate in worksheet

    I modified to search for each of the 3 values I need.
    in the cell I type:
    =FindTechNumber(n) or maybe just
    =FindTechNumber() ?

    Cell AD35 is a data validation list that refers to the range in the function below
    [vba]Function FindTechNumber()
    Dim n

    With Worksheets("Chart")
    n = Application.VLookup(Range("AD35"), Range("AJ:AO6"), 3)
    End With

    End Function[/vba]
    This just evaluates to #Value!
    How do I properly call this function?

    I use another one like this:
    [vba]Function FileSavedIn()
    Select Case ActiveWorkbook.FileFormat
    Case 56: FileSavedIn = ".xls" ' Excel 2003
    Case 55: FileSavedIn = ".xlam" ' Excel 2007 Open XML Add-in
    Case 54: FileSavedIn = ".xlts" ' Excel 2007 Open XML Template
    Case 53: FileSavedIn = ".xltm" ' Excel 2007 Open XML Template Macro Enabled
    Case 52: FileSavedIn = ".xlsm" ' Excel 2007 Open XML Macros Enabled
    Case 51: FileSavedIn = ".xlsx" ' Excel 2007 Open XML
    Case -4143: FileSavedIn = ".xls" ' Excel 2000 et plus (workbook normal)
    Case 43: FileSavedIn = ".xls" ' Excel 97/2000 (correct?)
    Case 39: FileSavedIn = ".xls" ' Excel 5 (correct?)
    Case 35: FileSavedIn = ".xls" ' Workbook Excel 4 (correct?)
    Case 33: FileSavedIn = ".xls" ' Sheet Excel 4 (correct?)
    Case 29: FileSavedIn = ".xls" ' Excel 3 (Correct?)
    Case 18: FileSavedIn = ".xla" ' Excel 97-2003 Add-in
    Case 17: FileSavedIn = ".xlt" ' Excel Template
    Case 16: FileSavedIn = ".xls" ' Excel 2.1 (Correct?)
    Case Else: FileSavedIn = ".xls" ' Unknown
    End Select
    End Function[/vba]

    in a cell I have :
    =FileSavedIn()
    this evaluates to .xls

  4. #4
    VBAX Tutor
    Joined
    Nov 2006
    Location
    North East Pennsylvania, USA
    Posts
    203
    Location
    mperrah,

    Please try this FIRST on a TEST copy of workbook.

    I changed your Function to a Macro.

    [VBA]

    Option Explicit
    Sub FindTechNumber()
    Dim lngLastRow As Long
    With Worksheets("Chart")
    lngLastRow = Sheets("Chart").Range("AJ" & Rows.Count).End(xlUp).Row
    Range("AJ7:AO" & lngLastRow).Sort Key1:=Range("AJ7"), Order1:=xlAscending, Header:=xlGuess, _
    OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom, _
    DataOption1:=xlSortNormal
    'technum address
    Range("AD37").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 3)"
    'TechPassValue address
    Range("AD38").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 5)"
    'TechFailValue address
    Range("AD39").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 6)"
    'Adjust this range for the range for the above 'tech' references
    With Range("AD37:AD39")
    .Copy
    .PasteSpecial Paste:=xlPasteValues, Operation:=xlNone, SkipBlanks _
    :=False, Transpose:=False
    End With
    Application.CutCopyMode = False
    Range("AE35").Select
    ' on change of validation list in AD35 re-calculate these values?
    End With
    End Sub

    [/VBA]


    Have a great day,
    Stan

  5. #5
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location

    testing not working

    A few changes.
    i had some values in the cels you called out.
    Should this make a vlue apear in the range AD42:AD44?
    Or do I need to call the formula first?

    [VBA]Sub FindTechNumber()
    Dim lngLastRow As Long
    With Worksheets("Chart")
    lngLastRow = Sheets("Chart").Range("AJ" & Rows.Count).End(xlUp).Row
    Range("AJ7:AO" & lngLastRow).Sort Key1:=Range("AJ7"), Order1:=xlAscending, Header:=xlGuess, _
    OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom, _
    DataOption1:=xlSortNormal
    'technum address
    Range("AD42").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 3)"
    'TechPassValue address
    Range("AD43").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 5)"
    'TechFailValue address
    Range("AD44").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 6)"
    'Adjust this range for the range for the above 'tech' references
    With Range("AD42:AD44")
    .Copy
    .PasteSpecial Paste:=xlPasteValues, Operation:=xlNone, SkipBlanks _
    :=False, Transpose:=False
    End With
    Application.CutCopyMode = False
    Range("AE35").Select
    ' on change of validation list in AD35 re-calculate these values?
    End With
    End Sub[/VBA]

  6. #6
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location

    got it

    I didn't realize you made it a sub instead of a function.
    i put in a command button and it fires perfect.
    One thing, can I make it fire on the change of the validation list instead?
    Mark

  7. #7
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location

    change double click to change?

    If I double click anywhere this fires,
    but if I just switch it to the Change event, it starts a un-ending loop.
    any ideas?

    [VBA]Private Sub Worksheet_BeforeDoubleClick(ByVal Target As Range, Cancel As Boolean)

    Dim lngLastRow As Long
    With Worksheets("Chart")
    lngLastRow = Sheets("Chart").Range("AJ" & Rows.Count).End(xlUp).Row
    Range("AJ7:AO" & lngLastRow).Sort Key1:=Range("AJ7"), Order1:=xlAscending, Header:=xlGuess, _
    OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom, _
    DataOption1:=xlSortNormal
    'technum address
    Range("AD42").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 3)"
    'TechPassValue address
    Range("AD43").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 5)"
    'TechFailValue address
    Range("AD44").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 6)"
    'Adjust this range for the range for the above 'tech' references
    With Range("AD42:AD44")
    .Copy
    .PasteSpecial Paste:=xlPasteValues, Operation:=xlNone, SkipBlanks _
    :=False, Transpose:=False
    End With
    Application.CutCopyMode = False
    Range("AE35").Select
    ' on change of validation list in AD35 re-calculate these values?
    End With
    End Sub[/VBA]

  8. #8
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location

    How do I use variables to pull data directly from source

    Got it to work.
    Now I realized I don't need the values on the sheet at all.
    I can store them as a variable.
    How would I use the VLookup in VBA and not paste it into the sheet?
    AJ7:AO67 is the data range I am looking up from
    the first column is what matches AD35
    The 3rd column is the tech number
    5th is the pass total and 6th is the fail total
    These values are actualy a link to the WQC Sheet that total everything
    using sumproduct.
    I could bypass the link and pull directly from the WQC sheet and keep it all in VBA, setting up and using the variables is where I'm not sure where to start.

    I could have the validation list pull from the range on WQC,
    then use the vlookup to pull the values directly
    Range is A7:E(count to end down)
    there the tech number is column 2, pass is 4 and fail is 5
    Here is what I have so far..
    [VBA]Private Sub Worksheet_Change(ByVal Target As Range)
    Dim tList As Range
    Dim lngLastRow As Long
    Set tList = Range("AD35")
    If Target.Cells.Count > 1 Then Exit Sub
    If Not Intersect(Target, tList) Is Nothing Then
    With Target
    With Worksheets("Chart")
    lngLastRow = Sheets("Chart").Range("AJ" & Rows.Count).End(xlUp).Row
    Range("AJ7:AO" & lngLastRow).Sort Key1:=Range("AJ7"), Order1:=xlAscending, Header:=xlGuess, _
    OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom, _
    DataOption1:=xlSortNormal
    'technum address
    Range("AD38").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 3)"
    'TechPassValue address
    Range("AD39").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 5)"
    'TechFailValue address
    Range("AD40").Formula = "=VLookup(AD35, $AJ$7:$AO$" & lngLastRow & ", 6)"
    'Adjust this range for the range for the above 'tech' references
    With Range("AD38:AD40")
    .Copy
    .PasteSpecial Paste:=xlPasteValues, Operation:=xlNone, SkipBlanks _
    :=False, Transpose:=False
    End With
    Application.CutCopyMode = False
    Range("AE35").Select
    ' on change of validation list in AD35 re-calculate these values?
    End With
    End With
    End If
    End Sub
    [/VBA]

  9. #9
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    As I showed you in post #2.
    ____________________________________________
    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

  10. #10
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location
    Bob,
    So these are variables I can call from the sheet?

    ="Pass" & ": "&TechPassValue &" Fail: "&TechFailValue



  11. #11
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    OH no, you would have to store the values somewhere when they are generated, then pick it from there (such as some off-screen worksheet cells).
    ____________________________________________
    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

  12. #12
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location
    I have a sheet named "Prompt" or "menuSheet" that are hidden,
    I could name a cell on one of these.
    then how do I store the value there?
    in VBA or as a formula

    in cell "=TechNumberValue()" ? using the sub
    or as we dim in #2
    in cell "=technum" ? pulling the variable

  13. #13
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location
    Would a combobox work better than a data validation list?
    how do I call a sub on a combobox change event?
    Last edited by mperrah; 07-30-2007 at 04:04 PM.

  14. #14
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location

    update

    How would I save a variable in the vba to avoid needing a helper cell on the sheet.
    for example. If I can use the vlookup within vba and store the result as a named variable (or range) that I can use in a formula in the sheet.

    vlookup shows the tech number based on the filllistsource and offset,
    that result is used in a formula in a cell, how do I name the variable in vba
    and how do I use that variable in the worksheet?

  15. #15
    VBAX Expert mperrah's Avatar
    Joined
    Mar 2005
    Posts
    744
    Location

    replace formula

    How can I replace the vlookup formula by using just vba.
    The code in previous posts made the cell contents equal the formula rather than typing it in, but how do eliminate the formula all together?
    I need a code to update dynamicaly a validation list source
    and change the data a chart uses, now it is vlookup and formula.

    I have a drop down validation list in A35 that is sourced from a range on sheet("WQC") I pasted links on the Chart sheet.
    The WQC sheet totals: the number of jobs per tech, the pass, and fail.
    the source range has the tech name in column a, (not used here)
    number in b, total jobs in c, pass in d, and fail in e.
    then I have a range on sheet("chart") that uses sumproduct to check the results per tech based on the jobs within a date range, then the chart updates based on the tech I choose from the validation list. This range is the chart data source.

    My problem is the techs numbers are different in each office and my validation list needs to be updated if the techs are added or removed.
    Also I am trying to avoid the cells with the vlookup being deleted.
    Locking the cells won't allow the data to change with the different tech being chosen from the drop down validation list..

    I appreciate your help.
    Mark

  16. #16
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    You would need to to a find on the lookup value in the first column of the lookup table, and if and when found, get the column offset (3, 5, and 6 in your example) from that cell to get the value.
    Last edited by Bob Phillips; 08-11-2007 at 12:21 PM.
    ____________________________________________
    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

  17. #17
    VBAX Mentor
    Joined
    Jun 2005
    Posts
    374
    Location
    hello
    i am trying to take advantage of this thread for another.
    i have a data base,all the macros in a workbook.i want to use th vlookup function to return a macro name by entering a number.
    [VBA]Function FindTechNumber(num)
    On Error Resume Next
    With Worksheets("projects")
    FindTechNumber = Application.VLookup(num, Range("A11750"), 3)
    End With
    End Function[/VBA]
    what is wrong with my function?.
    thanks
    moshe

  18. #18
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Maybe

    [vba]

    Function FindTechNumber(num)
    On Error Resume Next
    With Worksheets("projects")
    FindTechNumber = Application.VLookup(num, Range("A11750"), 3,False)
    End With
    End Function
    [/vba]

    Is there any possibility it won't be found?
    ____________________________________________
    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

  19. #19
    VBAX Mentor
    Joined
    Jun 2005
    Posts
    374
    Location
    and why is that.i only emulate what a vlookup should do.
    moshe

  20. #20
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Why is what?
    ____________________________________________
    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

Posting Permissions

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