String Functions
String manipulation is an essential skill when working with data in VBA. Whether parsing CSV files, validating user input, or formatting data, you’ll frequently need to split, search, extract, and replace text.
This article covers the most commonly used VBA string functions, from basic usage to practical applications.
When You Need String Manipulation
String manipulation is necessary in many real-world scenarios:
- CSV data processing: Split comma-separated strings into arrays
- File path analysis: Extract filenames or folder names from paths
- Data validation: Check if specific strings are present
- Email address parsing: Separate username and domain
- Address formatting: Extract state, city, or zip code components
- Fixed-length data: Read specific characters from known positions
VBA provides powerful string functions to handle these tasks efficiently.
String Function Overview
Here are the main string functions available in VBA:
| Function | Purpose | Return Type |
|---|---|---|
| Split | Split string by delimiter | Array |
| Join | Combine array into string | String |
| InStr | Find position of substring | Long |
| InStrRev | Find position from end | Long |
| Mid | Extract from specified position | String |
| Left | Extract from beginning | String |
| Right | Extract from end | String |
| Replace | Replace text | String |
| Trim | Remove leading/trailing spaces | String |
| Len | Get string length | Long |
Let’s explore each function in detail.
Split Function: Dividing Strings
Basic Syntax
Split(String, [Delimiter], [Limit], [Compare])
The Split function divides a string at each delimiter and returns an array.
Basic Usage
Sub SplitBasicExample()
Dim text As String
Dim parts() As String
' Split comma-separated string
text = "apple,banana,orange,grape"
parts = Split(text, ",")
' Display results
Dim i As Long
For i = LBound(parts) To UBound(parts)
Debug.Print i & ": " & parts(i)
Next i
' Output:
' 0: apple
' 1: banana
' 2: orange
' 3: grape
End Sub
LBound(parts) always returns 0. Processing CSV Data
Sub ProcessCSVData()
Dim csvLine As String
Dim fields() As String
' CSV line (typically read from file)
csvLine = "John Smith,Sales,New York,[email protected]"
' Split by comma
fields = Split(csvLine, ",")
' Output to cells
Range("A1").Value = fields(0) ' Name
Range("B1").Value = fields(1) ' Department
Range("C1").Value = fields(2) ' Location
Range("D1").Value = fields(3) ' Email
End Sub
Limiting Split Count
Sub SplitWithLimit()
Dim text As String
Dim parts() As String
text = "2025-10-20-Monday-Holiday"
' Split only first 3 parts (rest stays combined)
parts = Split(text, "-", 3)
Debug.Print parts(0) ' 2025
Debug.Print parts(1) ' 10
Debug.Print parts(2) ' 20-Monday-Holiday
End Sub
The third argument limits the number of splits. Remaining text stays in the last element.
Join Function: Combining Arrays
Basic Syntax
Join(Array, [Delimiter])
Join is the opposite of Split—it combines array elements into a single string with a delimiter.
Basic Usage
Sub JoinBasicExample()
Dim fruits() As Variant
Dim result As String
' Define array
fruits = Array("apple", "banana", "orange")
' Join with comma
result = Join(fruits, ",")
Debug.Print result ' apple,banana,orange
' Join with space
result = Join(fruits, " ")
Debug.Print result ' apple banana orange
' Join with newline
result = Join(fruits, vbCrLf)
Debug.Print result
End Sub
Combining Split and Join
Sub SplitJoinCombo()
Dim text As String
Dim parts() As String
Dim result As String
' Process CSV data
text = "apple,banana,orange"
' Split
parts = Split(text, ",")
' Modify each element (e.g., add numbering)
Dim i As Long
For i = LBound(parts) To UBound(parts)
parts(i) = (i + 1) & ". " & parts(i)
Next i
' Join back
result = Join(parts, vbCrLf)
Debug.Print result
' Output:
' 1. apple
' 2. banana
' 3. orange
End Sub
InStr Function: Finding Text Position
Basic Syntax
InStr([Start], String, SearchString, [Compare])
InStr finds the position of a substring within a string. Returns 0 if not found.
Basic Usage
Sub InStrBasicExample()
Dim text As String
Dim pos As Long
text = "Hello World"
' Find "World"
pos = InStr(text, "World")
Debug.Print pos ' 7
' Find "world" (case-sensitive by default)
pos = InStr(text, "world")
Debug.Print pos ' 0 (not found)
' Case-insensitive search
pos = InStr(1, text, "world", vbTextCompare)
Debug.Print pos ' 7
End Sub
Check If String Contains Substring
Function Contains(text As String, search As String) As Boolean
Contains = (InStr(1, text, search, vbTextCompare) > 0)
End Function
Sub TestContains()
Debug.Print Contains("Hello World", "World") ' True
Debug.Print Contains("Hello World", "world") ' True (case-insensitive)
Debug.Print Contains("Hello World", "foo") ' False
End Sub
Find All Occurrences
Sub FindAllOccurrences()
Dim text As String
Dim search As String
Dim pos As Long
Dim count As Long
text = "The quick brown fox jumps over the lazy fox"
search = "fox"
pos = 1
count = 0
Do
pos = InStr(pos, text, search)
If pos > 0 Then
count = count + 1
Debug.Print "Found at position " & pos
pos = pos + 1 ' Move past current match
End If
Loop While pos > 0
Debug.Print "Total occurrences: " & count
End Sub
InStrRev Function: Finding from End
InStrRev searches from the end of the string.
Sub InStrRevExample()
Dim filePath As String
Dim pos As Long
filePath = "C:\Users\John\Documents\report.xlsx"
' Find last backslash (to extract filename)
pos = InStrRev(filePath, "\")
Debug.Print pos ' Position of last "\"
' Extract filename
Dim fileName As String
fileName = Mid(filePath, pos + 1)
Debug.Print fileName ' report.xlsx
End Sub
Mid Function: Extracting Substrings
Basic Syntax
Mid(String, Start, [Length])
Mid extracts a substring from a specified position.
Basic Usage
Sub MidBasicExample()
Dim text As String
text = "Hello World"
' Extract from position 7
Debug.Print Mid(text, 7) ' World
' Extract 5 characters from position 1
Debug.Print Mid(text, 1, 5) ' Hello
' Extract 3 characters from position 7
Debug.Print Mid(text, 7, 3) ' Wor
End Sub
Fixed-Length Data Parsing
Sub ParseFixedLengthData()
' Fixed-length record: Name(20) + Age(3) + Dept(10)
Dim record As String
record = "John Smith 030Sales "
Dim name As String
Dim age As String
Dim dept As String
name = Trim(Mid(record, 1, 20)) ' John Smith
age = Trim(Mid(record, 21, 3)) ' 30
dept = Trim(Mid(record, 24, 10)) ' Sales
Debug.Print "Name: " & name
Debug.Print "Age: " & age
Debug.Print "Dept: " & dept
End Sub
Left and Right Functions
Left Function
Extracts characters from the beginning of a string.
Sub LeftExample()
Dim text As String
text = "Hello World"
Debug.Print Left(text, 5) ' Hello
Debug.Print Left(text, 1) ' H
End Sub
Right Function
Extracts characters from the end of a string.
Sub RightExample()
Dim text As String
text = "Hello World"
Debug.Print Right(text, 5) ' World
Debug.Print Right(text, 1) ' d
End Sub
Practical Example: Extract File Extension
Function GetFileExtension(filePath As String) As String
Dim dotPos As Long
dotPos = InStrRev(filePath, ".")
If dotPos > 0 Then
GetFileExtension = Right(filePath, Len(filePath) - dotPos)
Else
GetFileExtension = ""
End If
End Function
Sub TestExtension()
Debug.Print GetFileExtension("report.xlsx") ' xlsx
Debug.Print GetFileExtension("document.pdf") ' pdf
Debug.Print GetFileExtension("image.backup.png") ' png
End Sub
Replace Function
Basic Syntax
Replace(String, Find, ReplaceWith, [Start], [Count], [Compare])
Basic Usage
Sub ReplaceBasicExample()
Dim text As String
text = "Hello World"
' Replace "World" with "VBA"
Debug.Print Replace(text, "World", "VBA") ' Hello VBA
' Replace all spaces with underscores
text = "Hello World How Are You"
Debug.Print Replace(text, " ", "_") ' Hello_World_How_Are_You
' Case-insensitive replace
text = "Hello WORLD"
Debug.Print Replace(text, "world", "VBA", , , vbTextCompare) ' Hello VBA
End Sub
Limit Replacement Count
Sub ReplaceLimitedCount()
Dim text As String
text = "one two one three one four"
' Replace only first 2 occurrences
Debug.Print Replace(text, "one", "ONE", , 2)
' ONE two ONE three one four
End Sub
Trim Functions
VBA provides three trim functions:
| Function | Purpose |
|---|---|
| Trim | Remove leading and trailing spaces |
| LTrim | Remove leading spaces only |
| RTrim | Remove trailing spaces only |
Sub TrimExample()
Dim text As String
text = " Hello World "
Debug.Print "[" & Trim(text) & "]" ' [Hello World]
Debug.Print "[" & LTrim(text) & "]" ' [Hello World ]
Debug.Print "[" & RTrim(text) & "]" ' [ Hello World]
End Sub
Trim functions only remove space characters (ASCII 32). They don’t remove tabs, newlines, or other whitespace. Use Replace for those.
Len Function
Returns the length of a string.
Sub LenExample()
Debug.Print Len("Hello") ' 5
Debug.Print Len("Hello World") ' 11
Debug.Print Len("") ' 0
End Sub
Practical Applications
Parse File Paths
Function GetFileName(fullPath As String) As String
Dim lastSlash As Long
lastSlash = InStrRev(fullPath, "\")
If lastSlash = 0 Then lastSlash = InStrRev(fullPath, "/")
If lastSlash > 0 Then
GetFileName = Mid(fullPath, lastSlash + 1)
Else
GetFileName = fullPath
End If
End Function
Function GetFolderPath(fullPath As String) As String
Dim lastSlash As Long
lastSlash = InStrRev(fullPath, "\")
If lastSlash = 0 Then lastSlash = InStrRev(fullPath, "/")
If lastSlash > 0 Then
GetFolderPath = Left(fullPath, lastSlash - 1)
Else
GetFolderPath = ""
End If
End Function
Sub TestPathFunctions()
Dim path As String
path = "C:\Users\John\Documents\report.xlsx"
Debug.Print GetFileName(path) ' report.xlsx
Debug.Print GetFolderPath(path) ' C:\Users\John\Documents
End Sub
Pad Strings
Function PadLeft(text As String, totalLength As Long, Optional padChar As String = " ") As String
If Len(text) >= totalLength Then
PadLeft = text
Else
PadLeft = String(totalLength - Len(text), padChar) & text
End If
End Function
Function PadRight(text As String, totalLength As Long, Optional padChar As String = " ") As String
If Len(text) >= totalLength Then
PadRight = text
Else
PadRight = text & String(totalLength - Len(text), padChar)
End If
End Function
Sub TestPadding()
Debug.Print "[" & PadLeft("42", 5, "0") & "]" ' [00042]
Debug.Print "[" & PadRight("Hi", 10) & "]" ' [Hi ]
End Sub
Summary
VBA string functions are essential tools for text processing:
| Function | Key Use Case |
|---|---|
| Split | Parse delimited data |
| Join | Combine array elements |
| InStr | Find text position |
| Mid | Extract substrings |
| Left/Right | Extract from ends |
| Replace | Text substitution |
| Trim | Clean whitespace |
| Len | Get string length |
Master these functions to handle any string manipulation task efficiently in VBA.