ShapeRange.Tags-Eigenschaft (PowerPoint)

Gibt ein Tags -Objekt, das die Tags für das angegebene Objekt darstellt. Schreibgeschützt.

Syntax

Ausdruck. Tags

Ausdruck Eine Variable, die ein ShapeRange-Objekt darstellt.

Rückgabewert

Tags

Beispiel

Hinweis

[!HINWEIS] Tagwerte werden hinzugefügt und in Großschreibung gespeichert. Für Tests von Tagwerten muss Großschreibung verwendet werden, wie im zweiten Beispiel zu sehen.

This example adds a tag named "REGION" and a tag named "PRIORITY" to slide one in the active presentation.

With Application.ActivePresentation.Slides(1).Tags

    .Add "Region", "East"     'Adds "Region" tag with value "East"

    .Add "Priority", "Low"    'Adds "Priority" tag with value "Low"

End With

This example searches through the tags for each slide in the active presentation. If there's a tag named "PRIORITY," a message box displays the tag value. If the object doesn't have a tag named "PRIORITY," the example adds this tag with the value "Unknown."

For Each s In Application.ActivePresentation.Slides

    With s.Tags

        found = False

        For i = 1 To .Count

          If .Name(i) = "PRIORITY" Then

              found = True

              slNum = .Parent.SlideIndex

              MsgBox "Slide " & slNum & " Priority: " & .Value(i)

          End If

        Next

        If Not found Then

          slNum = .Parent.SlideIndex

          .Add "Priority", "Unknown"

          MsgBox "Slide " & slNum & " Priority tag added: Unknown"

        End If

    End With

Next

Siehe auch

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