Recreate VLOOKUP

Maintained on

Excel’s VLOOKUP function is a very convenient tool for searching specific values and retrieving related data. However, by using VBA (Visual Basic for Applications), you can perform even more flexible and automated data searches. This article provides a detailed explanation of how to implement VLOOKUP-like operations using VBA.

Basic Structure of VLOOKUP Function

First, let’s review Excel’s VLOOKUP function.

VLOOKUP_Function_Syntax
=VLOOKUP(lookup_value, table_array, col_index_num, [range_lookup])

For example, to search for a value in cell A1 within the range B1:C10 and return the value from the 2nd column (column C) of that row when found:

VLOOKUP_Example
=VLOOKUP(A1, B1:C10, 2, FALSE)

Using VLOOKUP in VBA

All Excel functions can be used in VBA, so you can call the VLOOKUP function running in Excel from VBA.

Calling_VLOOKUP_from_VBA
Application.WorksheetFunction.VLookup(lookup_value, table_array, col_index_num, False)

By calling the Vlookup function defined in the WorksheetFunction class, you can use the VLOOKUP function from VBA.

However, when you want to perform more flexible data searches, creating a custom function in VBA is useful. The next section introduces how to create a custom function in VBA that has similar functionality to the VLOOKUP function.

Code to Recreate VLOOKUP in VBA

Next, let me show you how to perform the same operation in VBA.

Function CustomVlookup(lookup_value As Variant, table_array As Range, col_index_num As Integer) As Variant
    Dim cell As Range
    For Each cell In table_array.Columns(1).Cells
        If cell.Value = lookup_value Then
            CustomVlookup = cell.Offset(0, col_index_num - 1).Value
            Exit Function
        End If
    Next cell
    CustomVlookup = "Not Found"
End Function

The code above defines a custom function CustomVlookup in VBA that has similar functionality to the VLOOKUP function. Here’s how to use it:

Sub TestCustomVlookup()
    Dim result As Variant
    result = CustomVlookup("SearchValue", Sheets("Sheet1").Range("B1:C10"), 2)
    MsgBox result
End Sub

Advanced Techniques

So far, there’s no particular need to create a custom function, but using VBA enables various advanced techniques.

While standard VLOOKUP only supports exact matches, VBA allows partial match searches.

Function CustomVlookupPartial(lookup_value As String, table_array As Range, col_index_num As Integer) As Variant
    Dim cell As Range
    For Each cell In table_array.Columns(1).Cells
        If InStr(1, cell.Value, lookup_value) > 0 Then
            CustomVlookupPartial = cell.Offset(0, col_index_num - 1).Value
            Exit Function
        End If
    Next cell
    CustomVlookupPartial = "Not Found"
End Function

Switching Between Exact and Partial Matches

It’s also important to be able to switch between exact and partial matches as needed. For example, you can let the user specify this with an argument.

Function CustomVlookupFlexible(lookup_value As Variant, table_array As Range, col_index_num As Integer, Optional partial_match As Boolean = False) As Variant
    Dim cell As Range
    For Each cell In table_array.Columns(1).Cells
        If (partial_match And InStr(1, cell.Value, lookup_value) > 0) Or (Not partial_match And cell.Value = lookup_value) Then
            CustomVlookupFlexible = cell.Offset(0, col_index_num - 1).Value
            Exit Function
        End If
    Next cell
    CustomVlookupFlexible = "Not Found"
End Function

Error Handling

To prevent errors when data is not found, implement appropriate error handling.

Function CustomVlookupWithErrorHandling(lookup_value As Variant, table_array As Range, col_index_num As Integer) As Variant
    On Error GoTo ErrorHandler
    Dim cell As Range
    For Each cell In table_array.Columns(1).Cells
        If cell.Value = lookup_value Then
            CustomVlookupWithErrorHandling = cell.Offset(0, col_index_num - 1).Value
            Exit Function
        End If
    Next cell
    CustomVlookupWithErrorHandling = "Not Found"
    Exit Function

ErrorHandler:
    CustomVlookupWithErrorHandling = "Error: " & Err.Description
End Function

Practical Usage Examples

For example, searching for employee information based on employee ID.

Sub SearchEmployeeInfo()
    Dim employeeID As String
    Dim result As Variant
    employeeID = InputBox("Enter_employee_ID:")
    result = CustomVlookup(employeeID, Sheets("EmployeeData").Range("A1:D100"), 2)

    If result = "Not Found" Then
        MsgBox "Employee_information_not_found."
    Else
        MsgBox "Employee_Name: " & result
    End If
End Sub

Auto-Filling Product Information

Automatically filling cells with information when a product code is entered.

Sub AutoFillProductInfo()
    Dim productCode As String
    Dim productName As Variant
    Dim productPrice As Variant

    productCode = Cells(2, 1).Value '_Assumes_product_code_is_in_cell_A2
    productName = CustomVlookup(productCode, Sheets("ProductData").Range("A1:C100"), 2)
    productPrice = CustomVlookup(productCode, Sheets("ProductData").Range("A1:C100"), 3)

    If productName = "Not Found" Or productPrice = "Not Found" Then
        MsgBox "Product_information_not_found."
    Else
        Cells(2, 2).Value = productName '_Enter_product_name_in_cell_B2
        Cells(2, 3).Value = productPrice '_Enter_price_in_cell_C2
    End If
End Sub

Summary

Using VBA enables flexible data searches that aren’t limited by Excel’s VLOOKUP function. By creating custom functions combining these techniques, you can easily perform processing tailored to your business needs. Please try incorporating these into your own projects.

#VBA #Excel #VLOOKUP #Data Search #Function