在某一 Microsoft Office 应用程序中控制其他 Microsoft Office 应用程序

如果要在一个 Microsoft Office 应用程序中运行使用另一个应用程序中对象的代码,请按照下列步骤操作:

运行代码

  1. 在“引用”对话框(“工具”菜单)中,设置对其他应用程序的类型库的引用。 然后,对象、属性和方法将显示在对象浏览器中,并在编译时检查语法。 此外,您还可以获得有关它们的快捷帮助。

  2. 将对象变量声明为特定类型,该对象变量将引用其他应用程序中的对象。 使用提供 对象的应用程序的名称限定每个类型。 例如,以下语句声明一个指向 Microsoft Word文档的变量,以及另一个引用 Microsoft Excel 工作簿的变量。

      Dim appWD As Word.Application, wbXL As Excel.Workbook
    

    注意 如果希望提前绑定代码,则必须执行上述步骤。

  3. CreateObject 函数与要在其他应用程序中使用的对象的 OLE 编程标识符 一起使用,如以下示例所示。 若要查看其他应用程序的会话,请将 Visible 属性设置为 True

      Dim appWD As Word.Application 
    
    Set appWD = CreateObject("Word.Application") 
    appWd.Visible = True
    
  4. 对包含在变量中的对象应用属性和方法。 例如,下述指令创建新的 Word 文档。

    Dim appWD As Word.Application 
    
    Set appWD = CreateObject("Word.Application") 
    appWD.Documents.Add
    
  5. 使用完其他应用程序后,使用 Quit 方法将其关闭,然后将其对象变量设置为 Nothing 以释放它正在使用的任何内存,如以下示例所示。

    appWd.Quit 
    Set appWd = Nothing
    

提供的示例代码:Bill Jelen,MrExcel.com 以下代码示例为电子表格中的每一行数据创建新的 Microsoft Office Word 文件。

' You must pick Microsoft Word Object Library from Tools>References
' in the VB editor to execute Word commands.
Sub ControlWord()
    Dim appWD As Word.Application
    ' Create a new instance of Word and make it visible
    Set appWD = CreateObject("Word.Application.12")
    appWD.Visible = True

    ' Find the last row with data in the spreadsheet
    FinalRow = Range("A9999").End(xlUp).Row
    For i = 1 To FinalRow
        ' Copy the current row
        Worksheets("Sheet1").Rows(i).Copy
        ' Tell Word to create a new document
        appWD.Documents.Add
        ' Tell Word to paste the contents of the clipboard into the new document.
        appWD.Selection.Paste
        ' Save the new document with a sequential file name.
        appWD.ActiveDocument.SaveAs Filename:="File" & i
        ' Close the new Word document.
        appWD.ActiveDocument.Close
    Next i
    ' Close the Word application.
    appWD.Quit
End Sub

提供的示例代码:Dennis Wallentin、VSTO & .NET & Excel 此示例从包含三个值的命名区域W_Data获取单元格值,并将这些值插入到Word文档中。 这些值插入到名为 td1、td2td3 的书签位置。 若要运行此示例,必须具有一个名为 W_Data 的区域,其中包含工作簿 中 Sheet1 上的三个值。 您必须将一个名为 Word 文档 Test.docx 保存在与 Excel 工作簿相同的位置,并且Word文档必须具有名为 td1td2td3 的三个书签。

' You must pick Microsoft Word Object Library from Tools>References
' in the Visual Basic editor to execute Word commands.

Option Explicit

Sub Add_Single_Values_Word()
Dim wdApp As Word.Application
Dim wdDoc As Word.Document
Dim wdRange1 As Word.Range
Dim wdRange2 As Word.Range
Dim wdRange3 As Word.Range

Dim wbBook As Workbook
Dim wsSheet As Worksheet

Dim vaData As Variant

Set wbBook = ThisWorkbook
Set wsSheet = wbBook.Worksheets("Sheet1")

vaData = wsSheet.Range("W_Data").Value

' Instantiate the Word Objects.
Set wdApp = New Word.Application
Set wdDoc = wdApp.Documents.Open(wbBook.Path & "\Test.docx")

With wdDoc
    Set wdRange1 = .Bookmarks("td1").Range
    Set wdRange2 = .Bookmarks("td2").Range
    Set wdRange3 = .Bookmarks("td3").Range
End With

' Write values to the bookmarks.
wdRange1.Text = vaData(1, 1)
wdRange2.Text = vaData(2, 1)
wdRange3.Text = vaData(3, 1)

With wdDoc
    .Save
    .Close
End With

wdApp.Quit

' Release the objects from memory.
Set wdRange1 = Nothing
Set wdRange2 = Nothing
Set wdRange3 = Nothing
Set wdDoc = Nothing
Set wdApp = Nothing

End Sub

关于参与者

MVP Bill Jelen 是有关 Microsoft Excel 的二十多本书的作者。 他是 Leo Laporte 的 TechTV 的常客,也是 MrExcel.com 的主持人,该网站包含超过 300,000 个关于 Excel 的问题和答案。

Dennis Wallentin 是 VSTO & .NET & Excel 的作者,该博客专注于适用于 Excel 和 Excel Services 的 .NET Framework 解决方案。 Dennis 已经从事 Excel 解决方案开发超过 20 年,同时也是“专业 Excel 开发:使用 Microsoft Excel、VBA 和 .NET 开发应用程序的权威指南(第 2 版)”的合著者。

支持和反馈

有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。