Cells × Range × Offset × Resize × CurrentRegion × SpecialCells を組み合わせると、表全体を動的に扱いながら、特定セル(空白・定数・数式など)を抽出して加工することができます。
実務で役立つ応用テンプレをまとめました。
基本操作(SpecialCells)
- 空白セルを選択
Range("A1").CurrentRegion.SpecialCells(xlCellTypeBlanks).Select
VB- 定数セルを選択
Range("A1").CurrentRegion.SpecialCells(xlCellTypeConstants).Interior.Color = vbYellow
VB- 数式セルを選択
Range("A1").CurrentRegion.SpecialCells(xlCellTypeFormulas).Font.Bold = True
VBCells × Offset × SpecialCells
- 表の右隣の空白セルを強調
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
tbl.Offset(0, tbl.Columns.Count).Resize(tbl.Rows.Count, 1).SpecialCells(xlCellTypeBlanks).Interior.Color = vbGreen
VB- 表の下にコピー+空白セルを塗りつぶし
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
tbl.Offset(tbl.Rows.Count + 1, 0).Resize(tbl.Rows.Count, tbl.Columns.Count).Value = tbl.Value
tbl.Offset(tbl.Rows.Count + 1, 0).Resize(tbl.Rows.Count, tbl.Columns.Count).SpecialCells(xlCellTypeBlanks).Value = "N/A"
VBResize × SpecialCells
- 表を拡張して空白セルを処理
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion.Resize(Range("A1").CurrentRegion.Rows.Count + 2, Range("A1").CurrentRegion.Columns.Count)
tbl.SpecialCells(xlCellTypeBlanks).Interior.Color = vbRed
VB- 表の最終列+空白セルを処理
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
tbl.Columns(tbl.Columns.Count).SpecialCells(xlCellTypeBlanks).Value = "未入力"
VB応用コピー&加工
- 表を右隣にコピー+数式セルを強調
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
tbl.Offset(0, tbl.Columns.Count + 1).Resize(tbl.Rows.Count, tbl.Columns.Count).Value = tbl.Value
tbl.Offset(0, tbl.Columns.Count + 1).Resize(tbl.Rows.Count, tbl.Columns.Count).SpecialCells(xlCellTypeFormulas).Font.Color = vbBlue
VB- 表を下にコピー+定数セルを強調
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
tbl.Offset(tbl.Rows.Count + 2, 0).Resize(tbl.Rows.Count, tbl.Columns.Count).Value = tbl.Value
tbl.Offset(tbl.Rows.Count + 2, 0).Resize(tbl.Rows.Count, tbl.Columns.Count).SpecialCells(xlCellTypeConstants).Interior.Color = vbYellow
VBループ処理応用
- 表の各行で空白セルを処理
Dim tbl As Range, r As Range
Set tbl = Range("A1").CurrentRegion
For Each r In tbl.Rows
On Error Resume Next
r.SpecialCells(xlCellTypeBlanks).Value = "空白補完"
On Error GoTo 0
Next r
VB- 表の各列で数式セルを処理
Dim tbl As Range, c As Range
Set tbl = Range("A1").CurrentRegion
For Each c In tbl.Columns
On Error Resume Next
c.SpecialCells(xlCellTypeFormulas).Font.Bold = True
On Error GoTo 0
Next c
VB高度な応用
- 表の右隣に「集計列」を追加し空白セルを補完
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
tbl.Offset(0, tbl.Columns.Count).Resize(tbl.Rows.Count, 1).Value = "集計"
tbl.Offset(0, tbl.Columns.Count).Resize(tbl.Rows.Count, 1).SpecialCells(xlCellTypeBlanks).Value = 0
VB- 表の下に「合計行」を追加し数式セルを強調
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
tbl.Offset(tbl.Rows.Count, 0).Resize(1, tbl.Columns.Count).Value = "合計行"
tbl.SpecialCells(xlCellTypeFormulas).Interior.Color = vbCyan
VB- 表全体の空白セルを一括補完
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
On Error Resume Next
tbl.SpecialCells(xlCellTypeBlanks).Value = "未入力"
On Error GoTo 0
VB- 表全体の定数セルを一括加工
Dim tbl As Range
Set tbl = Range("A1").CurrentRegion
On Error Resume Next
tbl.SpecialCells(xlCellTypeConstants).Font.Color = vbMagenta
On Error GoTo 0
VB実務での使い分けポイント
- 表全体を扱う → CurrentRegion
- 隣接セルにコピー → Offset
- 表を拡張 → Resize
- セル単位で操作 → Cells
- 特定セル抽出 → SpecialCells (Blanks, Constants, Formulas)
💡 この「Cells × Range × Offset × Resize × CurrentRegion × SpecialCells」テンプレを押さえておけば、表全体の動的処理+特定セル抽出+加工まで自在に扱えます。


