本示例从工作表 1 中获取名为“Chart 1”的图表,并将其导出为 .gif 文件。 然后,它将 .gif 文件插入到名为“ChartReport”的书签位置名为“ChartReport”的现有Word文档中。
示例代码提供者:Dennis Wallentin,VSTO & .NET & Excel
Sub Export_Chart_Word()
'Name of an existing Word document, and the name the chart will have when exported.
Const stWordDocument As String = "Chart Report.docx"
Const stChartName As String = "ChartReport.gif"
'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 ChartObj As ChartObject
'Initialize the Excel objects.
Set wbBook = ThisWorkbook
Set wsSheet = wbBook.Worksheets("Sheet1")
Set ChartObj = wsSheet.ChartObjects("Chart 1")
'Turn off screen updating.
Application.ScreenUpdating = False
'Export the chart to the current directory, using the specified name, and save the chart as a .gif
ChartObj.Chart.Export _
Filename:=wbBook.Path & "\" & stChartName, _
FilterName:="GIF"
'Initialize the Word objects to the existing Word document and bookmark.
Set wdApp = New Word.Application
Set wdDoc = wdApp.Documents.Open(wbBook.Path & "\" & stWordDocument)
Set wdbmRange = wdDoc.Bookmarks("ChartReport").Range
'If there is already an inline shape, that means the macro has been run before - clean up any artifacts.
On Error Resume Next
With wdDoc.InlineShapes(1)
.Select
.Delete
End With
On Error GoTo 0
'Add the .gif file to the document at the bookmarked location,
'and ensure that it is saved inside the Word doc.
With wdbmRange
.Select
.InlineShapes.AddPicture _
Filename:=wbBook.Path & "\" & stChartName, _
LinkToFile:=False, _
savewithdocument:=True
End With
'Save and close the Word document.
With wdDoc
.Save
.Close
End With
'Quit Word.
wdApp.Quit
'Clear the variables.
Set wdbmRange = Nothing
Set wdDoc = Nothing
Set wdApp = Nothing
'Delete the temporary .gif file.
On Error Resume Next
Kill wbBook.Path & "\" & stChartName
On Error GoTo 0
MsgBox "Chart exported successfully to " & stWordDocument
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 支持和反馈,获取有关如何接收支持和提供反馈的指南。