dbus-th-0.1.3.0: TemplateHaskell generator of DBus bindings

Safe HaskellNone
LanguageHaskell98

DBus.TH.EDSL

Synopsis

Documentation

module Data.Int

module Data.Word

data Client :: * #

An active client session to a message bus. Clients may send or receive method calls, and listen for or emit signals.

Instances

IsValue a => AutoMethod (DBusR (Either Reply a)) 

Methods

funTypes :: DBusR (Either Reply a) -> ([Type], [Type])

apply :: DBusR (Either Reply a) -> [Variant] -> DBusR Reply

IsValue a => AutoMethod (DBusR a) 

Methods

funTypes :: DBusR a -> ([Type], [Type])

apply :: DBusR a -> [Variant] -> DBusR Reply

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.

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.

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.

connectSession :: IO Client #

Connect to the bus specified in the environment variable DBUS_SESSION_BUS_ADDRESS, which must be set.

Throws a ClientError if DBUS_SESSION_BUS_ADDRESS is unset, contains an invalid address, or if connecting to the bus failed.

connectSystem :: IO Client #

Connect to the bus specified in the environment variable DBUS_SYSTEM_BUS_ADDRESS, or to unix:path=/var/run/dbus/system_bus_socket if DBUS_SYSTEM_BUS_ADDRESS is not set.

Throws a ClientError if DBUS_SYSTEM_BUS_ADDRESS contains an invalid address, or if connecting to the bus failed.

data Signature Source #

Function signature

Constructors

Return Name 
Name :-> Signature infixr 6 

Instances

Eq Signature Source # 
Data Signature Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Signature -> c Signature #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Signature #

toConstr :: Signature -> Constr #

dataTypeOf :: Signature -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Signature) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature) #

gmapT :: (forall b. Data b => b -> b) -> Signature -> Signature #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Signature -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Signature -> r #

gmapQ :: (forall d. Data d => d -> u) -> Signature -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Signature -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Signature -> m Signature #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Signature -> m Signature #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Signature -> m Signature #

Show Signature Source # 

signatureResult :: Signature -> Name Source #

Return type name for signature

data Function Source #

Function with DBus name and Haskell name

Constructors

Function 

Fields

Instances

Eq Function Source # 
Data Function Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Function -> c Function #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Function #

toConstr :: Function -> Constr #

dataTypeOf :: Function -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Function) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Function) #

gmapT :: (forall b. Data b => b -> b) -> Function -> Function #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Function -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Function -> r #

gmapQ :: (forall d. Data d => d -> u) -> Function -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Function -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Function -> m Function #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Function -> m Function #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Function -> m Function #

Show Function Source # 

(=::) :: String -> Signature -> Function infixr 5 Source #

Create a Function from it's name and Signature. Sets fnDBusName == fnName.

as :: Function -> String -> Function infixl 4 Source #

Set specific Haskell name for Function.

function Source #

Arguments

:: String

Bus name

-> String

Object name

-> String

Interface name

-> Maybe String

Prefix

-> Function

Function

-> Q [Dec] 

Generate binding for one method in specific DBus interface. If second argument is (Just prefix), then prefix will be added to the beginning of all DBus names and removed from all Haskell names.

interface Source #

Arguments

:: String

Bus name

-> String

Object name

-> String

Interface name

-> Maybe String

Prefix

-> [Function]

List of functions

-> Q [Dec] 

Generate bindings for methods in specific DBus interface. If second argument is (Just prefix), then prefix will be added to the beginning of all DBus names and removed from all Haskell names.

function' Source #

Arguments

:: String

Bus name

-> Maybe String

Just name - use fixed object name; Nothing - object name will be 2nd argument of generated function

-> String

Interface name

-> Maybe String

Prefix

-> Function

Function

-> Q [Dec] 

Generate binding for one method in specific DBus interface. If second argument is (Just prefix), then prefix will be added to the beginning of all DBus names and removed from all Haskell names.

interface' Source #

Arguments

:: String

Bus name

-> Maybe String

Just name - use fixed object name; Nothing - object name will be 2nd argument of generated functions

-> String

Interface name

-> Maybe String

Prefix

-> [Function]

List of functions

-> Q [Dec] 

Generate bindings for methods in specific DBus interface. If second argument is (Just prefix), then prefix will be added to the beginning of all DBus names and removed from all Haskell names.