本主題包含與下列各節中所識別工作相關的 Visual Basic 範例。
建立表格、插入文字及套用格式設定
下列範例會在使用中文件的開頭插入一個四欄三列的表格。 For Each...Next 結構是用來逐步執行表格中的每個儲存格。 在 For Each...Next 結構中, Range 物件的 InsertAfter 方法是用來將文字加入至表格儲存格 (第 1 個儲存格、第 2 個儲存格,依此類推)。
Sub CreateNewTable()
Dim docActive As Document
Dim tblNew As Table
Dim celTable As Cell
Dim intCount As Integer
Set docActive = ActiveDocument
Set tblNew = docActive.Tables.Add( _
Range:=docActive.Range(Start:=0, End:=0), NumRows:=3, _
NumColumns:=4)
intCount = 1
For Each celTable In tblNew.Range.Cells
celTable.Range.InsertAfter "Cell " & intCount
intCount = intCount + 1
Next celTable
tblNew.AutoFormat Format:=wdTableFormatColorful2, _
ApplyBorders:=True, ApplyFont:=True, ApplyColor:=True
End Sub
將文字插入表格儲存格
下列範例會將文字插入使用中文件內第一個表格的第一個儲存格。 Cell 方法會傳回單一 Cell 物件。 Range 屬性會傳回 Range 物件。 Delete 方法是用來刪除現有的文字,而 InsertAfter 方法會插入 "Cell 1,1" 文字。
Sub InsertTextInCell()
If ActiveDocument.Tables.Count >= 1 Then
With ActiveDocument.Tables(1).Cell(Row:=1, Column:=1).Range
.Delete
.InsertAfter Text:="Cell 1,1"
End With
End If
End Sub
傳回表格儲存格中的文字,但不傳回儲存格結尾標記
下列範例會傳回並顯示第一個文件表格之第一列中每個儲存格的內容。
Sub ReturnTableText()
Dim tblOne As Table
Dim celTable As Cell
Dim rngTable As Range
Set tblOne = ActiveDocument.Tables(1)
For Each celTable In tblOne.Rows(1).Cells
Set rngTable = ActiveDocument.Range(Start:=celTable.Range.Start, _
End:=celTable.Range.End - 1)
MsgBox rngTable.Text
Next celTable
End Sub
Sub ReturnCellText()
Dim tblOne As Table
Dim celTable As Cell
Dim rngTable As Range
Set tblOne = ActiveDocument.Tables(1)
For Each celTable In tblOne.Rows(1).Cells
Set rngTable = celTable.Range
rngTable.MoveEnd Unit:=wdCharacter, Count:=-1
MsgBox rngTable.Text
Next celTable
End Sub
將現有的文字轉換成表格
下列範例會在使用中文件的開頭插入以 Tab 分隔的文字,然後將文字轉換成表格。
Sub ConvertExistingText()
With Documents.Add.Content
.InsertBefore "one" & vbTab & "two" & vbTab & "three" & vbCr
.ConvertToTable Separator:=Chr(9), NumRows:=1, NumColumns:=3
End With
End Sub
傳回每個表格儲存的內容
下列範例會定義一個陣列,此陣列等於第一個文件表格中儲存格的數目 (假設 Option Base 1)。 For Each...Next 結構是用來傳回每個表格儲存格的內容,並將文字指派至對應的陣列元素。
Sub ReturnCellContentsToArray()
Dim intCells As Integer
Dim celTable As Cell
Dim strCells() As String
Dim intCount As Integer
Dim rngText As Range
If ActiveDocument.Tables.Count >= 1 Then
With ActiveDocument.Tables(1).Range
intCells = .Cells.Count
ReDim strCells(intCells)
intCount = 1
For Each celTable In .Cells
Set rngText = celTable.Range
rngText.MoveEnd Unit:=wdCharacter, Count:=-1
strCells(intCount) = rngText
intCount = intCount + 1
Next celTable
End With
End If
End Sub
將使用中文件內的所有表格複製到新文件中
下列範例會將目前文件中的表格複製到新的文件中。
Sub CopyTablesToNewDoc()
Dim docOld As Document
Dim rngDoc As Range
Dim tblDoc As Table
If ActiveDocument.Tables.Count >= 1 Then
Set docOld = ActiveDocument
Set rngDoc = Documents.Add.Range(Start:=0, End:=0)
For Each tblDoc In docOld.Tables
tblDoc.Range.Copy
With rngDoc
.Paste
.Collapse Direction:=wdCollapseEnd
.InsertParagraphAfter
.Collapse Direction:=wdCollapseEnd
End With
Next
End If
End Sub
支援和意見反應
有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應。