Gtk2HsContentsIndex
Media.Streaming.GStreamer.Core.Element
Contents
Detail
Types
Element Operations
Synopsis
data Element
class ObjectClass o => ElementClass o
castToElement :: GObjectClass obj => obj -> Element
toElement :: ElementClass o => o -> Element
data ElementFlags
= ElementLockedState
| ElementIsSink
| ElementUnparenting
data State
= StateVoidPending
| StateNull
| StateReady
| StatePaused
| StatePlaying
data StateChange
= StateChangeNullToReady
| StateChangeReadyToPaused
| StateChangePausedToPlaying
| StateChangePlayingToPaused
| StateChangePausedToReady
| StateChangeReadyToNull
data StateChangeReturn
= StateChangeFailure
| StateChangeSuccess
| StateChangeAsync
| StateChangeNoPreroll
elementAddPad :: (ElementClass elementT, PadClass padT) => elementT -> padT -> IO Bool
elementGetCompatiblePad :: (ElementClass elementT, PadClass padT) => elementT -> padT -> Caps -> IO (Maybe Pad)
elementGetCompatiblePadTemplate :: (ElementClass elementT, PadTemplateClass padTemplateT) => elementT -> padTemplateT -> IO (Maybe PadTemplate)
elementGetRequestPad :: ElementClass elementT => elementT -> String -> IO (Maybe Pad)
elementGetStaticPad :: ElementClass elementT => elementT -> String -> IO (Maybe Pad)
elementReleaseRequestPad :: (ElementClass elementT, PadClass padT) => elementT -> padT -> IO ()
elementRemovePad :: (ElementClass elementT, PadClass padT) => elementT -> padT -> IO Bool
elementIteratePads :: ElementClass elementT => elementT -> IO (Iterator Pad)
elementIterateSinkPads :: ElementClass elementT => elementT -> IO (Iterator Pad)
elementIterateSrcPads :: ElementClass elementT => elementT -> IO (Iterator Pad)
elementLink :: (ElementClass srcT, ElementClass sinkT) => srcT -> sinkT -> IO Bool
elementUnlink :: (ElementClass srcT, ElementClass sinkT) => srcT -> sinkT -> IO ()
elementLinkPads :: (ElementClass srcT, ElementClass sinkT) => srcT -> Maybe String -> sinkT -> Maybe String -> IO Bool
elementUnlinkPads :: (ElementClass srcT, ElementClass sinkT) => srcT -> String -> sinkT -> String -> IO ()
elementLinkPadsFiltered :: (ElementClass srcT, ElementClass sinkT) => srcT -> Maybe String -> sinkT -> Maybe String -> Caps -> IO Bool
elementLinkFiltered :: (ElementClass srcT, ElementClass sinkT) => srcT -> sinkT -> Maybe Caps -> IO Bool
elementSetBaseTime :: ElementClass elementT => elementT -> ClockTimeDiff -> IO ()
elementGetBaseTime :: ElementClass elementT => elementT -> IO ClockTimeDiff
elementSetBus :: (ElementClass elementT, BusClass busT) => elementT -> busT -> IO ()
elementGetBus :: ElementClass elementT => elementT -> IO Bus
elementGetFactory :: ElementClass elementT => elementT -> IO ElementFactory
elementSetIndex :: (ElementClass elementT, IndexClass indexT) => elementT -> indexT -> IO ()
elementIsIndexable :: ElementClass elementT => elementT -> IO Bool
elementRequiresClock :: ElementClass elementT => elementT -> IO Bool
elementSetClock :: (ElementClass elementT, ClockClass clockT) => elementT -> clockT -> IO Bool
elementGetClock :: ElementClass elementT => elementT -> IO (Maybe Clock)
elementProvidesClock :: ElementClass elementT => elementT -> IO Bool
elementProvideClock :: ElementClass elementT => elementT -> IO (Maybe Clock)
elementSetState :: ElementClass elementT => elementT -> State -> IO StateChangeReturn
elementGetState :: ElementClass elementT => elementT -> ClockTime -> IO (StateChangeReturn, Maybe State, Maybe State)
elementSetLockedState :: ElementClass elementT => elementT -> Bool -> IO Bool
elementIsLockedState :: ElementClass elementT => elementT -> IO Bool
elementAbortState :: ElementClass elementT => elementT -> IO ()
elementStateGetName :: State -> String
elementStateChangeReturnGetName :: StateChangeReturn -> String
elementSyncStateWithParent :: ElementClass elementT => elementT -> IO Bool
elementGetQueryTypes :: ElementClass element => element -> IO [QueryType]
elementQuery :: (ElementClass element, QueryClass query) => element -> query -> IO Bool
elementQueryConvert :: ElementClass element => element -> Format -> Int64 -> Format -> IO (Maybe (Format, Word64))
elementQueryPosition :: ElementClass element => element -> Format -> IO (Maybe (Format, Word64))
elementQueryDuration :: ElementClass element => element -> Format -> IO (Maybe (Format, Word64))
elementSendEvent :: (ElementClass element, EventClass event) => element -> event -> IO Bool
elementSeekSimple :: ElementClass element => element -> Format -> [SeekFlags] -> Int64 -> IO Bool
elementSeek :: ElementClass element => element -> Double -> Format -> [SeekFlags] -> SeekType -> Int64 -> SeekType -> Int64 -> IO Bool
elementNoMorePads :: ElementClass element => Signal element (IO ())
elementPadAdded :: ElementClass element => Signal element (Pad -> IO ())
elementPadRemoved :: ElementClass element => Signal element (Pad -> IO ())
Detail

Element is the abstract base class needed to construct an element that can be used in a GStreamer pipeline.

All elements have pads (of the type Pad). These pads link to pads on other elements. Buffers flow between these linked pads. An Element has a Pad for each input (or sink) and output (or source).

An element's pad can be retrieved by name with elementGetStaticPad or elementGetRequestPad. An Iterator over all an element's pads can be retrieved with elementIteratePads.

Elements can be linked through their pads. If the link is straightforward, use the elementLink convenience function to link two elements. Use elementLinkFiltered to link two elements constrained by a specified set of Caps. For finer control, use elementLinkPads and elementLinkPadsFiltered to specify the pads to link on each element by name.

Each element has a State. You can get and set the state of an element with elementGetState and elementSetState. To get a string representation of a State, use elementStateGetName.

You can get and set a Clock on an element using elementGetClock and elementSetClock. Some elements can provide a clock for the pipeline if elementProvidesClock returns True. With the elementProvideClock method one can retrieve the clock provided by such an element. Not all elements require a clock to operate correctly. If elementRequiresClock returns True, a clock should be set on the element with elementSetClock.

Note that clock slection and distribution is normally handled by the toplevel Pipeline so the clock functions should only be used in very specific situations.

Types
data Element
show/hide Instances
class ObjectClass o => ElementClass o
show/hide Instances
castToElement :: GObjectClass obj => obj -> Element
toElement :: ElementClass o => o -> Element
data ElementFlags
The flags that an Element may have.
Constructors
ElementLockedStateparent state changes are ignored
ElementIsSinkthe element is a sink
ElementUnparentingchild is being removed from the parent bin
show/hide Instances
data State
Constructors
StateVoidPending
StateNull
StateReady
StatePaused
StatePlaying
show/hide Instances
Enum State
Eq State
Show State
data StateChange
The different state changes that are passed to the state change functions of Elements.
Constructors
StateChangeNullToReadystate change from StateNull to StateReady
StateChangeReadyToPausedstate change from StateReady to StatePaused
StateChangePausedToPlayingstate change from StatePaused to StatePlaying
StateChangePlayingToPausedstate change from StatePlaying to StatePaused
StateChangePausedToReadystate change from StatePaused to StateReady
StateChangeReadyToNullstate change from StateReady to StateNull
show/hide Instances
data StateChangeReturn
Constructors
StateChangeFailure
StateChangeSuccess
StateChangeAsync
StateChangeNoPreroll
show/hide Instances
Element Operations
elementAddPad
:: (ElementClass elementT, PadClass padT)
=> elementTelement - an element
-> padTpad -
-> IO Bool

Add a pad (link point) to an element. The pad's parent will be set to element.

Pads are not automatically activated so elements should perform the needed steps to activate the pad in case this pad is added in the StatePaused or StatePlaying state. See padSetActive for more information about activating pads.

This function will emit the elementPadAdded signal on the element.

elementGetCompatiblePad
:: (ElementClass elementT, PadClass padT)
=> elementTelement - an element
-> padTpad - a pad
-> Capscaps - the Caps to use as a filter
-> IO (Maybe Pad)a Pad that is compatible with pad, or Nothing if none was found
Look for an unlinked pad to which the pad can link. It is not guaranteed that linking the pads will work, though it should work in most cases.
elementGetCompatiblePadTemplate
:: (ElementClass elementT, PadTemplateClass padTemplateT)
=> elementTelement - an element
-> padTemplateTpadTemplate - a pad template
-> IO (Maybe PadTemplate)the compatible PadTemplate, or Nothing if none was found
Retrieve a pad template from element that is compatible with padTemplate. Pads from compatible templates can be linked together.
elementGetRequestPad
:: ElementClass elementT
=> elementTelement - an element
-> Stringname -
-> IO (Maybe Pad)the requested Pad if found, otherwise Nothing.
Retrieve a pad from the element by name. This version only retrieves request pads. The pad should be released with elementReleaseRequestPad.
elementGetStaticPad
:: ElementClass elementT
=> elementTelement - an element
-> Stringname -
-> IO (Maybe Pad)the requested Pad if found, otherwise Nothing.
Retreive a pad from element by name. This version only retrieves already-existing (i.e. static) pads.
elementReleaseRequestPad
:: (ElementClass elementT, PadClass padT)
=> elementTelement -
-> padTpad -
-> IO ()
Release a request pad that was previously obtained with elementGetRequestPad.
elementRemovePad
:: (ElementClass elementT, PadClass padT)
=> elementTelement -
-> padTpad -
-> IO BoolTrue if the pad was succcessfully removed, otherwise False

Remove pad from element.

This function is used by plugin developers and should not be used by applications. Pads that were dynamically requested from elements with elementGetRequestPad should be released with the elementReleaseRequestPad function instead.

Pads are not automatically deactivated so elements should perform the needed steps to deactivate the pad in case this pad is removed in the PAUSED or PLAYING state. See padSetActive for more information about deactivating pads.

The pad and the element should be unlocked when calling this function.

This function will emit the padRemoved signal on the element.

Returns: True if the pad could be removed. Can return False if the pad does not belong to the provided element.

elementIteratePads
:: ElementClass elementT
=> elementTelement -
-> IO (Iterator Pad)an iterator over the element's pads.
Retrieve an Iterator over element's pads.
elementIterateSinkPads :: ElementClass elementT => elementT -> IO (Iterator Pad)
Retrieve an Iterator over element's sink pads.
elementIterateSrcPads :: ElementClass elementT => elementT -> IO (Iterator Pad)
Retrieve an Iterator over element's src pads.
elementLink
:: (ElementClass srcT, ElementClass sinkT)
=> srcTsrc -
-> sinkTsink -
-> IO BoolTrue if the pads could be linked, otherwise False

Link src to sink. The link must be from source to sink; the other direction will not be tried. The function looks for existing pads that aren't linked yet. It will request new pads if necessary. Such pads must be released manually (with elementReleaseRequestPad) when unlinking. If multiple links are possible, only one is established.

Make sure you have added your elements to a Bin or Pipeline with binAdd before trying to link them.

elementUnlink :: (ElementClass srcT, ElementClass sinkT) => srcT -> sinkT -> IO ()
Unlink all source pads of the src from all sink pads of the sink.
elementLinkPads
:: (ElementClass srcT, ElementClass sinkT)
=> srcTsrc - the element containing the source pad
-> Maybe StringsrcPadName - the name of the source pad, or Nothing for any pad
-> sinkTsink - the element containing the sink pad
-> Maybe StringsinkPadName - the name of the sink pad, or Nothing for any pad
-> IO BoolTrue if the pads could be linked, otherwise False
Link the named pads of src and sink.
elementUnlinkPads
:: (ElementClass srcT, ElementClass sinkT)
=> srcTsrc -
-> StringsrcPadName -
-> sinkTsink -
-> StringsinkPadName -
-> IO ()
Unlink the named pads of src and sink.
elementLinkPadsFiltered
:: (ElementClass srcT, ElementClass sinkT)
=> srcTsrc -
-> Maybe StringsrcPadName -
-> sinkTsink -
-> Maybe StringsinkPadName -
-> Capscaps -
-> IO BoolTrue if the pads could be linked, otherwise False
Link the named pads of src and sink. A side effect is that if one of the pads has no parent, it becomes a child of the parent of the other element. If they have different parents, the link will fail. If caps is not Nothing, make sure that the Caps of the link is a subset of caps.
elementLinkFiltered
:: (ElementClass srcT, ElementClass sinkT)
=> srcTsrc -
-> sinkTsink -
-> Maybe Capscaps -
-> IO BoolTrue if the pads could be linked, otherwise False

Link src to dest using the given Caps as a filter. The link must be from source to sink; the other direction will not be tried. The function looks for existing pads that aren't linked yet. If will request new pads if necessary. If multiple links are possible, only one is established.

Make sure you have added your elements to a Bin or Pipeline with binAdd before trying to link them.

elementSetBaseTime
:: ElementClass elementT
=> elementTelement -
-> ClockTimeDifftime -
-> IO ()
Set the base time of element. See elementGetBaseTime for more information.
elementGetBaseTime
:: ElementClass elementT
=> elementTelement -
-> IO ClockTimeDiffthe base time of the element
Return the base time of element. The base time is the absolute time of the clock when this element was last set to StatePlaying. Subtract the base time from the clock time to get the stream time of the element.
elementSetBus
:: (ElementClass elementT, BusClass busT)
=> elementTelement -
-> busTbus -
-> IO ()
Set the Bus used by element. For internal use only, unless you're testing elements.
elementGetBus
:: ElementClass elementT
=> elementTelement -
-> IO Busthe bus used by the element
Get the bus of element. Not that only a Pipeline will provide a bus for the application.
elementGetFactory
:: ElementClass elementT
=> elementTelement -
-> IO ElementFactorythe factory that created element
Get the factory used to create element.
elementSetIndex
:: (ElementClass elementT, IndexClass indexT)
=> elementTelement -
-> indexTindex -
-> IO ()
Set the Index used by element.
elementIsIndexable
:: ElementClass elementT
=> elementTelement -
-> IO BoolTrue if the element can be indexed
Determine whether element can be indexed.
elementRequiresClock
:: ElementClass elementT
=> elementTelement -
-> IO BoolTrue if the element requires a clock
Determine whether element requires a clock.
elementSetClock
:: (ElementClass elementT, ClockClass clockT)
=> elementTelement -
-> clockTclock -
-> IO BoolTrue if the element accepted the clock
Set the Clock used by element.
elementGetClock
:: ElementClass elementT
=> elementTelement -
-> IO (Maybe Clock)the clock, or Nothing if element has none
Get the Clock used by element.
elementProvidesClock
:: ElementClass elementT
=> elementTelement -
-> IO BoolTrue if the element provides a clock
Determine whether element provides a clock. A Clock provided by an element can be used as the global clock for a pipeline. An element that can provide a clock is only required to do so in the StatePaused state, meaning that it is fully negotiated and has allocated the resources needed to operate the clock.
elementProvideClock
:: ElementClass elementT
=> elementTelement -
-> IO (Maybe Clock)a Clock, or Nothing if none could be provided

Get the Clock provided by element.

Note that an element is only required to provide a clock in the StatePaused state. Some elements can provide a clock in other states.

elementSetState
:: ElementClass elementT
=> elementTelement -
-> Statestate -
-> IO StateChangeReturnthe result of the state change

Set the state of element to state. This function will try to set the requested state by going through all the intermediary states and calling the class's state change function for each.

This function can return StateChangeAsync, in which case the element will perform the remainder of the state change asynchronously in another thread. An application can use elementGetState to wait for the completion of the state change or it can wait for a state change message on the bus.

elementGetState
:: ElementClass elementT
=> elementTelement -
-> ClockTimetimeout -
-> IO (StateChangeReturn, Maybe State, Maybe State)the result of the state change, the current state, and the pending state

Get the state of element.

For elements that performed an asynchronous state change, as reported by elementSetState, this function will block up to the specified timeout value for the state change to complete. If the element completes the state change or goes into an error, this function returns immediately with a return value of StateChangeSuccess or StateChangeFailure, respectively.

This function returns StateChangeNoPreroll if the element successfully changed its state but is not able to provide data yet. This mostly happens for live sources that not only produce data in the StatePlaying state. While the state change return is equivalent to StateChangeSuccess, it is returned to the application to signal that some sink elements might not be able to somplete their state change because an element is not producing data to complete the preroll. When setting the element to playing, the preroll will complete and playback will start.

elementSetLockedState
:: ElementClass elementT
=> elementTelement -
-> BoollockedState - True for locked, False for unlocked
-> IO BoolTrue if the state was changed, False if bad parameters were given or no change was needed
Lock the state of element, so state changes in the parent don't affect this element any longer.
elementIsLockedState
:: ElementClass elementT
=> elementTelement -
-> IO BoolTrue if element's state is locked, False otherwise
Determine whether element's state is locked.
elementAbortState
:: ElementClass elementT
=> elementTelement -
-> IO ()

Abort element's state change. This function is used by elements that do asynchronous state changes and find out something is wrong.

This function should be called with the state lock held.

elementStateGetName
:: Statestate -
-> Stringthe name of state
Get a string representation of state.
elementStateChangeReturnGetName
:: StateChangeReturnstateRet -
-> Stringthe name of stateRet

Get a string representation of stateRet.

Since 0.10.11.

elementSyncStateWithParent
:: ElementClass elementT
=> elementTelement -
-> IO BoolTrue if the element's state could be synced with its parent's state
Try to change the state of element to the same as its parent. If this function returns False, the state of the element is undefined.
elementGetQueryTypes :: ElementClass element => element -> IO [QueryType]
elementQuery
:: (ElementClass element, QueryClass query)
=> elementelement -
-> queryquery -
-> IO BoolTrue if the query could be performed

Perform a query on the given element.

For elements that don't implement a query handler, this function forwards the query to a random srcpad or to the peer of a random linked sinkpad of this element.

elementQueryConvert
:: ElementClass element
=> elementelement - the element to query
-> FormatsrcFormat - the format to convert from
-> Int64srcVal - the value to convert
-> FormatdestFormat - the format to convert to
-> IO (Maybe (Format, Word64))the resulting format and value
Query an element for the convertion of a value from one format to another.
elementQueryPosition
:: ElementClass element
=> elementelement - the element to query
-> Formatformat - the format requested
-> IO (Maybe (Format, Word64))the resulting format and value
Query an element for its stream position.
elementQueryDuration
:: ElementClass element
=> elementelement - the element to query
-> Formatformat - the format requested
-> IO (Maybe (Format, Word64))the resulting format and value
Query an element for its stream duration.
elementSendEvent
:: (ElementClass element, EventClass event)
=> elementelement - the element to send the event to
-> eventevent - the event to send
-> IO BoolTrue if the event was handled

Send an event to an element.

If the element doesn't implement an event handler, the event will be pushed to a random linked sink pad for upstream events or a random linked source pad for downstream events.

elementSeekSimple
:: ElementClass element
=> elementelement - the element to seek on
-> Formatformat - the Format to evecute the seek in, such as FormatTime
-> [SeekFlags]seekFlags - seek options; playback applications will usually want to use [SeekFlagFlush,SeekFlagKeyUnit]
-> Int64seekPos - the position to seek to, relative to start; if you are doing a seek in FormatTime this value is in nanoseconds; see second, msecond, usecond, & nsecond
-> IO BoolTrue if the seek operation succeeded

Perform a seek on the given element. This function only supports seeking to a position relative to the start of the stream. For more complex operations like segment seeks (such as for looping), or changing the playback rate, or seeking relative to the last configured playback segment you should use elementSeek.

In a completely prerolled pipeline in the StatePaused or StatePlaying states, seeking is always guaranteed to return True on a seekable media type, or False when the media type is certainly not seekable (such as a live stream).

Some elements allow for seeking in the StateReady state, in which case they will store the seek event and execute it when they are put into the StatePaused state. If the element supports seek in StateReady, it will always return True when it recieves the event in the StateReady state.

elementSeek
:: ElementClass element
=> elementelement - the element to seek on
-> Doublerate - the new playback rate
-> Formatformat - the format of the seek values
-> [SeekFlags]seekFlags - the options to use
-> SeekTypecurType - type and flags for the new current position
-> Int64cur - the value of the new current position
-> SeekTypestopType - type and flags for the new stop position
-> Int64stop - the value of the new stop position
-> IO BoolTrue if the event was handled
Send a seek event to an element. See eventNewSeek for the details of the parameters. The seek event is sent to the element using elementSendEvent.
elementNoMorePads :: ElementClass element => Signal element (IO ())
The signal emitted when an element will not generate more dynamic pads.
elementPadAdded :: ElementClass element => Signal element (Pad -> IO ())
The signal emitted when a new Pad has been added to the element.
elementPadRemoved :: ElementClass element => Signal element (Pad -> IO ())
The signal emitted when a Pad has been removed from the element.
Produced by Haddock version 0.8