Document.BuiltInDocumentProperties 属性 (Word)
返回一个 DocumentProperties 集合,代表指定文档的所有内置文档属性。
语法
expression. BuiltInDocumentProperties
表达式是必需的。 一个代表 Document 对象的变量。
备注
若要返回单个 DocumentProperty 对象表示特定的内置文档属性,请使用 BuiltinDocumentProperties 属性。 如果 Microsoft Word 没有定义某个内置文档属性的值,则读取该文档属性的 Value 属性将产生错误。
有关返回集合的单个成员的信息,请参阅 从集合中返回对象。
使用 CustomDocumentProperties 属性返回的自定义文档属性的集合。
示例
本示例在活动文档的末尾插入一个内置属性列表。
Sub ListProperties()
Dim rngDoc As Range
Dim proDoc As DocumentProperty
Set rngDoc = ActiveDocument.Content
rngDoc.Collapse Direction:=wdCollapseEnd
For Each proDoc In ActiveDocument.BuiltInDocumentProperties
With rngDoc
.InsertParagraphAfter
.InsertAfter proDoc.Name & "= "
On Error Resume Next
.InsertAfter proDoc.Value
End With
Next
End Sub
本示例显示活动文档中的单词数。
Sub DisplayTotalWords()
Dim intWords As Integer
intWords = ActiveDocument.BuiltInDocumentProperties(wdPropertyWords)
MsgBox "This document contains " & intWords & " words."
End Sub
另请参阅
支持和反馈
有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。