gi-clutter-1.0.3: clutter GObject bindings
CopyrightWill Thompson and Iñaki García Etxebarria
LicenseLGPL-2.1
MaintainerIñaki García Etxebarria
Safe HaskellSafe-Inferred
LanguageHaskell2010

GI.Clutter.Objects.Timeline

Description

The Timeline structure contains only private data and should be accessed using the provided API

Since: 0.2

Synopsis

Exported types

newtype Timeline Source #

Memory-managed wrapper type.

Constructors

Timeline (ManagedPtr Timeline) 

Instances

Instances details
Eq Timeline Source # 
Instance details

Defined in GI.Clutter.Objects.Timeline

GObject Timeline Source # 
Instance details

Defined in GI.Clutter.Objects.Timeline

ManagedPtrNewtype Timeline Source # 
Instance details

Defined in GI.Clutter.Objects.Timeline

Methods

toManagedPtr :: Timeline -> ManagedPtr Timeline

TypedObject Timeline Source # 
Instance details

Defined in GI.Clutter.Objects.Timeline

Methods

glibType :: IO GType

HasParentTypes Timeline Source # 
Instance details

Defined in GI.Clutter.Objects.Timeline

IsGValue (Maybe Timeline) Source #

Convert Timeline to and from GValue. See toGValue and fromGValue.

Instance details

Defined in GI.Clutter.Objects.Timeline

Methods

gvalueGType_ :: IO GType

gvalueSet_ :: Ptr GValue -> Maybe Timeline -> IO ()

gvalueGet_ :: Ptr GValue -> IO (Maybe Timeline)

type ParentTypes Timeline Source # 
Instance details

Defined in GI.Clutter.Objects.Timeline

type ParentTypes Timeline = '[Object, Scriptable]

class (GObject o, IsDescendantOf Timeline o) => IsTimeline o Source #

Type class for types which can be safely cast to Timeline, for instance with toTimeline.

Instances

Instances details
(GObject o, IsDescendantOf Timeline o) => IsTimeline o Source # 
Instance details

Defined in GI.Clutter.Objects.Timeline

toTimeline :: (MonadIO m, IsTimeline o) => o -> m Timeline Source #

Cast to Timeline, for types for which this is known to be safe. For general casts, use castTo.

Methods

addMarker

timelineAddMarker Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Text

markerName: the unique name for this marker

-> Double

progress: the normalized value of the position of the martke

-> m () 

Adds a named marker that will be hit when the timeline has reached the specified progress.

Markers are unique string identifiers for a given position on the timeline. Once timeline reaches the given progress of its duration, if will emit a markerReached signal for each marker attached to that particular point.

A marker can be removed with timelineRemoveMarker. The timeline can be advanced to a marker using timelineAdvanceToMarker.

See also: timelineAddMarkerAtTime

Since: 1.14

addMarkerAtTime

timelineAddMarkerAtTime Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Text

markerName: the unique name for this marker

-> Word32

msecs: position of the marker in milliseconds

-> m () 

Adds a named marker that will be hit when the timeline has been running for msecs milliseconds.

Markers are unique string identifiers for a given position on the timeline. Once timeline reaches the given msecs, it will emit a markerReached signal for each marker attached to that position.

A marker can be removed with timelineRemoveMarker. The timeline can be advanced to a marker using timelineAdvanceToMarker.

See also: timelineAddMarker

Since: 0.8

advance

timelineAdvance Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: A Timeline

-> Word32

msecs: Time to advance to

-> m () 

Advance timeline to the requested point. The point is given as a time in milliseconds since the timeline started.

The timeline will not emit the Timeline::newFrame signal for the given time. The first newFrame signal after the call to timelineAdvance will be emit the skipped markers.

advanceToMarker

timelineAdvanceToMarker Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Text

markerName: the name of the marker

-> m () 

Advances timeline to the time of the given markerName.

Like timelineAdvance, this function will not emit the Timeline::newFrame for the time where markerName is set, nor it will emit Timeline::markerReached for markerName.

Since: 0.8

clone

timelineClone Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: Timeline to duplicate.

-> m Timeline

Returns: a new Timeline, cloned from timeline

Deprecated: (Since version 1.10)Use timelineNew or g_object_new() instead

Create a new Timeline instance which has property values matching that of supplied timeline. The cloned timeline will not be started and will not be positioned to the current position of the original timeline: you will have to start it with timelineStart.

The only cloned properties are:

Since: 0.4

getAutoReverse

timelineGetAutoReverse Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Bool

Returns: True if the timeline should automatically reverse, and False otherwise

Retrieves the value set by timelineSetAutoReverse.

Since: 1.6

getCubicBezierProgress

timelineGetCubicBezierProgress Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m (Bool, Point, Point)

Returns: True if the timeline is using a cubic bezier progress more, and False otherwise

Retrieves the control points for the cubic bezier progress mode.

Since: 1.12

getCurrentRepeat

timelineGetCurrentRepeat Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Int32

Returns: the current repeat

Retrieves the current repeat for a timeline.

Repeats start at 0.

Since: 1.10

getDelay

timelineGetDelay Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Word32

Returns: the delay in milliseconds.

Retrieves the delay set using timelineSetDelay.

Since: 0.4

getDelta

timelineGetDelta Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Word32

Returns: the amount of time in milliseconds elapsed since the last frame

Retrieves the amount of time elapsed since the last ClutterTimelinenewFrame signal.

This function is only useful inside handlers for the newFrame signal, and its behaviour is undefined if the timeline is not playing.

Since: 0.6

getDirection

timelineGetDirection Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m TimelineDirection

Returns: the direction of the timeline

Retrieves the direction of the timeline set with timelineSetDirection.

Since: 0.6

getDuration

timelineGetDuration Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Word32

Returns: the duration of the timeline, in milliseconds.

Retrieves the duration of a Timeline in milliseconds. See timelineSetDuration.

Since: 0.6

getDurationHint

timelineGetDurationHint Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Int64

Returns: the full duration of the Timeline

Retrieves the full duration of the timeline, taking into account the current value of the Timeline:repeatCount property.

If the Timeline:repeatCount property is set to -1, this function will return MAXINT64.

The returned value is to be considered a hint, and it's only valid as long as the timeline hasn't been changed.

Since: 1.10

getElapsedTime

timelineGetElapsedTime Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: A Timeline

-> m Word32

Returns: current elapsed time in milliseconds.

Request the current time position of the timeline.

getLoop

timelineGetLoop Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Bool

Returns: True if the timeline is looping

Deprecated: (Since version 1.10)Use timelineGetRepeatCount instead.

Gets whether timeline is looping

getProgress

timelineGetProgress Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Double

Returns: the normalized current position in the timeline.

The position of the timeline in a normalized [-1, 2] interval.

The return value of this function is determined by the progress mode set using timelineSetProgressMode, or by the progress function set using timelineSetProgressFunc.

Since: 0.6

getProgressMode

timelineGetProgressMode Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m AnimationMode

Returns: a AnimationMode

Retrieves the progress mode set using timelineSetProgressMode or timelineSetProgressFunc.

Since: 1.10

getRepeatCount

timelineGetRepeatCount Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m Int32

Returns: the number of repeats

Retrieves the number set using timelineSetRepeatCount.

Since: 1.10

getStepProgress

timelineGetStepProgress Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> m (Bool, Int32, StepMode)

Returns: True if the timeline is using a step progress mode, and False otherwise

Retrieves the parameters of the step progress mode used by timeline.

Since: 1.12

hasMarker

timelineHasMarker Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Text

markerName: the name of the marker

-> m Bool

Returns: True if the marker was found

Checks whether timeline has a marker set with the given name.

Since: 0.8

isPlaying

timelineIsPlaying Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: A Timeline

-> m Bool

Returns: True if timeline is currently playing

Queries state of a Timeline.

listMarkers

timelineListMarkers Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Int32

msecs: the time to check, or -1

-> m ([Text], Word64)

Returns: a newly allocated, Nothing terminated string array containing the names of the markers. Use strfreev when done.

Retrieves the list of markers at time msecs. If msecs is a negative integer, all the markers attached to timeline will be returned.

Since: 0.8

new

timelineNew Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Word32

msecs: Duration of the timeline in milliseconds

-> m Timeline

Returns: the newly created Timeline instance. Use objectUnref when done using it

Creates a new Timeline with a duration of msecs.

Since: 0.6

pause

timelinePause Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: A Timeline

-> m () 

Pauses the Timeline on current frame

removeMarker

timelineRemoveMarker Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Text

markerName: the name of the marker to remove

-> m () 

Removes markerName, if found, from timeline.

Since: 0.8

rewind

timelineRewind Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: A Timeline

-> m () 

Rewinds Timeline to the first frame if its direction is TimelineDirectionForward and the last frame if it is TimelineDirectionBackward.

setAutoReverse

timelineSetAutoReverse Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Bool

reverse: True if the timeline should reverse the direction

-> m () 

Sets whether timeline should reverse the direction after the emission of the Timeline::completed signal.

Setting the Timeline:autoReverse property to True is the equivalent of connecting a callback to the Timeline::completed signal and changing the direction of the timeline from that callback; for instance, this code:

static void
reverse_timeline (ClutterTimeline *timeline)
{
  ClutterTimelineDirection dir = clutter_timeline_get_direction (timeline);

  if (dir == CLUTTER_TIMELINE_FORWARD)
    dir = CLUTTER_TIMELINE_BACKWARD;
  else
    dir = CLUTTER_TIMELINE_FORWARD;

  clutter_timeline_set_direction (timeline, dir);
}
...
  timeline = clutter_timeline_new (1000);
  clutter_timeline_set_repeat_count (timeline, -1);
  g_signal_connect (timeline, "completed",
                    G_CALLBACK (reverse_timeline),
                    NULL);

can be effectively replaced by:

 timeline = clutter_timeline_new (1000);
 clutter_timeline_set_repeat_count (timeline, -1);
 clutter_timeline_set_auto_reverse (timeline);

Since: 1.6

setCubicBezierProgress

timelineSetCubicBezierProgress Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Point

c1: the first control point for the cubic bezier

-> Point

c2: the second control point for the cubic bezier

-> m () 

Sets the Timeline:progressMode of timeline to AnimationModeCubicBezier, and sets the two control points for the cubic bezier.

The cubic bezier curve is between (0, 0) and (1, 1). The X coordinate of the two control points must be in the [ 0, 1 ] range, while the Y coordinate of the two control points can exceed this range.

Since: 1.12

setDelay

timelineSetDelay Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Word32

msecs: delay in milliseconds

-> m () 

Sets the delay, in milliseconds, before timeline should start.

Since: 0.4

setDirection

timelineSetDirection Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> TimelineDirection

direction: the direction of the timeline

-> m () 

Sets the direction of timeline, either TimelineDirectionForward or TimelineDirectionBackward.

Since: 0.6

setDuration

timelineSetDuration Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Word32

msecs: duration of the timeline in milliseconds

-> m () 

Sets the duration of the timeline, in milliseconds. The speed of the timeline depends on the ClutterTimeline:fps setting.

Since: 0.6

setLoop

timelineSetLoop Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Bool

loop: True for enable looping

-> m () 

Deprecated: (Since version 1.10)Use timelineSetRepeatCount instead.

Sets whether timeline should loop.

This function is equivalent to calling timelineSetRepeatCount with -1 if loop is True, and with 0 if loop is False.

setProgressFunc

timelineSetProgressFunc Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Maybe TimelineProgressFunc

func: a progress function, or Nothing

-> m () 

Sets a custom progress function for timeline. The progress function will be called by timelineGetProgress and will be used to compute the progress value based on the elapsed time and the total duration of the timeline.

If func is not Nothing, the Timeline:progressMode property will be set to AnimationModeCustomMode.

If func is Nothing, any previously set progress function will be unset, and the Timeline:progressMode property will be set to AnimationModeLinear.

Since: 1.10

setProgressMode

timelineSetProgressMode Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> AnimationMode

mode: the progress mode, as a AnimationMode

-> m () 

Sets the progress function using a value from the AnimationMode enumeration. The mode cannot be AnimationModeCustomMode or bigger than AnimationModeAnimationLast.

Since: 1.10

setRepeatCount

timelineSetRepeatCount Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Int32

count: the number of times the timeline should repeat

-> m () 

Sets the number of times the timeline should repeat.

If count is 0, the timeline never repeats.

If count is -1, the timeline will always repeat until it's stopped.

Since: 1.10

setStepProgress

timelineSetStepProgress Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: a Timeline

-> Int32

nSteps: the number of steps

-> StepMode

stepMode: whether the change should happen at the start or at the end of the step

-> m () 

Sets the Timeline:progressMode of the timeline to AnimationModeSteps and provides the parameters of the step function.

Since: 1.12

skip

timelineSkip Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: A Timeline

-> Word32

msecs: Amount of time to skip

-> m () 

Advance timeline by the requested time in milliseconds

start

timelineStart Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: A Timeline

-> m () 

Starts the Timeline playing.

stop

timelineStop Source #

Arguments

:: (HasCallStack, MonadIO m, IsTimeline a) 
=> a

timeline: A Timeline

-> m () 

Stops the Timeline and moves to frame 0

Properties

autoReverse

If the direction of the timeline should be automatically reversed when reaching the end.

Since: 1.6

constructTimelineAutoReverse :: (IsTimeline o, MonadIO m) => Bool -> m (GValueConstruct o) Source #

Construct a GValueConstruct with valid value for the “auto-reverse” property. This is rarely needed directly, but it is used by new.

getTimelineAutoReverse :: (MonadIO m, IsTimeline o) => o -> m Bool Source #

Get the value of the “auto-reverse” property. When overloading is enabled, this is equivalent to

get timeline #autoReverse

setTimelineAutoReverse :: (MonadIO m, IsTimeline o) => o -> Bool -> m () Source #

Set the value of the “auto-reverse” property. When overloading is enabled, this is equivalent to

set timeline [ #autoReverse := value ]

delay

A delay, in milliseconds, that should be observed by the timeline before actually starting.

Since: 0.4

constructTimelineDelay :: (IsTimeline o, MonadIO m) => Word32 -> m (GValueConstruct o) Source #

Construct a GValueConstruct with valid value for the “delay” property. This is rarely needed directly, but it is used by new.

getTimelineDelay :: (MonadIO m, IsTimeline o) => o -> m Word32 Source #

Get the value of the “delay” property. When overloading is enabled, this is equivalent to

get timeline #delay

setTimelineDelay :: (MonadIO m, IsTimeline o) => o -> Word32 -> m () Source #

Set the value of the “delay” property. When overloading is enabled, this is equivalent to

set timeline [ #delay := value ]

direction

The direction of the timeline, either TimelineDirectionForward or TimelineDirectionBackward.

Since: 0.6

constructTimelineDirection :: (IsTimeline o, MonadIO m) => TimelineDirection -> m (GValueConstruct o) Source #

Construct a GValueConstruct with valid value for the “direction” property. This is rarely needed directly, but it is used by new.

getTimelineDirection :: (MonadIO m, IsTimeline o) => o -> m TimelineDirection Source #

Get the value of the “direction” property. When overloading is enabled, this is equivalent to

get timeline #direction

setTimelineDirection :: (MonadIO m, IsTimeline o) => o -> TimelineDirection -> m () Source #

Set the value of the “direction” property. When overloading is enabled, this is equivalent to

set timeline [ #direction := value ]

duration

Duration of the timeline in milliseconds, depending on the ClutterTimeline:fps value.

Since: 0.6

constructTimelineDuration :: (IsTimeline o, MonadIO m) => Word32 -> m (GValueConstruct o) Source #

Construct a GValueConstruct with valid value for the “duration” property. This is rarely needed directly, but it is used by new.

getTimelineDuration :: (MonadIO m, IsTimeline o) => o -> m Word32 Source #

Get the value of the “duration” property. When overloading is enabled, this is equivalent to

get timeline #duration

setTimelineDuration :: (MonadIO m, IsTimeline o) => o -> Word32 -> m () Source #

Set the value of the “duration” property. When overloading is enabled, this is equivalent to

set timeline [ #duration := value ]

loop

Whether the timeline should automatically rewind and restart.

As a side effect, setting this property to True will set the Timeline:repeatCount property to -1, while setting this property to False will set the Timeline:repeatCount property to 0.

constructTimelineLoop :: (IsTimeline o, MonadIO m) => Bool -> m (GValueConstruct o) Source #

Construct a GValueConstruct with valid value for the “loop” property. This is rarely needed directly, but it is used by new.

getTimelineLoop :: (MonadIO m, IsTimeline o) => o -> m Bool Source #

Get the value of the “loop” property. When overloading is enabled, this is equivalent to

get timeline #loop

setTimelineLoop :: (MonadIO m, IsTimeline o) => o -> Bool -> m () Source #

Set the value of the “loop” property. When overloading is enabled, this is equivalent to

set timeline [ #loop := value ]

progressMode

Controls the way a Timeline computes the normalized progress.

Since: 1.10

constructTimelineProgressMode :: (IsTimeline o, MonadIO m) => AnimationMode -> m (GValueConstruct o) Source #

Construct a GValueConstruct with valid value for the “progress-mode” property. This is rarely needed directly, but it is used by new.

getTimelineProgressMode :: (MonadIO m, IsTimeline o) => o -> m AnimationMode Source #

Get the value of the “progress-mode” property. When overloading is enabled, this is equivalent to

get timeline #progressMode

setTimelineProgressMode :: (MonadIO m, IsTimeline o) => o -> AnimationMode -> m () Source #

Set the value of the “progress-mode” property. When overloading is enabled, this is equivalent to

set timeline [ #progressMode := value ]

repeatCount

Defines how many times the timeline should repeat.

If the repeat count is 0, the timeline does not repeat.

If the repeat count is set to -1, the timeline will repeat until it is stopped.

Since: 1.10

constructTimelineRepeatCount :: (IsTimeline o, MonadIO m) => Int32 -> m (GValueConstruct o) Source #

Construct a GValueConstruct with valid value for the “repeat-count” property. This is rarely needed directly, but it is used by new.

getTimelineRepeatCount :: (MonadIO m, IsTimeline o) => o -> m Int32 Source #

Get the value of the “repeat-count” property. When overloading is enabled, this is equivalent to

get timeline #repeatCount

setTimelineRepeatCount :: (MonadIO m, IsTimeline o) => o -> Int32 -> m () Source #

Set the value of the “repeat-count” property. When overloading is enabled, this is equivalent to

set timeline [ #repeatCount := value ]

Signals

completed

type TimelineCompletedCallback = IO () Source #

The Timeline::completed signal is emitted when the timeline's elapsed time reaches the value of the Timeline:duration property.

This signal will be emitted even if the Timeline is set to be repeating.

If you want to get notification on whether the Timeline has been stopped or has finished its run, including its eventual repeats, you should use the Timeline::stopped signal instead.

afterTimelineCompleted :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineCompletedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the completed signal, to be run after the default handler. When overloading is enabled, this is equivalent to

after timeline #completed callback

By default the object invoking the signal is not passed to the callback. If you need to access it, you can use the implit ?self parameter. Note that this requires activating the ImplicitParams GHC extension.

onTimelineCompleted :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineCompletedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the completed signal, to be run before the default handler. When overloading is enabled, this is equivalent to

on timeline #completed callback

markerReached

type TimelineMarkerReachedCallback Source #

Arguments

 = Text

markerName: the name of the marker reached

-> Int32

msecs: the elapsed time

-> IO () 

The markerReached signal is emitted each time a timeline reaches a marker set with timelineAddMarkerAtTime. This signal is detailed with the name of the marker as well, so it is possible to connect a callback to the markerReached signal for a specific marker with:

<informalexample><programlisting> clutter_timeline_add_marker_at_time (timeline, "foo", 500); clutter_timeline_add_marker_at_time (timeline, "bar", 750);

g_signal_connect (timeline, "marker-reached", G_CALLBACK (each_marker_reached), NULL); g_signal_connect (timeline, "marker-reachedfoo", G_CALLBACK (foo_marker_reached), NULL); g_signal_connect (timeline, "marker-reachedbar", G_CALLBACK (bar_marker_reached), NULL); </programlisting></informalexample>

In the example, the first callback will be invoked for both the "foo" and "bar" marker, while the second and third callbacks will be invoked for the "foo" or "bar" markers, respectively.

Since: 0.8

afterTimelineMarkerReached :: (IsTimeline a, MonadIO m) => a -> Maybe Text -> ((?self :: a) => TimelineMarkerReachedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the markerReached signal, to be run after the default handler. When overloading is enabled, this is equivalent to

after timeline #markerReached callback

This signal admits a optional parameter detail. If it's not Nothing, we will connect to “marker-reached::detail” instead.

By default the object invoking the signal is not passed to the callback. If you need to access it, you can use the implit ?self parameter. Note that this requires activating the ImplicitParams GHC extension.

onTimelineMarkerReached :: (IsTimeline a, MonadIO m) => a -> Maybe Text -> ((?self :: a) => TimelineMarkerReachedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the markerReached signal, to be run before the default handler. When overloading is enabled, this is equivalent to

on timeline #markerReached callback

This signal admits a optional parameter detail. If it's not Nothing, we will connect to “marker-reached::detail” instead.

newFrame

type TimelineNewFrameCallback Source #

Arguments

 = Int32

msecs: the elapsed time between 0 and duration

-> IO () 

The newFrame signal is emitted for each timeline running timeline before a new frame is drawn to give animations a chance to update the scene.

afterTimelineNewFrame :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineNewFrameCallback) -> m SignalHandlerId Source #

Connect a signal handler for the newFrame signal, to be run after the default handler. When overloading is enabled, this is equivalent to

after timeline #newFrame callback

By default the object invoking the signal is not passed to the callback. If you need to access it, you can use the implit ?self parameter. Note that this requires activating the ImplicitParams GHC extension.

onTimelineNewFrame :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineNewFrameCallback) -> m SignalHandlerId Source #

Connect a signal handler for the newFrame signal, to be run before the default handler. When overloading is enabled, this is equivalent to

on timeline #newFrame callback

paused

type TimelinePausedCallback = IO () Source #

The paused signal is emitted when timelinePause is invoked.

afterTimelinePaused :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelinePausedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the paused signal, to be run after the default handler. When overloading is enabled, this is equivalent to

after timeline #paused callback

By default the object invoking the signal is not passed to the callback. If you need to access it, you can use the implit ?self parameter. Note that this requires activating the ImplicitParams GHC extension.

onTimelinePaused :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelinePausedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the paused signal, to be run before the default handler. When overloading is enabled, this is equivalent to

on timeline #paused callback

started

type TimelineStartedCallback = IO () Source #

The started signal is emitted when the timeline starts its run. This might be as soon as timelineStart is invoked or after the delay set in the ClutterTimeline:delay property has expired.

afterTimelineStarted :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineStartedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the started signal, to be run after the default handler. When overloading is enabled, this is equivalent to

after timeline #started callback

By default the object invoking the signal is not passed to the callback. If you need to access it, you can use the implit ?self parameter. Note that this requires activating the ImplicitParams GHC extension.

onTimelineStarted :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineStartedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the started signal, to be run before the default handler. When overloading is enabled, this is equivalent to

on timeline #started callback

stopped

type TimelineStoppedCallback Source #

Arguments

 = Bool

isFinished: True if the signal was emitted at the end of the timeline.

-> IO () 

The Timeline::stopped signal is emitted when the timeline has been stopped, either because timelineStop has been called, or because it has been exhausted.

This is different from the Timeline::completed signal, which gets emitted after every repeat finishes.

If the Timeline has is marked as infinitely repeating, this signal will never be emitted.

Since: 1.12

afterTimelineStopped :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineStoppedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the stopped signal, to be run after the default handler. When overloading is enabled, this is equivalent to

after timeline #stopped callback

By default the object invoking the signal is not passed to the callback. If you need to access it, you can use the implit ?self parameter. Note that this requires activating the ImplicitParams GHC extension.

onTimelineStopped :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineStoppedCallback) -> m SignalHandlerId Source #

Connect a signal handler for the stopped signal, to be run before the default handler. When overloading is enabled, this is equivalent to

on timeline #stopped callback