Comment.DateTime property (PowerPoint)
Returns the date and time a comment was created.
Syntax
expression. DateTime
expression A variable that represents a Comment object.
Return value
Date
Remarks
Don't confuse this property with the DateAndTime property, which applies to the headers and footers of a slide.
Example
The following example provides information about all the comments for a given slide.
Sub ListComments()
Dim cmtExisting As Comment
Dim strAuthorInfo As String
For Each cmtExisting In ActivePresentation.Slides(1).Comments
With cmtExisting
strAuthorInfo = strAuthorInfo & .Author & "'s comment #" & _
.AuthorIndex & " (" & .Text & ") was created on " & _
.DateTime & vbCrLf
End With
Next
If strAuthorInfo <> "" Then
MsgBox strAuthorInfo
Else
MsgBox "There are no comments on this slide."
End If
End Sub
See also
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.