udbus-0.2.3: Small DBus implementation

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell98

Network.DBus

Contents

Description

 

Synopsis

handle connections to DBus

establish Source #

Arguments

:: IO DBusContext

function to create a new dbus context (busGetSystem or busGetSession)

-> (DBusContext -> IO ())

function to authenticate to dbus

-> IO DBusConnection 

Establish a new connection to dbus, using the two functions to first establish a new context, and second to authenticate to the bus. this will automatically create a mainloop thread.

disconnect :: DBusConnection -> IO () Source #

Close dbus socket and stop mainloop thread.

data DBusConnection Source #

opaque type representing a connection to DBus and a receiving dispatcher thread. maintain table to route message between handlers.

Types

data DBusError Source #

Constructors

DBusError 

Instances

Eq DBusError Source # 
Data DBusError Source # 

Methods

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

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

toConstr :: DBusError -> Constr #

dataTypeOf :: DBusError -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DBusError Source # 
Exception DBusError Source # 
DBusMessageable DBusError Source # 

data DBusValue Source #

DBus Types

Instances

Eq DBusValue Source # 
Data DBusValue Source # 

Methods

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

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

toConstr :: DBusValue -> Constr #

dataTypeOf :: DBusValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DBusValue Source # 
DBusTypeable DBusValue Source # 

class DBusTypeable a where Source #

Minimal complete definition

toSignature, toDBusValue, fromDBusValue

Instances

DBusTypeable Bool Source # 
DBusTypeable Double Source # 
DBusTypeable Int16 Source # 
DBusTypeable Int32 Source # 
DBusTypeable Int64 Source # 
DBusTypeable Word8 Source # 
DBusTypeable Word16 Source # 
DBusTypeable Word32 Source # 
DBusTypeable Word64 Source # 
DBusTypeable String Source # 
DBusTypeable ObjectPath Source # 
DBusTypeable DBusValue Source # 

newtype ObjectPath Source #

Constructors

ObjectPath 

Fields

Instances

Eq ObjectPath Source # 
Data ObjectPath Source # 

Methods

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

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

toConstr :: ObjectPath -> Constr #

dataTypeOf :: ObjectPath -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectPath Source # 
Show ObjectPath Source # 
IsString ObjectPath Source # 
DBusTypeable ObjectPath Source # 

newtype PackedString Source #

Constructors

PackedString 

Instances

Eq PackedString Source # 
Data PackedString Source # 

Methods

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

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

toConstr :: PackedString -> Constr #

dataTypeOf :: PackedString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PackedString Source # 
Show PackedString Source # 
IsString PackedString Source # 

data Type Source #

One possible signature element

Instances

Eq Type Source # 

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Data Type Source # 

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

type Signature = [Type] Source #

A list of signature element

type SignatureElem = Type Source #

Deprecated: use Type instead

newtype ErrorName Source #

Constructors

ErrorName 

Fields

Instances

Eq ErrorName Source # 
Data ErrorName Source # 

Methods

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

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

toConstr :: ErrorName -> Constr #

dataTypeOf :: ErrorName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ErrorName Source # 
Show ErrorName Source # 
IsString ErrorName Source # 

newtype Member Source #

Constructors

Member 

Fields

standard way to interact with dbus

addMatch :: DBusConnection -> DBusMatchRules -> IO () Source #

Add a match rules which will cause to receive message that aren't directed to this connection but match this rule.

main loop creation

runMainLoop :: DBusContext -> IO DBusConnection Source #

run a main DBus loop which will create a new dispatcher handshake on the bus and wait for message to dispatch

runMainLoopCatchall :: (DBusMessage -> IO ()) -> DBusContext -> IO DBusConnection Source #

similar to runMainLoop but also give the ability to specify a catch-all-message callback for any message that are not handled by specific function.

interact with the connection

call :: DBusConnection -> BusName -> DBusCall -> IO DBusReturn Source #

call a method on the DBus, and wait synchronously for the return value.

reply :: DBusMessageable a => DBusConnection -> a -> IO Serial Source #

Send an arbitrary DBusMessageable message on the bus, using a new serial value. the serial value allocated is returned to the caller.

PS: completely misnamed.

registerPath :: DBusConnection -> ObjectPath -> DispatchTable Callback -> IO () Source #

Deprecated: use registerCall

unregisterPath :: DBusConnection -> ObjectPath -> IO () Source #

Deprecated: use unregisterCall

registerCall :: DBusConnection -> ObjectPath -> DispatchTable Callback -> IO () Source #

Register a method handler table for a specific object path

unregisterCall :: DBusConnection -> ObjectPath -> IO () Source #

Unregister all method handlers for a specific object path

registerSignal :: DBusConnection -> ObjectPath -> DispatchTable Signalback -> IO () Source #

Register a signal handler table for a specific object path

unregisterSignal :: DBusConnection -> ObjectPath -> IO () Source #

Unregister all signals handler for a specific object path

Types to interact with the dispatcher

type Signalback = BusName -> Signature -> Body -> IO () Source #

type Callback = Serial -> Signature -> Body -> IO () Source #

create a new context on system or session bus

busGetSystem :: IO DBusContext Source #

create a new DBus context on system bus

busGetSession :: IO DBusContext Source #

create a new DBus context on session bus

authenticate methods available

authenticate :: DBusContext -> ByteString -> IO () Source #

authenticate to DBus using a raw bytestring.

authenticateUID :: DBusContext -> Int -> IO () Source #

authenticate to DBus using a UID.

authenticateWithRealUID :: DBusContext -> IO () Source #

use the real user UID to authenticate to DBus.