TableStyle.RowStripe property (Word)

Returns or sets a Long that represents the number of rows to include in the banding when a style specifies odd- or even-row banding. Read/write.

Syntax

expression. RowStripe

expression A variable that represents a 'TableStyle' object.

Remarks

Use the Condition method to set odd- or even-column banding for a table style.

Example

This example creates and formats a new table style then applies the new style to a new table. The resulting style causes three columns every third column and two rows every second row to have 20% shading.

Sub NewTableStyle() 
 Dim styTable As Style 
 
 With ActiveDocument 
 Set styTable = .Styles.Add(Name:="TableStyle 1", _ 
 Type:=wdStyleTypeTable) 
 
 With .Styles("TableStyle 1").Table 
 .Condition(wdEvenColumnBanding).Shading _ 
 .Texture = wdTexture20Percent 
 .ColumnStripe = 3 
 .Condition(wdEvenRowBanding).Shading _ 
 .Texture = wdTexture20Percent 
 .RowStripe = 2 
 End With 
 
 With .Tables.Add(Range:=Selection.Range, NumRows:=15, _ 
 NumColumns:=15) 
 .Style = ActiveDocument.Styles("TableStyle 1") 
 End With 
 End With 
 
End Sub

See also

TableStyle 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.