将表导出到Word文档

本示例采用工作表 1 上名为“Table1”的表,并将其复制到名为“Report”的书签位置上名为“季度报表”的现有Word文档中。

示例代码提供者:Dennis Wallentin,VSTO & .NET & Excel

Sub Export_Table_Word()

    'Name of the existing Word doc.
    Const stWordReport As String = "Quarter Report.docx"
    
    'Word objects.
    Dim wdApp As Word.Application
    Dim wdDoc As Word.Document
    Dim wdbmRange As Word.Range
    
    'Excel objects.
    Dim wbBook As Workbook
    Dim wsSheet As Worksheet
    Dim rnReport As Range
    
    'Initialize the Excel objects.
    Set wbBook = ThisWorkbook
    Set wsSheet = wbBook.Worksheets("Sheet1")
    Set rnReport = wsSheet.Range("Table1")
    
    'Initialize the Word objects.
    Set wdApp = New Word.Application
    Set wdDoc = wdApp.Documents.Open(wbBook.Path & "\" & stWordReport)
    Set wdbmRange = wdDoc.Bookmarks("Report").Range
    
    'If the macro has been run before, clean up any artifacts before trying to paste the table in again.
    On Error Resume Next
    With wdDoc.InlineShapes(1)
        .Select
        .Delete
    End With
    On Error GoTo 0
    
    'Turn off screen updating.
    Application.ScreenUpdating = False
    
    'Copy the report to the clipboard.
    rnReport.Copy
    
    'Select the range defined by the "Report" bookmark and paste in the report from clipboard.
    With wdbmRange
        .Select
        .PasteSpecial Link:=False, _
                      DataType:=wdPasteMetafilePicture, _
                      Placement:=wdInLine, _
                      DisplayAsIcon:=False
    End With
    
    'Save and close the Word doc.
    With wdDoc
        .Save
        .Close
    End With
    
    'Quit Word.
    wdApp.Quit
    
    'Null out your variables.
    Set wdbmRange = Nothing
    Set wdDoc = Nothing
    Set wdApp = Nothing
    
    'Clear out the clipboard, and turn screen updating back on.
    With Application
        .CutCopyMode = False
        .ScreenUpdating = True
    End With
    
    MsgBox "The report has successfully been " & vbNewLine & _
           "transferred to " & stWordReport, vbInformation

End Sub

关于参与者

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

支持和反馈

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