Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- class Message a
- data MethodCall
- methodCall :: ObjectPath -> InterfaceName -> MemberName -> MethodCall
- methodCallPath :: MethodCall -> ObjectPath
- methodCallInterface :: MethodCall -> Maybe InterfaceName
- methodCallMember :: MethodCall -> MemberName
- methodCallSender :: MethodCall -> Maybe BusName
- methodCallDestination :: MethodCall -> Maybe BusName
- methodCallAutoStart :: MethodCall -> Bool
- methodCallReplyExpected :: MethodCall -> Bool
- methodCallBody :: MethodCall -> [Variant]
- data MethodReturn
- methodReturn :: Serial -> MethodReturn
- methodReturnSerial :: MethodReturn -> Serial
- methodReturnSender :: MethodReturn -> Maybe BusName
- methodReturnDestination :: MethodReturn -> Maybe BusName
- methodReturnBody :: MethodReturn -> [Variant]
- data MethodError
- methodError :: Serial -> ErrorName -> MethodError
- methodErrorName :: MethodError -> ErrorName
- methodErrorSerial :: MethodError -> Serial
- methodErrorSender :: MethodError -> Maybe BusName
- methodErrorDestination :: MethodError -> Maybe BusName
- methodErrorBody :: MethodError -> [Variant]
- methodErrorMessage :: MethodError -> String
- data Signal
- signal :: ObjectPath -> InterfaceName -> MemberName -> Signal
- signalPath :: Signal -> ObjectPath
- signalMember :: Signal -> MemberName
- signalInterface :: Signal -> InterfaceName
- signalSender :: Signal -> Maybe BusName
- signalDestination :: Signal -> Maybe BusName
- signalBody :: Signal -> [Variant]
- data ReceivedMessage
- receivedMessageSerial :: ReceivedMessage -> Serial
- receivedMessageSender :: ReceivedMessage -> Maybe BusName
- receivedMessageBody :: ReceivedMessage -> [Variant]
- data Variant
- class IsVariant a where
- toVariant :: a -> Variant
- fromVariant :: Variant -> Maybe a
- variantType :: Variant -> Type
- class IsValue a => IsAtom a
- class IsVariant a => IsValue a
- typeOf :: IsValue a => a -> Type
- typeOf' :: IsValue a => Proxy a -> Type
- data Signature
- data Type
- signature :: MonadThrow m => [Type] -> m Signature
- signature_ :: [Type] -> Signature
- signatureTypes :: Signature -> [Type]
- formatSignature :: Signature -> String
- parseSignature :: MonadThrow m => String -> m Signature
- data ObjectPath
- objectPath_ :: String -> ObjectPath
- formatObjectPath :: ObjectPath -> String
- parseObjectPath :: MonadThrow m => String -> m ObjectPath
- data InterfaceName
- interfaceName_ :: String -> InterfaceName
- formatInterfaceName :: InterfaceName -> String
- parseInterfaceName :: MonadThrow m => String -> m InterfaceName
- data MemberName
- memberName_ :: String -> MemberName
- formatMemberName :: MemberName -> String
- parseMemberName :: MonadThrow m => String -> m MemberName
- data ErrorName
- errorName_ :: String -> ErrorName
- formatErrorName :: ErrorName -> String
- parseErrorName :: MonadThrow m => String -> m ErrorName
- data BusName
- busName_ :: String -> BusName
- formatBusName :: BusName -> String
- parseBusName :: MonadThrow m => String -> m BusName
- data Structure
- structureItems :: Structure -> [Variant]
- data Array
- arrayItems :: Array -> [Variant]
- data Dictionary
- dictionaryItems :: Dictionary -> [(Variant, Variant)]
- data Address
- addressMethod :: Address -> String
- addressParameters :: Address -> Map String String
- address :: String -> Map String String -> Maybe Address
- formatAddress :: Address -> String
- formatAddresses :: [Address] -> String
- parseAddress :: String -> Maybe Address
- parseAddresses :: String -> Maybe [Address]
- getSystemAddress :: IO (Maybe Address)
- getSessionAddress :: IO (Maybe Address)
- getStarterAddress :: IO (Maybe Address)
- data Endianness
- marshal :: Message msg => Endianness -> Serial -> msg -> Either MarshalError ByteString
- data MarshalError
- marshalErrorMessage :: MarshalError -> String
- unmarshal :: ByteString -> Either UnmarshalError ReceivedMessage
- data UnmarshalError
- unmarshalErrorMessage :: UnmarshalError -> String
- data Serial
- serialValue :: Serial -> Word32
- firstSerial :: Serial
- nextSerial :: Serial -> Serial
- data UUID
- formatUUID :: UUID -> String
- randomUUID :: IO UUID
Messages
Instances
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.
Instances
Show MethodCall Source # | |
Defined in DBus.Internal.Message showsPrec :: Int -> MethodCall -> ShowS # show :: MethodCall -> String # showList :: [MethodCall] -> ShowS # | |
Message MethodCall Source # | |
Defined in DBus.Internal.Message messageTypeCode :: MethodCall -> Word8 Source # messageHeaderFields :: MethodCall -> [HeaderField] Source # messageBody :: MethodCall -> [Variant] Source # messageFlags :: MethodCall -> Word8 Source # | |
Eq MethodCall Source # | |
Defined in DBus.Internal.Message (==) :: MethodCall -> MethodCall -> Bool # (/=) :: MethodCall -> MethodCall -> Bool # |
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.
Instances
Show MethodReturn Source # | |
Defined in DBus.Internal.Message showsPrec :: Int -> MethodReturn -> ShowS # show :: MethodReturn -> String # showList :: [MethodReturn] -> ShowS # | |
Message MethodReturn Source # | |
Defined in DBus.Internal.Message messageTypeCode :: MethodReturn -> Word8 Source # messageHeaderFields :: MethodReturn -> [HeaderField] Source # messageBody :: MethodReturn -> [Variant] Source # messageFlags :: MethodReturn -> Word8 Source # | |
Eq MethodReturn Source # | |
Defined in DBus.Internal.Message (==) :: MethodReturn -> MethodReturn -> Bool # (/=) :: MethodReturn -> MethodReturn -> Bool # |
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.
Instances
Show MethodError Source # | |
Defined in DBus.Internal.Message showsPrec :: Int -> MethodError -> ShowS # show :: MethodError -> String # showList :: [MethodError] -> ShowS # | |
Message MethodError Source # | |
Defined in DBus.Internal.Message messageTypeCode :: MethodError -> Word8 Source # messageHeaderFields :: MethodError -> [HeaderField] Source # messageBody :: MethodError -> [Variant] Source # messageFlags :: MethodError -> Word8 Source # | |
Eq MethodError Source # | |
Defined in DBus.Internal.Message (==) :: MethodError -> MethodError -> Bool # (/=) :: MethodError -> MethodError -> Bool # |
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
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.
ReceivedMethodCall Serial MethodCall | |
ReceivedMethodReturn Serial MethodReturn | |
ReceivedMethodError Serial MethodError | |
ReceivedSignal Serial Signal |
Instances
Show ReceivedMessage Source # | |
Defined in DBus.Internal.Message showsPrec :: Int -> ReceivedMessage -> ShowS # show :: ReceivedMessage -> String # showList :: [ReceivedMessage] -> ShowS # | |
Eq ReceivedMessage Source # | |
Defined in DBus.Internal.Message (==) :: ReceivedMessage -> ReceivedMessage -> Bool # (/=) :: ReceivedMessage -> ReceivedMessage -> Bool # |
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
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
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.
Instances
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.
Instances
typeOf :: IsValue a => a -> Type Source #
Deprecated. Get the D-Bus type corresponding to the given Haskell value. The value
may be undefined
.
typeOf' :: IsValue a => Proxy a -> Type Source #
Get the D-Bus type corresponding to the given Haskell type a
.
Signatures
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.
Instances
IsString Signature Source # | |
Defined in DBus.Internal.Types fromString :: String -> Signature # | |
Show Signature Source # | |
IsAtom Signature Source # | |
IsValue Signature Source # | |
IsVariant Signature Source # | |
NFData Signature Source # | |
Defined in DBus.Internal.Types | |
Eq Signature Source # | |
Ord Signature Source # | |
Defined in DBus.Internal.Types |
Instances
signature :: MonadThrow m => [Type] -> m Signature Source #
Convert a list of types into a valid signature.
Throws 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 :: MonadThrow m => String -> m Signature Source #
Parse a signature string into a valid signature.
Throws 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.
Instances
objectPath_ :: String -> ObjectPath Source #
formatObjectPath :: ObjectPath -> String Source #
parseObjectPath :: MonadThrow m => String -> m ObjectPath Source #
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.
Instances
interfaceName_ :: String -> InterfaceName Source #
parseInterfaceName :: MonadThrow m => String -> m InterfaceName Source #
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.
Instances
memberName_ :: String -> MemberName Source #
formatMemberName :: MemberName -> String Source #
parseMemberName :: MonadThrow m => String -> m MemberName Source #
Error names
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.
errorName_ :: String -> ErrorName Source #
formatErrorName :: ErrorName -> String Source #
parseErrorName :: MonadThrow m => String -> m ErrorName Source #
Bus names
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.
formatBusName :: BusName -> String Source #
parseBusName :: MonadThrow m => String -> m BusName Source #
Non-native containers
Structures
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.
structureItems :: Structure -> [Variant] Source #
Arrays
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
.
arrayItems :: Array -> [Variant] Source #
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
.
Instances
Show Dictionary Source # | |
Defined in DBus.Internal.Types showsPrec :: Int -> Dictionary -> ShowS # show :: Dictionary -> String # showList :: [Dictionary] -> ShowS # | |
IsVariant Dictionary Source # | |
Defined in DBus.Internal.Types toVariant :: Dictionary -> Variant Source # fromVariant :: Variant -> Maybe Dictionary Source # | |
Eq Dictionary Source # | |
Defined in DBus.Internal.Types (==) :: Dictionary -> Dictionary -> Bool # (/=) :: Dictionary -> Dictionary -> Bool # |
dictionaryItems :: Dictionary -> [(Variant, Variant)] Source #
Addresses
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.
addressMethod :: Address -> String Source #
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 first address in the environment variable
DBUS_SESSION_BUS_ADDRESS
, which must be set.
Returns Nothing
if DBUS_SYSTEM_BUS_ADDRESS
contains an invalid address
or DBUS_SESSION_BUS_ADDRESS
is unset XDG_RUNTIME_DIR
doesn't have /bus
.
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
data Endianness Source #
Instances
Show Endianness Source # | |
Defined in DBus.Internal.Wire showsPrec :: Int -> Endianness -> ShowS # show :: Endianness -> String # showList :: [Endianness] -> ShowS # | |
Eq Endianness Source # | |
Defined in DBus.Internal.Wire (==) :: Endianness -> Endianness -> Bool # (/=) :: Endianness -> Endianness -> Bool # |
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.
data MarshalError Source #
Instances
Show MarshalError Source # | |
Defined in DBus.Internal.Wire showsPrec :: Int -> MarshalError -> ShowS # show :: MarshalError -> String # showList :: [MarshalError] -> ShowS # | |
Eq MarshalError Source # | |
Defined in DBus.Internal.Wire (==) :: MarshalError -> MarshalError -> Bool # (/=) :: MarshalError -> MarshalError -> Bool # |
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.
data UnmarshalError Source #
Instances
Show UnmarshalError Source # | |
Defined in DBus.Internal.Wire showsPrec :: Int -> UnmarshalError -> ShowS # show :: UnmarshalError -> String # showList :: [UnmarshalError] -> ShowS # | |
Eq UnmarshalError Source # | |
Defined in DBus.Internal.Wire (==) :: UnmarshalError -> UnmarshalError -> Bool # (/=) :: UnmarshalError -> UnmarshalError -> Bool # |
Message serials
A value used to uniquely identify a particular message within a session. Serials are 32-bit unsigned integers, and eventually wrap.
serialValue :: Serial -> Word32 Source #
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
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.