Safe Haskell | None |
---|---|
Language | Haskell98 |
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
- data Client = Client {}
- type DBusR a = ReaderT Client IO a
- data PathInfo = PathInfo {}
- pathInterfaces :: Lens' PathInfo [Interface]
- pathChildren :: Lens' PathInfo (Map String PathInfo)
- pathLens :: Applicative f => ObjectPath -> ((PathInfo -> f PathInfo) -> Maybe PathInfo -> f (Maybe PathInfo)) -> (PathInfo -> f PathInfo) -> PathInfo -> f PathInfo
- findPath :: ObjectPath -> PathInfo -> Maybe PathInfo
- data Interface = Interface {}
- defaultInterface :: Interface
- connect :: Address -> IO Client
- connectSystem :: IO Client
- connectSession :: IO Client
- connectStarter :: IO Client
- disconnect :: Client -> IO ()
- call :: Client -> MethodCall -> IO (Either MethodError MethodReturn)
- call_ :: Client -> MethodCall -> IO MethodReturn
- callNoReply :: Client -> MethodCall -> IO ()
- getProperty :: Client -> MethodCall -> IO (Either MethodError Variant)
- getPropertyValue :: IsValue a => Client -> MethodCall -> IO (Either MethodError a)
- setProperty :: Client -> MethodCall -> Variant -> IO (Either MethodError MethodReturn)
- setPropertyValue :: IsValue a => Client -> MethodCall -> a -> IO (Maybe MethodError)
- getAllProperties :: Client -> MethodCall -> IO (Either MethodError MethodReturn)
- getAllPropertiesMap :: Client -> MethodCall -> IO (Either MethodError (Map String Variant))
- buildPropertiesInterface :: Client -> Interface
- export :: Client -> ObjectPath -> Interface -> IO ()
- unexport :: Client -> ObjectPath -> IO ()
- data Method = Method {}
- makeMethod :: MemberName -> Signature -> Signature -> (MethodCall -> DBusR Reply) -> Method
- class AutoMethod a
- autoMethod :: AutoMethod fn => MemberName -> fn -> Method
- autoMethodWithMsg :: AutoMethod fn => MemberName -> (MethodCall -> fn) -> Method
- data Property = Property {
- propertyName :: MemberName
- propertyType :: Type
- propertyGetter :: Maybe (IO Variant)
- propertySetter :: Maybe (Variant -> IO ())
- autoProperty :: forall v. IsValue v => MemberName -> Maybe (IO v) -> Maybe (v -> IO ()) -> Property
- readOnlyProperty :: IsValue v => MemberName -> IO v -> Property
- data Reply
- = ReplyReturn [Variant]
- | ReplyError ErrorName [Variant]
- throwError :: ErrorName -> String -> [Variant] -> IO a
- data SignalHandler
- addMatch :: Client -> MatchRule -> (Signal -> IO ()) -> IO SignalHandler
- removeMatch :: Client -> SignalHandler -> IO ()
- emit :: Client -> Signal -> IO ()
- listen :: Client -> MatchRule -> (Signal -> IO ()) -> IO ()
- data MatchRule
- formatMatchRule :: MatchRule -> String
- matchAny :: MatchRule
- matchSender :: MatchRule -> Maybe BusName
- matchDestination :: MatchRule -> Maybe BusName
- matchPath :: MatchRule -> Maybe ObjectPath
- matchInterface :: MatchRule -> Maybe InterfaceName
- matchMember :: MatchRule -> Maybe MemberName
- matchPathNamespace :: MatchRule -> Maybe ObjectPath
- buildIntrospectionObject :: [Interface] -> PathInfo -> [String] -> Object
- buildIntrospectionInterface :: Interface -> Interface
- buildIntrospectionMethod :: Method -> Method
- buildIntrospectionProperty :: Property -> Property
- buildIntrospectableInterface :: Client -> Interface
- requestName :: Client -> BusName -> [RequestNameFlag] -> IO RequestNameReply
- releaseName :: Client -> BusName -> IO ReleaseNameReply
- data RequestNameFlag
- nameAllowReplacement :: RequestNameFlag
- nameReplaceExisting :: RequestNameFlag
- nameDoNotQueue :: RequestNameFlag
- data RequestNameReply
- data ReleaseNameReply
- data ClientError
- clientError :: String -> ClientError
- clientErrorMessage :: ClientError -> String
- clientErrorFatal :: ClientError -> Bool
- data ClientOptions t
- clientSocketOptions :: ClientOptions t -> SocketOptions t
- clientThreadRunner :: ClientOptions t -> IO () -> IO ()
- defaultClientOptions :: ClientOptions SocketTransport
- connectWith :: TransportOpen t => ClientOptions t -> Address -> IO Client
- dbusName :: BusName
- dbusPath :: ObjectPath
- data ErrorName
- errorFailed :: ErrorName
- errorInvalidParameters :: ErrorName
- errorUnknownMethod :: ErrorName
Clients
An active client session to a message bus. Clients may send or receive method calls, and listen for or emit signals.
Path/Interface storage
pathLens :: Applicative f => ObjectPath -> ((PathInfo -> f PathInfo) -> Maybe PathInfo -> f (Maybe PathInfo)) -> (PathInfo -> f PathInfo) -> PathInfo -> f PathInfo Source #
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.
getPropertyValue :: IsValue a => Client -> MethodCall -> IO (Either MethodError a) Source #
setProperty :: Client -> MethodCall -> Variant -> IO (Either MethodError MethodReturn) Source #
setPropertyValue :: IsValue a => Client -> MethodCall -> a -> IO (Maybe MethodError) Source #
getAllProperties :: Client -> MethodCall -> IO (Either MethodError MethodReturn) Source #
getAllPropertiesMap :: Client -> MethodCall -> IO (Either MethodError (Map String Variant)) Source #
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 -> IOReply
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.
Method | |
|
:: 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.
funTypes, apply
Instances
IsValue a => AutoMethod (IO (Either Reply a)) Source # | |
IsValue a => AutoMethod (IO a) Source # | |
IsValue a => AutoMethod (DBusR (Either Reply a)) Source # | |
IsValue a => AutoMethod (DBusR a) Source # | |
(IsValue a, AutoMethod fn) => AutoMethod (a -> fn) Source # | |
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.
autoMethodWithMsg :: AutoMethod fn => MemberName -> (MethodCall -> fn) -> Method Source #
Property | |
|
autoProperty :: forall v. IsValue v => MemberName -> Maybe (IO v) -> Maybe (v -> IO ()) -> Property Source #
readOnlyProperty :: IsValue v => MemberName -> IO v -> Property Source #
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
data SignalHandler Source #
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
formatMatchRule :: MatchRule -> String Source #
Convert a match rule into the textual format accepted by the bus.
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
Eq RequestNameFlag Source # | |
Defined in DBus.Client (==) :: RequestNameFlag -> RequestNameFlag -> Bool # (/=) :: RequestNameFlag -> RequestNameFlag -> Bool # | |
Show RequestNameFlag Source # | |
Defined in DBus.Client showsPrec :: Int -> RequestNameFlag -> ShowS # show :: RequestNameFlag -> String # showList :: [RequestNameFlag] -> ShowS # |
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 #
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, |
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
Eq RequestNameReply Source # | |
Defined in DBus.Client (==) :: RequestNameReply -> RequestNameReply -> Bool # (/=) :: RequestNameReply -> RequestNameReply -> Bool # | |
Show RequestNameReply Source # | |
Defined in DBus.Client showsPrec :: Int -> RequestNameReply -> ShowS # show :: RequestNameReply -> String # showList :: [RequestNameReply] -> ShowS # |
data ReleaseNameReply Source #
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
Eq ReleaseNameReply Source # | |
Defined in DBus.Client (==) :: ReleaseNameReply -> ReleaseNameReply -> Bool # (/=) :: ReleaseNameReply -> ReleaseNameReply -> Bool # | |
Show ReleaseNameReply Source # | |
Defined in DBus.Client showsPrec :: Int -> ReleaseNameReply -> ShowS # show :: ReleaseNameReply -> String # showList :: [ReleaseNameReply] -> ShowS # |
Client errors
data ClientError Source #
Instances
Eq ClientError Source # | |
Defined in DBus.Client (==) :: ClientError -> ClientError -> Bool # (/=) :: ClientError -> ClientError -> Bool # | |
Show ClientError Source # | |
Defined in DBus.Client showsPrec :: Int -> ClientError -> ShowS # show :: ClientError -> String # showList :: [ClientError] -> ShowS # | |
Exception ClientError Source # | |
Defined in DBus.Client |
clientError :: String -> ClientError Source #
clientErrorFatal :: ClientError -> Bool Source #
Advanced connection options
data ClientOptions t Source #
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.
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.