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

Safe HaskellNone
LanguageHaskell98

DBus

Contents

Synopsis

Connection management

data ConnectionType Source

Which Bus to connect to

Constructors

System

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

Session

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

Address String

The bus at the give addresss

connectBus Source

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 Bool Source

Check whether connection is alive

waitFor :: DBusConnection -> IO () Source

Wait until connection is closed

Message handling

objectRoot :: Object -> Handler Source

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

Signals

matchSignal :: MessageHeader -> MatchRule -> Bool Source

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

Representable Types

class Representable a where Source

Associated Types

type RepType a :: DBusType Source

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

data DBusValue :: DBusType -> * where Source

Instances

Eq (DBusValue t) 
SingI DBusType t => Show (DBusValue t) 
SingI DBusType t => IsMethod (IO (DBusValue t)) 
(IsMethod f, SingI DBusType t) => IsMethod (DBusValue t -> f) 
type ArgTypes (IO (DBusValue t)) = [] DBusType 
type ResultType (IO (DBusValue t)) = t 
type ArgTypes (DBusValue t -> f) = (:) DBusType t (ArgTypes f) 
type ResultType (DBusValue t -> f) = ResultType f 

data DBusStruct :: [DBusType] -> * where Source

Constructors

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

Instances

data SomeDBusValue where Source

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

data DBusSimpleType Source

Instances

Eq DBusSimpleType 
Data DBusSimpleType 
Read DBusSimpleType 
Show DBusSimpleType 
Typeable * DBusSimpleType 
SingI DBusSimpleType TypeSignature 
SingI DBusSimpleType TypeObjectPath 
SingI DBusSimpleType TypeString 
SingI DBusSimpleType TypeUnixFD 
SingI DBusSimpleType TypeDouble 
SingI DBusSimpleType TypeUInt64 
SingI DBusSimpleType TypeInt64 
SingI DBusSimpleType TypeUInt32 
SingI DBusSimpleType TypeInt32 
SingI DBusSimpleType TypeUInt16 
SingI DBusSimpleType TypeInt16 
SingI DBusSimpleType TypeBoolean 
SingI DBusSimpleType TypeByte 
SEq DBusSimpleType (KProxy DBusSimpleType) 
PEq DBusSimpleType (KProxy DBusSimpleType) 
SingKind DBusSimpleType (KProxy DBusSimpleType) 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictEntrySym0 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictSym0 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) DBusSimpleTypeSym0 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictEntrySym1 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictSym1 
data Sing DBusSimpleType where 
type (:==) DBusSimpleType a0 b0 = Equals_1627481895 a0 b0 
type Apply DBusType DBusSimpleType DBusSimpleTypeSym0 l0 = DBusSimpleTypeSym1 l0 
type DemoteRep DBusSimpleType (KProxy DBusSimpleType) = DBusSimpleType 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictEntrySym0 l0 = TypeDictEntrySym1 l0 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictSym0 l0 = TypeDictSym1 l0 

data DBusType Source

Instances

Eq DBusType 
Data DBusType 
Read DBusType 
Show DBusType 
Typeable * DBusType 
SingI DBusType TypeUnit 
SingI DBusType TypeVariant 
SEq DBusType (KProxy DBusType) 
PEq DBusType (KProxy DBusType) 
SingI [DBusType] n0 => SingI DBusType (TypeStruct n) 
SingI DBusType n0 => SingI DBusType (TypeArray n) 
SingI DBusSimpleType n0 => SingI DBusType (DBusSimpleType n) 
SingKind DBusType (KProxy DBusType) 
(SingI DBusSimpleType n0, SingI DBusType n1) => SingI DBusType (TypeDictEntry n n) 
(SingI DBusSimpleType n0, SingI DBusType n1) => SingI DBusType (TypeDict n n) 
SuppressUnusedWarnings (TyFun [DBusType] DBusType -> *) TypeStructSym0 
SuppressUnusedWarnings (TyFun DBusType DBusType -> *) TypeArraySym0 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictEntrySym0 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictSym0 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) DBusSimpleTypeSym0 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictEntrySym1 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictSym1 
data Sing DBusType where 
type (:==) DBusType a0 b0 = Equals_1627481902 a0 b0 
type Apply DBusType DBusType TypeArraySym0 l0 = TypeArraySym1 l0 
type Apply DBusType DBusSimpleType DBusSimpleTypeSym0 l0 = DBusSimpleTypeSym1 l0 
type Apply DBusType DBusType (TypeDictEntrySym1 l1) l0 = TypeDictEntrySym2 l1 l0 
type Apply DBusType DBusType (TypeDictSym1 l1) l0 = TypeDictSym2 l1 l0 
type DemoteRep DBusType (KProxy DBusType) = DBusType 
type Apply DBusType [DBusType] TypeStructSym0 l0 = TypeStructSym1 l0 
type ArgParity ([] DBusType) = Null 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictEntrySym0 l0 = TypeDictEntrySym1 l0 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictSym0 l0 = TypeDictSym1 l0 
type ArgParity ((:) DBusType x xs) = Arg (ArgParity xs) 

Objects

objectPath :: Text -> ObjectPath Source

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

Methods

data Method where Source

Constructors

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

Instances

data MethodWrapper av rv where Source

Constructors

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

data MethodDescription parity where Source

Constructors

(:->) :: Text -> MethodDescription n -> MethodDescription (Arg n) infixr 0 
Result :: Text -> MethodDescription Null 

callMethod Source

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