Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria |
Safe Haskell | None |
Language | Haskell2010 |
- Exported types
- Methods
- Overloaded methods
- addAllocationMeta
- addAllocationParam
- addAllocationPool
- addBufferingRange
- addSchedulingMode
- findAllocationMeta
- getNAllocationMetas
- getNAllocationParams
- getNAllocationPools
- getNBufferingRanges
- getNSchedulingModes
- getStructure
- hasSchedulingMode
- hasSchedulingModeWithFlags
- newAcceptCaps
- newAllocation
- newBitrate
- newBuffering
- newCaps
- newContext
- newConvert
- newCustom
- newDrain
- newDuration
- newFormats
- newLatency
- newPosition
- newScheduling
- newSeeking
- newSegment
- newUri
- parseAcceptCaps
- parseAcceptCapsResult
- parseAllocation
- parseBitrate
- parseBufferingPercent
- parseBufferingRange
- parseBufferingStats
- parseCaps
- parseCapsResult
- parseContext
- parseContextType
- parseConvert
- parseDuration
- parseLatency
- parseNFormats
- parseNthAllocationMeta
- parseNthAllocationParam
- parseNthAllocationPool
- parseNthBufferingRange
- parseNthFormat
- parseNthSchedulingMode
- parsePosition
- parseScheduling
- parseSeeking
- parseSegment
- parseUri
- parseUriRedirection
- parseUriRedirectionPermanent
- removeNthAllocationMeta
- removeNthAllocationParam
- removeNthAllocationPool
- setAcceptCapsResult
- setBitrate
- setBufferingPercent
- setBufferingRange
- setBufferingStats
- setCapsResult
- setContext
- setConvert
- setDuration
- setFormatsv
- setLatency
- setNthAllocationParam
- setNthAllocationPool
- setPosition
- setScheduling
- setSeeking
- setSegment
- setUri
- setUriRedirection
- setUriRedirectionPermanent
- writableStructure
- Properties
Queries can be performed on pads (padQuery
) and elements
(elementQuery
). Please note that some queries might need a running
pipeline to work.
Queries can be created using the gst_query_new_*() functions. Query values can be set using gst_query_set_*(), and parsed using gst_query_parse_*() helpers.
The following example shows how to query the duration of a pipeline:
C code
GstQuery *query; gboolean res; query = gst_query_new_duration (GST_FORMAT_TIME); res = gst_element_query (pipeline, query); if (res) { gint64 duration; gst_query_parse_duration (query, NULL, &duration); g_print ("duration = %"GST_TIME_FORMAT, GST_TIME_ARGS (duration)); } else { g_print ("duration query failed..."); } gst_query_unref (query);
Synopsis
- newtype Query = Query (ManagedPtr Query)
- newZeroQuery :: MonadIO m => m Query
- queryAddAllocationMeta :: (HasCallStack, MonadIO m) => Query -> GType -> Maybe Structure -> m ()
- queryAddAllocationParam :: (HasCallStack, MonadIO m, IsAllocator a) => Query -> Maybe a -> Maybe AllocationParams -> m ()
- queryAddAllocationPool :: (HasCallStack, MonadIO m, IsBufferPool a) => Query -> Maybe a -> Word32 -> Word32 -> Word32 -> m ()
- queryAddBufferingRange :: (HasCallStack, MonadIO m) => Query -> Int64 -> Int64 -> m Bool
- queryAddSchedulingMode :: (HasCallStack, MonadIO m) => Query -> PadMode -> m ()
- queryFindAllocationMeta :: (HasCallStack, MonadIO m) => Query -> GType -> m (Bool, Word32)
- queryGetNAllocationMetas :: (HasCallStack, MonadIO m) => Query -> m Word32
- queryGetNAllocationParams :: (HasCallStack, MonadIO m) => Query -> m Word32
- queryGetNAllocationPools :: (HasCallStack, MonadIO m) => Query -> m Word32
- queryGetNBufferingRanges :: (HasCallStack, MonadIO m) => Query -> m Word32
- queryGetNSchedulingModes :: (HasCallStack, MonadIO m) => Query -> m Word32
- queryGetStructure :: (HasCallStack, MonadIO m) => Query -> m (Maybe Structure)
- queryHasSchedulingMode :: (HasCallStack, MonadIO m) => Query -> PadMode -> m Bool
- queryHasSchedulingModeWithFlags :: (HasCallStack, MonadIO m) => Query -> PadMode -> [SchedulingFlags] -> m Bool
- queryNewAcceptCaps :: (HasCallStack, MonadIO m) => Caps -> m Query
- queryNewAllocation :: (HasCallStack, MonadIO m) => Caps -> Bool -> m Query
- queryNewBitrate :: (HasCallStack, MonadIO m) => m Query
- queryNewBuffering :: (HasCallStack, MonadIO m) => Format -> m Query
- queryNewCaps :: (HasCallStack, MonadIO m) => Caps -> m Query
- queryNewContext :: (HasCallStack, MonadIO m) => Text -> m Query
- queryNewConvert :: (HasCallStack, MonadIO m) => Format -> Int64 -> Format -> m Query
- queryNewCustom :: (HasCallStack, MonadIO m) => QueryType -> Maybe Structure -> m (Maybe Query)
- queryNewDrain :: (HasCallStack, MonadIO m) => m Query
- queryNewDuration :: (HasCallStack, MonadIO m) => Format -> m Query
- queryNewFormats :: (HasCallStack, MonadIO m) => m Query
- queryNewLatency :: (HasCallStack, MonadIO m) => m Query
- queryNewPosition :: (HasCallStack, MonadIO m) => Format -> m Query
- queryNewScheduling :: (HasCallStack, MonadIO m) => m Query
- queryNewSeeking :: (HasCallStack, MonadIO m) => Format -> m Query
- queryNewSegment :: (HasCallStack, MonadIO m) => Format -> m Query
- queryNewUri :: (HasCallStack, MonadIO m) => m Query
- queryParseAcceptCaps :: (HasCallStack, MonadIO m) => Query -> m Caps
- queryParseAcceptCapsResult :: (HasCallStack, MonadIO m) => Query -> m Bool
- queryParseAllocation :: (HasCallStack, MonadIO m) => Query -> m (Caps, Bool)
- queryParseBitrate :: (HasCallStack, MonadIO m) => Query -> m Word32
- queryParseBufferingPercent :: (HasCallStack, MonadIO m) => Query -> m (Bool, Int32)
- queryParseBufferingRange :: (HasCallStack, MonadIO m) => Query -> m (Format, Int64, Int64, Int64)
- queryParseBufferingStats :: (HasCallStack, MonadIO m) => Query -> m (BufferingMode, Int32, Int32, Int64)
- queryParseCaps :: (HasCallStack, MonadIO m) => Query -> m Caps
- queryParseCapsResult :: (HasCallStack, MonadIO m) => Query -> m Caps
- queryParseContext :: (HasCallStack, MonadIO m) => Query -> m Context
- queryParseContextType :: (HasCallStack, MonadIO m) => Query -> m (Bool, Text)
- queryParseConvert :: (HasCallStack, MonadIO m) => Query -> m (Format, Int64, Format, Int64)
- queryParseDuration :: (HasCallStack, MonadIO m) => Query -> m (Format, Int64)
- queryParseLatency :: (HasCallStack, MonadIO m) => Query -> m (Bool, Word64, Word64)
- queryParseNFormats :: (HasCallStack, MonadIO m) => Query -> m Word32
- queryParseNthAllocationMeta :: (HasCallStack, MonadIO m) => Query -> Word32 -> m (GType, Structure)
- queryParseNthAllocationParam :: (HasCallStack, MonadIO m) => Query -> Word32 -> m (Allocator, AllocationParams)
- queryParseNthAllocationPool :: (HasCallStack, MonadIO m) => Query -> Word32 -> m (BufferPool, Word32, Word32, Word32)
- queryParseNthBufferingRange :: (HasCallStack, MonadIO m) => Query -> Word32 -> m (Bool, Int64, Int64)
- queryParseNthFormat :: (HasCallStack, MonadIO m) => Query -> Word32 -> m Format
- queryParseNthSchedulingMode :: (HasCallStack, MonadIO m) => Query -> Word32 -> m PadMode
- queryParsePosition :: (HasCallStack, MonadIO m) => Query -> m (Format, Int64)
- queryParseScheduling :: (HasCallStack, MonadIO m) => Query -> m ([SchedulingFlags], Int32, Int32, Int32)
- queryParseSeeking :: (HasCallStack, MonadIO m) => Query -> m (Format, Bool, Int64, Int64)
- queryParseSegment :: (HasCallStack, MonadIO m) => Query -> m (Double, Format, Int64, Int64)
- queryParseUri :: (HasCallStack, MonadIO m) => Query -> m Text
- queryParseUriRedirection :: (HasCallStack, MonadIO m) => Query -> m Text
- queryParseUriRedirectionPermanent :: (HasCallStack, MonadIO m) => Query -> m Bool
- queryRemoveNthAllocationMeta :: (HasCallStack, MonadIO m) => Query -> Word32 -> m ()
- queryRemoveNthAllocationParam :: (HasCallStack, MonadIO m) => Query -> Word32 -> m ()
- queryRemoveNthAllocationPool :: (HasCallStack, MonadIO m) => Query -> Word32 -> m ()
- querySetAcceptCapsResult :: (HasCallStack, MonadIO m) => Query -> Bool -> m ()
- querySetBitrate :: (HasCallStack, MonadIO m) => Query -> Word32 -> m ()
- querySetBufferingPercent :: (HasCallStack, MonadIO m) => Query -> Bool -> Int32 -> m ()
- querySetBufferingRange :: (HasCallStack, MonadIO m) => Query -> Format -> Int64 -> Int64 -> Int64 -> m ()
- querySetBufferingStats :: (HasCallStack, MonadIO m) => Query -> BufferingMode -> Int32 -> Int32 -> Int64 -> m ()
- querySetCapsResult :: (HasCallStack, MonadIO m) => Query -> Caps -> m ()
- querySetContext :: (HasCallStack, MonadIO m) => Query -> Context -> m ()
- querySetConvert :: (HasCallStack, MonadIO m) => Query -> Format -> Int64 -> Format -> Int64 -> m ()
- querySetDuration :: (HasCallStack, MonadIO m) => Query -> Format -> Int64 -> m ()
- querySetFormatsv :: (HasCallStack, MonadIO m) => Query -> [Format] -> m ()
- querySetLatency :: (HasCallStack, MonadIO m) => Query -> Bool -> Word64 -> Word64 -> m ()
- querySetNthAllocationParam :: (HasCallStack, MonadIO m, IsAllocator a) => Query -> Word32 -> Maybe a -> Maybe AllocationParams -> m ()
- querySetNthAllocationPool :: (HasCallStack, MonadIO m, IsBufferPool a) => Query -> Word32 -> Maybe a -> Word32 -> Word32 -> Word32 -> m ()
- querySetPosition :: (HasCallStack, MonadIO m) => Query -> Format -> Int64 -> m ()
- querySetScheduling :: (HasCallStack, MonadIO m) => Query -> [SchedulingFlags] -> Int32 -> Int32 -> Int32 -> m ()
- querySetSeeking :: (HasCallStack, MonadIO m) => Query -> Format -> Bool -> Int64 -> Int64 -> m ()
- querySetSegment :: (HasCallStack, MonadIO m) => Query -> Double -> Format -> Int64 -> Int64 -> m ()
- querySetUri :: (HasCallStack, MonadIO m) => Query -> Text -> m ()
- querySetUriRedirection :: (HasCallStack, MonadIO m) => Query -> Text -> m ()
- querySetUriRedirectionPermanent :: (HasCallStack, MonadIO m) => Query -> Bool -> m ()
- queryWritableStructure :: (HasCallStack, MonadIO m) => Query -> m Structure
- getQueryMiniObject :: MonadIO m => Query -> m MiniObject
- getQueryType :: MonadIO m => Query -> m QueryType
- setQueryType :: MonadIO m => Query -> QueryType -> m ()
Exported types
Memory-managed wrapper type.
Instances
Eq Query Source # | |
GBoxed Query Source # | |
Defined in GI.Gst.Structs.Query | |
ManagedPtrNewtype Query Source # | |
Defined in GI.Gst.Structs.Query toManagedPtr :: Query -> ManagedPtr Query | |
TypedObject Query Source # | |
Defined in GI.Gst.Structs.Query glibType :: IO GType | |
IsGValue Query Source # | Convert |
Defined in GI.Gst.Structs.Query toGValue :: Query -> IO GValue fromGValue :: GValue -> IO Query | |
HasParentTypes Query Source # | |
Defined in GI.Gst.Structs.Query | |
tag ~ 'AttrSet => Constructible Query tag Source # | |
type ParentTypes Query Source # | |
Defined in GI.Gst.Structs.Query type ParentTypes Query = '[] :: [Type] |
Methods
Overloaded methods
addAllocationMeta
queryAddAllocationMeta Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> GType |
|
-> Maybe Structure |
|
-> m () |
Add api
with params
as one of the supported metadata API to query
.
addAllocationParam
queryAddAllocationParam Source #
:: (HasCallStack, MonadIO m, IsAllocator a) | |
=> Query |
|
-> Maybe a |
|
-> Maybe AllocationParams |
|
-> m () |
Add allocator
and its params
as a supported memory allocator.
addAllocationPool
queryAddAllocationPool Source #
:: (HasCallStack, MonadIO m, IsBufferPool a) | |
=> Query |
|
-> Maybe a |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> m () |
Set the pool parameters in query
.
addBufferingRange
queryAddBufferingRange Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Int64 |
|
-> Int64 |
|
-> m Bool | Returns: a |
Set the buffering-ranges array field in query
. The current last
start position of the array should be inferior to start
.
addSchedulingMode
queryAddSchedulingMode Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> PadMode |
|
-> m () |
Add mode
as one of the supported scheduling modes to query
.
findAllocationMeta
queryFindAllocationMeta Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> GType |
|
-> m (Bool, Word32) | Returns: |
Check if query
has metadata api
set. When this function returns True
,
index
will contain the index where the requested API and the parameters
can be found.
getNAllocationMetas
queryGetNAllocationMetas Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m Word32 | Returns: the metadata API array size as a |
Retrieve the number of values currently stored in the meta API array of the query's structure.
getNAllocationParams
queryGetNAllocationParams Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m Word32 | Returns: the allocator array size as a |
Retrieve the number of values currently stored in the allocator params array of the query's structure.
If no memory allocator is specified, the downstream element can handle the default memory allocator. The first memory allocator in the query should be generic and allow mapping to system memory, all following allocators should be ordered by preference with the preferred one first.
getNAllocationPools
queryGetNAllocationPools Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m Word32 | Returns: the pool array size as a |
Retrieve the number of values currently stored in the pool array of the query's structure.
getNBufferingRanges
queryGetNBufferingRanges Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m Word32 | Returns: the range array size as a |
Retrieve the number of values currently stored in the buffered-ranges array of the query's structure.
getNSchedulingModes
queryGetNSchedulingModes Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m Word32 | Returns: the scheduling mode array size as a |
Retrieve the number of values currently stored in the scheduling mode array of the query's structure.
getStructure
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m (Maybe Structure) | Returns: the |
Get the structure of a query.
hasSchedulingMode
queryHasSchedulingMode Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> PadMode |
|
-> m Bool | Returns: |
Check if query
has scheduling mode set.
When checking if upstream supports pull mode, it is usually not enough to just check for GST_PAD_MODE_PULL with this function, you also want to check whether the scheduling flags returned by 'GI.Gst.Structs.Query.queryParseScheduling' have the seeking flag set (meaning random access is supported, not only sequential pulls).
hasSchedulingModeWithFlags
queryHasSchedulingModeWithFlags Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> PadMode |
|
-> [SchedulingFlags] |
|
-> m Bool | Returns: |
Check if query
has scheduling mode set and flags
is set in
query scheduling flags.
newAcceptCaps
Constructs a new query object for querying if caps
are accepted.
Free-function: gst_query_unref()
newAllocation
:: (HasCallStack, MonadIO m) | |
=> Caps |
|
-> Bool |
|
-> m Query | Returns: a new |
Constructs a new query object for querying the allocation properties.
Free-function: gst_query_unref()
newBitrate
Constructs a new query object for querying the bitrate.
Free-function: gst_query_unref()
Since: 1.16
newBuffering
:: (HasCallStack, MonadIO m) | |
=> Format |
|
-> m Query | Returns: a new |
Constructs a new query object for querying the buffering status of a stream.
Free-function: gst_query_unref()
newCaps
Constructs a new query object for querying the caps.
The CAPS query should return the allowable caps for a pad in the context of the element's state, its link to other elements, and the devices or files it has opened. These caps must be a subset of the pad template caps. In the NULL state with no links, the CAPS query should ideally return the same caps as the pad template. In rare circumstances, an object property can affect the caps returned by the CAPS query, but this is discouraged.
For most filters, the caps returned by CAPS query is directly affected by the allowed caps on other pads. For demuxers and decoders, the caps returned by the srcpad's getcaps function is directly related to the stream data. Again, the CAPS query should return the most specific caps it reasonably can, since this helps with autoplugging.
The filter
is used to restrict the result caps, only the caps matching
filter
should be returned from the CAPS query. Specifying a filter might
greatly reduce the amount of processing an element needs to do.
Free-function: gst_query_unref()
newContext
:: (HasCallStack, MonadIO m) | |
=> Text |
|
-> m Query | Returns: a new |
Constructs a new query object for querying the pipeline-local context.
Free-function: gst_query_unref()
Since: 1.2
newConvert
:: (HasCallStack, MonadIO m) | |
=> Format |
|
-> Int64 |
|
-> Format |
|
-> m Query | Returns: a |
Constructs a new convert query object. Use gst_query_unref()
when done with it. A convert query is used to ask for a conversion between
one format and another.
Free-function: gst_query_unref()
newCustom
:: (HasCallStack, MonadIO m) | |
=> QueryType |
|
-> Maybe Structure |
|
-> m (Maybe Query) | Returns: a new |
Constructs a new custom query object. Use gst_query_unref()
when done with it.
Free-function: gst_query_unref()
newDrain
Constructs a new query object for querying the drain state.
Free-function: gst_query_unref()
newDuration
:: (HasCallStack, MonadIO m) | |
=> Format |
|
-> m Query | Returns: a new |
Constructs a new stream duration query object to query in the given format.
Use gst_query_unref()
when done with it. A duration query will give the
total length of the stream.
Free-function: gst_query_unref()
newFormats
Constructs a new query object for querying formats of the stream.
Free-function: gst_query_unref()
newLatency
Constructs a new latency query object.
Use gst_query_unref()
when done with it. A latency query is usually performed
by sinks to compensate for additional latency introduced by elements in the
pipeline.
Free-function: gst_query_unref()
newPosition
:: (HasCallStack, MonadIO m) | |
=> Format |
|
-> m Query | Returns: a new |
Constructs a new query stream position query object. Use gst_query_unref()
when done with it. A position query is used to query the current position
of playback in the streams, in some format.
Free-function: gst_query_unref()
newScheduling
Constructs a new query object for querying the scheduling properties.
Free-function: gst_query_unref()
newSeeking
:: (HasCallStack, MonadIO m) | |
=> Format |
|
-> m Query | Returns: a new |
Constructs a new query object for querying seeking properties of the stream.
Free-function: gst_query_unref()
newSegment
:: (HasCallStack, MonadIO m) | |
=> Format |
|
-> m Query | Returns: a new |
Constructs a new segment query object. Use gst_query_unref()
when done with it. A segment query is used to discover information about the
currently configured segment for playback.
Free-function: gst_query_unref()
newUri
Constructs a new query URI query object. Use gst_query_unref()
when done with it. An URI query is used to query the current URI
that is used by the source or sink.
Free-function: gst_query_unref()
parseAcceptCaps
Get the caps from query
. The caps remains valid as long as query
remains
valid.
parseAcceptCapsResult
queryParseAcceptCapsResult Source #
Parse the result from query
and store in result
.
parseAllocation
Parse an allocation query, writing the requested caps in caps
and
whether a pool is needed in needPool
, if the respective parameters
are non-Nothing
.
Pool details can be retrieved using queryGetNAllocationPools
and
queryParseNthAllocationPool
.
parseBitrate
Get the results of a bitrate query. See also querySetBitrate
.
Since: 1.16
parseBufferingPercent
queryParseBufferingPercent Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m (Bool, Int32) |
Get the percentage of buffered data. This is a value between 0 and 100.
The busy
indicator is True
when the buffering is in progress.
parseBufferingRange
queryParseBufferingRange Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m (Format, Int64, Int64, Int64) |
Parse an available query, writing the format into format
, and
other results into the passed parameters, if the respective parameters
are non-Nothing
parseBufferingStats
queryParseBufferingStats Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m (BufferingMode, Int32, Int32, Int64) |
Extracts the buffering stats values from query
.
parseCaps
Get the filter from the caps query
. The caps remains valid as long as
query
remains valid.
parseCapsResult
Get the caps result from query
. The caps remains valid as long as
query
remains valid.
parseContext
Get the context from the context query
. The context remains valid as long as
query
remains valid.
Since: 1.2
parseContextType
queryParseContextType Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m (Bool, Text) | Returns: a |
Parse a context type from an existing GST_QUERY_CONTEXT query.
Since: 1.2
parseConvert
Parse a convert query answer. Any of srcFormat
, srcValue
, destFormat
,
and destValue
may be Nothing
, in which case that value is omitted.
parseDuration
Parse a duration query answer. Write the format of the duration into format
,
and the value into duration
, if the respective variables are non-Nothing
.
parseLatency
Parse a latency query answer.
parseNFormats
Parse the number of formats in the formats query
.
parseNthAllocationMeta
queryParseNthAllocationMeta Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m (GType, Structure) | Returns: a |
Parse an available query and get the metadata API
at index
of the metadata API array.
parseNthAllocationParam
queryParseNthAllocationParam Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m (Allocator, AllocationParams) |
Parse an available query and get the allocator and its params
at index
of the allocator array.
parseNthAllocationPool
queryParseNthAllocationPool Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m (BufferPool, Word32, Word32, Word32) |
Get the pool parameters in query
.
Unref pool
with objectUnref
when it's not needed any more.
parseNthBufferingRange
queryParseNthBufferingRange Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m (Bool, Int64, Int64) | Returns: a |
Parse an available query and get the start and stop values stored
at the index
of the buffered ranges array.
parseNthFormat
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m Format |
Parse the format query and retrieve the nth
format from it into
format
. If the list contains less elements than nth
, format
will be
set to GST_FORMAT_UNDEFINED.
parseNthSchedulingMode
queryParseNthSchedulingMode Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m PadMode | Returns: a |
Parse an available query and get the scheduling mode
at index
of the scheduling modes array.
parsePosition
Parse a position query, writing the format into format
, and the position
into cur
, if the respective parameters are non-Nothing
.
parseScheduling
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m ([SchedulingFlags], Int32, Int32, Int32) |
Set the scheduling properties.
parseSeeking
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m (Format, Bool, Int64, Int64) |
Parse a seeking query, writing the format into format
, and
other results into the passed parameters, if the respective parameters
are non-Nothing
parseSegment
Parse a segment query answer. Any of rate
, format
, startValue
, and
stopValue
may be Nothing
, which will cause this value to be omitted.
See querySetSegment
for an explanation of the function arguments.
parseUri
Parse an URI query, writing the URI into uri
as a newly
allocated string, if the respective parameters are non-Nothing
.
Free the string with free
after usage.
parseUriRedirection
queryParseUriRedirection Source #
Parse an URI query, writing the URI into uri
as a newly
allocated string, if the respective parameters are non-Nothing
.
Free the string with free
after usage.
Since: 1.2
parseUriRedirectionPermanent
queryParseUriRedirectionPermanent Source #
Parse an URI query, and set permanent
to True
if there is a redirection
and it should be considered permanent. If a redirection is permanent,
applications should update their internal storage of the URI, otherwise
they should make all future requests to the original URI.
Since: 1.4
removeNthAllocationMeta
queryRemoveNthAllocationMeta Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m () |
Remove the metadata API at index
of the metadata API array.
removeNthAllocationParam
queryRemoveNthAllocationParam Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m () |
Remove the allocation param at index
of the allocation param array.
Since: 1.2
removeNthAllocationPool
queryRemoveNthAllocationPool Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m () |
Remove the allocation pool at index
of the allocation pool array.
Since: 1.2
setAcceptCapsResult
querySetAcceptCapsResult Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Bool |
|
-> m () |
Set result
as the result for the query
.
setBitrate
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Word32 |
|
-> m () |
Set the results of a bitrate query. The nominal bitrate is the average bitrate expected over the length of the stream as advertised in file headers (or similar).
Since: 1.16
setBufferingPercent
querySetBufferingPercent Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Bool |
|
-> Int32 |
|
-> m () |
Set the percentage of buffered data. This is a value between 0 and 100.
The busy
indicator is True
when the buffering is in progress.
setBufferingRange
querySetBufferingRange Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Format |
|
-> Int64 |
|
-> Int64 |
|
-> Int64 |
|
-> m () |
Set the available query result fields in query
.
setBufferingStats
querySetBufferingStats Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> BufferingMode |
|
-> Int32 |
|
-> Int32 |
|
-> Int64 |
|
-> m () |
Configures the buffering stats values in query
.
setCapsResult
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Caps |
|
-> m () |
Set the caps
result in query
.
setContext
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Context |
|
-> m () |
Answer a context query by setting the requested context.
Since: 1.2
setConvert
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Format |
|
-> Int64 |
|
-> Format |
|
-> Int64 |
|
-> m () |
Answer a convert query by setting the requested values.
setDuration
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Format |
|
-> Int64 |
|
-> m () |
Answer a duration query by setting the requested value in the given format.
setFormatsv
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> [Format] |
|
-> m () |
Set the formats query result fields in query
. The number of formats passed
in the formats
array must be equal to nFormats
.
setLatency
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Bool |
|
-> Word64 |
|
-> Word64 |
|
-> m () |
Answer a latency query by setting the requested values in the given format.
setNthAllocationParam
querySetNthAllocationParam Source #
:: (HasCallStack, MonadIO m, IsAllocator a) | |
=> Query |
|
-> Word32 |
|
-> Maybe a |
|
-> Maybe AllocationParams |
|
-> m () |
Parse an available query and get the allocator and its params
at index
of the allocator array.
setNthAllocationPool
querySetNthAllocationPool Source #
:: (HasCallStack, MonadIO m, IsBufferPool a) | |
=> Query |
|
-> Word32 |
|
-> Maybe a |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> m () |
Set the pool parameters in query
.
setPosition
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Format |
|
-> Int64 |
|
-> m () |
Answer a position query by setting the requested value in the given format.
setScheduling
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> [SchedulingFlags] |
|
-> Int32 |
|
-> Int32 |
|
-> Int32 |
|
-> m () |
Set the scheduling properties.
setSeeking
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Format |
|
-> Bool |
|
-> Int64 |
|
-> Int64 |
|
-> m () |
Set the seeking query result fields in query
.
setSegment
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Double |
|
-> Format |
|
-> Int64 |
|
-> Int64 |
|
-> m () |
Answer a segment query by setting the requested values. The normal playback segment of a pipeline is 0 to duration at the default rate of 1.0. If a seek was performed on the pipeline to play a different segment, this query will return the range specified in the last seek.
startValue
and stopValue
will respectively contain the configured
playback range start and stop values expressed in format
.
The values are always between 0 and the duration of the media and
startValue
<= stopValue
. rate
will contain the playback rate. For
negative rates, playback will actually happen from stopValue
to
startValue
.
setUri
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Text |
|
-> m () |
Answer a URI query by setting the requested URI.
setUriRedirection
querySetUriRedirection Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Text |
|
-> m () |
Answer a URI query by setting the requested URI redirection.
Since: 1.2
setUriRedirectionPermanent
querySetUriRedirectionPermanent Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> Bool |
|
-> m () |
Answer a URI query by setting the requested URI redirection to permanent or not.
Since: 1.4
writableStructure
queryWritableStructure Source #
:: (HasCallStack, MonadIO m) | |
=> Query |
|
-> m Structure | Returns: the |
Get the structure of a query. This method should be called with a writable
query
so that the returned structure is guaranteed to be writable.
Properties
miniObject
The parent MiniObject
type
getQueryMiniObject :: MonadIO m => Query -> m MiniObject Source #
Get the value of the “mini_object
” field.
When overloading is enabled, this is equivalent to
get
query #miniObject
type
the QueryType
getQueryType :: MonadIO m => Query -> m QueryType Source #
Get the value of the “type
” field.
When overloading is enabled, this is equivalent to
get
query #type
setQueryType :: MonadIO m => Query -> QueryType -> m () Source #
Set the value of the “type
” field.
When overloading is enabled, this is equivalent to
set
query [ #type:=
value ]