Shapes, objet (Project)

Représente une collection d’objets Shape dans un rapport personnalisé.

Exemple

Utilisez la propriété Report.Shapes pour obtenir l’objet de collection Shapes . Dans l’exemple suivant, le rapport doit être l’affichage actif pour obtenir la collection Shapes ; sinon, vous obtenez une erreur d’exécution 424 (objet requis) dans l’instruction For Each oShape In oReport.Shapes .

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 = "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

Méthodes

Nom
AddCallout
AddChart
AddConnector
AddCurve
AddLabel
AddLine
AddPolyline
AddShape
AddTable
AddTextbox
AddTextEffect
BuildFreeform
Élément
Range
SelectAll

Propriétés

Nom
Background
Count
Default
Parent
Value

Voir aussi

Shape ObjectReport ObjetShapeRange Objet

Assistance et commentaires

Avez-vous des questions ou des commentaires sur Office VBA ou sur cette documentation ? Consultez la rubrique concernant l’assistance pour Office VBA et l’envoi de commentaires afin d’obtenir des instructions pour recevoir une assistance et envoyer vos commentaires.