Shapes.AddLabel method (Project)

Creates a label in a report, and returns a Shape object that represents the new label.

Syntax

expression. AddLabel (Orientation, Left, Top, Width, Height)

expression A variable that represents a Shapes object.

Parameters

Name Required/Optional Data type Description
Orientation Required MsoTextOrientation The text orientation within the label.
Left Required Single The position (in points) of the left edge of the label relative to the left side of the report.
Top Required Single The position (in points) of the top edge of the label relative to the top of the report.
Width Required Single The width of the label, in points.
Height Required Single The height of the label, in points.
Orientation Required MSOTEXTORIENTATION
Left Required FLOAT
Top Required FLOAT
Width Required FLOAT
Height Required FLOAT

Return value

Shape

Example

The following example adds a green label with the text "Hello report!" to a new report.

Sub AddHelloLabel()
    Dim shapeReport As Report
    Dim reportName As String
    Dim labelShape As shape
    
    ' Add a report.
    reportName = "Label report"
    Set shapeReport = ActiveProject.Reports.Add(reportName)

    Set labelShape = shapeReport.Shapes.AddLabel(msoTextOrientationHorizontal, 30, 30, 120, 40)

    With labelShape
        With .Fill
            .BackColor.RGB = RGB(red:=&H20, green:=&HFF, blue:=&H20)
            .Visible = msoTrue
        End With
        
        .TextFrame2.AutoSize = msoAutoSizeShapeToFitText
        .TextFrame2.HorizontalAnchor = msoAnchorCenter
        
        With .TextFrame2.TextRange
            .Text = "Hello report!"
            .Font.Bold = msoTrue
            .Font.Name = "Calibri"
            .Font.Size = 18
        End With
    End With
End Sub

See also

Shapes Object Shape Object

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.