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

Safe HaskellNone
LanguageHaskell98

DBus

Contents

Description

Basic types, useful to every D-Bus application.

Authors of client applications should import DBus.Client, which provides an easy RPC-oriented interface to D-Bus methods and signals.

Synopsis

Messages

class Message a Source

Minimal complete definition

messageTypeCode, messageHeaderFields, messageBody

Method calls

data MethodCall Source

A method call is a request to run some procedure exported by the remote process. Procedures are identified by an (object_path, interface_name, method_name) tuple.

methodCall :: ObjectPath -> InterfaceName -> MemberName -> MethodCall Source

Construct a new MethodCall for the given object, interface, and method.

Use fields such as methodCallDestination and methodCallBody to populate a MethodCall.

{-# LANGUAGE OverloadedStrings #-}

methodCall "/" "org.example.Math" "Add"
    { methodCallDestination = Just "org.example.Calculator"
    , methodCallBody = [toVariant (1 :: Int32), toVariant (2 :: Int32)]
    }
 

methodCallPath :: MethodCall -> ObjectPath Source

The object path of the method call. Conceptually, object paths act like a procedural language's pointers. Each object referenced by a path is a collection of procedures.

methodCallInterface :: MethodCall -> Maybe InterfaceName Source

The interface of the method call. Each object may implement any number of interfaces. Each method is part of at least one interface.

In certain cases, this may be Nothing, but most users should set it to a value.

methodCallMember :: MethodCall -> MemberName Source

The method name of the method call. Method names are unique within an interface, but might not be unique within an object.

methodCallSender :: MethodCall -> Maybe BusName Source

The name of the application that sent this call.

Most users will just leave this empty, because the bus overwrites the sender for security reasons. Setting the sender manually is used for peer-peer connections.

Defaults to Nothing.

methodCallDestination :: MethodCall -> Maybe BusName Source

The name of the application to send the call to.

Most users should set this. If a message with no destination is sent to the bus, the bus will behave as if the destination was set to org.freedesktop.DBus. For peer-peer connections, the destination can be empty because there is only one peer.

Defaults to Nothing.

methodCallAutoStart :: MethodCall -> Bool Source

Set whether the bus should auto-start the remote

Defaults to True.

methodCallReplyExpected :: MethodCall -> Bool Source

Set whether a reply is expected. This can save network and cpu resources by inhibiting unnecessary replies.

Defaults to True.

methodCallBody :: MethodCall -> [Variant] Source

The arguments to the method call. See toVariant.

Defaults to [].

Method returns

data MethodReturn Source

A method return is a reply to a method call, indicating that the call succeeded.

methodReturn :: Serial -> MethodReturn Source

Construct a new MethodReturn, in reply to a method call with the given serial.

Use fields such as methodReturnBody to populate a MethodReturn.

methodReturnSerial :: MethodReturn -> Serial Source

The serial of the original method call. This lets the original caller match up this reply to the pending call.

methodReturnSender :: MethodReturn -> Maybe BusName Source

The name of the application that is returning from a call.

Most users will just leave this empty, because the bus overwrites the sender for security reasons. Setting the sender manually is used for peer-peer connections.

Defaults to Nothing.

methodReturnDestination :: MethodReturn -> Maybe BusName Source

The name of the application that initiated the call.

Most users should set this. If a message with no destination is sent to the bus, the bus will behave as if the destination was set to org.freedesktop.DBus. For peer-peer connections, the destination can be empty because there is only one peer.

Defaults to Nothing.

methodReturnBody :: MethodReturn -> [Variant] Source

Values returned from the method call. See toVariant.

Defaults to [].

Method errors

data MethodError Source

A method error is a reply to a method call, indicating that the call received an error and did not succeed.

methodError :: Serial -> ErrorName -> MethodError Source

Construct a new MethodError, in reply to a method call with the given serial.

Use fields such as methodErrorBody to populate a MethodError.

methodErrorName :: MethodError -> ErrorName Source

The name of the error type. Names are used so clients can handle certain classes of error differently from others.

methodErrorSerial :: MethodError -> Serial Source

The serial of the original method call. This lets the original caller match up this reply to the pending call.

methodErrorSender :: MethodError -> Maybe BusName Source

The name of the application that is returning from a call.

Most users will just leave this empty, because the bus overwrites the sender for security reasons. Setting the sender manually is used for peer-peer connections.

Defaults to Nothing.

methodErrorDestination :: MethodError -> Maybe BusName Source

The name of the application that initiated the call.

Most users should set this. If a message with no destination is sent to the bus, the bus will behave as if the destination was set to org.freedesktop.DBus. For peer-peer connections, the destination can be empty because there is only one peer.

Defaults to Nothing.

methodErrorBody :: MethodError -> [Variant] Source

Additional information about the error. By convention, if the error body contains any items, the first item should be a string describing the error.

methodErrorMessage :: MethodError -> String Source

Get a human-readable description of the error, by returning the first item in the error body if it's a string.

Signals

data Signal Source

Signals are broadcast by applications to notify other clients of some event.

signal :: ObjectPath -> InterfaceName -> MemberName -> Signal Source

Construct a new Signal for the given object, interface, and signal name.

Use fields such as signalBody to populate a Signal.

signalPath :: Signal -> ObjectPath Source

The path of the object that emitted this signal.

signalMember :: Signal -> MemberName Source

The name of this signal.

signalInterface :: Signal -> InterfaceName Source

The interface that this signal belongs to.

signalSender :: Signal -> Maybe BusName Source

The name of the application that emitted this signal.

Most users will just leave this empty, because the bus overwrites the sender for security reasons. Setting the sender manually is used for peer-peer connections.

Defaults to Nothing.

signalDestination :: Signal -> Maybe BusName Source

The name of the application to emit the signal to. If Nothing, the signal is sent to any application that has registered an appropriate match rule.

Defaults to Nothing.

signalBody :: Signal -> [Variant] Source

Additional information about the signal, such as the new value or the time.

Defaults to [].

Received messages

data ReceivedMessage Source

Not an actual message type, but a wrapper around messages received from the bus. Each value contains the message's Serial.

If casing against these constructors, always include a default case to handle messages of an unknown type. New message types may be added to the D-Bus specification, and applications should handle them gracefully by either ignoring or logging them.

receivedMessageSerial :: ReceivedMessage -> Serial Source

No matter what sort of message was received, get its serial.

receivedMessageSender :: ReceivedMessage -> Maybe BusName Source

No matter what sort of message was received, get its sender (if provided).

receivedMessageBody :: ReceivedMessage -> [Variant] Source

No matter what sort of message was received, get its body (if provided).

Variants

data Variant Source

Variants may contain any other built-in D-Bus value. Besides representing native VARIANT values, they allow type-safe storage and inspection of D-Bus collections.

class IsVariant a where Source

Instances

IsVariant Bool Source 
IsVariant Double Source 
IsVariant Int16 Source 
IsVariant Int32 Source 
IsVariant Int64 Source 
IsVariant Word8 Source 
IsVariant Word16 Source 
IsVariant Word32 Source 
IsVariant Word64 Source 
IsVariant String Source 
IsVariant Fd Source 
IsVariant ByteString Source 
IsVariant ByteString Source 
IsVariant Text Source 
IsVariant Text Source 
IsVariant Serial Source 
IsVariant Dictionary Source 
IsVariant Array Source 
IsVariant Structure Source 
IsVariant BusName Source 
IsVariant ErrorName Source 
IsVariant MemberName Source 
IsVariant InterfaceName Source 
IsVariant ObjectPath Source 
IsVariant Variant Source 
IsVariant Signature Source 
IsValue a => IsVariant [a] Source 
IsValue a => IsVariant (Vector a) Source 
(IsVariant a1, IsVariant a2) => IsVariant (a1, a2) Source 
(Ord k, IsAtom k, IsValue v) => IsVariant (Map k v) Source 
(IsVariant a1, IsVariant a2, IsVariant a3) => IsVariant (a1, a2, a3) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4) => IsVariant (a1, a2, a3, a4) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5) => IsVariant (a1, a2, a3, a4, a5) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6) => IsVariant (a1, a2, a3, a4, a5, a6) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7) => IsVariant (a1, a2, a3, a4, a5, a6, a7) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13, IsVariant a14) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) Source 
(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13, IsVariant a14, IsVariant a15) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) Source 

variantType :: Variant -> Type Source

Every variant is strongly-typed; that is, the type of its contained value is known at all times. This function retrieves that type, so that the correct cast can be used to retrieve the value.

class IsValue a => IsAtom a Source

Atomic types can be used as keys to dictionaries.

Users may not provide new instances of IsAtom because this could allow dictionaries to be created with invalid keys.

Minimal complete definition

toAtom, fromAtom

class IsVariant a => IsValue a Source

Value types can be used as items in containers, such as lists or dictionaries.

Users may not provide new instances of IsValue because this could allow containers to be created with items of heterogenous types.

Minimal complete definition

typeOf, toValue, fromValue

Instances

IsValue Bool Source 
IsValue Double Source 
IsValue Int16 Source 
IsValue Int32 Source 
IsValue Int64 Source 
IsValue Word8 Source 
IsValue Word16 Source 
IsValue Word32 Source 
IsValue Word64 Source 
IsValue String Source 
IsValue Fd Source 
IsValue ByteString Source 
IsValue ByteString Source 
IsValue Text Source 
IsValue Text Source 
IsValue ObjectPath Source 
IsValue Variant Source 
IsValue Signature Source 
IsValue a => IsValue [a] Source 
IsValue a => IsValue (Vector a) Source 
(IsValue a1, IsValue a2) => IsValue (a1, a2) Source 
(Ord k, IsAtom k, IsValue v) => IsValue (Map k v) Source 
(IsValue a1, IsValue a2, IsValue a3) => IsValue (a1, a2, a3) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4) => IsValue (a1, a2, a3, a4) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5) => IsValue (a1, a2, a3, a4, a5) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6) => IsValue (a1, a2, a3, a4, a5, a6) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7) => IsValue (a1, a2, a3, a4, a5, a6, a7) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13, IsValue a14) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) Source 
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13, IsValue a14, IsValue a15) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) Source 

typeOf :: IsValue a => a -> Type Source

Get the D-Bus type corresponding to the given Haskell value. The value may be undefined.

Signatures

data Signature Source

A signature is a list of D-Bus types, obeying some basic rules of validity.

The rules of signature validity are complex: see http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-signatures for details.

signature :: [Type] -> Maybe Signature Source

Convert a list of types into a valid signature.

Returns Nothing if the given types are not a valid signature.

signature_ :: [Type] -> Signature Source

Convert a list of types into a valid signature.

Throws an exception if the given types are not a valid signature.

signatureTypes :: Signature -> [Type] Source

Get the list of types in a signature. The inverse of signature.

formatSignature :: Signature -> String Source

Convert a signature into a signature string. The inverse of parseSignature.

parseSignature :: String -> Maybe Signature Source

Parse a signature string into a valid signature.

Returns Nothing if the given string is not a valid signature.

Object paths

data ObjectPath Source

Object paths are special strings, used to identify a particular object exported from a D-Bus application.

Object paths must begin with a slash, and consist of alphanumeric characters separated by slashes.

See http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-marshaling-object-path for details.

Names

Interface names

data InterfaceName Source

Interfaces are used to group a set of methods and signals within an exported object. Interface names consist of alphanumeric characters separated by periods.

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

Member names

data MemberName Source

Member names are used to identify a single method or signal within an interface. Method names consist of alphanumeric characters.

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

Error names

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.

Bus names

data BusName Source

Bus names are used to identify particular clients on the message bus. A bus name may be either unique or well-known, where unique names start with a colon. Bus names consist of alphanumeric characters separated by periods.

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

Non-native containers

Structures

data Structure Source

A D-Bus Structure is a container type similar to Haskell tuples, storing values of any type that is convertable to IsVariant. A Structure may contain up to 255 values.

Most users can use the IsVariant instance for tuples to extract the values of a structure. This type is for very large structures, which may be awkward to work with as tuples.

Arrays

data Array Source

A D-Bus Array is a container type similar to Haskell lists, storing zero or more values of a single D-Bus type.

Most users can use the IsVariant instance for lists or vectors to extract the values of an array. This type is for advanced use cases, where the user wants to convert array values to Haskell types that are not instances of IsValue.

Dictionaries

data Dictionary Source

A D-Bus Dictionary is a container type similar to Haskell maps, storing zero or more associations between keys and values.

Most users can use the IsVariant instance for maps to extract the values of a dictionary. This type is for advanced use cases, where the user wants to convert dictionary items to Haskell types that are not instances of IsValue.

Addresses

data Address Source

When a D-Bus server must listen for connections, or a client must connect to a server, the listening socket's configuration is specified with an address. An address contains the method, which determines the protocol and transport mechanism, and parameters, which provide additional method-specific information about the address.

address :: String -> Map String String -> Maybe Address Source

Try to convert a method string and parameter map to an Address.

Returns Nothing if the method or parameters are invalid.

formatAddress :: Address -> String Source

Convert an address to a string in the format expected by parseAddress.

formatAddresses :: [Address] -> String Source

Convert a list of addresses to a string in the format expected by parseAddresses.

parseAddress :: String -> Maybe Address Source

Try to parse a string containing one valid address.

An address string is in the format method:key1=val1,key2=val2. There are some limitations on the characters allowed within methods and parameters; see the D-Bus specification for full details.

parseAddresses :: String -> Maybe [Address] Source

Try to parse a string containing one or more valid addresses.

Addresses are separated by semicolons. See parseAddress for the format of addresses.

getSystemAddress :: IO (Maybe Address) Source

Returns the address in the environment variable DBUS_SYSTEM_BUS_ADDRESS, or unix:path=/var/run/dbus/system_bus_socket if DBUS_SYSTEM_BUS_ADDRESS is not set.

Returns Nothing if DBUS_SYSTEM_BUS_ADDRESS contains an invalid address.

getSessionAddress :: IO (Maybe Address) Source

Returns the address in the environment variable DBUS_SESSION_BUS_ADDRESS, which must be set.

Returns Nothing if DBUS_SYSTEM_BUS_ADDRESS is unset or contains an invalid address.

getStarterAddress :: IO (Maybe Address) Source

Returns the address in the environment variable DBUS_STARTER_ADDRESS, which must be set.

Returns Nothing if DBUS_STARTER_ADDRESS is unset or contains an invalid address.

Message marshaling

Marshal

marshal :: Message msg => Endianness -> Serial -> msg -> Either MarshalError ByteString Source

Convert a Message into a ByteString. Although unusual, it is possible for marshaling to fail; if this occurs, an error will be returned instead.

Unmarshal

unmarshal :: ByteString -> Either UnmarshalError ReceivedMessage Source

Parse a ByteString into a ReceivedMessage. The result can be inspected to see what type of message was parsed. Unknown message types can still be parsed successfully, as long as they otherwise conform to the D-Bus standard.

Message serials

data Serial Source

A value used to uniquely identify a particular message within a session. Serials are 32-bit unsigned integers, and eventually wrap.

firstSerial :: Serial Source

Get the first serial in the sequence.

nextSerial :: Serial -> Serial Source

Get the next serial in the sequence. This may wrap around to firstSerial.

D-Bus UUIDs

data UUID Source

A D-Bus UUID is 128 bits of data, usually randomly generated. They are used for identifying unique server instances to clients.

Older versions of the D-Bus spec also called these values GUIDs.

D-Bus UUIDs are not the same as the RFC-standardized UUIDs or GUIDs.

formatUUID :: UUID -> String Source

Format a D-Bus UUID as hex-encoded ASCII.

randomUUID :: IO UUID Source

Generate a random D-Bus UUID. This value is suitable for use in a randomly-allocated address, or as a listener's socket address "guid" parameter.