Objeto Shapes (projeto)Shapes object (Project)
Representa uma coleção de objetos Shape em um relatório personalizado.Represents a collection of Shape objects in a custom report.
ExemploExample
Use a propriedade Report. Shapes para obter o objeto da coleção Shapes .Use the Report.Shapes property to get the Shapes collection object. No exemplo a seguir, o relatório deve ser o modo de exibição ativo para obter a coleção Shapes ; caso contrário, você receberá um erro de tempo de execução 424 (objeto necessário For Each oShape In oReport.Shapes
) na instrução.In the following example, the report must be the active view to get the Shapes collection; otherwise, you get a run-time error 424 (Object required) in the For Each oShape In oReport.Shapes
statement.
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étodosMethods
PropriedadesProperties
NomeName |
---|
BackgroundBackground |
CountCount |
DefaultDefault |
ParentParent |
ValorValue |
Confira tambémSee also
Shape ObjectObjeto derelatório de objeto de formaShapeRange Shape Object Report Object ShapeRange Object
Suporte e comentáriosSupport and feedback
Tem dúvidas ou quer enviar comentários sobre o VBA para Office ou sobre esta documentação?Have questions or feedback about Office VBA or this documentation? Confira Suporte e comentários sobre o VBA para Office a fim de obter orientação sobre as maneiras pelas quais você pode receber suporte e fornecer comentários.Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.