Trim関数

にメンテナンス済み

Trim、LTrim、RTrim 関数は、文字列の先頭や末尾の空白(スペース)を削除する VBA の関数です。データクレンジング、CSV ファイルの処理、ユーザー入力の正規化などに必須の関数です。

基本構文

Trim 関数

Trim(文字列)

先頭と末尾の両方の空白を削除します。

LTrim 関数

LTrim(文字列)

先頭(Left)の空白のみを削除します。

RTrim 関数

RTrim(文字列)

末尾(Right)の空白のみを削除します。

引数と戻り値

関数引数必須戻り値
Trim文字列String両端の空白を削除した文字列
LTrim文字列String先頭の空白を削除した文字列
RTrim文字列String末尾の空白を削除した文字列
チェック

これらの関数は、半角スペース(ASCII 32)のみを削除します。全角スペースやタブ文字、改行文字は削除されません。

基本的な使い方

Trim 関数の基本

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

    ' 両端に空白がある文字列
    text = "   Hello World   "
    result = Trim(text)
    Debug.Print "[" & result & "]"  ' [Hello World]

    ' 先頭のみ空白
    text = "   Hello"
    result = Trim(text)
    Debug.Print "[" & result & "]"  ' [Hello]

    ' 末尾のみ空白
    text = "World   "
    result = Trim(text)
    Debug.Print "[" & result & "]"  ' [World]

    ' 空白なし(変化なし)
    text = "Hello"
    result = Trim(text)
    Debug.Print "[" & result & "]"  ' [Hello]
End Sub

LTrim 関数の基本

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

    text = "   Hello World   "

    ' 先頭の空白のみ削除
    result = LTrim(text)
    Debug.Print "[" & result & "]"  ' [Hello World   ]
End Sub

RTrim 関数の基本

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

    text = "   Hello World   "

    ' 末尾の空白のみ削除
    result = RTrim(text)
    Debug.Print "[" & result & "]"  ' [   Hello World]
End Sub

3 つの関数の比較

trim_compare.bas
Sub CompareTrimFunctions()
    Dim text As String

    text = "   Hello World   "

    Debug.Print "元の文字列: [" & text & "]"
    Debug.Print "Trim:       [" & Trim(text) & "]"
    Debug.Print "LTrim:      [" & LTrim(text) & "]"
    Debug.Print "RTrim:      [" & RTrim(text) & "]"

    ' 出力:
    ' 元の文字列: [   Hello World   ]
    ' Trim:       [Hello World]
    ' LTrim:      [Hello World   ]
    ' RTrim:      [   Hello World]
End Sub

ユーザー入力の処理

InputBox の値を正規化

trim_inputbox.bas
Sub NormalizeUserInput()
    Dim userInput As String
    Dim normalized As String

    ' ユーザーが誤って空白を入力する可能性がある
    userInput = InputBox("名前を入力してください")

    ' 空白を削除して正規化
    normalized = Trim(userInput)

    If normalized = "" Then
        MsgBox "名前が入力されていません"
    Else
        MsgBox "ようこそ、" & normalized & "さん"
    End If
End Sub

セル値の一括トリミング

trim_cells.bas
Sub TrimAllCells()
    Dim ws As Worksheet
    Dim lastRow As Long
    Dim i As Long
    Dim cell As Range

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

    ' A列のすべてのセルをトリミング
    For i = 1 To lastRow
        Set cell = ws.Cells(i, 1)
        If Not IsEmpty(cell.Value) Then
            cell.Value = Trim(cell.Value)
        End If
    Next i

    MsgBox "トリミングが完了しました"
End Sub

CSV 処理での活用

CSV 読み込み時の空白削除

trim_csv_read.bas
Sub ReadCSVWithTrim()
    Dim filePath As String
    Dim fileNum As Integer
    Dim line As String
    Dim values() As String
    Dim i As Long
    Dim ws As Worksheet
    Dim row As Long

    Set ws = ActiveSheet
    row = 1

    filePath = "C:\data\sample.csv"
    fileNum = FreeFile

    Open filePath For Input As #fileNum

    Do Until EOF(fileNum)
        Line Input #fileNum, line

        ' カンマで分割
        values = Split(line, ",")

        ' 各値をトリミングしてセルに書き込み
        For i = 0 To UBound(values)
            ws.Cells(row, i + 1).Value = Trim(values(i))
        Next i

        row = row + 1
    Loop

    Close #fileNum
End Sub

CSV 出力時の空白処理

trim_csv_write.bas
Sub WriteCSVWithTrim()
    Dim ws As Worksheet
    Dim lastRow As Long
    Dim lastCol As Long
    Dim i As Long
    Dim j As Long
    Dim filePath As String
    Dim fileNum As Integer
    Dim line As String
    Dim value As String

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

    filePath = "C:\data\output.csv"
    fileNum = FreeFile

    Open filePath For Output As #fileNum

    For i = 1 To lastRow
        line = ""
        For j = 1 To lastCol
            ' セル値をトリミング
            value = Trim(ws.Cells(i, j).Value)

            ' カンマ区切りで追加
            If j > 1 Then line = line & ","
            line = line & value
        Next j

        Print #fileNum, line
    Next i

    Close #fileNum
End Sub

データクレンジング

複数の空白を 1 つに変換

trim_multiple_spaces.bas
Function NormalizeSpaces(text As String) As String
    Dim result As String

    ' 両端をトリミング
    result = Trim(text)

    ' 複数の連続する空白を1つに置換
    Do While InStr(result, "  ") > 0
        result = Replace(result, "  ", " ")
    Loop

    NormalizeSpaces = result
End Function

Sub TestNormalizeSpaces()
    Dim text As String

    text = "   Hello    World   "
    Debug.Print "[" & NormalizeSpaces(text) & "]"
    ' 出力: [Hello World]
End Sub

固定長データの処理

trim_fixed_length.bas
Sub ProcessFixedLengthData()
    Dim record As String
    Dim name As String
    Dim address As String

    ' 固定長レコード(各フィールドが空白でパディングされている)
    record = "山田太郎    東京都新宿区西新宿    "

    ' 名前(最初の10文字)
    name = Trim(Left(record, 10))
    Debug.Print "名前: [" & name & "]"  ' [山田太郎]

    ' 住所(11文字目以降)
    address = Trim(Mid(record, 11))
    Debug.Print "住所: [" & address & "]"  ' [東京都新宿区西新宿]
End Sub

データベースフィールドのクレンジング

trim_database.bas
Sub CleanDatabaseData()
    Dim ws As Worksheet
    Dim lastRow As Long
    Dim i As Long

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

    ' 名前列(A列)と住所列(B列)をクレンジング
    For i = 2 To lastRow  ' ヘッダー行をスキップ
        ' 名前をトリミング
        If Not IsEmpty(ws.Cells(i, 1).Value) Then
            ws.Cells(i, 1).Value = Trim(ws.Cells(i, 1).Value)
        End If

        ' 住所をトリミング
        If Not IsEmpty(ws.Cells(i, 2).Value) Then
            ws.Cells(i, 2).Value = Trim(ws.Cells(i, 2).Value)
        End If
    Next i

    MsgBox "データクレンジングが完了しました"
End Sub

全角スペースの処理

全角スペースも削除する関数

trim_fullwidth.bas
Function TrimAll(text As String) As String
    Dim result As String

    ' 全角スペース(Chr(12288))と半角スペースを削除
    result = text

    ' 先頭の空白を削除
    Do While Left(result, 1) = " " Or Left(result, 1) = " "
        result = Mid(result, 2)
    Loop

    ' 末尾の空白を削除
    Do While Right(result, 1) = " " Or Right(result, 1) = " "
        result = Left(result, Len(result) - 1)
    Loop

    TrimAll = result
End Function

Sub TestTrimAll()
    Dim text As String

    ' 半角と全角の空白が混在
    text = "   Hello World   "

    Debug.Print "Trim:    [" & Trim(text) & "]"
    Debug.Print "TrimAll: [" & TrimAll(text) & "]"

    ' 出力:
    ' Trim:    [ Hello World ]  ← 全角スペースが残る
    ' TrimAll: [Hello World]      ← すべての空白が削除される
End Sub
チェック

標準のTrim関数は、全角スペース(Chr(12288))を削除しません。日本語データを扱う場合は、全角スペースも考慮した独自関数の作成を検討してください。

全角・半角スペースを正規化

trim_normalize_all_spaces.bas
Function NormalizeAllSpaces(text As String) As String
    Dim result As String

    ' 全角スペースを半角スペースに変換
    result = Replace(text, " ", " ")

    ' 複数の空白を1つに
    Do While InStr(result, "  ") > 0
        result = Replace(result, "  ", " ")
    Loop

    ' 両端をトリミング
    result = Trim(result)

    NormalizeAllSpaces = result
End Function

Sub TestNormalizeAll()
    Debug.Print "[" & NormalizeAllSpaces("  Hello  World  ") & "]"
    ' 出力: [Hello World]
End Sub

タブや改行の処理

タブ文字の削除

trim_with_tab.bas
Function TrimWithTab(text As String) As String
    Dim result As String

    ' タブ文字(Chr(9))も削除
    result = text

    ' 先頭のスペースとタブを削除
    Do While Left(result, 1) = " " Or Left(result, 1) = vbTab
        result = Mid(result, 2)
    Loop

    ' 末尾のスペースとタブを削除
    Do While Right(result, 1) = " " Or Right(result, 1) = vbTab
        result = Left(result, Len(result) - 1)
    Loop

    TrimWithTab = result
End Function

Sub TestTrimWithTab()
    Dim text As String

    text = vbTab & "  Hello World  " & vbTab
    Debug.Print "[" & TrimWithTab(text) & "]"
    ' 出力: [Hello World]
End Sub

改行を含む文字列のトリミング

trim_multiline.bas
Function TrimMultiLine(text As String) As String
    Dim lines() As String
    Dim i As Long
    Dim result As String

    ' 改行で分割
    lines = Split(text, vbCrLf)

    ' 各行をトリミング
    For i = 0 To UBound(lines)
        lines(i) = Trim(lines(i))
    Next i

    ' 再結合
    TrimMultiLine = Join(lines, vbCrLf)
End Function

Sub TestTrimMultiLine()
    Dim text As String

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

    Debug.Print TrimMultiLine(text)
    ' 出力:
    ' Line 1
    ' Line 2
    ' Line 3
End Sub

パフォーマンス最適化

大量データのトリミング

trim_performance.bas
Sub TrimLargeDataset()
    Dim ws As Worksheet
    Dim lastRow As Long
    Dim dataArray As Variant
    Dim i As Long
    Dim startTime As Double

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

    startTime = Timer

    ' 配列に読み込んで処理(高速化)
    dataArray = ws.Range("A1:A" & lastRow).Value

    For i = 1 To UBound(dataArray, 1)
        If Not IsEmpty(dataArray(i, 1)) Then
            dataArray(i, 1) = Trim(dataArray(i, 1))
        End If
    Next i

    ' 配列を一括書き込み
    ws.Range("A1:A" & lastRow).Value = dataArray

    Debug.Print "処理時間: " & Format(Timer - startTime, "0.000") & "秒"
End Sub
チェック

大量のセルをトリミングする場合は、セルを1つずつ処理するのではなく、配列に読み込んで処理し、最後に一括書き込みすると高速化できます。

注意点とエラー処理

Null 値と Empty 値の処理

trim_null_empty.bas
Function SafeTrim(value As Variant) As String
    If IsNull(value) Then
        SafeTrim = ""
    ElseIf IsEmpty(value) Then
        SafeTrim = ""
    ElseIf VarType(value) = vbString Then
        SafeTrim = Trim(value)
    Else
        SafeTrim = Trim(CStr(value))
    End If
End Function

Sub TestSafeTrim()
    Debug.Print "[" & SafeTrim("  Hello  ") & "]"  ' [Hello]
    Debug.Print "[" & SafeTrim(Empty) & "]"        ' []
    Debug.Print "[" & SafeTrim(123) & "]"          ' [123]
End Sub

空白のみの文字列

trim_space_only.bas
Sub TrimSpaceOnly()
    Dim text As String
    Dim result As String

    ' 空白のみの文字列
    text = "     "
    result = Trim(text)

    Debug.Print "長さ: " & Len(result)  ' 0
    Debug.Print "空文字列: " & (result = "")  ' True
End Sub
チェック

空白のみの文字列をTrimすると、空文字列("")になります。空チェックを行う際は、Trim後の文字列の長さを確認してください。

まとめ

Trim、LTrim、RTrim 関数は、文字列の空白を削除する基本的かつ重要な関数です。

重要なポイント

  • Trim:両端の空白を削除
  • LTrim:先頭の空白のみ削除
  • RTrim:末尾の空白のみ削除
  • 半角スペース(ASCII 32)のみが対象
  • 全角スペース、タブ、改行は削除されない
  • データクレンジングや CSV 処理に必須

使い分けのポイント

  • ユーザー入力の正規化:Trim
  • 固定長データの右詰め維持:LTrimのみ
  • ログ出力の整形:RTrimのみ
  • データベース連携:Trim + 全角スペース対応

関連関数

Trim 関数ファミリーを適切に使うことで、クリーンで信頼性の高いデータ処理が実現できます。

#VBA #Trim #LTrim #RTrim #文字列操作 #クレンジング