Trim Functions

Maintained on

The Trim, LTrim, and RTrim functions remove leading and/or trailing spaces from strings. They’re essential for data cleansing, CSV processing, and normalizing user input.

Basic Syntax

Trim Function

Trim(string)

Removes spaces from both the beginning and end.

LTrim Function

LTrim(string)

Removes spaces from the beginning (Left) only.

RTrim Function

RTrim(string)

Removes spaces from the end (Right) only.

Parameters and Return Values

FunctionParameterTypeRequiredReturn Value
TrimstringStringYesString with both leading and trailing spaces removed
LTrimstringStringYesString with leading spaces removed
RTrimstringStringYesString with trailing spaces removed
チェック

These functions only remove half-width space characters (ASCII 32). Full-width spaces, tabs, and line breaks are not removed.

Basic Usage

Trim Function Basics

trim_basic.bas
Sub TrimBasicExample()
    Dim text As String
    Dim result As String

    ' String with spaces on both ends
    text = "   Hello World   "
    result = Trim(text)
    Debug.Print "[" & result & "]"  ' [Hello World]

    ' Leading spaces only
    text = "   Hello"
    result = Trim(text)
    Debug.Print "[" & result & "]"  ' [Hello]

    ' Trailing spaces only
    text = "World   "
    result = Trim(text)
    Debug.Print "[" & result & "]"  ' [World]

    ' No spaces (no change)
    text = "Hello"
    result = Trim(text)
    Debug.Print "[" & result & "]"  ' [Hello]
End Sub

LTrim Function Basics

ltrim_basic.bas
Sub LTrimBasicExample()
    Dim text As String
    Dim result As String

    text = "   Hello World   "

    ' Remove leading spaces only
    result = LTrim(text)
    Debug.Print "[" & result & "]"  ' [Hello World   ]
End Sub

RTrim Function Basics

rtrim_basic.bas
Sub RTrimBasicExample()
    Dim text As String
    Dim result As String

    text = "   Hello World   "

    ' Remove trailing spaces only
    result = RTrim(text)
    Debug.Print "[" & result & "]"  ' [   Hello World]
End Sub

Comparing All Three Functions

trim_compare.bas
Sub CompareTrimFunctions()
    Dim text As String

    text = "   Hello World   "

    Debug.Print "Original: [" & text & "]"
    Debug.Print "Trim:     [" & Trim(text) & "]"
    Debug.Print "LTrim:    [" & LTrim(text) & "]"
    Debug.Print "RTrim:    [" & RTrim(text) & "]"

    ' Output:
    ' Original: [   Hello World   ]
    ' Trim:     [Hello World]
    ' LTrim:    [Hello World   ]
    ' RTrim:    [   Hello World]
End Sub

Handling Full-Width Spaces and Other Whitespace

The built-in Trim functions don’t remove full-width spaces or other whitespace characters. Here’s a custom function that handles them:

trim_extended.bas
Function TrimAll(text As String) As String
    Dim result As String
    result = text

    ' Remove leading characters
    Do While Len(result) > 0
        Select Case Left(result, 1)
            Case " ", Chr(12288), vbTab, vbCr, vbLf  ' Space, full-width space, tab, CR, LF
                result = Mid(result, 2)
            Case Else
                Exit Do
        End Select
    Loop

    ' Remove trailing characters
    Do While Len(result) > 0
        Select Case Right(result, 1)
            Case " ", Chr(12288), vbTab, vbCr, vbLf
                result = Left(result, Len(result) - 1)
            Case Else
                Exit Do
        End Select
    Loop

    TrimAll = result
End Function

Sub TestTrimAll()
    Dim text As String

    ' Full-width spaces (Chr(12288) = full-width space)
    text = Chr(12288) & "Hello" & Chr(12288)
    Debug.Print "[" & Trim(text) & "]"      ' Still has full-width spaces
    Debug.Print "[" & TrimAll(text) & "]"   ' [Hello]

    ' Mixed whitespace
    text = vbTab & "  Hello  " & vbCrLf
    Debug.Print "[" & TrimAll(text) & "]"   ' [Hello]
End Sub

Practical Examples

Data Cleansing from CSV

trim_csv_cleansing.bas
Sub CleanseCSVData()
    Dim ws As Worksheet
    Dim rng As Range
    Dim cell As Range

    Set ws = ThisWorkbook.Sheets("Data")
    Set rng = ws.UsedRange

    For Each cell In rng
        If Not IsEmpty(cell) And VarType(cell.Value) = vbString Then
            cell.Value = Trim(cell.Value)
        End If
    Next cell

    MsgBox "Data cleansing complete!", vbInformation
End Sub

Normalizing User Input

trim_normalize_input.bas
Function NormalizeInput(userInput As String) As String
    Dim result As String

    ' Remove leading/trailing spaces
    result = Trim(userInput)

    ' Remove multiple internal spaces
    Do While InStr(result, "  ") > 0
        result = Replace(result, "  ", " ")
    Loop

    NormalizeInput = result
End Function

Sub TestNormalizeInput()
    Debug.Print NormalizeInput("  Hello    World  ")  ' "Hello World"
End Sub

Comparing Strings (Ignoring Whitespace)

trim_compare_strings.bas
Function StringsMatch(str1 As String, str2 As String) As Boolean
    StringsMatch = (Trim(LCase(str1)) = Trim(LCase(str2)))
End Function

Sub TestStringsMatch()
    Debug.Print StringsMatch("  Hello  ", "hello")      ' True
    Debug.Print StringsMatch("World", "  world  ")      ' True
    Debug.Print StringsMatch("Hello", "World")          ' False
End Sub

Validating Required Fields

trim_validate_required.bas
Function IsFieldEmpty(fieldValue As String) As Boolean
    IsFieldEmpty = (Len(Trim(fieldValue)) = 0)
End Function

Sub ValidateForm()
    Dim name As String
    Dim email As String

    name = Range("B2").Value
    email = Range("B3").Value

    If IsFieldEmpty(name) Then
        MsgBox "Name is required!", vbExclamation
        Exit Sub
    End If

    If IsFieldEmpty(email) Then
        MsgBox "Email is required!", vbExclamation
        Exit Sub
    End If

    MsgBox "Validation passed!", vbInformation
End Sub

Cleaning Import Data

trim_clean_import.bas
Sub CleanImportedData()
    Dim ws As Worksheet
    Dim lastRow As Long
    Dim lastCol As Long
    Dim i As Long, j As Long
    Dim cellValue As Variant

    Set ws = ActiveSheet
    lastRow = ws.Cells(ws.Rows.Count, 1).End(xlUp).Row
    lastCol = ws.Cells(1, ws.Columns.Count).End(xlToLeft).Column

    Application.ScreenUpdating = False

    For i = 1 To lastRow
        For j = 1 To lastCol
            cellValue = ws.Cells(i, j).Value
            If VarType(cellValue) = vbString Then
                ws.Cells(i, j).Value = Trim(cellValue)
            End If
        Next j
    Next i

    Application.ScreenUpdating = True
    MsgBox "Cleaned " & lastRow & " rows.", vbInformation
End Sub

Formatting Names

trim_format_names.bas
Function FormatName(fullName As String) As String
    Dim parts() As String
    Dim i As Long

    ' Split and trim each part
    parts = Split(Trim(fullName), " ")

    For i = LBound(parts) To UBound(parts)
        parts(i) = Trim(parts(i))
        If Len(parts(i)) > 0 Then
            ' Capitalize first letter
            parts(i) = UCase(Left(parts(i), 1)) & LCase(Mid(parts(i), 2))
        End If
    Next i

    FormatName = Join(parts, " ")
End Function

Sub TestFormatName()
    Debug.Print FormatName("  john   smith  ")   ' John Smith
    Debug.Print FormatName("JANE DOE")           ' Jane Doe
End Sub

Summary

The Trim family of functions is essential for string processing in VBA:

FunctionRemoves
TrimBoth leading and trailing spaces
LTrimLeading (left) spaces only
RTrimTrailing (right) spaces only

Key points:

  • Only removes half-width spaces (ASCII 32)
  • Full-width spaces, tabs, and line breaks require custom handling
  • Essential for data cleansing and input validation
  • Often used before string comparison
  • Combine with other string functions for comprehensive text processing

Master these functions for clean, reliable string handling in your VBA applications.

#VBA #Trim #LTrim #RTrim #String Operations #Data Cleansing