| Maintainer | gtk2hs-devel@lists.sourceforge.net | 
|---|---|
| Stability | alpha | 
| Portability | portable (depends on GHC) | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Media.Streaming.GStreamer.Core.Bus
Description
An asynchronous message bus subsystem.
- data Bus
 - class ObjectClass o => BusClass o
 - data BusSyncReply
 - type BusSyncHandler = Bus -> Message -> IO BusSyncReply
 - castToBus :: GObjectClass obj => obj -> Bus
 - gTypeBus :: GType
 - busGetFlags :: BusClass busT => busT -> IO [BusFlags]
 - busSetFlags :: BusClass busT => busT -> [BusFlags] -> IO ()
 - busUnsetFlags :: BusClass busT => busT -> [BusFlags] -> IO ()
 - busNew :: IO Bus
 - busPost :: BusClass busT => busT -> Message -> IO Bool
 - busHavePending :: BusClass busT => busT -> IO Bool
 - busPeek :: BusClass busT => busT -> IO (Maybe Message)
 - busPop :: BusClass busT => busT -> IO (Maybe Message)
 - busTimedPop :: BusClass busT => busT -> Maybe ClockTime -> IO (Maybe Message)
 - busSetFlushing :: BusClass busT => busT -> Bool -> IO ()
 - busSetSyncHandler :: BusClass busT => busT -> Maybe BusSyncHandler -> IO ()
 - busUseSyncSignalHandler :: BusClass busT => busT -> IO ()
 - busCreateWatch :: BusClass busT => busT -> IO Source
 - busAddWatch :: BusClass busT => busT -> Priority -> BusFunc -> IO HandlerId
 - busDisableSyncMessageEmission :: BusClass busT => busT -> IO ()
 - busEnableSyncMessageEmission :: BusClass busT => busT -> IO ()
 - busAddSignalWatch :: BusClass busT => busT -> Priority -> IO ()
 - busRemoveSignalWatch :: BusClass busT => busT -> IO ()
 - busPoll :: BusClass busT => busT -> [MessageType] -> ClockTimeDiff -> IO Message
 - busMessage :: BusClass busT => Signal busT (Message -> IO ())
 - busSyncMessage :: BusClass busT => Signal busT (Message -> IO ())
 
Detail
The Bus is resposible for delivering Messages in a
 first-in, first-out order, from the streaming threads to the
 application.
Since the application typically only wants to deal with
 delivery of these messages from one thread, the Bus will
 marshal the messages between different threads. This is
 important since the actual streaming of media is done in
 a thread separate from the application.
The Bus provides support for Source
 based notifications. This makes it possible to handle the
 delivery in the GLib Source.
A message is posted on the bus with the busPost method. With
 the busPeek and busPop methods one can look at or retrieve
 a previously posted message.
The bus can be polled with the busPoll method. This methods
 blocks up to the specified timeout value until one of the
 specified messages types is posted on the bus. The application
 can then pop the messages from the bus to handle
 them. Alternatively the application can register an
 asynchronous bus function using busAddWatch. This function
 will install a Source in the default
 GLib main loop and will deliver messages a short while after
 they have been posted. Note that the main loop should be
 running for the asynchronous callbacks.
It is also possible to get messages from the bus without any
 thread marshalling with the busSetSyncHandler method. This
 makes it possible to react to a message in the same thread that
 posted the message on the bus. This should only be used if the
 application is able to deal with messages from different
 threads.
Every Pipeline has one bus.
Note that a Pipeline will set its bus into flushing state
 when changing from StateReady to StateNull.
Types
The result of a BusSyncHandler.
data BusSyncReply Source #
Instances
A handler that will be invoked synchronously when a new message is injected into the bus. This function is mostly used internally. Only one sync handler may be attached to a given bus.
type BusSyncHandler = Bus -> Message -> IO BusSyncReply Source #
castToBus :: GObjectClass obj => obj -> Bus Source #
Bus Operations
Get the flags set on this bus.
Set flags on this bus.
Unset flags on this bus.
Arguments
| :: BusClass busT | |
| => busT | 
  | 
| -> Message | 
  | 
| -> IO Bool | 
  | 
Post a message to the bus.
Arguments
| :: BusClass busT | |
| => busT | 
  | 
| -> IO Bool | 
  | 
Check if there are pending messages on the bus.
Arguments
| :: BusClass busT | |
| => busT | 
  | 
| -> IO (Maybe Message) | the first   | 
Get the message at the front of the queue. Any message returned will remain on the queue.
Arguments
| :: BusClass busT | |
| => busT | 
  | 
| -> IO (Maybe Message) | the first   | 
Get the message at the front of the queue. It will be removed from the queue.
Arguments
| :: BusClass busT | |
| => busT | 
  | 
| -> Maybe BusSyncHandler | 
  | 
| -> IO () | 
Set the synchronous message handler on the bus. The function will be called every time a new message is posted to the bus. Note that the function will be called from the thread context of the poster.
Calling this function will replace any previously set sync
 handler. If Nothing is passed to this function, it will unset
 the handler.
busUseSyncSignalHandler Source #
Use a synchronous message handler that converts all messages to signals.
Create a watch for the bus. The Source will dispatch a signal
 whenever a message is on the bus. After the signal is dispatched,
 the message is popped off the bus.
Arguments
| :: BusClass busT | |
| => busT | 
  | 
| -> Priority | 
  | 
| -> BusFunc | 
  | 
| -> IO HandlerId | the event source ID  | 
Adds a bus watch to the default main context with the given priority. This function is used to receive asynchronous messages in the main loop.
The watch can be removed by calling sourceRemove.
busDisableSyncMessageEmission Source #
Instructs GStreamer to stop emitting the busSyncMessage signal
 for this bus. See busEnableSyncMessageEmission for more
 information.
In the event that multiple pieces of code have called
 busEnableSyncMessageEmission, the sync-message
 emissions will only be stopped after all calls to
 busEnableSyncMessageEmission were "cancelled" by
 calling this function.
busEnableSyncMessageEmission Source #
Instructs GStreamer to emit the busSyncMessage signal after
 running the bus's sync handler. This function is here so that
 programmers can ensure that they can synchronously receive
 messages without having to affect what the bin's sync handler is.
This function may be called multiple times. To clean up, the
 caller is responsible for calling busDisableSyncMessageEmission
 as many times as this function is called.
While this function looks similar to busAddSignalWatch, it is
 not exactly the same -- this function enables synchronous
 emission of signals when messages arrive; busAddSignalWatch
 adds an idle callback to pop messages off the bus
 asynchronously. The busSyncMessage signal comes from the thread
 of whatever object posted the message; the busMessage signal is
 marshalled to the main thread via the main loop.
Adds a bus signal watch to the default main context with the
 given priority. After calling this method, the bus will emit the
 busMessage signal for each message posted on the bus.
This function may be called multiple times. To clean up, the
 caller is responsible for calling busRemoveSignalWatch as many
 times.
Remove the signal watch that was added with busAddSignalWatch.
Arguments
| :: BusClass busT | |
| => busT | 
  | 
| -> [MessageType] | 
  | 
| -> ClockTimeDiff | 
  | 
| -> IO Message | 
Poll the bus for a message. Will block while waiting for messages
 to come. You can specify the maximum amount of time to wait with
 the timeout parameter. If timeout is negative, the function
 will wait indefinitely.
Messages not in events will be popped off the bus and ignored.
Because busPoll is implemented using the busMessage signal
 enabled by busAddSignalWatch, calling busPoll will cause the
 busMessage signal to be emitted for every message that the
 function sees. Thus, a busMessage signal handler will see every
 message that busPoll sees -- neither will steal messages from
 the other.
This function will run a main loop in the default main context while polling.
Bus Signals
busSyncMessage :: BusClass busT => Signal busT (Message -> IO ()) Source #
A message has been posted on the bus. This signal is emitted from the thread that posted the message so one has to be careful with locking.
This signal will not be emitted by default, you must first call
 busUseSyncSignalHandler if you want this signal to be emitted
 when a message is posted on the bus.