Exportando um gráfico para um documento de Word

Este exemplo usa um gráfico chamado "Gráfico 1" da Planilha 1 e o exporta como um arquivo .gif. Em seguida, ele insere o arquivo .gif em um documento Word existente chamado "Relatório gráfico" no local marcado chamado "ChartReport".

Código de exemplo fornecido por: 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

Sobre o colaborador

Dennis Wallentin é o autor do VSTO & .NET & Excel, um blog que se concentra em soluções .NET Framework para Excel e Serviços do Excel. Dennis vem desenvolvendo soluções Excel há mais de 20 anos e também é coautor de "Desenvolvimento do Excel Profissional: O Guia Definitivo para o Desenvolvimento de Aplicativos Usando o Microsoft Excel, VBA e .NET (2ª Edição)".

Suporte e comentários

Tem dúvidas ou quer enviar comentários sobre o VBA para Office ou sobre esta documentação? Confira Suporte e comentários sobre o VBA para Office a fim de obter orientação sobre as maneiras pelas quais você pode receber suporte e fornecer comentários.