Hinweis
Für den Zugriff auf diese Seite ist eine Autorisierung erforderlich. Sie können versuchen, sich anzumelden oder das Verzeichnis zu wechseln.
Für den Zugriff auf diese Seite ist eine Autorisierung erforderlich. Sie können versuchen, das Verzeichnis zu wechseln.
In diesem Beispiel wird der Bereich A1:A10 auf Blatt 1 in die erste Tabelle in einem vorhandenen Word Dokument namens "Table Report" exportiert.
Beispielcode bereitgestellt von:Dennis Wallentin, VSTO & .NET & Excel
Sub Export_Table_Data_Word()
'Name of the existing Word document
Const stWordDocument As String = "Table Report.docx"
'Word objects.
Dim wdApp As Word.Application
Dim wdDoc As Word.Document
Dim wdCell As Word.Cell
'Excel objects
Dim wbBook As Workbook
Dim wsSheet As Worksheet
'Count used in a FOR loop to fill the Word table.
Dim lnCountItems As Long
'Variant to hold the data to be exported.
Dim vaData As Variant
'Initialize the Excel objects
Set wbBook = ThisWorkbook
Set wsSheet = wbBook.Worksheets("Sheet1")
vaData = wsSheet.Range("A1:A10").Value
'Instantiate Word and open the "Table Reports" document.
Set wdApp = New Word.Application
Set wdDoc = wdApp.Documents.Open(wbBook.Path & "\" & stWordDocument)
lnCountItems = 1
'Place the data from the variant into the table in the Word doc.
For Each wdCell In wdDoc.Tables(1).Columns(1).Cells
wdCell.Range.Text = vaData(lnCountItems, 1)
lnCountItems = lnCountItems + 1
Next wdCell
'Save and close the Word doc.
With wdDoc
.Save
.Close
End With
wdApp.Quit
'Null out the variables.
Set wdCell = Nothing
Set wdDoc = Nothing
Set wdApp = Nothing
MsgBox "The " & stWordDocument & "'s table has successfully " & vbNewLine & _
"been updated!", vbInformation
End Sub
Über den Autor
Dennis Wallentin ist Autor des Blogs VSTO & .NET & Excel, dessen Schwerpunkt auf .NET Framework-Lösungen für Excel und Excel Services liegt. Dennis entwickelt Excel-Lösungen seit über 20 Jahren und ist Co-Autor von "Professional Excel Development: The Definitive Guide to Developing Applications Using Microsoft Excel, VBA and .NET (2nd Edition)."
Support und Feedback
Haben Sie Fragen oder Feedback zu Office VBA oder zu dieser Dokumentation? Unter Office VBA-Support und Feedback finden Sie Hilfestellung zu den Möglichkeiten, wie Sie Support erhalten und Feedback abgeben können.