Gtk2HsContentsIndex
Media.Streaming.GStreamer.Core.Buffer
Contents
Types
Buffer Operations
Synopsis
data Buffer
class MiniObjectClass o => BufferClass o
data BufferFlags
= BufferPreroll
| BufferDiscont
| BufferInCaps
| BufferGap
| BufferDeltaUnit
castToBuffer :: MiniObjectClass obj => obj -> Buffer
toBuffer :: BufferClass o => o -> Buffer
isBuffer :: BufferClass o => o -> Bool
bufferOffsetNone :: BufferOffset
bufferGetFlags :: BufferClass bufferT => bufferT -> [BufferFlags]
bufferGetFlagsM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m [BufferFlags]
bufferSetFlagsM :: (BufferClass bufferT, MonadIO m) => [BufferFlags] -> MiniObjectT bufferT m ()
bufferUnsetFlagsM :: (BufferClass bufferT, MonadIO m) => [BufferFlags] -> MiniObjectT bufferT m ()
bufferGetSize :: BufferClass bufferT => bufferT -> Word
bufferGetSizeM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m Word
bufferGetData :: BufferClass bufferT => bufferT -> ByteString
bufferGetDataM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m ByteString
bufferSetDataM :: (BufferClass bufferT, MonadIO m) => ByteString -> MiniObjectT bufferT m ()
unsafeBufferGetPtrM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m (Ptr Word8)
bufferGetTimestamp :: BufferClass bufferT => bufferT -> Maybe ClockTime
bufferGetTimestampM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m (Maybe ClockTime)
bufferSetTimestampM :: (BufferClass bufferT, MonadIO m) => Maybe ClockTime -> MiniObjectT bufferT m ()
bufferGetDuration :: BufferClass bufferT => bufferT -> Maybe ClockTime
bufferGetDurationM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m (Maybe ClockTime)
bufferSetDurationM :: (BufferClass bufferT, MonadIO m) => Maybe ClockTime -> MiniObjectT bufferT m ()
bufferGetCaps :: BufferClass bufferT => bufferT -> Maybe Caps
bufferGetCapsM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m (Maybe Caps)
bufferSetCapsM :: (BufferClass bufferT, MonadIO m) => Maybe Caps -> MiniObjectT bufferT m ()
bufferGetOffset :: BufferClass bufferT => bufferT -> Maybe Word64
bufferGetOffsetM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m (Maybe Word64)
bufferSetOffsetM :: (BufferClass bufferT, MonadIO m) => Maybe Word64 -> MiniObjectT bufferT m ()
bufferGetOffsetEnd :: BufferClass bufferT => bufferT -> Maybe Word64
bufferGetOffsetEndM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m (Maybe Word64)
bufferSetOffsetEndM :: (BufferClass bufferT, MonadIO m) => Maybe Word64 -> MiniObjectT bufferT m ()
bufferIsDiscont :: BufferClass bufferT => bufferT -> Bool
bufferIsDiscontM :: (BufferClass bufferT, MonadIO m) => MiniObjectT bufferT m Bool
bufferCreateEmpty :: MonadIO m => MiniObjectT Buffer m a -> m (Buffer, a)
bufferCreate :: MonadIO m => Word -> MiniObjectT Buffer m a -> m (Buffer, a)
bufferCreateSub :: BufferClass bufferT => bufferT -> Word -> Word -> Maybe Buffer
bufferIsSpanFast :: (BufferClass bufferT1, BufferClass bufferT2) => bufferT1 -> bufferT2 -> Bool
bufferSpan :: (BufferClass bufferT1, BufferClass bufferT2) => bufferT1 -> Word32 -> bufferT2 -> Word32 -> Maybe Buffer
bufferMerge :: (BufferClass bufferT1, BufferClass bufferT2) => bufferT1 -> bufferT2 -> Buffer
Types
Buffers are the basic unit of data transfer in GStreamer. The Buffer type provides all the state necessary to define a region of memory as part of a stream. Sub-buffers are also supported, allowing a smaller region of a Buffer to become its own Buffer, with mechansims in place to ensure that neither memory space goes away prematurely.
data Buffer
show/hide Instances
class MiniObjectClass o => BufferClass o
show/hide Instances
data BufferFlags
The flags a Buffer may have.
Constructors
BufferPrerollthe buffer is part of a preroll and should not be displayed
BufferDiscontthe buffer marks a discontinuity in the stream
BufferInCapsthe buffer has been added as a field in a Caps
BufferGapthe buffer has been created to fill a gap in the stream
BufferDeltaUnitthe buffer cannot be decoded independently
show/hide Instances
castToBuffer :: MiniObjectClass obj => obj -> Buffer
toBuffer :: BufferClass o => o -> Buffer
isBuffer :: BufferClass o => o -> Bool
Buffer Operations
bufferOffsetNone :: BufferOffset
The undefined BufferOffset value.
bufferGetFlags
:: BufferClass bufferT
=> bufferTbuffer - a Buffer
-> [BufferFlags]the flags set on buffer
Get the flags set on buffer.
bufferGetFlagsM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m [BufferFlags]the flags set on the current Buffer
Get the flags set on the current Buffer.
bufferSetFlagsM
:: (BufferClass bufferT, MonadIO m)
=> [BufferFlags]flags - the flags to set on the current Buffer
-> MiniObjectT bufferT m ()
Set flags on the current Buffer.
bufferUnsetFlagsM
:: (BufferClass bufferT, MonadIO m)
=> [BufferFlags]flags - the flags to unset on the current Buffer
-> MiniObjectT bufferT m ()
Unset flags on the current Buffer.
bufferGetSize
:: BufferClass bufferT
=> bufferTbuffer - a Buffer
-> Wordthe size of buffer in bytes
Get buffer's size in bytes.
bufferGetSizeM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m Wordthe size of the current Buffer in bytes
Get the size of the current Buffer in bytes.
bufferGetData
:: BufferClass bufferT
=> bufferTbuffer - a Buffer
-> ByteStringthe data stored in buffer
Make an O(n) copy of the data stored in buffer.
bufferGetDataM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m ByteStringthe data stored in the current Buffer
Make an O(n) copy of the current Buffer.
bufferSetDataM
:: (BufferClass bufferT, MonadIO m)
=> ByteStringbs - the data to store in the current Buffer
-> MiniObjectT bufferT m ()
Store an O(n) copy of the provided data in the current Buffer.
unsafeBufferGetPtrM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m (Ptr Word8)a pointer to the data stored in the current Buffer
Get a raw pointer to the internal data area for the current buffer. The pointer may be used to write into the data area if desired. This function is unsafe in that the pointer should not be used once the Buffer is returned.
bufferGetTimestamp
:: BufferClass bufferT
=> bufferTbuffer - a Buffer
-> Maybe ClockTimethe timestamp on buffer
Get the timestamp on buffer.
bufferGetTimestampM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m (Maybe ClockTime)the timestamp on the current Buffer
Get the timestamp on the current Buffer.
bufferSetTimestampM
:: (BufferClass bufferT, MonadIO m)
=> Maybe ClockTimetimestamp - the timestamp to set on the current Buffer
-> MiniObjectT bufferT m ()
Set the timestamp on the current Buffer.
bufferGetDuration
:: BufferClass bufferT
=> bufferTbuffer - a Buffer
-> Maybe ClockTimethe duration of buffer
Get the duration of buffer.
bufferGetDurationM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m (Maybe ClockTime)the duration of the current Buffer
Get the duration of the current Buffer.
bufferSetDurationM
:: (BufferClass bufferT, MonadIO m)
=> Maybe ClockTimeduration - the duration to set on the current Buffer
-> MiniObjectT bufferT m ()
Set the duration of the current Buffer.
bufferGetCaps
:: BufferClass bufferT
=> bufferTbuffer - a buffer
-> Maybe Capsthe Caps of buffer if set, otherwise Nothing
Get the Caps of buffer.
bufferGetCapsM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m (Maybe Caps)the Caps of the current Buffer if set, otherwise Nothing
Get the caps of the current Buffer.
bufferSetCapsM
:: (BufferClass bufferT, MonadIO m)
=> Maybe Capscaps - the Caps to set on the current Buffer, or Nothing to unset them
-> MiniObjectT bufferT m ()
Set the caps of the current Buffer.
bufferGetOffset
:: BufferClass bufferT
=> bufferTbuffer - a buffer
-> Maybe Word64the start offset of buffer if set, otherwise Nothing
Get the start offset of the Buffer.
bufferGetOffsetM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m (Maybe Word64)the start offset of the current Buffer if set, otherwise Nothing
Get the start offset of the current Buffer.
bufferSetOffsetM
:: (BufferClass bufferT, MonadIO m)
=> Maybe Word64offset - the start offset to set on the current buffer
-> MiniObjectT bufferT m ()
Set the start offset of the current Buffer.
bufferGetOffsetEnd
:: BufferClass bufferT
=> bufferTbuffer - a buffer
-> Maybe Word64the end offset of buffer if set, otherwise Nothing
Get the end offset of the Buffer.
bufferGetOffsetEndM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m (Maybe Word64)the start offset of the current Buffer if set, otherwise Nothing
Get the end offset of the current Buffer.
bufferSetOffsetEndM
:: (BufferClass bufferT, MonadIO m)
=> Maybe Word64offset - the end offset to set on the current buffer
-> MiniObjectT bufferT m ()
Set the end offset of the current Buffer.
bufferIsDiscont
:: BufferClass bufferT
=> bufferTbuffer - a buffer
-> BoolTrue if buffer marks a discontinuity in a stream
Return True if the Buffer marks a discontinuity in a stream, or False otherwise. This typically occurs after a seek or a dropped buffer from a live or network source.
bufferIsDiscontM
:: (BufferClass bufferT, MonadIO m)
=> MiniObjectT bufferT m BoolTrue if the current buffer marks a discontinuity in a stream
Return True if the current Buffer marks a discontinuity in a stream, or False otherwise.
bufferCreateEmpty
:: MonadIO m
=> MiniObjectT Buffer m amutate - the mutating action
-> m (Buffer, a)the new buffer and the action's result
Create an empty Buffer and mutate it according to the given action. Once this function returns, the Buffer is immutable.
bufferCreate
:: MonadIO m
=> Wordsize - the size of the Buffer to be created
-> MiniObjectT Buffer m amutate - the mutating action
-> m (Buffer, a)the new Buffer and the action's result
Create and mutate a Buffer of the given size.
bufferCreateSub
:: BufferClass bufferT
=> bufferTparent - the parent buffer
-> Wordoffset - the offset
-> Wordsize - the size
-> Maybe Bufferthe new sub-buffer
Create a sub-buffer from an existing Buffer with the given offset and size. This sub-buffer uses the actual memory space of the parent buffer. Thus function will copy the offset and timestamp fields when the offset is 0. Otherwise, they will both be set to Nothing. If the offset is 0 and the size is the total size of the parent, the duration and offset end fields are also copied. Otherwise they will be set to Nothing.
bufferIsSpanFast
:: (BufferClass bufferT1, BufferClass bufferT2)
=> bufferT1buffer1 - the first buffer
-> bufferT2buffer2 - the second buffer
-> BoolTrue if the buffers are contiguous, or False if copying would be required
Return True if bufferSpan can be done without copying the data, or False otherwise.
bufferSpan
:: (BufferClass bufferT1, BufferClass bufferT2)
=> bufferT1buffer1 - the first buffer
-> Word32offset - the offset into the concatenated buffer
-> bufferT2buffer2 - the second buffer
-> Word32len - the length of the final buffer
-> Maybe Bufferthe spanning buffer, or Nothing if the arguments are invalid

Create a new Buffer that consists of a span across the given buffers. Logically, the buffers are concatenated to make a larger buffer, and a new buffer is created at the given offset and with the given size.

If the two buffers are children of the same larger buffer, and are contiguous, no copying is necessary. You can use bufferIsSpanFast to determine if copying is needed.

bufferMerge
:: (BufferClass bufferT1, BufferClass bufferT2)
=> bufferT1buffer1 - a buffer
-> bufferT2buffer2 - a buffer
-> Bufferthe concatenation of the buffers
Concatenate two buffers. If the buffers point to contiguous memory areas, no copying will occur.
Produced by Haddock version 0.8