d-bus-0.0.1.1: Permissively licensed D-Bus client library

Safe HaskellNone

DBus

Contents

Synopsis

Connection management

data ConnectionType Source

Which Bus to connect to

Constructors

Session

The well-known system bus. First the environmental variable DBUS_SESSION_BUS_ADDRESS is checked and if it doesn't exist the address unix:path=\var/run/dbus/system_bus_socket/ is used

System

The well-known system bus. Refers to the address stored in the environmental variable DBUS_SESSION_BUS_ADDRESS

Address String

The bus at the give addresss

connectBusSource

Arguments

:: ConnectionType

Bus to connect to

-> MethodCallHandler

Handler for incoming method calls

-> SignalHandler

Handler for incoming signals

-> IO DBusConnection 

Create a new connection to a message bus

checkAlive :: DBusConnection -> IO BoolSource

Check whether connection is alive

waitFor :: DBusConnection -> IO ()Source

Wait until connection is closed

Message handling

objectRoot :: Object -> HandlerSource

Create a message handler that dispatches matches to the methods in a root object

Signals

matchSignal :: MessageHeader -> MatchRule -> BoolSource

Match a Signal against a rule. The argN, argNPath and arg0namespace parameter are ignored at the moment

Representable Types

class Representable a whereSource

Associated Types

type RepType a :: DBusTypeSource

Instances

Representable Bool 
Representable Double 
Representable Int16 
Representable Int32 
Representable Int64 
Representable Word8 
Representable Word16 
Representable Word32 
Representable Word64 
Representable () 
Representable ByteString 
Representable Text 
Representable Signature 
Representable ObjectPath 
Representable Endian 
Representable HeaderField 
Representable HeaderFields 
Representable Flags 
Representable MessageType 
Representable MessageHeader 
(Representable a, SingI DBusType (RepType a)) => Representable [a] 
(Representable l, Representable r, SingI DBusType (RepType l), SingI DBusType (RepType r)) => Representable (Either l r) 
(Representable a, Representable b) => Representable (a, b) 
(Ord k, Representable k, ~ DBusType (RepType k) (DBusSimpleType r), Representable v) => Representable (Map k v) 
(Representable a, Representable b, Representable c) => Representable (a, b, c) 
(Representable a, Representable b, Representable c, Representable d) => Representable (a, b, c, d) 
(Representable a, Representable b, Representable c, Representable d, Representable e) => Representable (a, b, c, d, e) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f) => Representable (a, b, c, d, e, f) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g) => Representable (a, b, c, d, e, f, g) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h) => Representable (a, b, c, d, e, f, g, h) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i) => Representable (a, b, c, d, e, f, g, h, i) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j) => Representable (a, b, c, d, e, f, g, h, i, j) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k) => Representable (a, b, c, d, e, f, g, h, i, j, k) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l) => Representable (a, b, c, d, e, f, g, h, i, j, k, l) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p, Representable q) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p, Representable q, Representable r) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p, Representable q, Representable r, Representable s) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p, Representable q, Representable r, Representable s, Representable t) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 

DBus specific types

DBus Values

castDBV :: (SingI s, SingI t) => DBusValue s -> Maybe (DBusValue t)Source

data DBusStruct whereSource

Constructors

StructSingleton :: DBusValue a -> DBusStruct `[a]` 
StructCons :: DBusValue a -> DBusStruct as -> DBusStruct (a : as) 

Instances

Eq (DBusStruct t) 
SingI [DBusType] a => Show (DBusStruct a) 

data SomeDBusValue whereSource

Constructors

DBV :: SingI t => DBusValue t -> SomeDBusValue 

Instances

fromVariant :: SingI t => DBusValue TypeVariant -> Maybe (DBusValue t)Source

Extract a DBusValue from a Variant iff the type matches or return nothing

Signature

typeOf :: SingI t => DBusValue t -> DBusTypeSource

ObjectPath

objectPath :: Text -> ObjectPathSource

Parse an object path. Contrary to the standard, empty path parts are ignored

Methods

data Method whereSource

Constructors

Method :: (SingI avs, SingI t) => MethodWrapper avs t -> Text -> MethodDescription (ArgParity avs) -> Method 

Instances

data MethodWrapper av rv whereSource

Constructors

MReturn :: SingI t => IO (DBusValue t) -> MethodWrapper `[]` t 
MAsk :: SingI t => (DBusValue t -> MethodWrapper avs rv) -> MethodWrapper (t : avs) rv 

callMethodSource

Arguments

:: Text

Entity to send the message to

-> ObjectPath

Object

-> Text

Interface

-> Text

Member (method) name

-> [SomeDBusValue]

Arguments

-> [Flag]

Method call flags

-> DBusConnection

Connection to send the call over

-> IO (STM (Either [SomeDBusValue] SomeDBusValue)) 

Asychronously call a method. Returns an STM action that waits for the returned value.

callMethod'Source

Arguments

:: (SingI (RepType a), Representable a, MonadThrow m, MonadIO m) 
=> Text

Entity to send the message to

-> ObjectPath

Object

-> Text

Interface

-> Text

Member (method) to call

-> [SomeDBusValue]

Arguments

-> [Flag]

Method call flags

-> DBusConnection

Connection to send the call over

-> m a 

Synchronously call a method. Returned errors are thrown as MethodErrors. If the returned value's type doesn't match the expected type a MethodSignatureMissmatch is thrown.

Introspection

Message Bus