Split Function

Maintained on

The Split function divides a string by a specified delimiter and returns an array. It’s extremely useful for processing CSV data and parsing delimited strings.

Basic Syntax

Split(expression, [delimiter], [limit], [compare])

Parameters

ParameterTypeRequiredDescription
expressionStringYesThe string to split
delimiterStringNoThe delimiter (defaults to space)
limitLongNoMaximum number of splits (no limit if omitted)
compareVbCompareMethodNoString comparison method

Return Value

An array of strings (0-based index)

Basic Usage

Simple Split

split_basic.bas
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
チェック
The Split function returns a 0-based array. LBound(parts) always returns 0.

Processing CSV Data

split_csv.bas
Sub ProcessCSVData()
    Dim csvLine As String
    Dim fields() As String

    ' CSV line (typically read from file)
    csvLine = "John Smith,Sales,New York,jsmith@example.com"

    ' 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 the Number of Splits

split_limit.bas
Sub SplitWithLimit()
    Dim text As String
    Dim parts() As String

    text = "2025-10-20-Monday-Holiday"

    ' Split only first 3 times (4th element contains the rest)
    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 parameter limits the number of splits. The remaining text stays combined in the last element.

Splitting by Space

split_space.bas
Sub SplitBySpace()
    Dim text As String
    Dim words() As String

    text = "Hello World from VBA"

    ' Split by space (delimiter omitted)
    words = Split(text)

    Dim i As Long
    For i = LBound(words) To UBound(words)
        Debug.Print words(i)
    Next i

    ' Output:
    ' Hello
    ' World
    ' from
    ' VBA
End Sub

Practical Examples

Parsing URL Query Parameters

split_url_params.bas
Sub ParseURLParams()
    Dim url As String
    Dim queryString As String
    Dim params() As String
    Dim param() As String
    Dim i As Long

    url = "https://example.com/page?name=John&age=30&city=NYC"

    ' Extract query string
    If InStr(url, "?") > 0 Then
        queryString = Split(url, "?")(1)

        ' Split by &
        params = Split(queryString, "&")

        For i = LBound(params) To UBound(params)
            ' Split each param by =
            param = Split(params(i), "=")
            Debug.Print param(0) & " = " & param(1)
        Next i
    End If

    ' Output:
    ' name = John
    ' age = 30
    ' city = NYC
End Sub

Processing Multi-Line Text

split_multiline.bas
Sub ProcessMultilineText()
    Dim text As String
    Dim lines() As String
    Dim i As Long

    text = "Line 1" & vbCrLf & "Line 2" & vbCrLf & "Line 3"

    ' Split by line break
    lines = Split(text, vbCrLf)

    For i = LBound(lines) To UBound(lines)
        Debug.Print "Line " & (i + 1) & ": " & lines(i)
    Next i
End Sub

Extracting File Extension

split_file_extension.bas
Function GetFileExtension(filePath As String) As String
    Dim parts() As String

    parts = Split(filePath, ".")

    If UBound(parts) > 0 Then
        GetFileExtension = parts(UBound(parts))
    Else
        GetFileExtension = ""
    End If
End Function

Sub TestGetExtension()
    Debug.Print GetFileExtension("document.xlsx")     ' xlsx
    Debug.Print GetFileExtension("archive.tar.gz")    ' gz
    Debug.Print GetFileExtension("noextension")       ' (empty)
End Sub

Processing Tab-Separated Values

split_tsv.bas
Sub ProcessTSV()
    Dim tsvData As String
    Dim rows() As String
    Dim cols() As String
    Dim i As Long, j As Long

    tsvData = "Name" & vbTab & "Age" & vbTab & "City" & vbCrLf & _
              "John" & vbTab & "30" & vbTab & "NYC" & vbCrLf & _
              "Jane" & vbTab & "25" & vbTab & "LA"

    ' Split into rows
    rows = Split(tsvData, vbCrLf)

    For i = LBound(rows) To UBound(rows)
        ' Split each row into columns
        cols = Split(rows(i), vbTab)

        For j = LBound(cols) To UBound(cols)
            Cells(i + 1, j + 1).Value = cols(j)
        Next j
    Next i
End Sub

Counting Words

split_word_count.bas
Function CountWords(text As String) As Long
    Dim words() As String
    Dim cleanText As String

    ' Remove extra spaces
    cleanText = Trim(text)

    If Len(cleanText) = 0 Then
        CountWords = 0
        Exit Function
    End If

    ' Split by space
    words = Split(cleanText, " ")
    CountWords = UBound(words) + 1
End Function

Sub TestWordCount()
    Debug.Print CountWords("Hello World")              ' 2
    Debug.Print CountWords("The quick brown fox")      ' 4
    Debug.Print CountWords("")                         ' 0
End Sub

Working with Join Function

Split and Join are complementary functions. Join combines array elements back into a string:

split_and_join.bas
Sub SplitAndJoin()
    Dim text As String
    Dim parts() As String

    text = "apple,banana,orange"

    ' Split
    parts = Split(text, ",")

    ' Modify
    parts(1) = "BANANA"

    ' Join back with different delimiter
    Debug.Print Join(parts, " | ")  ' apple | BANANA | orange
End Sub

Summary

The Split function is essential for string parsing in VBA:

  • Returns a 0-based array
  • Defaults to space delimiter if omitted
  • Use limit parameter to control number of splits
  • Combine with Join for round-trip string manipulation
  • Perfect for CSV, TSV, and URL parameter processing

Master Split along with Join for powerful string manipulation capabilities.

#VBA #Split #String Operations #Array