Excel VBA 逆引き集 | Exit For

Excel VBA
スポンサーリンク

Exit For

Exit ForFor…Next ループを途中で抜けるための命令です。
「条件を満たしたら即終了」「最初の一致だけ処理したい」など、無駄な繰り返しを避けて効率化できます。初心者向けに最短コードから実務テンプレートまで整理しました。


基本構文と最短コード

Sub ExitFor_Basic()
    Dim i As Long
    For i = 1 To 10
        Cells(i, 1).Value = i
        If i = 5 Then Exit For
    Next i
End Sub
VB
  • ポイント:
    • Exit For が実行されると、ループは即終了。
    • 以降の繰り返しはスキップされ、Next の外へ抜ける。

条件成立で途中終了(検索処理の定番)

Sub ExitFor_Search()
    Dim i As Long, last As Long
    last = Cells(Rows.Count, "A").End(xlUp).Row

    For i = 2 To last
        If Cells(i, "A").Value = "東京" Then
            Cells(i, "B").Value = "見つかった!"
            Exit For
        End If
    Next i
End Sub
VB
  • ポイント:
    • 最初の一致だけ処理したいときに便利。
    • すべて探すなら Exit For を使わず最後まで回す。

複数条件で終了(しきい値チェック)

Sub ExitFor_Threshold()
    Dim i As Long, last As Long
    last = Cells(Rows.Count, "E").End(xlUp).Row

    For i = 2 To last
        If Cells(i, "E").Value > 1000000 Then
            Cells(i, "F").Value = "しきい値超過"
            Exit For
        End If
    Next i
End Sub
VB
  • ポイント:
    • 「最初に基準を超えた行」だけ処理して終了。
    • 大量データでも無駄なループを避けられる。

ネストしたループでの Exit For

Sub ExitFor_Nested()
    Dim r As Long, c As Long
    For r = 2 To 10
        For c = 2 To 5
            If Cells(r, c).Value = "NG" Then
                Cells(r, c).Interior.Color = vbRed
                Exit For   '内側ループだけ終了
            End If
        Next c
    Next r
End Sub
VB
  • ポイント:
    • Exit For は「現在のループ」だけ抜ける。
    • 外側のループは続行される。

実務テンプレート

'1) 顧客名を検索して最初の一致だけ処理
Sub FindCustomer()
    Dim i As Long, last As Long
    last = Cells(Rows.Count, "B").End(xlUp).Row
    For i = 2 To last
        If Cells(i, "B").Value = "佐藤" Then
            MsgBox "佐藤さんは " & i & " 行目にいます"
            Exit For
        End If
    Next i
End Sub

'2) 空白行に到達したら終了(途中の空白で打ち切り)
Sub StopAtBlank()
    Dim i As Long
    For i = 2 To 100
        If Cells(i, "A").Value = "" Then Exit For
        Cells(i, "C").Value = "処理済"
    Next i
End Sub

'3) 最初の「緊急」行を強調して終了
Sub HighlightFirstUrgent()
    Dim i As Long, last As Long
    last = Cells(Rows.Count, "A").End(xlUp).Row
    For i = 2 To last
        If Cells(i, "A").Value = "緊急" Then
            Rows(i).Font.Bold = True
            Rows(i).Interior.Color = RGB(255, 199, 206)
            Exit For
        End If
    Next i
End Sub
VB

例題で練習

例題1:最初に金額が30万を超えた行を見つける

Sub Example_FindFirstOver300k()
    Dim i As Long, last As Long
    last = Cells(Rows.Count, "E").End(xlUp).Row
    For i = 2 To last
        If Cells(i, "E").Value > 300000 Then
            MsgBox "最初の超過は " & i & " 行目です"
            Exit For
        End If
    Next i
End Sub
VB

例題2:最初のエラーセルを検出して終了

Sub Example_FindErrorCell()
    Dim i As Long
    For i = 2 To 100
        If IsError(Cells(i, "C").Value) Then
            Cells(i, "D").Value = "エラーあり"
            Exit For
        End If
    Next i
End Sub
VB

実務の落とし穴と対策

  • Exit Forは「現在のループ」だけ終了: ネスト時は外側まで抜けたいならフラグ変数を使う。
  • 検索と全件処理の違い: 最初の一致だけなら Exit For、全件処理なら最後まで回す。
  • 無駄なループ削減: 大量データでは Exit For を入れるだけで速度改善。
  • 条件の明確化: 「終了条件」を必ず書く。曖昧だと意図せず途中で止まる。
タイトルとURLをコピーしました