Excel VBA 逆引き集 | FINDでセル検索

Excel VBA
スポンサーリンク

FINDでセル検索

セル内の文字列・数値を素早く見つけて扱うなら、Range.Findが最短で柔軟。初心者でも迷わない「基本→複数ヒット→応用(見出し検索・範囲限定)→安全テンプレ」を、実務の落とし穴込みでまとめます。


基本の使い方(最初の一致を1件だけ取得)

Sub Find_Basic_WholeMatch()
    Dim rng As Range, hit As Range
    Set rng = Range("A2:A1000")                       '検索範囲
    Set hit = rng.Find(What:="商品A", LookAt:=xlWhole, LookIn:=xlValues)
    If Not hit Is Nothing Then
        MsgBox "見つかったセル: " & hit.Address
    Else
        MsgBox "見つかりません"
    End If
End Sub
VB
  • ポイント:
    • LookAt: 完全一致は xlWhole、部分一致は xlPart。
    • LookIn: 値を検索するなら xlValues、数式内の文字列なら xlFormulas。
    • 見つからないとき: Nothing チェックで安全に分岐。

複数ヒットを全部列挙(FindNextの定型パターン)

Sub Find_AllHits_List()
    Dim rng As Range, first As String, hit As Range
    Set rng = Range("A2:A1000")

    Set hit = rng.Find(What:="ERROR", LookAt:=xlPart, LookIn:=xlValues)
    If hit Is Nothing Then
        MsgBox "該当なし": Exit Sub
    End If

    first = hit.Address
    Do
        Debug.Print "ヒット: "; hit.Address; " 値="; hit.Value
        Set hit = rng.FindNext(After:=hit)
    Loop While Not hit Is Nothing And hit.Address <> first
End Sub
VB
  • ポイント:
    • ループの鍵: 最初のヒットの Address を控え、FindNextで巡回→最初に戻ったら終了。
    • 部分一致でログ抽出: xlPart と LookIn:=xlValues が定番。

見出し(列・行)を検索して列番号/行番号に使う

Sub Find_HeaderColumn()
    Dim headerRow As Range, hit As Range, colNo As Long
    Set headerRow = Range("A1:Z1")
    Set hit = headerRow.Find(What:="金額", LookAt:=xlWhole, LookIn:=xlValues)
    If Not hit Is Nothing Then
        colNo = hit.Column                       'ワークシート上の列番号
        Cells(2, colNo).Value = "ここに計算結果"
    End If
End Sub
VB
  • ポイント:
    • ワークシートの列番号: hit.Column をそのまま使える。
    • 「どの列が見出しか」を動的に決められる。

指定範囲に絞って、ヒット行の値を横展開

Sub Find_RowProcess()
    Dim rng As Range, hit As Range, r As Long
    Set rng = Range("A2:A10000")
    Set hit = rng.Find(What:="顧客1001", LookAt:=xlWhole)
    If Not hit Is Nothing Then
        r = hit.Row
        Cells(r, "H").Value = Cells(r, "C").Value * Cells(r, "D").Value  'H列へ計算結果
    End If
End Sub
VB
  • ポイント:
    • Rowを使う: 見つかったセルの行番号で同じ行の他列へアクセス。

応用テンプレ:複数キーワードを色付け・抽出コピー

Sub Find_MultiKeywords_HighlightAndCopy()
    Dim kw As Variant: kw = Array("ERROR", "WARN", "CRITICAL")
    Dim src As Range: Set src = Range("A2:A50000")
    Dim outRow As Long: outRow = 2

    Dim i As Long, first As String, hit As Range
    For i = LBound(kw) To UBound(kw)
        Set hit = src.Find(What:=kw(i), LookAt:=xlPart, LookIn:=xlValues)
        If Not hit Is Nothing Then
            first = hit.Address
            Do
                hit.Interior.Color = RGB(255, 235, 156)                '色付け
                Worksheets("抽出").Cells(outRow, 1).Value = hit.Value  '抽出コピー
                outRow = outRow + 1
                Set hit = src.FindNext(hit)
            Loop While Not hit Is Nothing And hit.Address <> first
        End If
    Next i
End Sub
VB
  • ポイント:
    • 複数キーワード: 配列で回すだけで拡張。
    • Find状態の引き継ぎ注意: 1キーワードの列挙は1ループで完結してから次のキーワードへ。

安全・高速ラップ(業務用の土台)

Sub Find_SafeWrap()
    Dim scr As Boolean: scr = Application.ScreenUpdating
    Dim ev As Boolean: ev = Application.EnableEvents
    Dim calc As XlCalculation: calc = Application.Calculation
    On Error GoTo Cleanup

    Application.ScreenUpdating = False
    Application.EnableEvents = False
    Application.Calculation = xlCalculationManual

    '=== ここにFindの本処理 ===

Cleanup:
    Application.Calculation = calc
    Application.EnableEvents = ev
    Application.ScreenUpdating = scr
End Sub
VB
  • ポイント:
    • 設定退避→復帰: 途中エラーでも環境が元に戻る。
    • 大量検索: これだけで体感が軽くなる。

引数の使い分け(よく使うものだけ)

  • What: 検索文字列(数値も可)。
  • LookAt:
    • xlWhole(完全一致)
    • xlPart(部分一致)
  • LookIn:
    • xlValues(表示値)
    • xlFormulas(数式テキスト)
  • SearchOrder:
    • xlByRows(行方向)
    • xlByColumns(列方向)
  • MatchCase: True/False(大文字小文字を区別するか)

よくある落とし穴と対策

  • 状態引き継ぎで意図しない検索になる:
    • 対策: 毎回 LookAt/LookIn/MatchCase を明示指定。Find→FindNextは1ループで完結させる。
  • FindNextの無限ループ:
    • 対策: 最初のヒット Address を記録し、同じ Address に戻ったら終了。
  • 数式を検索したいのに見つからない:
    • 対策: LookIn:=xlFormulas を使う。値なら xlValues。
  • 「123」と「00123」問題:
    • 対策: 範囲の値を事前に整えるか、検索文字列の型を意図に合わせて統一。
  • 部分一致で余計なヒット:
    • 対策: 完全一致(xlWhole)で絞るか、検索語に前後条件(例:「[」や区切り)を含めて誤ヒットを減らす。

例題で練習

'例1:A列で「商品B」を完全一致検索→ヒット行の数量×単価をHへ
Sub Example_FindRowCalc()
    Dim hit As Range
    Set hit = Range("A2:A10000").Find(What:="商品B", LookAt:=xlWhole, LookIn:=xlValues)
    If Not hit Is Nothing Then
        Dim r As Long: r = hit.Row
        Cells(r, "H").Value = Val(Cells(r, "C").Value) * Val(Cells(r, "D").Value)
    End If
End Sub

'例2:部分一致で「ERROR」をすべて赤文字に
Sub Example_FindAllColor()
    Dim rng As Range: Set rng = Range("A2:A50000")
    Dim first As String, hit As Range
    Set hit = rng.Find(What:="ERROR", LookAt:=xlPart, LookIn:=xlValues)
    If hit Is Nothing Then Exit Sub
    first = hit.Address
    Do
        hit.Font.Color = vbRed
        Set hit = rng.FindNext(hit)
    Loop While Not hit Is Nothing And hit.Address <> first
End Sub

'例3:見出し「単価」列を見つけて、その列だけ値化
Sub Example_FindHeader_ValuesOnly()
    Dim head As Range, colNo As Long
    Set head = Range("A1:Z1").Find(What:="単価", LookAt:=xlWhole, LookIn:=xlValues)
    If Not head Is Nothing Then
        colNo = head.Column
        With Range(Cells(2, colNo), Cells(10000, colNo))
            .Value = .Value
        End With
    End If
End Sub
VB
タイトルとURLをコピーしました