ListLevel.ApplyPictureBullet-Methode (Word)

Formatiert einen Absatz oder einen Bereich von Absätzen mit einem Bildaufzählungszeichen.

Syntax

Ausdruck. ApplyPictureBullet( _FileName_ )

Ausdruck: Erforderlich. Eine Variable, die ein ListLevel-Objekt darstellt.

Parameter

Name Erforderlich/Optional Datentyp Beschreibung
FileName Erforderlich String Der Pfad und der Dateiname der Bilddatei.

Beispiel

In diesem Beispiel wird ein neues Dokument mit einer Liste erstellt, und alle Absätze mit Ausnahme des ersten und des letzten werden mit Bildaufzählungszeichen formatiert.

Sub ApplyPictureBulletsToParagraphs() 
 Dim docNew As Document 
 Dim rngRange As Range 
 Dim lstTemplate As ListTemplate 
 Dim intPara As Integer 
 Dim intCount As Integer 
 
 'Set the initial value of object variables 
 Set docNew = Documents.Add 
 
 'Add paragraphs to the new document, including eight list items 
 With Selection 
 .TypeText Text:="This is an introductory paragraph." 
 .TypeParagraph 
 End With 
 Do Until intPara = 8 
 With Selection 
 .TypeText Text:="This is a list item." 
 .TypeParagraph 
 End With 
 intPara = intPara + 1 
 Loop 
 Selection.TypeText Text:="This is a concluding paragraph." 
 
 'Count the total number of paragraphs in the document 
 intCount = docNew.Paragraphs.Count 
 
 'Set the range to include all paragraphs in the 
 'document except the first and the last 
 Set rngRange = docNew.Range( _ 
 Start:=ActiveDocument.Paragraphs(2).Range.Start, _ 
 End:=ActiveDocument.Paragraphs(intCount - 1).Range.End) 
 
 'Format the list template as a bullet 
 Set lstTemplate = ListGalleries(Index:=wdBulletGallery) _ 
 .ListTemplates(7) 
 
 'Format list with a picture bullet 
 lstTemplate.ListLevels(1).ApplyPictureBullet _ 
 FileName:="c:\pictures\bluebullet.gif" 
 
 'Apply the list format settings to the range 
 rngRange.ListFormat.ApplyListTemplate _ 
 ListTemplate:=lstTemplate 
End Sub

Siehe auch

ListLevel-Objekt

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.