AnimationBehavior.PropertyEffect-Eigenschaft (PowerPoint)
Gibt ein PropertyEffect -Objekt für ein bestimmtes Animationsverhalten zurück. Schreibgeschützt.
Syntax
Ausdruck. PropertyEffect
Ausdruck Eine Variable, die ein AnimationBehavior-Objekt darstellt.
Rückgabewert
PropertyEffect
Beispiel
Das folgende Beispiel fügt der aktiven Präsentation eine Form mit einem Effekt hinzu und legt deren Animationseffekteigenschaften fest, um Farben zu ändern.
Sub AddShapeSetAnimFill()
Dim effBlinds As Effect
Dim shpRectangle As Shape
Dim animBlinds As AnimationBehavior
'Adds rectangle and sets animation effect
Set shpRectangle = ActivePresentation.Slides(1).Shapes _
.AddShape(Type:=msoShapeRectangle, Left:=100, _
Top:=100, Width:=50, Height:=50)
Set effBlinds = ActivePresentation.Slides(1).TimeLine.MainSequence _
.AddEffect(Shape:=shpRectangle, effectId:=msoAnimEffectBlinds)
'Sets the duration of the animation
effBlinds.Timing.Duration = 3
'Adds a behavior to the animation
Set animBlinds = effBlinds.Behaviors.Add(msoAnimTypeProperty)
'Sets the animation color effect and the formula to use
With animBlinds.PropertyEffect
.Property = msoAnimColor
.From = RGB(Red:=0, Green:=0, Blue:=255)
.To = RGB(Red:=255, Green:=0, Blue:=0)
End With
End Sub
Siehe auch
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.