dbus-0.10.12: 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

Method calls

data MethodCall #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

Set whether the bus should auto-start the remote

Defaults to True.

methodCallReplyExpected :: MethodCall -> Bool #

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

Defaults to True.

methodCallBody :: MethodCall -> [Variant] #

The arguments to the method call. See toVariant.

Defaults to [].

Method returns

data MethodReturn #

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

methodReturn :: Serial -> MethodReturn #

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 #

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

methodReturnSender :: MethodReturn -> Maybe BusName #

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 #

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] #

Values returned from the method call. See toVariant.

Defaults to [].

Method errors

data MethodError #

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 #

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 #

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

methodErrorSerial :: MethodError -> Serial #

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

methodErrorSender :: MethodError -> Maybe BusName #

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 #

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] #

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 #

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 #

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

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

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

Use fields such as signalBody to populate a Signal.

signalPath :: Signal -> ObjectPath #

The path of the object that emitted this signal.

signalMember :: Signal -> MemberName #

The name of this signal.

signalInterface :: Signal -> InterfaceName #

The interface that this signal belongs to.

signalSender :: Signal -> Maybe BusName #

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 #

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] #

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

Defaults to [].

Received messages

data ReceivedMessage #

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 #

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

receivedMessageSender :: ReceivedMessage -> Maybe BusName #

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

receivedMessageBody :: ReceivedMessage -> [Variant] #

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

Variants

data Variant #

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 #

Minimal complete definition

toVariant, fromVariant

Methods

toVariant :: a -> Variant #

fromVariant :: Variant -> Maybe a #

Instances

IsVariant Bool # 
IsVariant Double # 
IsVariant Int16 # 
IsVariant Int32 # 
IsVariant Int64 # 
IsVariant Word8 # 
IsVariant Word16 # 
IsVariant Word32 # 
IsVariant Word64 # 
IsVariant Fd # 
IsVariant String # 
IsVariant ByteString # 
IsVariant ByteString # 
IsVariant Text # 

Methods

toVariant :: Text -> Variant #

fromVariant :: Variant -> Maybe Text #

IsVariant Text # 

Methods

toVariant :: Text -> Variant #

fromVariant :: Variant -> Maybe Text #

IsVariant Serial # 
IsVariant Dictionary # 
IsVariant Array # 
IsVariant Structure # 
IsVariant BusName # 
IsVariant ErrorName # 
IsVariant MemberName # 
IsVariant InterfaceName # 
IsVariant ObjectPath # 
IsVariant Variant # 
IsVariant Signature # 
IsValue a => IsVariant [a] # 

Methods

toVariant :: [a] -> Variant #

fromVariant :: Variant -> Maybe [a] #

IsValue a => IsVariant (Vector a) # 

Methods

toVariant :: Vector a -> Variant #

fromVariant :: Variant -> Maybe (Vector a) #

(IsVariant a1, IsVariant a2) => IsVariant (a1, a2) # 

Methods

toVariant :: (a1, a2) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2) #

(Ord k, IsAtom k, IsValue v) => IsVariant (Map k v) # 

Methods

toVariant :: Map k v -> Variant #

fromVariant :: Variant -> Maybe (Map k v) #

(IsVariant a1, IsVariant a2, IsVariant a3) => IsVariant (a1, a2, a3) # 

Methods

toVariant :: (a1, a2, a3) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3) #

(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4) => IsVariant (a1, a2, a3, a4) # 

Methods

toVariant :: (a1, a2, a3, a4) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4) #

(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5) => IsVariant (a1, a2, a3, a4, a5) # 

Methods

toVariant :: (a1, a2, a3, a4, a5) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5) #

(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6) => IsVariant (a1, a2, a3, a4, a5, a6) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6) #

(IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7) => IsVariant (a1, a2, a3, a4, a5, a6, a7) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7) #

(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) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7, a8) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8) #

(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) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9) #

(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) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) #

(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) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) #

(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) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) #

(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) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) #

(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) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) #

(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) # 

Methods

toVariant :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) -> Variant #

fromVariant :: Variant -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) #

variantType :: Variant -> Type #

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 #

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

Instances

IsAtom Bool # 

Methods

toAtom :: Bool -> Atom

fromAtom :: Atom -> Maybe Bool

IsAtom Double # 

Methods

toAtom :: Double -> Atom

fromAtom :: Atom -> Maybe Double

IsAtom Int16 # 

Methods

toAtom :: Int16 -> Atom

fromAtom :: Atom -> Maybe Int16

IsAtom Int32 # 

Methods

toAtom :: Int32 -> Atom

fromAtom :: Atom -> Maybe Int32

IsAtom Int64 # 

Methods

toAtom :: Int64 -> Atom

fromAtom :: Atom -> Maybe Int64

IsAtom Word8 # 

Methods

toAtom :: Word8 -> Atom

fromAtom :: Atom -> Maybe Word8

IsAtom Word16 # 

Methods

toAtom :: Word16 -> Atom

fromAtom :: Atom -> Maybe Word16

IsAtom Word32 # 

Methods

toAtom :: Word32 -> Atom

fromAtom :: Atom -> Maybe Word32

IsAtom Word64 # 

Methods

toAtom :: Word64 -> Atom

fromAtom :: Atom -> Maybe Word64

IsAtom Fd # 

Methods

toAtom :: Fd -> Atom

fromAtom :: Atom -> Maybe Fd

IsAtom String # 

Methods

toAtom :: String -> Atom

fromAtom :: Atom -> Maybe String

IsAtom Text # 

Methods

toAtom :: Text -> Atom

fromAtom :: Atom -> Maybe Text

IsAtom Text # 

Methods

toAtom :: Text -> Atom

fromAtom :: Atom -> Maybe Text

IsAtom ObjectPath # 

Methods

toAtom :: ObjectPath -> Atom

fromAtom :: Atom -> Maybe ObjectPath

IsAtom Signature # 

Methods

toAtom :: Signature -> Atom

fromAtom :: Atom -> Maybe Signature

class IsVariant a => IsValue a #

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 # 

Methods

typeOf :: Bool -> Type

toValue :: Bool -> Value

fromValue :: Value -> Maybe Bool

IsValue Double # 

Methods

typeOf :: Double -> Type

toValue :: Double -> Value

fromValue :: Value -> Maybe Double

IsValue Int16 # 

Methods

typeOf :: Int16 -> Type

toValue :: Int16 -> Value

fromValue :: Value -> Maybe Int16

IsValue Int32 # 

Methods

typeOf :: Int32 -> Type

toValue :: Int32 -> Value

fromValue :: Value -> Maybe Int32

IsValue Int64 # 

Methods

typeOf :: Int64 -> Type

toValue :: Int64 -> Value

fromValue :: Value -> Maybe Int64

IsValue Word8 # 

Methods

typeOf :: Word8 -> Type

toValue :: Word8 -> Value

fromValue :: Value -> Maybe Word8

IsValue Word16 # 

Methods

typeOf :: Word16 -> Type

toValue :: Word16 -> Value

fromValue :: Value -> Maybe Word16

IsValue Word32 # 

Methods

typeOf :: Word32 -> Type

toValue :: Word32 -> Value

fromValue :: Value -> Maybe Word32

IsValue Word64 # 

Methods

typeOf :: Word64 -> Type

toValue :: Word64 -> Value

fromValue :: Value -> Maybe Word64

IsValue Fd # 

Methods

typeOf :: Fd -> Type

toValue :: Fd -> Value

fromValue :: Value -> Maybe Fd

IsValue String # 

Methods

typeOf :: String -> Type

toValue :: String -> Value

fromValue :: Value -> Maybe String

IsValue ByteString # 

Methods

typeOf :: ByteString -> Type

toValue :: ByteString -> Value

fromValue :: Value -> Maybe ByteString

IsValue ByteString # 

Methods

typeOf :: ByteString -> Type

toValue :: ByteString -> Value

fromValue :: Value -> Maybe ByteString

IsValue Text # 

Methods

typeOf :: Text -> Type

toValue :: Text -> Value

fromValue :: Value -> Maybe Text

IsValue Text # 

Methods

typeOf :: Text -> Type

toValue :: Text -> Value

fromValue :: Value -> Maybe Text

IsValue ObjectPath # 

Methods

typeOf :: ObjectPath -> Type

toValue :: ObjectPath -> Value

fromValue :: Value -> Maybe ObjectPath

IsValue Variant # 

Methods

typeOf :: Variant -> Type

toValue :: Variant -> Value

fromValue :: Value -> Maybe Variant

IsValue Signature # 

Methods

typeOf :: Signature -> Type

toValue :: Signature -> Value

fromValue :: Value -> Maybe Signature

IsValue a => IsValue [a] # 

Methods

typeOf :: [a] -> Type

toValue :: [a] -> Value

fromValue :: Value -> Maybe [a]

IsValue a => IsValue (Vector a) # 

Methods

typeOf :: Vector a -> Type

toValue :: Vector a -> Value

fromValue :: Value -> Maybe (Vector a)

(IsValue a1, IsValue a2) => IsValue (a1, a2) # 

Methods

typeOf :: (a1, a2) -> Type

toValue :: (a1, a2) -> Value

fromValue :: Value -> Maybe (a1, a2)

(Ord k, IsAtom k, IsValue v) => IsValue (Map k v) # 

Methods

typeOf :: Map k v -> Type

toValue :: Map k v -> Value

fromValue :: Value -> Maybe (Map k v)

(IsValue a1, IsValue a2, IsValue a3) => IsValue (a1, a2, a3) # 

Methods

typeOf :: (a1, a2, a3) -> Type

toValue :: (a1, a2, a3) -> Value

fromValue :: Value -> Maybe (a1, a2, a3)

(IsValue a1, IsValue a2, IsValue a3, IsValue a4) => IsValue (a1, a2, a3, a4) # 

Methods

typeOf :: (a1, a2, a3, a4) -> Type

toValue :: (a1, a2, a3, a4) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4)

(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5) => IsValue (a1, a2, a3, a4, a5) # 

Methods

typeOf :: (a1, a2, a3, a4, a5) -> Type

toValue :: (a1, a2, a3, a4, a5) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5)

(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6) => IsValue (a1, a2, a3, a4, a5, a6) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6) -> Type

toValue :: (a1, a2, a3, a4, a5, a6) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6)

(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7) => IsValue (a1, a2, a3, a4, a5, a6, a7) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7)

(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) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7, a8) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7, a8) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8)

(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) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9)

(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) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10)

(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) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11)

(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) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12)

(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) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13)

(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) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14)

(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) # 

Methods

typeOf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) -> Type

toValue :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) -> Value

fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15)

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

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

Signatures

data Signature #

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 #

Convert a list of types into a valid signature.

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

signature_ :: [Type] -> Signature #

Convert a list of types into a valid signature.

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

signatureTypes :: Signature -> [Type] #

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

formatSignature :: Signature -> String #

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

parseSignature :: String -> Maybe Signature #

Parse a signature string into a valid signature.

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

Object paths

data ObjectPath #

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

Member names

Error names

data ErrorName #

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 #

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 #

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 #

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.

Instances

Dictionaries

data Dictionary #

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 #

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.

Instances

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

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

Returns Nothing if the method or parameters are invalid.

formatAddress :: Address -> String #

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

formatAddresses :: [Address] -> String #

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

parseAddress :: String -> Maybe Address #

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] #

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) #

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) #

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) #

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 #

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 #

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 #

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

firstSerial :: Serial #

Get the first serial in the sequence.

nextSerial :: Serial -> Serial #

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

D-Bus UUIDs

data UUID #

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.

Instances

Eq UUID # 

Methods

(==) :: UUID -> UUID -> Bool #

(/=) :: UUID -> UUID -> Bool #

Ord UUID # 

Methods

compare :: UUID -> UUID -> Ordering #

(<) :: UUID -> UUID -> Bool #

(<=) :: UUID -> UUID -> Bool #

(>) :: UUID -> UUID -> Bool #

(>=) :: UUID -> UUID -> Bool #

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Show UUID # 

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

formatUUID :: UUID -> String #

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

randomUUID :: IO UUID #

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.