メモを操作(新形式/スレッドコメント)
Excelの“新しいコメント(スレッド形式)”をVBAで扱う方法を、初心者向けに安全な最短コードでまとめます。基本は Range.AddCommentThreaded(追加)、Range.CommentThreaded(取得)、CommentThreaded.Text(編集)、CommentThreaded.AddReply(返信)、CommentThreaded.Delete(削除)です。旧来の「メモ(Comment)」とはオブジェクトが異なるため、扱い方が違います。
基本:新形式コメントの追加・取得
Sub ThreadedComment_Basics()
'追加:B2セルにスレッドコメントを付ける
Range("B2").AddCommentThreaded "確認済み(担当:営業)"
'取得:コメントがあれば本文を読み取る
Dim tc As CommentThreaded
Set tc = Range("B2").CommentThreaded
If Not tc Is Nothing Then
MsgBox "B2のコメント:" & tc.Text
Else
MsgBox "B2にコメントはありません。"
End If
End Sub
VB- ポイント:
- 追加: Range.AddCommentThreaded “テキスト”。
- 取得: Range.CommentThreaded はそのセルのスレッドの“先頭コメント”を返す。Nothing判定で存在チェック。
コメントの編集(本文の上書き/追記)
Sub ThreadedComment_Edit()
Dim tc As CommentThreaded
Set tc = Range("C3").CommentThreaded
If tc Is Nothing Then
Range("C3").AddCommentThreaded "初回登録:" & Format(Now, "yyyy/mm/dd hh:nn")
Else
'権限がない場合に備えて安全に試みる
On Error Resume Next
tc.Text "更新:" & Format(Now, "yyyy/mm/dd hh:nn") & vbCrLf & "内容:承認待ち"
If Err.Number <> 0 Then
MsgBox "編集権限がないため更新できませんでした。"
End If
On Error GoTo 0
End If
End Sub
VB- ポイント:
- Textで上書き: tc.Text “新しい本文”。
- 権限対策: 他人のコメントは編集できない場合があるため、エラー回避と通知を入れる。
返信を追加(スレッド化)
Sub ThreadedComment_AddReply()
Dim tc As CommentThreaded
Set tc = Range("D5").CommentThreaded
If tc Is Nothing Then
Range("D5").AddCommentThreaded "起票:" & Format(Date, "yyyy/mm/dd")
Set tc = Range("D5").CommentThreaded
End If
'返信を追加
tc.AddReply "承認済み(課長):" & Format(Now, "hh:nn")
End Sub
VB- ポイント:
- AddReply: スレッドに返信を追加して会話形式にできる。
- 存在しない場合: 先に AddCommentThreaded で起票してから返信。
一覧取得・書き出し(シート全体)
Sub ThreadedComments_ListAll()
Dim c As CommentThreaded, r As Long
r = 1
'シート全体のスレッドコメントを列挙
For Each c In ActiveSheet.CommentsThreaded
Cells(r, 1).Value = c.Parent.Address 'セル番地
Cells(r, 2).Value = c.Text '本文(先頭)
Cells(r, 3).Value = c.Author '作成者(表示名)
Cells(r, 4).Value = c.Date '作成日時
r = r + 1
Next
End Sub
VB- ポイント:
- CommentsThreadedコレクション: シート全体の新形式コメントにアクセス。
- Parent: どのセルのコメントかを取得できる。
削除・一括削除(範囲/シート)
Sub ThreadedComment_DeleteSingle()
Dim tc As CommentThreaded
Set tc = Range("E3").CommentThreaded
If Not tc Is Nothing Then tc.Delete
End Sub
Sub ThreadedComment_ClearRange()
Dim cell As Range
For Each cell In Range("B2:E20")
If Not cell.CommentThreaded Is Nothing Then
cell.CommentThreaded.Delete
End If
Next
End Sub
VB- ポイント:
- Delete: CommentThreaded.Deleteで削除。
- 範囲の一括: ループで存在チェック→削除。旧形式のClearCommentsは新形式に効かない。
表示と操作の補助
Sub ThreadedComments_ShowPane()
'右側のコメントペインを開く(環境により効かない場合あり)
CommandBars("Comments").Visible = True
End Sub
VB- ポイント:
- ペイン表示: コメントの確認をしやすくなる。UIに依存するため環境差が出る場合あり。
例題で練習
例題1:選択範囲に「要確認」を一括付与(重複回避)
Sub Example_AddFlagToSelection()
Dim c As Range
For Each c In Selection
If c.CommentThreaded Is Nothing Then
c.AddCommentThreaded "要確認:" & Format(Date, "yyyy/mm/dd")
End If
Next
End Sub
VB例題2:F列の負値セルに自動コメント+返信で承認ログ
Sub Example_AutoFlagAndReply()
Dim last As Long, r As Long, tc As CommentThreaded
last = Cells(Rows.Count, "F").End(xlUp).Row
For r = 3 To last
With Cells(r, "F")
If .Value < 0 Then
If .CommentThreaded Is Nothing Then .AddCommentThreaded "負値検出:" & Format(Now, "mm/dd hh:nn")
Set tc = .CommentThreaded
tc.AddReply "承認済み(担当):" & Format(Now, "hh:nn")
End If
End With
Next
End Sub
VB例題3:シートのコメント一覧を別シートへログ出力
Sub Example_ExportThreadedComments()
Dim wsLog As Worksheet, c As CommentThreaded, r As Long
Set wsLog = Worksheets.Add
wsLog.Range("A1:D1").Value = Array("セル", "本文", "作成者", "日時")
r = 2
For Each c In ActiveSheet.CommentsThreaded
wsLog.Cells(r, 1).Value = c.Parent.Address
wsLog.Cells(r, 2).Value = c.Text
wsLog.Cells(r, 3).Value = c.Author
wsLog.Cells(r, 4).Value = c.Date
r = r + 1
Next
wsLog.Columns("A:D").AutoFit
End Sub
VB実務の落とし穴と対策
- 旧形式との混同:
- 対策: 旧形式は Comment/AddComment、新形式は CommentThreaded/AddCommentThreaded。メソッドが異なるため、目的に合わせて使い分ける。
- 編集権限の問題:
- 対策: 他ユーザー作成のコメントは編集不可の場合あり。Text更新時はエラーハンドリング(On Error)を入れ、失敗時はメッセージで通知。
- 一括削除の誤操作:
- 対策: 範囲を限定し、存在チェック(Is Nothing)→Deleteの順で安全に処理。全削除前にログ出力すると安心。
- 環境差(バージョン依存):
- 対策: 新形式は Microsoft 365/2019以降が前提。共有相手の環境確認を行う。

