Application.AlignTableCellVerticalCenter-Methode (Project)

Richtet Text an der vertikalen Mitte der Zelle für ausgewählte Zellen in einer Berichtstabelle aus.

Syntax

Ausdruck. AlignTableCellVerticalCenter

expression Eine Variable, die ein Application-Objekt darstellt.

Rückgabewert

Boolean

Beispiel

Im folgenden Beispiel richtet das AlignTableCells-Makro den Text für alle Tabellen im angegebenen Bericht aus.

Sub TestAlignReportTables()
    Dim reportName As String
    Dim alignment As String   ' The value can be "top", "center", or "bottom".
    
    reportName = "Align Table Cells Report"
    alignment = "top"
    
    AlignTableCells reportName, alignment
End Sub

' Align the text for all tables in a specified report.
Sub AlignTableCells(reportName As String, alignment As String)
    Dim theReport As Report
    Dim shp As Shape
    
    Set theReport = ActiveProject.Reports(reportName)
    
    ' Activate the report. If the report is already active,
    ' ignore the run-time error 1004 from the Apply method.
    On Error Resume Next
    theReport.Apply
    On Error GoTo 0
    
    For Each shp In theReport.Shapes
        Debug.Print "Shape: " & shp.Type & ", " & shp.Name
        
        If shp.HasTable Then
            shp.Select
            
            Select Case alignment
                Case "top"
                    AlignTableCellTop
                Case "center"
                    AlignTableCellVerticalCenter
                Case "bottom"
                    AlignTableCellBottom
                Case Else
                    Debug.Print "AlignTableCells error: " & vbCrLf _
                        & "alignment must be top, center, or bottom."
                End Select
        End If
    Next shp
End Sub

Siehe auch

Application-Objekt

AligntableCellTop-Methode des BerichtsobjektsAligntableCellBottom-Methode

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.