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

Safe HaskellNone
LanguageHaskell2010

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 :: Objects -> Handler Source

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

ignore :: Monad m => t -> t1 -> t2 -> m () Source

Ignore all incoming messages/signals

Signals

matchSignal :: Signal a -> MatchRule -> Bool Source

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

addMatch :: (MonadIO m, MonadThrow m) => MatchRule -> DBusConnection -> m () Source

Add a match rule

removeMatch :: (MonadIO m, MonadThrow m) => MatchRule -> DBusConnection -> m () Source

Remove a match rule

addSignalHandler :: MatchSignal -> MatchRule -> (SomeSignal -> IO ()) -> DBusConnection -> IO () Source

Add a match rule for the given signal specification and call function on all incoming matching signals

signalChan :: MatchSignal -> DBusConnection -> IO (TChan SomeSignal) Source

Add a match rule for the given signal specification and put all incoming signals into the TChan

handleSignal :: Representable a => SignalDescription (FlattenRepType (RepType a)) -> Maybe Text -> MatchRule -> (a -> IO ()) -> DBusConnection -> IO () Source

Add a match rule (computed from the SignalDescription) and install a handler that tries to convert the Signal's body and passes it to the callback

Representable Types

class SingI (RepType a) => Representable a where Source

Class of types that can be represented in the D-Bus type system.

The toRep and fromRep functions form a Prism and should follow the "obvious" laws:

  • fromRep (toRep x) == Just x
  • fmap toRep (fromRep x) =<= Just x

(where x =<= y iff x is Nothing or x == y)

All DBusValues represent themselves and instances for the following "canonical" pairs are provided

Haskell type => D-Bus type

  • WordX and IntX => UIntX and IntX respectively (for X in {16, 32, 64})
  • Bool => Boolean
  • Word8 => Byte
  • Double => Double
  • Text => String
  • ObjectPath => ObjectPath
  • DBusType => Signature
  • [a] => Array of a (for Representable a)
  • ByteString => Array of Byte
  • Tuples up to length 20 => Structs of equal length where each of the members is itself Representable
  • Map => Dict where the keys can be represented by a DBusSimpleType

An instance for String is impossible because it conflicts with the instance for lists (use Text instead)

Also note that no Representable instances are provided for Int, Integer and Float.

You can automatically derive an instance for your own Types with makeRepresentable

Associated Types

type RepType a :: DBusType Source

The DBusType that represents this type

Methods

toRep :: a -> DBusValue (RepType a) Source

Conversion from Haskell to D-Bus types

fromRep :: DBusValue (RepType a) -> Maybe a Source

Conversion from D-Bus to Haskell types.

type family FlattenRepType a :: [DBusType] Source

Equations

FlattenRepType TypeUnit = `[]` 
FlattenRepType (TypeStruct ts) = ts 
FlattenRepType (DBusSimpleType wild_1627489505) = Apply (Apply (:$) (Let1627489513TSym1 wild_1627489505)) `[]` 
FlattenRepType (TypeArray wild_1627489503) = Apply (Apply (:$) (Let1627489518TSym1 wild_1627489503)) `[]` 
FlattenRepType (TypeDict wild_1627489499 wild_1627489501) = Apply (Apply (:$) (Let1627489524TSym2 wild_1627489499 wild_1627489501)) `[]` 
FlattenRepType (TypeDictEntry wild_1627489495 wild_1627489497) = Apply (Apply (:$) (Let1627489534TSym2 wild_1627489495 wild_1627489497)) `[]` 
FlattenRepType TypeVariant = Apply (Apply (:$) Let1627489542TSym0) `[]` 

DBus specific types

DBus Values

data DBusValue :: DBusType -> * where Source

Instances

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 

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

Types that are not composite. These can be the keys of a Dict

Instances

Eq DBusSimpleType Source 
Data DBusSimpleType Source 
Read DBusSimpleType Source 
Show DBusSimpleType Source 
SingI DBusSimpleType TypeByte Source 
SingI DBusSimpleType TypeBoolean Source 
SingI DBusSimpleType TypeInt16 Source 
SingI DBusSimpleType TypeUInt16 Source 
SingI DBusSimpleType TypeInt32 Source 
SingI DBusSimpleType TypeUInt32 Source 
SingI DBusSimpleType TypeInt64 Source 
SingI DBusSimpleType TypeUInt64 Source 
SingI DBusSimpleType TypeDouble Source 
SingI DBusSimpleType TypeUnixFD Source 
SingI DBusSimpleType TypeString Source 
SingI DBusSimpleType TypeObjectPath Source 
SingI DBusSimpleType TypeSignature Source 
SEq DBusSimpleType (KProxy DBusSimpleType) Source 
PEq DBusSimpleType (KProxy DBusSimpleType) Source 
SDecide DBusSimpleType (KProxy DBusSimpleType) Source 
SingKind DBusSimpleType (KProxy DBusSimpleType) Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictEntrySym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) Let1627489534TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) Let1627489524TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) DBusSimpleTypeSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) Let1627489513TSym0 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictEntrySym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictSym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) Let1627489534TSym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) Let1627489524TSym1 Source 
data Sing DBusSimpleType where Source 
type (:/=) DBusSimpleType x y = Not ((:==) DBusSimpleType x y) 
type (:==) DBusSimpleType a0 b0 = Equals_1627483970 a0 b0 Source 
type Apply DBusType DBusSimpleType DBusSimpleTypeSym0 l0 = DBusSimpleTypeSym1 l0 Source 
type Apply DBusType DBusSimpleType Let1627489513TSym0 l0 = Let1627489513TSym1 l0 Source 
type DemoteRep DBusSimpleType (KProxy DBusSimpleType) = DBusSimpleType Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictEntrySym0 l0 = TypeDictEntrySym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictSym0 l0 = TypeDictSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType Let1627489534TSym0 l0 = Let1627489534TSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType Let1627489524TSym0 l0 = Let1627489524TSym1 l0 Source 

data DBusType Source

Instances

Eq DBusType Source 
Data DBusType Source 
Read DBusType Source 
Show DBusType Source 
SingI DBusType TypeVariant Source 
SingI DBusType TypeUnit Source 
SEq DBusType (KProxy DBusType) Source 
PEq DBusType (KProxy DBusType) Source 
SDecide DBusType (KProxy DBusType) Source 
SingI DBusSimpleType n0 => SingI DBusType (DBusSimpleType n) Source 
SingI DBusType n0 => SingI DBusType (TypeArray n) Source 
SingI [DBusType] n0 => SingI DBusType (TypeStruct n) Source 
SingKind DBusType (KProxy DBusType) Source 
(SingI DBusSimpleType n0, SingI DBusType n1) => SingI DBusType (TypeDict n n) Source 
(SingI DBusSimpleType n0, SingI DBusType n1) => SingI DBusType (TypeDictEntry n n) Source 
SuppressUnusedWarnings (TyFun [DBusType] DBusType -> *) TypeStructSym0 Source 
SuppressUnusedWarnings (TyFun DBusType [DBusType] -> *) FlattenRepTypeSym0 Source 
SuppressUnusedWarnings (TyFun DBusType DBusType -> *) TypeArraySym0 Source 
SuppressUnusedWarnings (TyFun DBusType DBusType -> *) Let1627489518TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictEntrySym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) Let1627489534TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) Let1627489524TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) DBusSimpleTypeSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) Let1627489513TSym0 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictEntrySym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictSym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) Let1627489534TSym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) Let1627489524TSym1 Source 
data Sing DBusType where Source 
type (:/=) DBusType x y = Not ((:==) DBusType x y) 
type (:==) DBusType a0 b0 = Equals_1627483977 a0 b0 Source 
type Apply DBusType DBusType TypeArraySym0 l0 = TypeArraySym1 l0 Source 
type Apply DBusType DBusType Let1627489518TSym0 l0 = Let1627489518TSym1 l0 Source 
type Apply DBusType DBusSimpleType DBusSimpleTypeSym0 l0 = DBusSimpleTypeSym1 l0 Source 
type Apply DBusType DBusSimpleType Let1627489513TSym0 l0 = Let1627489513TSym1 l0 Source 
type Apply DBusType DBusType (TypeDictEntrySym1 l1) l0 = TypeDictEntrySym2 l1 l0 Source 
type Apply DBusType DBusType (TypeDictSym1 l1) l0 = TypeDictSym2 l1 l0 Source 
type Apply DBusType DBusType (Let1627489534TSym1 l1) l0 = Let1627489534TSym2 l1 l0 Source 
type Apply DBusType DBusType (Let1627489524TSym1 l1) l0 = Let1627489524TSym2 l1 l0 Source 
type DemoteRep DBusType (KProxy DBusType) = DBusType Source 
type Apply DBusType [DBusType] TypeStructSym0 l0 = TypeStructSym1 l0 Source 
type Apply [DBusType] DBusType FlattenRepTypeSym0 l0 = FlattenRepTypeSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictEntrySym0 l0 = TypeDictEntrySym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictSym0 l0 = TypeDictSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType Let1627489534TSym0 l0 = Let1627489534TSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType Let1627489524TSym0 l0 = Let1627489524TSym1 l0 Source 

Objects

newtype Object Source

Constructors

Object 

Instances

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 ts) => MethodWrapper avs ts -> Text -> ArgumentDescription (ArgParity avs) -> ArgumentDescription (ArgParity ts) -> Method 

data MethodWrapper av rv where Source

Constructors

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

callMethod Source

Arguments

:: (Representable args, Representable ret) 
=> Text

Entity to send the message to

-> ObjectPath

Object

-> Text

Interface

-> Text

Member (method) to call

-> args

Arguments

-> [Flag]

Method call flags

-> DBusConnection

Connection to send the call over

-> IO (Either MethodError ret) 

Synchronously call a method.

This is the "cooked" version of callMethod''. It automatically converts arguments and returns values.

If the returned value's type doesn't match the expected type a MethodSignatureMissmatch is returned

You can pass in and extract multiple arguments and return values with types that are represented by DBus Structs (e.g. tuples). More specifically, multiple arguments/return values are handled in the following way:

  • If the method returns multiple values and the RepType of the expected return value is a struct it tries to match up the arguments with the struct fields
  • If the method returns a single struct and the RepType is a struct it will try to match up those two
  • If the RepType of the expected return value is not a struct it will only match if the method returned exactly one value and those two match up (as per normal)

This means that if the RepType of the expected return value is a struct it might be matched in two ways: Either by the method returning multiple values or the method returning a single struct. At the moment there is no way to exclude either

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.

This is the "raw" version of callMethod. It doesn't do argument conversion.

fromResponse :: Representable a => Either [SomeDBusValue] [SomeDBusValue] -> Either MethodError a Source

Try to convert the response to a method call top Haskell types

data SomeMethodDescription where Source

Constructors

SMD :: (SingI args, SingI rets) => MethodDescription args rets -> SomeMethodDescription 

Properties

data SomeProperty where Source

Constructors

SomeProperty :: forall t. SingI t => Property t -> SomeProperty 

mkProperty :: Representable a => ObjectPath -> Text -> Text -> Maybe (MethodHandlerT IO a) -> Maybe (a -> MethodHandlerT IO Bool) -> PropertyEmitsChangedSignal -> Property (RepType a) Source

Create a property from a getter and a setter. It will emit a PropertyChanged signal when the setter is called. To change this behaviour modify the propertyEmitsChangedSignal field

mkTVarProperty :: Representable a => ObjectPath -> Text -> Text -> PropertyAccess -> PropertyEmitsChangedSignal -> TVar a -> Property (RepType a) Source

Make a property out of a TVar. The property is considered changed on every outside set, no matter if the updated value is actually different from the old one

Introspection

Message Bus

Re-exports

def :: Default a => a

The default value for this type.