dbus-1.2.21: A client library for the D-Bus IPC system.
Safe HaskellNone
LanguageHaskell2010

DBus.Client

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.

Instances

Instances details
IsValue a => AutoMethod (DBusR (Either Reply a)) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: DBusR (Either Reply a) -> ([Type], [Type])

apply :: DBusR (Either Reply a) -> [Variant] -> DBusR Reply

IsValue a => AutoMethod (DBusR a) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: DBusR a -> ([Type], [Type])

apply :: DBusR a -> [Variant] -> DBusR Reply

Path/Interface storage

data PathInfo Source #

Instances

Instances details
Eq PathInfo Source # 
Instance details

Defined in DBus.Client

Connecting to a bus

connect :: Address -> IO Client Source #

Connect to the bus at the specified address.

Throws a ClientError on failure.

connectSystem :: IO Client Source #

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 Client Source #

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 Client Source #

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 MethodReturn Source #

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.

getProperty :: Client -> MethodCall -> IO (Either MethodError Variant) Source #

Retrieve a property using the method call parameters that were provided.

Throws a ClientError if the property request couldn't be sent.

Receiving method calls

export :: Client -> ObjectPath -> Interface -> IO () Source #

Export the given Interface at the given ObjectPath

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"
   defaultInterface { interfaceName = "com.example.HelloWorld"
                    , interfaceMethods =
                      [ method "com.example.HelloWorld" "Ping" ping
                      , autoMethod "com.example.HelloWorld" "Hello" sayHello
                      ]
                    }
 

unexport :: Client -> ObjectPath -> IO () Source #

Revokes the export of the given ObjectPath. This will remove all interfaces and methods associated with the path.

makeMethod Source #

Arguments

:: MemberName 
-> Signature

Input parameter signature

-> Signature

Output parameter signature

-> (MethodCall -> DBusR 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.

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.

Minimal complete definition

funTypes, apply

Instances

Instances details
IsValue a => AutoMethod (IO (Either Reply a)) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: IO (Either Reply a) -> ([Type], [Type])

apply :: IO (Either Reply a) -> [Variant] -> DBusR Reply

IsValue a => AutoMethod (IO a) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: IO a -> ([Type], [Type])

apply :: IO a -> [Variant] -> DBusR Reply

IsValue a => AutoMethod (DBusR (Either Reply a)) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: DBusR (Either Reply a) -> ([Type], [Type])

apply :: DBusR (Either Reply a) -> [Variant] -> DBusR Reply

IsValue a => AutoMethod (DBusR a) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: DBusR a -> ([Type], [Type])

apply :: DBusR a -> [Variant] -> DBusR Reply

(IsValue a, AutoMethod fn) => AutoMethod (a -> fn) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: (a -> fn) -> ([Type], [Type])

apply :: (a -> fn) -> [Variant] -> DBusR Reply

autoMethod :: AutoMethod fn => MemberName -> fn -> Method Source #

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.

autoProperty :: forall v. IsValue v => MemberName -> Maybe (IO v) -> Maybe (v -> IO ()) -> Property Source #

data Reply Source #

Instances

Instances details
IsValue a => AutoMethod (IO (Either Reply a)) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: IO (Either Reply a) -> ([Type], [Type])

apply :: IO (Either Reply a) -> [Variant] -> DBusR Reply

IsValue a => AutoMethod (DBusR (Either Reply a)) Source # 
Instance details

Defined in DBus.Client

Methods

funTypes :: DBusR (Either Reply a) -> ([Type], [Type])

apply :: DBusR (Either Reply a) -> [Variant] -> DBusR Reply

throwError Source #

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.

Signals

addMatch :: Client -> MatchRule -> (Signal -> IO ()) -> IO SignalHandler 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.

The returned SignalHandler can be passed to removeMatch to stop handling this signal.

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

removeMatch :: Client -> SignalHandler -> IO () Source #

Request that the bus stop forwarding signals for the given handler.

Throws a ClientError if the match rule couldn't be removed from the bus.

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

Emit the signal on the bus.

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

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

Deprecated: Prefer DBus.Client.addMatch in new code.

Equivalent to addMatch, but does not return the added SignalHandler.

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

Instances details
Show MatchRule Source # 
Instance details

Defined in DBus.Client

formatMatchRule :: MatchRule -> String Source #

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

matchAny :: MatchRule Source #

Match any signal.

matchSender :: MatchRule -> Maybe BusName Source #

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 BusName Source #

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

matchPath :: MatchRule -> Maybe ObjectPath Source #

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

matchInterface :: MatchRule -> Maybe InterfaceName Source #

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

matchMember :: MatchRule -> Maybe MemberName Source #

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

matchPathNamespace :: MatchRule -> Maybe ObjectPath Source #

If set, only receives signals sent with the given path or any of its children.

Introspection

Name reservation

requestName :: Client -> BusName -> [RequestNameFlag] -> IO RequestNameReply Source #

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 ReleaseNameReply Source #

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

Throws a ClientError if the call failed.

data RequestNameFlag Source #

Instances

Instances details
Eq RequestNameFlag Source # 
Instance details

Defined in DBus.Client

Show RequestNameFlag Source # 
Instance details

Defined in DBus.Client

nameAllowReplacement :: RequestNameFlag Source #

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 :: RequestNameFlag Source #

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

nameDoNotQueue :: RequestNameFlag Source #

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.

UnknownRequestNameReply Word32

Not exported; exists to generate a compiler warning if users case on the reply and forget to include a default case.

Instances

Instances details
Eq RequestNameReply Source # 
Instance details

Defined in DBus.Client

Show RequestNameReply Source # 
Instance details

Defined in DBus.Client

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.

UnknownReleaseNameReply Word32

Not exported; exists to generate a compiler warning if users case on the reply and forget to include a default case.

Instances

Instances details
Eq ReleaseNameReply Source # 
Instance details

Defined in DBus.Client

Show ReleaseNameReply Source # 
Instance details

Defined in DBus.Client

Client errors

Advanced connection options

clientSocketOptions :: ClientOptions t -> SocketOptions t Source #

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

clientThreadRunner :: ClientOptions t -> IO () -> IO () Source #

A function to run the client thread. The provided IO computation should be called repeatedly; each time it is called, it will process one incoming message.

The provided computation will throw a ClientError if it fails to process an incoming message, or if the connection is lost.

The default implementation is forever.

defaultClientOptions :: ClientOptions SocketTransport Source #

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

connectWith :: TransportOpen t => ClientOptions t -> Address -> IO Client Source #

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

Throws a ClientError on failure.

data ErrorName Source #

Error names are used to identify which type of error was returned from a method call. Error names consist of alphanumeric characters separated by periods.

See http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-names-error for details.

Instances

Instances details
Eq ErrorName Source # 
Instance details

Defined in DBus.Internal.Types

Ord ErrorName Source # 
Instance details

Defined in DBus.Internal.Types

Show ErrorName Source # 
Instance details

Defined in DBus.Internal.Types

IsString ErrorName Source # 
Instance details

Defined in DBus.Internal.Types

NFData ErrorName Source # 
Instance details

Defined in DBus.Internal.Types

Methods

rnf :: ErrorName -> () #

IsVariant ErrorName Source # 
Instance details

Defined in DBus.Internal.Types