InStr関数

にメンテナンス済み

InStr 関数は、文字列内で検索文字列が最初に現れる位置を返す VBA の関数です。文字列の検証、データの抽出、条件分岐など、様々な場面で活用できる重要な関数です。

基本構文

InStr 関数(先頭から検索)

InStr([開始位置], 文字列, 検索文字列, [比較方法])

InStrRev 関数(末尾から検索)

InStrRev(文字列, 検索文字列, [開始位置], [比較方法])

引数(InStr)

引数必須説明
開始位置Long×検索開始位置(省略時は 1)
文字列String検索対象の文字列
検索文字列String検索する文字列
比較方法VbCompareMethod×大文字小文字の区別

戻り値

  • 見つかった場合:位置(1 から始まる)
  • 見つからない場合:0
チェック

InStr関数の位置は1から始まります(0ではありません)。見つからない場合は0を返すため、条件分岐でIf position > 0 Thenのようにチェックします。

基本的な使い方

シンプルな検索

instr_basic.bas
Sub InStrBasicExample()
    Dim text As String
    Dim position As Long

    text = "東京都新宿区西新宿"

    ' 「新宿」の位置を検索
    position = InStr(text, "新宿")
    Debug.Print position  ' 4(4文字目から始まる)

    ' 見つからない場合
    position = InStr(text, "大阪")
    Debug.Print position  ' 0
End Sub

検索開始位置の指定

instr_start_position.bas
Sub InStrWithStartPosition()
    Dim text As String
    Dim position As Long

    text = "192.168.1.1"

    ' 最初の「.」を検索
    position = InStr(text, ".")
    Debug.Print "最初のドット: " & position  ' 4

    ' 2番目の「.」を検索(最初のドットの次から)
    position = InStr(position + 1, text, ".")
    Debug.Print "2番目のドット: " & position  ' 8

    ' 3番目の「.」を検索
    position = InStr(position + 1, text, ".")
    Debug.Print "3番目のドット: " & position  ' 10
End Sub

文字列が含まれているかチェック

instr_contains.bas
Sub CheckStringContains()
    Dim email As String

    email = "[email protected]"

    ' メールアドレスの検証(@が含まれているか)
    If InStr(email, "@") > 0 Then
        Debug.Print "有効なメールアドレスの可能性があります"
    Else
        Debug.Print "無効なメールアドレスです"
    End If

    ' 特定のドメインをチェック
    If InStr(email, "example.com") > 0 Then
        Debug.Print "example.comドメインです"
    End If
End Sub

大文字小文字を区別しない検索

instr_case_insensitive.bas
Sub InStrCaseInsensitive()
    Dim text As String
    Dim position As Long

    text = "Hello World"

    ' 大文字小文字を区別する(デフォルト)
    position = InStr(text, "world")
    Debug.Print "区別する: " & position  ' 0(見つからない)

    ' 大文字小文字を区別しない
    position = InStr(1, text, "world", vbTextCompare)
    Debug.Print "区別しない: " & position  ' 7
End Sub

InStrRev 関数:末尾から検索

InStrRev 関数は、文字列の末尾から検索を開始します。ファイルパスからファイル名を抽出する際などに便利です。

instrrev_example.bas
Sub InStrRevExample()
    Dim filePath As String
    Dim position As Long
    Dim fileName As String
    Dim folderPath As String

    filePath = "C:\Users\Username\Documents\report.xlsx"

    ' 末尾から最初の「\」を検索
    position = InStrRev(filePath, "\")

    ' ファイル名を抽出
    fileName = Mid(filePath, position + 1)
    Debug.Print "ファイル名: " & fileName  ' report.xlsx

    ' フォルダパスを抽出
    folderPath = Left(filePath, position - 1)
    Debug.Print "フォルダ: " & folderPath  ' C:\Users\Username\Documents
End Sub
チェック

ファイルパスからファイル名を抽出する場合、InStrRev関数を使うと簡単です。末尾から検索するため、最後の区切り文字を見つけられます。

実践的な活用例

メールアドレスの検証

instr_validate_email.bas
Function IsValidEmail(email As String) As Boolean
    ' 基本的なメールアドレス検証
    If Len(email) = 0 Then
        IsValidEmail = False
        Exit Function
    End If

    ' @が含まれているか
    If InStr(email, "@") = 0 Then
        IsValidEmail = False
        Exit Function
    End If

    ' .が含まれているか
    If InStr(email, ".") = 0 Then
        IsValidEmail = False
        Exit Function
    End If

    ' @が複数含まれていないか
    Dim firstAt As Long
    Dim secondAt As Long
    firstAt = InStr(email, "@")
    secondAt = InStr(firstAt + 1, email, "@")

    If secondAt > 0 Then
        IsValidEmail = False
        Exit Function
    End If

    ' @の後に.があるか
    Dim dotAfterAt As Long
    dotAfterAt = InStr(firstAt, email, ".")

    If dotAfterAt = 0 Then
        IsValidEmail = False
        Exit Function
    End If

    IsValidEmail = True
End Function

Sub TestEmailValidation()
    Debug.Print IsValidEmail("[email protected]")  ' True
    Debug.Print IsValidEmail("invalid-email")      ' False
    Debug.Print IsValidEmail("user@@example.com")  ' False
End Sub

URL からドメインを抽出

instr_extract_domain.bas
Function ExtractDomain(url As String) As String
    Dim protocolEnd As Long
    Dim pathStart As Long
    Dim domain As String

    ' http://またはhttps://の後から開始
    protocolEnd = InStr(url, "://")

    If protocolEnd > 0 Then
        ' プロトコルの後から
        domain = Mid(url, protocolEnd + 3)
    Else
        domain = url
    End If

    ' 最初の/を検索(パスの開始)
    pathStart = InStr(domain, "/")

    If pathStart > 0 Then
        domain = Left(domain, pathStart - 1)
    End If

    ExtractDomain = domain
End Function

Sub TestExtractDomain()
    Debug.Print ExtractDomain("https://www.example.com/path/to/page")
    ' 出力: www.example.com

    Debug.Print ExtractDomain("http://example.com:8080/api")
    ' 出力: example.com:8080
End Sub

複数の文字列を検索

instr_multiple_search.bas
Function ContainsAny(text As String, searchWords() As String) As Boolean
    Dim word As Variant

    For Each word In searchWords
        If InStr(1, text, word, vbTextCompare) > 0 Then
            ContainsAny = True
            Exit Function
        End If
    Next word

    ContainsAny = False
End Function

Sub TestContainsAny()
    Dim text As String
    Dim keywords() As String

    text = "VBAでExcelの自動化を学ぶ"
    keywords = Split("Excel,Word,PowerPoint", ",")

    If ContainsAny(text, keywords) Then
        Debug.Print "キーワードが含まれています"
    End If
End Sub

文字列の置換位置を特定

instr_find_all_positions.bas
Sub FindAllPositions()
    Dim text As String
    Dim searchWord As String
    Dim position As Long
    Dim positions As String
    Dim startPos As Long

    text = "りんごとバナナとオレンジとりんご"
    searchWord = "りんご"

    startPos = 1

    Do
        position = InStr(startPos, text, searchWord)

        If position > 0 Then
            positions = positions & position & ", "
            startPos = position + Len(searchWord)
        End If
    Loop While position > 0

    ' 最後のカンマとスペースを削除
    If Len(positions) > 0 Then
        positions = Left(positions, Len(positions) - 2)
    End If

    Debug.Print "「" & searchWord & "」の位置: " & positions
    ' 出力: 「りんご」の位置: 1, 18
End Sub

ファイル拡張子の取得

instr_get_extension.bas
Function GetFileExtension(fileName As String) As String
    Dim dotPosition As Long

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

    If dotPosition > 0 Then
        GetFileExtension = Mid(fileName, dotPosition + 1)
    Else
        GetFileExtension = ""
    End If
End Function

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

特定の文字で始まる・終わるかチェック

instr_starts_ends_with.bas
Function StartsWith(text As String, prefix As String) As Boolean
    StartsWith = (InStr(1, text, prefix, vbTextCompare) = 1)
End Function

Function EndsWith(text As String, suffix As String) As Boolean
    Dim suffixLen As Long
    Dim textLen As Long

    suffixLen = Len(suffix)
    textLen = Len(text)

    If suffixLen > textLen Then
        EndsWith = False
        Exit Function
    End If

    EndsWith = (InStrRev(text, suffix, , vbTextCompare) = textLen - suffixLen + 1)
End Function

Sub TestStartsEndsWith()
    Dim fileName As String

    fileName = "report.xlsx"

    If StartsWith(fileName, "report") Then
        Debug.Print "「report」で始まります"
    End If

    If EndsWith(fileName, ".xlsx") Then
        Debug.Print "「.xlsx」で終わります"
    End If
End Sub

パフォーマンスと最適化

Like 演算子との比較

instr_vs_like.bas
Sub InStrVsLike()
    Dim text As String

    text = "[email protected]"

    ' InStr関数を使った検索
    If InStr(text, "@") > 0 Then
        Debug.Print "InStr: @が含まれています"
    End If

    ' Like演算子を使ったパターンマッチ
    If text Like "*@*" Then
        Debug.Print "Like: @が含まれています"
    End If

    ' 複雑なパターンはLike演算子が便利
    If text Like "*@*.com" Then
        Debug.Print "Like: .comドメインです"
    End If
End Sub
チェック

単純な文字列検索にはInStr関数、パターンマッチが必要な場合はLike演算子を使い分けましょう。InStr関数の方が若干高速です。

注意点と Tips

空文字列の検索

instr_empty_string.bas
Sub InStrEmptyString()
    Dim text As String
    Dim position As Long

    text = "Hello World"

    ' 空文字列を検索すると1が返る
    position = InStr(text, "")
    Debug.Print position  ' 1

    ' これは期待しない動作になる可能性があるため注意
End Sub
チェック

空文字列を検索すると、常に1(先頭位置)が返されます。検索前に検索文字列が空でないことを確認しましょう。

全角・半角の違い

instr_fullwidth_halfwidth.bas
Sub InStrFullwidthHalfwidth()
    Dim text As String
    Dim position As Long

    text = "VBA(Visual Basic for Applications)"

    ' 半角カッコ
    position = InStr(text, "(")
    Debug.Print "半角: " & position  ' 4

    ' 全角カッコ
    position = InStr(text, "(")
    Debug.Print "全角: " & position  ' 0(見つからない)
End Sub

まとめ

InStr 関数と InStrRev 関数は、文字列の検索と位置取得に必須の関数です。

重要なポイント

  • InStr:先頭から検索、InStrRev:末尾から検索
  • 戻り値は 1 から始まる位置(見つからない場合は 0)
  • 大文字小文字の区別を指定可能
  • 文字列の検証、抽出、条件分岐に最適
  • ファイルパス解析や URL 解析に便利

関連関数

InStr 関数をマスターすることで、様々な文字列処理が効率的に行えるようになります。

#VBA #InStr #InStrRev #文字列操作 #検索