Range.SpecialCellsで高速化
大量データを1セルずつループすると処理が遅くなります。そこで Range.SpecialCells を使うと「条件に合うセルだけ」を一気に取得でき、無駄な処理を省いて高速化できます。初心者向けに最短コードから実務テンプレートまで整理しました。
基本:空白セルだけを取得して処理
Sub SpecialCells_Blanks()
Dim rng As Range, blanks As Range, c As Range
Set rng = Range("A2:A100")
On Error Resume Next
Set blanks = rng.SpecialCells(xlCellTypeBlanks)
On Error GoTo 0
If Not blanks Is Nothing Then
For Each c In blanks
c.Value = "N/A" '空白を「N/A」で埋める
Next c
End If
End Sub
VB- ポイント:
xlCellTypeBlanks→ 空白セルだけを抽出。- 該当なしだとエラーになるので
On Errorでガード。 - ループ対象が「空白セルだけ」になるので高速。
数式セルだけを取得
Sub SpecialCells_Formulas()
Dim rng As Range, formulas As Range
Set rng = Range("B2:B100")
On Error Resume Next
Set formulas = rng.SpecialCells(xlCellTypeFormulas)
On Error GoTo 0
If Not formulas Is Nothing Then
formulas.Interior.Color = RGB(255, 255, 153) '背景を黄色に
End If
End Sub
VB- ポイント:
xlCellTypeFormulas→ 数式セルだけ。- 書式変更や値化などを一気に適用できる。
エラーセルだけを取得
Sub SpecialCells_Errors()
Dim rng As Range, errs As Range
Set rng = Range("C2:C200")
On Error Resume Next
Set errs = rng.SpecialCells(xlCellTypeFormulas, xlErrors)
On Error GoTo 0
If Not errs Is Nothing Then
errs.ClearContents 'エラーセルをクリア
End If
End Sub
VB- ポイント:
- 第2引数で「数式のうちエラーセル」を指定。
- エラーだけを狙い撃ちできる。
可視セルだけを取得(フィルタ後の高速処理)
Sub SpecialCells_Visible()
Dim rng As Range, vis As Range, c As Range
Set rng = Range("A1").CurrentRegion
rng.AutoFilter Field:=2, Criteria1:="営業A"
On Error Resume Next
Set vis = rng.Offset(1).Resize(rng.Rows.Count - 1).Columns(1).SpecialCells(xlCellTypeVisible)
On Error GoTo 0
If Not vis Is Nothing Then
For Each c In vis
Cells(c.Row, "G").Value = Cells(c.Row, "C").Value * Cells(c.Row, "D").Value
Next c
End If
End Sub
VB- ポイント:
xlCellTypeVisible→ フィルタで表示中のセルだけ。- 列を1本に絞って行番号で処理するのが定番。
実務テンプレート:よく使うパターン
'1) 空白セルを一括削除
Sub DeleteBlankRows()
Dim rng As Range, blanks As Range
Set rng = Range("A1").CurrentRegion
On Error Resume Next
Set blanks = rng.SpecialCells(xlCellTypeBlanks)
On Error GoTo 0
If Not blanks Is Nothing Then blanks.EntireRow.Delete
End Sub
'2) 数値セルだけ合計
Sub SumNumbersOnly()
Dim rng As Range, nums As Range, c As Range, s As Double
Set rng = Range("E2:E100")
On Error Resume Next
Set nums = rng.SpecialCells(xlCellTypeConstants, xlNumbers)
On Error GoTo 0
If Not nums Is Nothing Then
For Each c In nums
s = s + c.Value
Next c
Range("G2").Value = s
End If
End Sub
'3) フィルタ後の可視セルだけコピー
Sub CopyVisibleRows()
Dim rng As Range, vis As Range
Set rng = Range("A1").CurrentRegion
rng.AutoFilter Field:=3, Criteria1:=">=80"
On Error Resume Next
Set vis = rng.Offset(1).Resize(rng.Rows.Count - 1).SpecialCells(xlCellTypeVisible)
On Error GoTo 0
If Not vis Is Nothing Then vis.Copy Destination:=Range("H2")
End Sub
VB例題で練習
例題1:空白セルを「未入力」で埋める
Sub Example_FillBlanks()
Dim blanks As Range
On Error Resume Next
Set blanks = Range("B2:B50").SpecialCells(xlCellTypeBlanks)
On Error GoTo 0
If Not blanks Is Nothing Then blanks.Value = "未入力"
End Sub
VB例題2:フィルタ後の表示行だけ「対象」と書き込む
Sub Example_FlagVisibleRows()
Dim vis As Range, c As Range
Range("A1").CurrentRegion.AutoFilter Field:=2, Criteria1:="営業A"
On Error Resume Next
Set vis = Range("A2:A100").SpecialCells(xlCellTypeVisible)
On Error GoTo 0
If Not vis Is Nothing Then
For Each c In vis
Cells(c.Row, "F").Value = "対象"
Next c
End If
End Sub
VB実務の落とし穴と対策
- 該当なしでエラー: SpecialCells は対象が0件だとエラーになる。必ず
On ErrorとNothingチェックを入れる。 - 範囲指定の工夫: CurrentRegion は空白行で途切れる。必要なら最終行・最終列を計算して範囲を組み立てる。
- 大量データで高速化: 1セルずつループするより、SpecialCellsで対象を絞って一括処理する方が圧倒的に速い。
- 可視セル処理: フィルタ後は
xlCellTypeVisibleを使うのが定番。
