Style.Table property (Word)

Returns a TableStyle object representing properties that can be applied to a table using a table style.

Syntax

expression. Table

expression An expression that returns a 'Style' object.

Example

This example creates a new table style that specifies a surrounding border and special borders and shading for only the first and last rows and the last column.

Sub NewTableStyle() 
 Dim styTable As Style 
 
 Set styTable = ActiveDocument.Styles.Add( _ 
 Name:="TableStyle 1", Type:=wdStyleTypeTable) 
 
 With styTable.Table 
 
 'Apply borders around table, a double border to the heading row, 
 'a double border to the last column, and shading to last row 
 .Borders(wdBorderTop).LineStyle = wdLineStyleSingle 
 .Borders(wdBorderBottom).LineStyle = wdLineStyleSingle 
 .Borders(wdBorderLeft).LineStyle = wdLineStyleSingle 
 .Borders(wdBorderRight).LineStyle = wdLineStyleSingle 
 
 .Condition(wdFirstRow).Borders(wdBorderBottom) _ 
 .LineStyle = wdLineStyleDouble 
 
 .Condition(wdLastColumn).Borders(wdBorderLeft) _ 
 .LineStyle = wdLineStyleDouble 
 
 .Condition(wdLastRow).Shading _ 
 .BackgroundPatternColor = wdColorGray125 
 
 End With 
End Sub

See also

Style Object

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.