Como trabalhar com tabelas

Este tópico inclui exemplos do Visual Basic relacionados às tarefas identificadas nas seções a seguir.

Criar uma tabela, inserir texto e aplicar formatação

O exemplo a seguir insere uma tabela de quatro colunas e três linhas no início do documento ativo. A estrutura For Each...Next é utilizada para percorrer cada célula da tabela. Dentro do For Each... Próxima estrutura, o método InsertAfter do objeto Range é usado para adicionar texto às células da tabela (Célula 1, Célula 2 e assim por diante).

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

Inserir texto em uma célula de tabela

O exemplo a seguir insere texto na primeira célula da primeira tabela do documento ativo. O método Cell retorna um único objeto Cell . A propriedade Range retorna um objeto Range . O método Delete é usado para excluir o texto existente e o método InsertAfter insere o texto "Célula 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

Retornar texto de uma célula de tabela sem retornar a marca de fim de célula

O exemplo a seguir retorna e exibe o conteúdo de cada célula da primeira linha da primeira tabela do documento.

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

Converter texto existente em uma tabela

O exemplo a seguir insere texto delimitado por tabulações no início do documento ativo e converte o texto em uma tabela.

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

Retornar o conteúdo de cada célula da tabela

O exemplo a seguir define uma matriz igual ao número de células da primeira tabela do documento (assumindo Option Base 1). A estrutura For Each...Next é usada para retornar o conteúdo de cada célula de tabela e atribuir o texto ao elemento de matriz correspondente.

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

Copiar todas as tabelas do documento ativo para um novo documento

Este exemplo copia as tabelas do documento atual para um novo documento.

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

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.