Cell.Selected property (PowerPoint)

Returns True if the specified table cell is selected. Read-only.

Syntax

expression.Selected

expression A variable that represents a Cell object.

Return value

Boolean

Example

This example puts a border around the first cell in the specified table if the cell is selected.

Sub IsCellSelected()

    Dim celSelected As Cell

    Set celSelected = ActivePresentation.Slides(1).Shapes(1) _
        .Table.Columns(1).Cells(1)

    If celSelected.Selected Then
        With celSelected
            .Borders(ppBorderTop).DashStyle = msoLineRoundDot
            .Borders(ppBorderBottom).DashStyle = msoLineRoundDot
            .Borders(ppBorderLeft).DashStyle = msoLineRoundDot
            .Borders(ppBorderRight).DashStyle = msoLineRoundDot
        End With
    End If

End Sub

See also

Cell 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.