Excel VBA 逆引き集 | 数式セルだけ処理

Excel VBA
スポンサーリンク

数式セルだけ処理

数式セルだけを狙って処理したいときは、Range.SpecialCells(xlCellTypeFormulas) と Range.HasFormula の2本柱で安全・高速に扱えます。フィルタ後の可視セルやテーブルにも応用できます。


基本:数式セルだけを拾う

Sub Formulas_SelectBasic()
    Dim tgt As Range, formulas As Range
    Set tgt = Range("B2:B500") '対象範囲

    On Error Resume Next
    Set formulas = tgt.SpecialCells(xlCellTypeFormulas) '数式セルだけ取得
    On Error GoTo 0

    If Not formulas Is Nothing Then
        formulas.Interior.Color = RGB(255, 255, 153) '黄色でハイライト
    End If
End Sub
VB
  • キモ: SpecialCells(xlCellTypeFormulas) は「該当なし」だとエラー。On Error と Nothing チェックをセットで使う。
  • 高速化: 最初から「数式セルの集合」に絞って一括処理できるので速い。

点での判定:HasFormula を使う(セル単位の精密制御)

Sub Formulas_HasFormulaRowWise()
    Dim last As Long, r As Long
    last = Cells(Rows.Count, "E").End(xlUp).Row
    For r = 2 To last
        If Cells(r, "E").HasFormula Then
            Cells(r, "F").Value = "数式あり"
        End If
    Next r
End Sub
VB
  • メリット: 1セルずつ細かく分岐したいときに有効(混在範囲での精密制御)。
  • 使い分け: 一括処理は SpecialCells、条件分岐や別列出力は HasFormula。

定番タスク集

'1) 数式だけ「値化」して計算結果を固定
Sub Formulas_ConvertToValues()
    Dim tgt As Range, formulas As Range
    Set tgt = Range("C2:D500")
    On Error Resume Next
    Set formulas = tgt.SpecialCells(xlCellTypeFormulas)
    On Error GoTo 0
    If Not formulas Is Nothing Then formulas.Value = formulas.Value
End Sub

'2) 数式セルのエラーだけを検出してクリア
Sub Formulas_ClearErrorsOnly()
    Dim errs As Range
    On Error Resume Next
    Set errs = Range("E2:E500").SpecialCells(xlCellTypeFormulas, xlErrors)
    On Error GoTo 0
    If Not errs Is Nothing Then errs.ClearContents
End Sub

'3) 数式セルに一括で表示形式を適用
Sub Formulas_NumberFormat()
    Dim formulas As Range
    On Error Resume Next
    Set formulas = Range("G2:G1000").SpecialCells(xlCellTypeFormulas)
    On Error GoTo 0
    If Not formulas Is Nothing Then formulas.NumberFormat = "#,##0.00"
End Sub
VB
  • ラベルのポイント:
    • 値化: .Value = .Value が最速。リンク切りや負荷軽減に。
    • エラー抽出: 第2引数で xlErrors を指定して「数式の中のエラーのみ」。
    • 表示形式: 計算列の見た目統一に便利。

フィルタ後の「見えている数式」だけ処理

Sub Formulas_VisibleOnly()
    Dim rg As Range, vis As Range, formulasVis As Range
    Set rg = Range("A1").CurrentRegion
    rg.AutoFilter Field:=2, Criteria1:="=営業A" '例:B列で抽出

    On Error Resume Next
    Set vis = rg.Offset(1).Resize(rg.Rows.Count - 1).Columns(5).SpecialCells(xlCellTypeVisible) 'E列
    On Error GoTo 0
    If Not vis Is Nothing Then
        On Error Resume Next
        Set formulasVis = vis.SpecialCells(xlCellTypeFormulas) '可視かつ数式
        On Error GoTo 0
        If Not formulasVis Is Nothing Then
            formulasVis.Value = formulasVis.Value '見えている数式だけ値化
        End If
    End If
End Sub
VB
  • ラベルのポイント:
    • 二段絞り: 可視セル → 数式セルの順で再抽出。
    • 列を絞る: 行重複を避けるため、対象列は1本に限定。

テーブル(ListObject)の数式セルだけ処理

Sub Formulas_ListObjectValues()
    Dim lo As ListObject, tgt As Range, formulas As Range
    Set lo = ActiveSheet.ListObjects("売上テーブル")
    Set tgt = lo.ListColumns("計算金額").DataBodyRange

    On Error Resume Next
    Set formulas = tgt.SpecialCells(xlCellTypeFormulas)
    On Error GoTo 0

    If Not formulas Is Nothing Then formulas.Value = formulas.Value
End Sub
VB
  • ラベルのポイント:
    • 列名指定: ListColumns(“列名”) で壊れにくい。
    • DataBodyRange: 見出し除外、データ部のみ対象。

例題で練習

'例題1:数式セルだけ背景を薄緑、定数セルは触らない
Sub Example_HighlightFormulas()
    Dim f As Range
    On Error Resume Next
    Set f = Range("C2:F200").SpecialCells(xlCellTypeFormulas)
    On Error GoTo 0
    If Not f Is Nothing Then f.Interior.Color = RGB(198, 239, 206)
End Sub

'例題2:最初に見つかった「数式エラーセル」をマーキングして終了
Sub Example_FindFirstFormulaError()
    Dim r As Long
    r = 2
    Do While Cells(r, "E").Value <> ""
        If Cells(r, "E").HasFormula And IsError(Cells(r, "E").Value) Then
            Cells(r, "F").Value = "数式エラー"
            Exit Do
        End If
        r = r + 1
    Loop
End Sub

'例題3:選択範囲の数式だけ「小数2桁」に揃える
Sub Example_FormatSelectionFormulas()
    If TypeName(Selection) = "Range" Then
        Dim f As Range
        On Error Resume Next
        Set f = Selection.SpecialCells(xlCellTypeFormulas)
        On Error GoTo 0
        If Not f Is Nothing Then f.NumberFormat = "#,##0.00"
    End If
End Sub
VB

実務の落とし穴と対策

  • 0件時のエラー: SpecialCells は該当なしでエラー。On Error と Nothing チェックはテンプレに。
  • 数式の「空文字」: 数式が “” を返すセルは「空白に見える」が数式セル。HasFormula で判定する。
  • 値化の影響: .Value = .Value は数式を消す。元に戻せないので、必要なら先に .Formula を退避。
  • 可視セルの重複: 可視セル集合を行×列でそのまま回すと重複処理になりやすい。列を1本に絞るか、一括操作にする。
  • 速度最適化: できる限り「集合に対する一括操作」を使い、画面更新・再計算を一時オフに。
Sub SpeedWrap_Formulas()
    Application.ScreenUpdating = False
    Application.Calculation = xlCalculationManual

    '…数式セルの一括処理…

    Application.Calculation = xlCalculationAutomatic
    Application.ScreenUpdating = True
End Sub
VB
タイトルとURLをコピーしました