Application.AlignTableCellBottom method (Project)
Aligns text at the bottom of the cell, for selected cells in a report table.
Syntax
expression. AlignTableCellBottom
expression A variable that represents an Application object.
Return value
Boolean
Example
In the following example, the AlignTableCells macro aligns the text for all tables in the specified report.
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
See also
Report Object AlignTableCellTop Method AlignTableCellVerticalCenter Method
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.