Concatenate strings using Mid$ Function - danielep71/VBA-PERFORMANCE GitHub Wiki

[Home]] ](/danielep71/VBA-PERFORMANCE/wiki/[[Tips-and-Tricks)


1. Statement

When it is necessary to repeatedly add sets of characters to the same variable, it is possible to speed up the code by resorting to a simple trick based on the Mid$ command.

2. Description

The basic string operator “&” performs a string concatenation.

Some programmers (maybe with roots in QuickBasic) still use the “+” operator for performing string concatenation. This could be a dangerous practice that might introduce unexpected behaviors when either operand is not a string.

As many know, the "&" operator or the “+” operators are quite slow, especially with long strings.

To speed up the concatenation on the same variable, it is possible to pre-allocate a buffer large enough to contain the result of the operation.

Example:

Suppose you want to create a string by adding the first 10,000 integers to it.

The simplest way is as follows:

sRes = ""

For i = 1 To 10000: sRes = sRes & Str(i): Next

The problem with this approach is that the sRes variable is reallocated 10,000 times. It is possible to obtain the same result with a more efficient technique:

  1. pre-allocate a buffer big enough to hold the final string using the Space Function;
  2. use Mid$ function to build the final string.

3. Performance test

Sub Test_ConcatenateWithMid()
'Declare
    Dim i               As Long                     'Loop counter
    Dim MaxIter         As Long                     'Max # of iterations
    Dim iMethod         As Integer                  'Performance method
    Dim cPM             As cPerformanceMonitor      'Performance tracker
    Dim sRes            As String                   'Result string
    Dim lIndex          As Long                     'Counter
    Dim sSubStr         As String                   'Temp sub-string
    Dim lLength         As Long                     'Temp sub-string length

'------------------------------------------------------------------------------
'Initialize
    MaxIter = 100000
    iMethod = 2
    Set cPM = New cPerformanceMonitor
'------------------------------------------------------------------------------
'Test1
    sRes = vbNullString
    cPM.StartTimer (iMethod)
    For i = 1 To MaxIter
        sRes = sRes & str(i)
    Next i
    Debug.Print cPM.ElapsedTime(iMethod) & " - ""&"" concatenation"
'Test2
    sRes = vbNullString
    cPM.StartTimer (iMethod)
    For i = 1 To MaxIter
        sRes = sRes + str(i)
    Next i
    Debug.Print cPM.ElapsedTime(iMethod) & " - ""+"" concatenation"
'Test3
    sRes = vbNullString
    cPM.StartTimer (iMethod)
    sRes = Space(MaxIter * 10)
    lIndex = 1                          'Start from the first position
    For i = 1 To MaxIter
        sSubStr = Str(i)
        lLength = Len(sSubStr)
        Mid$(sRes, lIndex, lLength) = sSubStr
        lIndex = lIndex + lLength       'Index increment
    Next i
    sRes = Left$(sRes, lIndex - 1)      'Remove excess characters
    Debug.Print cPM.ElapsedTime(iMethod) & " - ""Mid$"" concatenation"
'------------------------------------------------------------------------------
'Exit
    Set cPM = Nothing
End Sub

4. Results

The results are the following:

Looping 100,000 times:

  • 00:00:03 - 578 ms - 000 µs - 000 ns - "&" concatenation
  • 00:00:03 - 438 ms - 000 µs - 000 ns - "+" concatenation
  • 00:00:00 - 015 ms - 000 µs - 000 ns - "Mid$" concatenation

Using Mid$ with a pre-allocated buffer is more than 200 times faster!

5. Conclusions

Improvement: more than 200 times faster.

Impact: more than 3 seconds.

The test shows a very significant performance increase


[Home]] ](/danielep71/VBA-PERFORMANCE/wiki/[[Tips-and-Tricks)