AnimationSettings.AnimateTextInReverse property (PowerPoint)

Determines whether the specified shape is built in reverse order. Applies only to shapes (such as shapes containing lists) that can be built in more than one step. Read/write.

Syntax

expression. AnimateTextInReverse

expression A variable that represents an AnimationSettings object.

Return value

MsoTriState

Remarks

The value of the AnimateTextInReverse Property property can be one of these MsoTriState constants.

Constant Description
msoFalse The specified shape is not built in reverse order.
msoTrue The specified shape is built in reverse order.

You don't see the effects of setting this property unless the specified shape gets animated. For a shape to be animated, the TextLevelEffect property of the AnimationSettings object for the shape must be set to something other than ppAnimateLevelNone and the Animate property must be set to True.

Example

This example adds a slide after slide one in the active presentation, sets the title text, adds a three-item list to the text placeholder, and sets the list to be built in reverse order.

With ActivePresentation.Slides.Add(2, ppLayoutText).Shapes
    .Item(1).TextFrame.TextRange.Text = "Top Three Reasons"
    With .Item(2)
        .TextFrame.TextRange = "Reason 1" & Chr(13) _
            & "Reason 2" & Chr(13) & "Reason 3"
        With .AnimationSettings
            .Animate = msoTrue
            .TextLevelEffect = ppAnimateByFirstLevel
            .AnimateTextInReverse = msoTrue
        End With
    End With
End With

See also

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