Finding

If your array contains less than 100,000 elements then looping through once is very efficient.
Exactly which method you use will depend on the following questions:
1) Is the array 1 dimensional or multi-dimensional.
2) Are you looking to conduct an exact match or just a partial match.
3) Do you need to know the position of the item if it exists.
4) How many searches do you need to do, it might be worth sorting the array.
5) How often is the data changing, you may need to keep re-sorting.


1-Dimensional Array - Exact Match

If you are using Excel VBA you can use the Excel MATCH worksheet function.

Public Function OneDimensional_Exact_One(ByVal arValues As Variant, _ 
                                         ByVal sFindValue As String) _
                                         As Boolean
   On Error GoTo AnError
   OneDimensional_Exact_One = Not IsError(Application.WorksheetFunction.Match(sFindValue, arValues, 0))
   Exit Function

AnError:
   OneDimensional_Exact_One = False
End Function

You can use the FILTER function to tell if an item exists in a one-dimensional array.
This function returns an array of any elements that contain a given text string.
This function takes a string array, text string and returns a one-dimensional array containing all the elements that match the search string.
This method does not distinguish between complete matches and substring matches.
This method does not work with numerical arrays since all the numbers have to be implicitly converted to text first

Public Function OneDimensional_Exact_Two(ByVal arValues As Variant, _ 
                                         ByVal sFindValue As String) _
                                         As Boolean
   
   OneDimensional_Exact_Two = (UBound(VBA.Filter(arValues, sFindValue)) > -1)
End Function

You can use the INSTR function after converting the array to a string concatenation
This method also uses the JOIN function to return a text string containing all the elements in an array (String).

Public Function OneDimensional_Exact_Three(ByVal arValues As Variant, _ 
                                           ByVal sFindValue As String) _
                                           As Boolean
Dim stextconcat As String
Dim sdelimiter As String

   sdelimiter = "--"
   stextconcat = sdelimiter & VBA.Join(arValues, sdelimiter) & sdelimiter
   OneDimensional_Exact_Three = VBA.InStr(1, stextconcat, sdelimiter & sFindValue & sdelimiter)
   
'use this line for case insensitive searches
'OneDimensional_Exact_Three = VBA.InStr(1, stextconcat, sdelimiter & sFindValue & sdelimiter, vbTextCompare)
End Function

You can loop through the array using a For Next - Each loop.

Public Function OneDimensional_Exact_Four(ByVal arValues As Variant, _ 
                                          ByVal sFindValue As String) _
                                          As Boolean
Dim sItem As Variant
   
   For Each sItem In arValues
      If sItem = sFindValue Then
          OneDimensional_Exact_Four = True
          Exit Function
      End If
   Next sItem
End Function

1-Dimensional Array - Partial Match

This function uses a 1-dimensional array starting at 1.

Public Sub Testing() 
Dim myArray(1 To 4) As String
Dim bfoundMatch As String

   myArray(1) = "one1"
   myArray(2) = "two3"
   myArray(3) = "three5"
   myArray(4) = "four7"
   
   bfoundMatch = OneDimensional_Partial(myArray, "two")
   Debug.Print bfoundMatch
End Sub

Public Function OneDimensional_Partial(ByVal arValues As Variant, _
                                       ByVal sFindValue As String) _
                                       As Boolean
   Dim lrow As Long
   Dim lcolumn As Long
    
   For lrow = LBound(arValues, 1) To UBound(arValues, 1)
      
      If (VBA.InStr(arValues(lrow), sFindValue) > 0) Then
         OneDimensional_Partial = True
         Exit Function
      End If
         
   Next lrow
End Function

2-Dimensional Array - Partial Match

This function uses a 2-dimensional array starting at 1.

Public Sub Testing() 
Dim myArray(1 To 4, 1 To 2) As String
Dim bfoundMatch As String

    myArray(1, 1) = "one1"
    myArray(1, 2) = "one2"
    myArray(2, 1) = "two3"
    myArray(2, 2) = "two4"
    myArray(3, 1) = "three5"
    myArray(3, 2) = "three6"
    myArray(4, 1) = "four7"
    myArray(4, 2) = "four8"
    
    bfoundMatch = TwoDimensional_Partial(myArray, "two")
    Debug.Print bfoundMatch
End Sub

Public Function TwoDimensional_Partial(ByVal arValues As Variant, _
                                       ByVal sFindValue As String) _
                                       As Boolean
   Dim lrow As Long
   Dim lcolumn As Long
    
   For lrow = LBound(arValues, 1) To UBound(arValues, 1)
      For lcolumn = LBound(arValues, 2) To UBound(arValues, 2)
      
         If (VBA.InStr(arValues(lrow, lcolumn), sFindValue) > 0) Then
            TwoDimensional_Partial = True
            Exit Function
         End If
         
      Next lcolumn
   Next lrow
End Function

Collection Object

A Collection object can also be used although to populate the collection you need to loop through the array.
This might be a good solution if you need to perform multiple searches in the same data set.

Public Function UsingCollection(ByVal arValues As Variant, _ 
                                ByVal sFindValue As String) _
                                As Boolean
Dim MyCollection As VBA.Collection
Dim lposition As Long
Dim sreturn As String
   
   On Error GoTo AnError
   Set MyCollection = New VBA.Collection
   For lposition = 0 To UBound(arValues)
      MyCollection.Add arValues(lposition), arValues(lposition)
   Next lposition
   sreturn = MyCollection.Item(sFindValue)
   UsingCollection = True
   Exit Function

AnError:
   UsingCollection = False
End Function

Dictionary Object

A Dictionary object can also be used although to populate the dictionary you need to loop through the array.
This will also need a reference to the Microsoft Scripting Runtime library.

Public Function UsingDictionary(ByVal arValues As Variant, _ 
                                ByVal sFindValue As String) _
                                As Boolean
Dim MyDictionary As Scripting.Dictionary
Dim lposition As Long
Dim sreturn As String
       
   Set MyDictionary = New Scripting.Dictionary
   For lposition = 0 To UBound(arValues)
      MyDictionary.Add arValues(lposition), arValues(lposition)
   Next lposition
   UsingDictionary = MyDictionary.Exists(sFindValue)
End Function

© 2023 Better Solutions Limited. All Rights Reserved. © 2023 Better Solutions Limited TopPrevNext