Excel VBA 逆引き集 | コメントの取得

Excel VBA
スポンサーリンク

コメントの取得

セルに付けた「コメント(旧来のメモ)」を VBA で読み取る方法をまとめます。初心者がつまずきやすい「存在チェック」「テキストの取り出し」「範囲内の一覧化」を例題付きで解説します。


基本:コメントを取得する

Sub GetCommentBasic()
    Dim txt As String
    'A1セルにコメントがあるか確認
    If Not Range("A1").Comment Is Nothing Then
        txt = Range("A1").Comment.Text
        MsgBox "A1のコメントは:" & vbCrLf & txt
    Else
        MsgBox "A1にはコメントがありません。"
    End If
End Sub
VB
  • ポイント:
    • Range.Comment が Nothing かどうかで存在を判定。
    • Comment.Text でコメント本文を取得。

複数セルのコメントを一覧で取得

Sub GetCommentsInRange()
    Dim c As Range
    Dim msg As String

    For Each c In Range("B2:E10")
        If Not c.Comment Is Nothing Then
            msg = msg & c.Address & " → " & c.Comment.Text & vbCrLf
        End If
    Next

    If msg <> "" Then
        MsgBox "コメント一覧:" & vbCrLf & msg
    Else
        MsgBox "この範囲にはコメントがありません。"
    End If
End Sub
VB
  • ポイント:
    • 範囲をループして、コメントがあるセルだけを抽出。
    • c.Address でセル番地を表示すると分かりやすい。

コメントをシート全体から取得してログに出力

Sub GetAllComments()
    Dim c As Comment
    Dim msg As String

    For Each c In ActiveSheet.Comments
        msg = msg & c.Parent.Address & " → " & c.Text & vbCrLf
    Next

    If msg <> "" Then
        Debug.Print msg  'イミディエイトウィンドウに出力
    Else
        MsgBox "このシートにはコメントがありません。"
    End If
End Sub
VB
  • ポイント:
    • ActiveSheet.Comments コレクションでシート内の全コメントを取得。
    • c.Parent.Address でコメントが付いているセル番地を確認。

改行入りコメントの取得(複数行対応)

Sub GetMultilineComment()
    Dim txt As String
    If Not Range("C3").Comment Is Nothing Then
        txt = Range("C3").Comment.Text
        MsgBox "C3のコメント:" & vbCrLf & txt
    End If
End Sub
VB
  • ポイント:
    • コメント本文は改行も含めてそのまま取得できる。
    • vbCrLf を含んだテキストもそのまま返ります。

例題で練習

例題1:選択範囲のコメントをまとめて表示

Sub Example_SelectedComments()
    Dim c As Range, msg As String
    For Each c In Selection
        If Not c.Comment Is Nothing Then
            msg = msg & c.Address & ": " & c.Comment.Text & vbCrLf
        End If
    Next
    If msg <> "" Then MsgBox msg Else MsgBox "選択範囲にコメントはありません。"
End Sub
VB

例題2:シート全体のコメントを一覧表に書き出す

Sub Example_CommentsToSheet()
    Dim c As Comment, r As Long
    r = 1
    For Each c In ActiveSheet.Comments
        Cells(r, 1).Value = c.Parent.Address
        Cells(r, 2).Value = c.Text
        r = r + 1
    Next
End Sub
VB

例題3:特定列(F列)のコメントだけ抽出

Sub Example_ColumnComments()
    Dim c As Range, msg As String
    For Each c In Columns("F").Cells
        If Not c.Comment Is Nothing Then
            msg = msg & c.Address & ": " & c.Comment.Text & vbCrLf
        End If
    Next
    If msg <> "" Then MsgBox msg Else MsgBox "F列にコメントはありません。"
End Sub
VB

実務の落とし穴と対策

  • 既存コメントがないセルで .Text を呼ぶとエラー → 事前に Is Nothing でチェック。
  • 大量コメントの処理が遅い → 必要範囲だけをループ、結果はイミディエイトウィンドウや別シートにまとめる。
  • 新しいコメント(スレッド形式)との違い → VBAの Comment は旧来の「メモ」に対応。Microsoft 365の「新しいコメント」は CommentThreaded として別扱い。
タイトルとURLをコピーしました