TextStyles-Objekt (Publisher)

Eine Auflistung von TextStyle Objekte, die die integrierten und benutzerdefinierten Formatvorlagen in einem Dokument darstellen.

HinwBemerkungeneise

Verwenden Sie die Document.TextStyles-Eigenschaft , um die TextStyles-Auflistung zurückzugeben.

Verwenden Sie die Hinzufügen Methode erstellen eine neue benutzerdefinierte Formatvorlage und der TextStyles -Auflistung hinzugefügt.

Beispiel

Im folgenden Beispiel wird eine Tabelle erstellt und listet alle Formatvorlagen in der aktiven Publikation.

Sub ListTextStyles() 
 Dim sty As TextStyle 
 Dim tbl As Table 
 Dim intRow As Integer 
 
 With ActiveDocument 
 Set tbl = .Pages(1).Shapes.AddTable(NumRows:=.TextStyles.Count, _ 
 NumColumns:=2, Left:=72, Top:=72, Width:=488, Height:=12).Table 
 For Each sty In .TextStyles 
 intRow = intRow + 1 
 With tbl.Rows(intRow) 
 .Cells(1).text = sty.Name 
 .Cells(2).text = sty.BaseStyle 
 End With 
 Next sty 
 End With 
End Sub

Im folgenden Beispiel wird eine neue Formatvorlage erstellt und wendet es auf den Absatz an der Cursorposition.

Sub ApplyTextStyle() 
 Dim styNew As TextStyle 
 Dim fntStyle As Font 
 
 'Create a new style 
 Set styNew = ActiveDocument.TextStyles.Add(StyleName:="NewStyle") 
 Set fntStyle = styNew.Font 
 
 'Format the Font object 
 With fntStyle 
 .Name = "Tahoma" 
 .Size = 20 
 .Bold = msoTrue 
 End With 
 
 'Apply the Font object formatting to the new style 
 styNew.Font = fntStyle 
 
 'Apply the new style to the selected paragraph 
 Selection.TextRange.ParagraphFormat.TextStyle = "NewStyle" 
End Sub

Methoden

Eigenschaften

Siehe auch

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.