Freigeben über


Report.Shapes-Eigenschaft (Project)

Ruft die Auflistung der Shape-Objekte im Bericht ab. Read-only- Shapes.

Syntax

Ausdruck. Formen

Ausdruck Eine Variable, die ein Report-Objekt darstellt.

Beispiel

Im folgenden Beispiel werden die Shapes in einem benutzerdefinierten Bericht aufgelistet. Der Bericht muss die aktive Ansicht sein, um die Shapes-Auflistung abzurufen. Andernfalls erhalten Sie den Laufzeitfehler 424 (Objekt erforderlich) in der For Each oShape In oReport.Shapes -Anweisung.

Sub ListShapesInReport()
    Dim oReports As Reports
    Dim oReport As Report
    Dim oShape As shape
    Dim reportName As String
    Dim msg As String
    Dim msgBoxTitle As String
    Dim numShapes As Integer
    
    numShapes = 0
    msg = ""
    reportName = "New Table Tests"
    Set oReports = ActiveProject.Reports
    
    If oReports.IsPresent(reportName) Then
        ' Make the report the active view.
        oReports(reportName).Apply
        
        Set oReport = oReports(reportName)
        msgBoxTitle = "Shapes in report: '" & oReport.Name & "'"
    
        For Each oShape In oReport.Shapes
            numShapes = numShapes + 1
            msg = msg & numShapes & ". Shape type: " & CStr(oShape.Type) _
                & ", '" & oShape.Name & "'" & vbCrLf
        Next oShape
        
        If numShapes > 0 Then
            MsgBox Prompt:=msg, Title:=msgBoxTitle
        Else
            MsgBox Prompt:="This report contains no shapes.", _
                Title:=msgBoxTitle
        End If
    Else
         MsgBox Prompt:="The requested report, '" & reportName _
            & "', does not exist.", Title:="Report error"
    End If
End Sub

Eigenschaftswert

FORMEN

Siehe auch

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