UCF-xlookup

Using XLOOKUP in Office 2019 #

Why #

Microsoft only releases new features for MS365. Otherwise, you’re forced to purchase an entirely new version. Spending extra money just for a few new functions feels wasteful, so I decided to benchmark the new features and build them as user-defined functions instead.

xlookup #

Unlike VLOOKUP or HLOOKUP, the XLOOKUP function allows you to search for values without being restricted by row or column order. With a bit of VBA, you can implement a similar function yourself.

Function XLOOKUP(ByVal lookup_value As Variant, _
                 ByVal lookup_array As Range, _
                 ByVal return_array As Range, _
                 Optional ByVal if_not_found As Variant = CVErr(xlErrNA), _
                 Optional ByVal match_mode As Long = 0, _
                 Optional ByVal search_mode As Long = 1) As Variant
    
    Dim i As Long, n As Long
    Dim arrL As Variant, arrR As Variant
   
    
    arrL = lookup_array.value
    arrR = return_array.value
    n = UBound(arrL, 1) * UBound(arrL, 2) 
   
    Dim stepVal As Long
    stepVal = IIf(search_mode = -1, -1, 1)
   
    
    Dim isRow As Boolean
    isRow = (UBound(arrL, 1) = 1)
   
    If isRow Then
        Dim j As Long
        If stepVal = 1 Then
            For j = 1 To UBound(arrL, 2)
                If arrL(1, j) = lookup_value Then
                    XLOOKUP = arrR(1, j)
                    Exit Function
                End If
            Next j
        Else
            For j = UBound(arrL, 2) To 1 Step -1
                If arrL(1, j) = lookup_value Then
                    XLOOKUP = arrR(1, j)
                    Exit Function
                End If
            Next j
        End If
    Else
        If stepVal = 1 Then
            For i = 1 To UBound(arrL, 1)
                If arrL(i, 1) = lookup_value Then
                    XLOOKUP = arrR(i, 1)
                    Exit Function
                End If
            Next i
        Else
            For i = UBound(arrL, 1) To 1 Step -1
                If arrL(i, 1) = lookup_value Then
                    XLOOKUP = arrR(i, 1)
                    Exit Function
                End If
            Next i
        End If
    End If   
    
    XLOOKUP = if_not_found
End Function

argument #

Here are the arguments for the custom XLOOKUP

lookup_value
the value you want to find
lookup_array
the array containing the lookup values
return_array
the array containing the return values
if_not_found(optional)
the value to return if no match is found
match_mode(optional)
0 = exact match, 1 = next larger value, -1 = next smaller value
search_mode(optional)
1 = search from first to last, -1 = search from last to first

 
In essence, this approach is similar to combining INDEX + MATCH. Of course, it won’t perform as well as the native XLOOKUP, but it’s still a practical workaround for Office 2019 users.

 

original post (Kor)