Easily extract text between two strings with this VBA Function. This user-defined function (UDF) can extract a substring between two characters, delimiters, words and more. The delimiters can be the same delimiter or unique strings. I call this UDF SuperMid because it behaves like the VBA Mid Function on steroids.

First, I’ll show you the function. Then, I’ll give you a couple examples of how it can be used to do some really awesome string manipulations.

To begin using it, all you have to do is copy and paste the function into your VBA editor and follow my examples! A description and how-to guide is included as comments in the VBA function so you can read them directly from your VBA editor.


Extract Text Between Two Strings with VBA

Public Function SuperMid(ByVal strMain As String, str1 As String, str2 As String, Optional reverse As Boolean) As String
'DESCRIPTION: Extract the portion of a string between the two substrings defined in str1 and str2.
'DEVELOPER: Ryan Wells (wellsr.com)
'HOW TO USE: - Pass the argument your main string and the 2 strings you want to find in the main string.
' - This function will extract the values between the end of your first string and the beginning
' of your next string.
' - If the optional boolean "reverse" is true, an InStrRev search will occur to find the last
' instance of the substrings in your main string.
Dim i As Integer, j As Integer, temp As Variant
On Error GoTo errhandler:
If reverse = True Then
    i = InStrRev(strMain, str1)
    j = InStrRev(strMain, str2)
    If Abs(j - i) < Len(str1) Then j = InStrRev(strMain, str2, i)
    If i = j Then 'try to search 2nd half of string for unique match
        j = InStrRev(strMain, str2, i - 1)
    End If
Else
    i = InStr(1, strMain, str1)
    j = InStr(1, strMain, str2)
    If Abs(j - i) < Len(str1) Then j = InStr(i + Len(str1), strMain, str2)
    If i = j Then 'try to search 2nd half of string for unique match
        j = InStr(i + 1, strMain, str2)
    End If
End If
If i = 0 And j = 0 Then GoTo errhandler:
If j = 0 Then j = Len(strMain) + Len(str2) 'just to make it arbitrarily large
If i = 0 Then i = Len(strMain) + Len(str1) 'just to make it arbitrarily large
If i > j And j <> 0 Then 'swap order
    temp = j
    j = i
    i = temp
    temp = str2
    str2 = str1
    str1 = temp
End If
i = i + Len(str1)
SuperMid = Mid(strMain, i, j - i)
Exit Function
errhandler:
MsgBox "Error extracting strings. Check your input" & vbNewLine & vbNewLine & "Aborting", , "Strings not found"
End
End Function

Make powerful macros with our free VBA Developer Kit

This is actually pretty neat. If you have trouble understanding or remembering it, our free VBA Developer Kit can help. It’s loaded with VBA shortcuts to help you make your own macros like this one - we’ll send a copy, along with our Big Book of Excel VBA Macros, to your email address below.

I'll take a free VBA Developer Kit

How to use the SuperMid Function

I’m going to provide several examples of how to use the SuperMid function to take all kinds of cool actions. Each example macro will have a comment at the bottom showing what the output will be. Note, you can also use the function as a formula directly in your spreadsheet! Just enter something like

=SuperMid(A9,"abc","xyz") into a cell in Excel.

Extract the string between two words

Sub ExtractSubstring()
str1 = "USER: myusername ADDRESS: unknown"
str2 = SuperMid(str1, "USER:", "ADDRESS:")
'Result: myusername
End Sub

Although I passed the function “USER:” first and “ADDRESS:” second, the function is smart enough to switch the order if it has to find your target words.

Extract the characters between two delimiters

Sub ExtractSubstring2()
str1 = "abc-123-xyz-000"
str2 = SuperMid(str1, "-", "-")
'Result: 123
End Sub

This macro will pull the words between the first two dashes.

Extract between the last occurrence of two substrings

Sub ExtractSubstring3()
str1 = "abc-123-xyz-000"
str2 = SuperMid(str1, "-", "-", True)
'Result: xyz
End Sub

This macro will pull the string between the last two dashes. To search the string backward, all you have to do is add the optional 4th argument with a value of True.

Extract all the text after a keyword

Sub ExtractSubstring4()
str1 = "How now brown cow"
str2 = SuperMid(str1, "now", "anyrandomstring")
'Result: brown cow
End Sub

Because the function can’t find the second string you pass it, it returns everything after your first string.

Extract a file name from path with VBA

Sub ExtractFileName()
str1 = "C:\Users\Ryan\Documents\readme.txt"
str2 = SuperMid(str1, "\", ".txt", True)
'Result: readme
End Sub

This is just a neat bonus sample to show you how to extract a file name from a path without the extension. If you want to keep the extension, just make the 2nd delimiter string equal to a random set of characters not present in your path.


SuperMid is one of my most powerful string manipulation functions. I use it all the time! I mostly use it to extract file names and to play with fixed-width data. When you’re ready for more awesome string manipulation functions, check out my article on replacing the Nth occurrence of a substring in a string.

Subscribe to my email list using the form below, share this article on social media and follow me on Twitter for more great VBA content.