Left/Right関数

にメンテナンス済み

Left 関数と Right 関数は、文字列の先頭または末尾から指定した文字数を抽出する VBA の関数です。プレフィックスの確認、拡張子の取得、電話番号の市外局番抽出など、様々な場面で活用できます。

基本構文

Left 関数

Left(文字列, 文字数)
引数必須説明
文字列String対象の文字列
文字数Long先頭から抽出する文字数

Right 関数

Right(文字列, 文字数)
引数必須説明
文字列String対象の文字列
文字数Long末尾から抽出する文字数

戻り値

抽出された部分文字列(String 型)

チェック

Left関数は先頭から、Right関数は末尾から指定した文字数を取得します。どちらも、指定した文字数が文字列全体の長さを超える場合は、文字列全体を返します。

Left 関数の基本的な使い方

先頭からの抽出

left_basic.bas
Sub LeftBasicExample()
    Dim text As String
    Dim result As String

    text = "Hello World"

    ' 先頭から5文字を抽出
    result = Left(text, 5)
    Debug.Print result  ' Hello

    ' 先頭から1文字を抽出
    result = Left(text, 1)
    Debug.Print result  ' H

    ' 先頭から8文字を抽出
    result = Left(text, 8)
    Debug.Print result  ' Hello Wo
End Sub

プレフィックスの確認

left_prefix_check.bas
Function HasPrefix(text As String, prefix As String) As Boolean
    If Len(text) >= Len(prefix) Then
        HasPrefix = (Left(text, Len(prefix)) = prefix)
    Else
        HasPrefix = False
    End If
End Function

Sub TestHasPrefix()
    Debug.Print HasPrefix("https://example.com", "https://")  ' True
    Debug.Print HasPrefix("http://example.com", "https://")   ' False
    Debug.Print HasPrefix("ftp://server.com", "ftp://")       ' True
End Sub

年月の抽出

left_date_extract.bas
Sub ExtractYearMonth()
    Dim dateText As String
    Dim yearMonth As String

    dateText = "2025-10-20"

    ' 先頭から7文字(yyyy-mm)を抽出
    yearMonth = Left(dateText, 7)
    Debug.Print "年月: " & yearMonth  ' 2025-10

    ' 年だけを抽出
    Dim year As String
    year = Left(dateText, 4)
    Debug.Print "年: " & year  ' 2025
End Sub

Right 関数の基本的な使い方

末尾からの抽出

right_basic.bas
Sub RightBasicExample()
    Dim text As String
    Dim result As String

    text = "Hello World"

    ' 末尾から5文字を抽出
    result = Right(text, 5)
    Debug.Print result  ' World

    ' 末尾から1文字を抽出
    result = Right(text, 1)
    Debug.Print result  ' d

    ' 末尾から8文字を抽出
    result = Right(text, 8)
    Debug.Print result  ' lo World
End Sub

ファイル拡張子の取得

right_extension.bas
Function GetExtension(fileName As String) As String
    Dim dotPos As Long

    ' 末尾から最初の.を検索
    dotPos = InStrRev(fileName, ".")

    If dotPos > 0 Then
        ' .以降を取得
        GetExtension = Right(fileName, Len(fileName) - dotPos)
    Else
        GetExtension = ""
    End If
End Function

Sub TestGetExtension()
    Debug.Print GetExtension("report.xlsx")       ' xlsx
    Debug.Print GetExtension("data.csv")          ' csv
    Debug.Print GetExtension("file.backup.txt")   ' txt
    Debug.Print GetExtension("README")            ' (空文字列)
End Sub

電話番号の末尾 4 桁

right_phone_last4.bas
Function GetPhoneLastFour(phoneNumber As String) As String
    ' ハイフンやスペースを除去
    phoneNumber = Replace(phoneNumber, "-", "")
    phoneNumber = Replace(phoneNumber, " ", "")

    ' 末尾4桁を取得
    If Len(phoneNumber) >= 4 Then
        GetPhoneLastFour = Right(phoneNumber, 4)
    Else
        GetPhoneLastFour = phoneNumber
    End If
End Function

Sub TestPhoneLastFour()
    Debug.Print GetPhoneLastFour("090-1234-5678")  ' 5678
    Debug.Print GetPhoneLastFour("03-1234-5678")   ' 5678
End Sub

実践的な活用例

URL のプロトコル判定

left_protocol.bas
Function GetProtocol(url As String) As String
    If Left(url, 8) = "https://" Then
        GetProtocol = "https"
    ElseIf Left(url, 7) = "http://" Then
        GetProtocol = "http"
    ElseIf Left(url, 6) = "ftp://" Then
        GetProtocol = "ftp"
    Else
        GetProtocol = "unknown"
    End If
End Function

Sub TestGetProtocol()
    Debug.Print GetProtocol("https://www.example.com")  ' https
    Debug.Print GetProtocol("http://example.com")       ' http
    Debug.Print GetProtocol("ftp://ftp.example.com")    ' ftp
    Debug.Print GetProtocol("www.example.com")          ' unknown
End Sub

ファイル名からベース名を取得

left_basename.bas
Function GetBaseName(fileName As String) As String
    Dim dotPos As Long

    dotPos = InStrRev(fileName, ".")

    If dotPos > 1 Then
        ' 拡張子を除いたベース名を取得
        GetBaseName = Left(fileName, dotPos - 1)
    Else
        GetBaseName = fileName
    End If
End Function

Sub TestGetBaseName()
    Debug.Print GetBaseName("report.xlsx")      ' report
    Debug.Print GetBaseName("data.backup.csv")  ' data.backup
    Debug.Print GetBaseName("README")           ' README
End Sub

郵便番号の前半・後半

left_right_zipcode.bas
Sub ParseZipCode()
    Dim zipCode As String
    Dim firstPart As String
    Dim secondPart As String

    ' ハイフンなしの郵便番号
    zipCode = "1234567"

    ' 前半3桁
    firstPart = Left(zipCode, 3)
    Debug.Print "前半: " & firstPart  ' 123

    ' 後半4桁
    secondPart = Right(zipCode, 4)
    Debug.Print "後半: " & secondPart  ' 4567

    ' フォーマット
    Debug.Print "郵便番号: " & firstPart & "-" & secondPart  ' 123-4567
End Sub

商品コードの接頭辞・接尾辞

left_right_product_code.bas
Sub ParseProductCode()
    Dim code As String
    Dim prefix As String
    Dim suffix As String

    code = "PRD-2025-ABC"

    ' プレフィックス(最初の3文字)
    prefix = Left(code, 3)
    Debug.Print "プレフィックス: " & prefix  ' PRD

    ' サフィックス(最後の3文字)
    suffix = Right(code, 3)
    Debug.Print "サフィックス: " & suffix  ' ABC

    ' 判定
    If prefix = "PRD" Then
        Debug.Print "製品コードです"
    End If
End Sub

クレジットカード番号の表示

right_credit_display.bas
Function FormatCreditCardLast4(cardNumber As String) As String
    ' 空白やハイフンを除去
    cardNumber = Replace(cardNumber, " ", "")
    cardNumber = Replace(cardNumber, "-", "")

    If Len(cardNumber) >= 4 Then
        ' 最後の4桁のみ表示
        FormatCreditCardLast4 = "**** **** **** " & Right(cardNumber, 4)
    Else
        FormatCreditCardLast4 = cardNumber
    End If
End Function

Sub TestCreditDisplay()
    Debug.Print FormatCreditCardLast4("1234567890123456")
    ' 出力: **** **** **** 3456

    Debug.Print FormatCreditCardLast4("4111-1111-1111-1111")
    ' 出力: **** **** **** 1111
End Sub

バージョン番号の比較

left_version.bas
Function GetMajorVersion(version As String) As Integer
    Dim dotPos As Long

    ' 最初の.の位置を検索
    dotPos = InStr(version, ".")

    If dotPos > 0 Then
        ' メジャーバージョンを取得
        GetMajorVersion = CInt(Left(version, dotPos - 1))
    Else
        GetMajorVersion = CInt(version)
    End If
End Function

Sub TestMajorVersion()
    Debug.Print GetMajorVersion("2.5.1")    ' 2
    Debug.Print GetMajorVersion("10.0.0")   ' 10
    Debug.Print GetMajorVersion("3")        ' 3
End Sub

両関数の組み合わせ

中間部分の抽出(Left と Right の組み合わせ)

left_right_combo.bas
Function ExtractMiddle(text As String, leftChars As Long, rightChars As Long) As String
    Dim temp As String

    ' 左側を除去
    temp = Right(text, Len(text) - leftChars)

    ' 右側を除去
    ExtractMiddle = Left(temp, Len(temp) - rightChars)
End Function

Sub TestExtractMiddle()
    Dim text As String
    text = "【重要】お知らせ【必読】"

    ' 最初の3文字と最後の3文字を除去
    Debug.Print ExtractMiddle(text, 3, 3)  ' お知らせ
End Sub

電話番号の市外局番と下 4 桁

left_right_phone.bas
Sub FormatPhoneDisplay(phoneNumber As String)
    Dim areaCode As String
    Dim lastFour As String

    ' ハイフンを除去
    phoneNumber = Replace(phoneNumber, "-", "")

    ' 市外局番(最初の2-3桁)
    If Left(phoneNumber, 1) = "0" Then
        If Left(phoneNumber, 2) = "03" Or Left(phoneNumber, 2) = "06" Then
            areaCode = Left(phoneNumber, 2)
        Else
            areaCode = Left(phoneNumber, 3)
        End If
    End If

    ' 下4桁
    lastFour = Right(phoneNumber, 4)

    Debug.Print "市外局番: " & areaCode
    Debug.Print "下4桁: " & lastFour
End Sub

Sub TestPhoneFormat()
    FormatPhoneDisplay("0312345678")   ' 市外局番: 03, 下4桁: 5678
    FormatPhoneDisplay("09012345678")  ' 市外局番: 090, 下4桁: 5678
End Sub

注意点と Tips

文字数が長すぎる場合

left_right_overflow.bas
Sub LeftRightOverflow()
    Dim text As String
    Dim result As String

    text = "Hello"

    ' 指定文字数が文字列長を超える場合
    result = Left(text, 100)
    Debug.Print "Left: [" & result & "]"  ' Hello(全体)

    result = Right(text, 100)
    Debug.Print "Right: [" & result & "]"  ' Hello(全体)
End Sub
チェック

指定した文字数が文字列全体の長さを超える場合、Left関数とRight関数はエラーにならず、文字列全体を返します。

空文字列の処理

left_right_empty.bas
Sub LeftRightEmpty()
    Dim text As String
    Dim result As String

    text = ""

    ' 空文字列に対する操作
    result = Left(text, 5)
    Debug.Print "Left: [" & result & "]"  ' 空文字列

    result = Right(text, 5)
    Debug.Print "Right: [" & result & "]"  ' 空文字列
End Sub

全角・半角の処理

left_right_fullwidth.bas
Sub LeftRightFullwidth()
    Dim text As String
    Dim result As String

    ' 全角文字も1文字としてカウント
    text = "こんにちは世界"

    result = Left(text, 5)
    Debug.Print result  ' こんにちは

    result = Right(text, 2)
    Debug.Print result  ' 世界
End Sub
チェック

Left関数とRight関数は、全角文字も半角文字も同じく1文字としてカウントします。バイト単位で処理したい場合は、LeftB関数やRightB関数を使用します。

エラー処理

left_right_error.bas
Function SafeLeft(text As String, length As Long) As String
    On Error Resume Next

    If length < 0 Then
        SafeLeft = ""
    ElseIf length = 0 Then
        SafeLeft = ""
    ElseIf length >= Len(text) Then
        SafeLeft = text
    Else
        SafeLeft = Left(text, length)
    End If

    On Error GoTo 0
End Function
チェック

文字数に負の値を指定するとエラーが発生します。ユーザー入力を受け取る場合は、必ず事前に値をチェックしてください。

パフォーマンス比較

Left/Right vs Mid

left_right_performance.bas
Sub ComparePerformance()
    Dim text As String
    Dim i As Long
    Dim startTime As Double
    Dim endTime As Double

    text = "1234567890"

    ' Left関数
    startTime = Timer
    For i = 1 To 100000
        Dim temp As String
        temp = Left(text, 5)
    Next i
    endTime = Timer
    Debug.Print "Left: " & Format(endTime - startTime, "0.000") & "秒"

    ' Mid関数(先頭から)
    startTime = Timer
    For i = 1 To 100000
        temp = Mid(text, 1, 5)
    Next i
    endTime = Timer
    Debug.Print "Mid: " & Format(endTime - startTime, "0.000") & "秒"
End Sub
チェック

先頭または末尾からの抽出には、Mid関数よりもLeft/Right関数の方がコードの意図が明確になります。パフォーマンス差はほとんどありません。

まとめ

Left 関数と Right 関数は、文字列の先頭や末尾から部分文字列を抽出する基本的な関数です。

重要なポイント

  • Left:先頭から指定文字数を抽出
  • Right:末尾から指定文字数を抽出
  • 指定文字数が文字列長を超えても、エラーにならず全体を返す
  • プレフィックス・サフィックスの確認に最適
  • InStr/InStrRev と組み合わせて動的な抽出が可能

関連関数

Left 関数と Right 関数を使いこなすことで、様々な文字列処理が簡潔かつ明確に記述できます。

#VBA #Left #Right #文字列操作 #抽出