dbus-0.10: A client library for the D-Bus IPC system.

Safe HaskellNone

DBus.Client

Contents

Description

D-Bus clients are an abstraction over the lower-level messaging system. When combined with an external daemon called the "bus", clients can perform remote procedure calls to other clients on the bus.

Clients may also listen for or emit signals, which are asynchronous broadcast notifications.

Example: connect to the session bus, and get a list of active names.

{-# LANGUAGE OverloadedStrings #-}

import Data.List (sort)
import DBus
import DBus.Client

main = do
    client <- connectSession
    
    -- Request a list of connected clients from the bus
    reply <- call_ client (methodCall "/org/freedesktop/DBus" "org.freedesktop.DBus" "ListNames")
        { methodCallDestination = Just "org.freedesktop.DBus"
        }
    
    -- org.freedesktop.DBus.ListNames() returns a single value, which is
    -- a list of names (here represented as [String])
    let Just names = fromVariant (methodReturnBody reply !! 0)
    
    -- Print each name on a line, sorted so reserved names are below
    -- temporary names.
    mapM_ putStrLn (sort names)

Synopsis

Clients

data Client Source

An active client session to a message bus. Clients may send or receive method calls, and listen for or emit signals.

Connecting to a bus

connect :: Address -> IO ClientSource

Connect to the bus at the specified address.

Throws a ClientError on failure.

connectSystem :: IO ClientSource

Connect to the bus specified in the environment variable DBUS_SYSTEM_BUS_ADDRESS, or to unix:path=/var/run/dbus/system_bus_socket if DBUS_SYSTEM_BUS_ADDRESS is not set.

Throws a ClientError if DBUS_SYSTEM_BUS_ADDRESS contains an invalid address, or if connecting to the bus failed.

connectSession :: IO ClientSource

Connect to the bus specified in the environment variable DBUS_SESSION_BUS_ADDRESS, which must be set.

Throws a ClientError if DBUS_SESSION_BUS_ADDRESS is unset, contains an invalid address, or if connecting to the bus failed.

connectStarter :: IO ClientSource

Connect to the bus specified in the environment variable DBUS_STARTER_ADDRESS, which must be set.

Throws a ClientError if DBUS_STARTER_ADDRESS is unset, contains an invalid address, or if connecting to the bus failed.

disconnect :: Client -> IO ()Source

Stop a Client's callback thread and close its underlying socket.

Sending method calls

call :: Client -> MethodCall -> IO (Either MethodError MethodReturn)Source

Send a method call to the bus, and wait for the response.

Throws a ClientError if the method call couldn't be sent, or if the reply couldn't be parsed.

call_ :: Client -> MethodCall -> IO MethodReturnSource

Send a method call to the bus, and wait for the response.

Unsets the noReplyExpected message flag before sending.

Throws a ClientError if the method call couldn't sent, if the reply couldn't be parsed, or if the reply was a MethodError.

callNoReply :: Client -> MethodCall -> IO ()Source

Send a method call to the bus, and do not wait for a response.

Sets the noReplyExpected message flag before sending.

Throws a ClientError if the method call couldn't be sent.

Receiving method calls

export :: Client -> ObjectPath -> [Method] -> IO ()Source

Export the given functions under the given ObjectPath and InterfaceName.

Use autoMethod to construct a Method from a function that accepts and returns simple types.

Use method to construct a Method from a function that handles parameter conversion manually.

ping :: MethodCall -> IO Reply
ping _ = replyReturn []

sayHello :: String -> IO String
sayHello name = return ("Hello " ++ name ++ "!")

export client "/hello_world"
    [ method "com.example.HelloWorld" "Ping" ping
    , autoMethod "com.example.HelloWorld" "Hello" sayHello
    ]

methodSource

Arguments

:: InterfaceName 
-> MemberName 
-> Signature

Input parameter signature

-> Signature

Output parameter signature

-> (MethodCall -> IO Reply) 
-> Method 

Define a method handler, which will accept method calls with the given interface and member name.

Note that the input and output parameter signatures are used for introspection, but are not checked when executing a method.

See autoMethod for an easier way to export functions with simple parameter and return types.

replyReturn :: [Variant] -> ReplySource

Reply to a method call with a successful return, containing the given body.

replyError :: ErrorName -> [Variant] -> ReplySource

Reply to a method call with an error, containing the given error name and body.

Typically, the first item of the error body is a string with a message describing the error.

throwErrorSource

Arguments

:: ErrorName 
-> String

Error message

-> [Variant]

Additional items of the error body

-> IO a 

Normally, any exceptions raised while executing a method will be given the generic "org.freedesktop.DBus.Error.Failed" name. throwError allows the programmer to specify an error name, and provide additional information to the remote application. You may use this instead of throwIO to abort a method call.

Automatic method signatures

class AutoMethod a Source

Used to automatically generate method signatures for introspection documents. To support automatic signatures, a method's parameters and return value must all be instances of IsValue.

This class maps Haskell idioms to D-Bus; it is therefore unable to generate some signatures. In particular, it does not support methods which accept/return a single structure, or single-element structures. It also cannot generate signatures for methods with parameters or return values which are only instances of IsVariant. For these cases, please use method.

To match common Haskell use, if the return value is a tuple, it will be converted to a list of return values.

Instances

AutoMethod (IO ()) 
IsValue a => AutoMethod (IO a) 
(IsValue a, AutoMethod fn) => AutoMethod (a -> fn) 

autoMethod :: AutoMethod fn => InterfaceName -> MemberName -> fn -> MethodSource

Prepare a Haskell function for export, automatically detecting the function's type signature.

See AutoMethod for details on the limitations of this function.

See method for exporting functions with user-defined types.

Signals

listen :: Client -> MatchRule -> (Signal -> IO ()) -> IO ()Source

Request that the bus forward signals matching the given rule to this client, and process them in a callback.

A received signal might be processed by more than one callback at a time. Callbacks each run in their own thread.

Throws a ClientError if the match rule couldn't be added to the bus.

emit :: Client -> Signal -> IO ()Source

Emit the signal on the bus.

Throws a ClientError if the signal message couldn't be sent.

Match rules

data MatchRule Source

A match rule describes which signals a particular callback is interested in. Use matchAny to construct match rules.

Example: a match rule which matches signals sent by the root object.

matchFromRoot :: MatchRule
matchFromRoot = matchAny { matchPath = Just "/" }

Instances

formatMatchRule :: MatchRule -> StringSource

Convert a match rule into the textual format accepted by the bus.

matchAny :: MatchRuleSource

Match any signal.

matchSender :: MatchRule -> Maybe BusNameSource

If set, only receives signals sent from the given bus name.

The standard D-Bus implementation from http://dbus.freedesktop.org/ almost always sets signal senders to the unique name of the sending client. If matchSender is a requested name like "com.example.Foo", it will not match any signals.

The exception is for signals sent by the bus itself, which always have a sender of "org.freedesktop.DBus".

matchDestination :: MatchRule -> Maybe BusNameSource

If set, only receives signals sent to the given bus name.

matchPath :: MatchRule -> Maybe ObjectPathSource

If set, only receives signals sent with the given path.

matchInterface :: MatchRule -> Maybe InterfaceNameSource

If set, only receives signals sent with the given interface name.

matchMember :: MatchRule -> Maybe MemberNameSource

If set, only receives signals sent with the given member name.

Name reservation

requestName :: Client -> BusName -> [RequestNameFlag] -> IO RequestNameReplySource

Asks the message bus to assign the given name to this client. The bus maintains a queue of possible owners, where the head of the queue is the current ("primary") owner.

There are several uses for name reservation:

  • Clients which export methods reserve a name so users and applications can send them messages. For example, the GNOME Keyring reserves the name "org.gnome.keyring" on the user's session bus, and NetworkManager reserves "org.freedesktop.NetworkManager" on the system bus.
  • When there are multiple implementations of a particular service, the service standard will ususally include a generic bus name for the service. This allows other clients to avoid depending on any particular implementation's name. For example, both the GNOME Keyring and KDE KWallet services request the "org.freedesktop.secrets" name on the user's session bus.
  • A process with "single instance" behavior can use name assignment to check whether the instance is already running, and invoke some method on it (e.g. opening a new window).

Throws a ClientError if the call failed.

releaseName :: Client -> BusName -> IO ReleaseNameReplySource

Release a name that this client previously requested. See requestName for an explanation of name reservation.

Throws a ClientError if the call failed.

nameAllowReplacement :: RequestNameFlagSource

Allow this client's reservation to be replaced, if another client requests it with the nameReplaceExisting flag.

If this client's reservation is replaced, this client will be added to the wait queue unless the request also included the nameDoNotQueue flag.

nameReplaceExisting :: RequestNameFlagSource

If the name being requested is already reserved, attempt to replace it. This only works if the current owner provided the nameAllowReplacement flag.

nameDoNotQueue :: RequestNameFlagSource

If the name is already in use, do not add this client to the queue, just return an error.

data RequestNameReply Source

Constructors

NamePrimaryOwner

This client is now the primary owner of the requested name.

NameInQueue

The name was already reserved by another client, and replacement was either not attempted or not successful.

NameExists

The name was already reserved by another client, DoNotQueue was set, and replacement was either not attempted or not successful.

NameAlreadyOwner

This client is already the primary owner of the requested name.

data ReleaseNameReply Source

Constructors

NameReleased

This client has released the provided name.

NameNonExistent

The provided name is not assigned to any client on the bus.

NameNotOwner

The provided name is not assigned to this client.

Client errors

Advanced connection options

clientSocketOptions :: ClientOptions t -> SocketOptions tSource

Options for the underlying socket, for advanced use cases. See the DBus.Socket module.

defaultClientOptions :: ClientOptions SocketTransportSource

Default client options. Uses the built-in Socket-based transport, which supports the tcp: and unix: methods.

connectWith :: TransportOpen t => ClientOptions t -> Address -> IO ClientSource

Connect to the bus at the specified address, with the given connection options. Most users should use connect instead.

Throws a ClientError on failure.