udbus-0.2.3: Small DBus implementation

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

Network.DBus.Actions

Contents

Description

 

Synopsis

Documentation

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

authenticate to DBus using a raw bytestring.

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

authenticate to DBus using a UID.

connectSession :: IO Handle Source #

connect to the dbus session bus define by the environment variable DBUS_SESSION_BUS_ADDRESS

connectSystem :: IO Handle Source #

connect to the dbus system bus

contextNew :: Handle -> IO DBusContext Source #

create a new DBus context from an handle

contextNewWith :: DBusTransport -> IO DBusContext Source #

create a new DBus context from a transport

busGetSession :: IO DBusContext Source #

create a new DBus context on session bus

busGetSystem :: IO DBusContext Source #

create a new DBus context on system bus

busGetNextSerial :: DBusContext -> IO Serial Source #

get the next serial usable, and increment the serial state.

busClose :: DBusContext -> IO () Source #

close this DBus context

messageSend :: DBusContext -> DBusMessage -> IO Serial Source #

send one message to the bus note that the serial of the message sent is allocated here.

messageSendWithSerial :: DBusContext -> Serial -> DBusMessage -> IO () Source #

send one message to the bus with a predefined serial number.

messageRecv :: DBusContext -> IO DBusMessage Source #

receive one single message from the bus it is not necessarily the reply from a previous sent message.

from Message module

type Serial = Word32 Source #

dbus serial number

read a message body

readBody :: DBusMessage -> Body Source #

read message's body using the signature field as reference

readBodyWith :: DBusMessage -> Signature -> Body Source #

read message's body with a defined signature

from Signature module

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 SignatureElem = Type Source #

Deprecated: use Type instead

type Signature = [Type] Source #

A list of signature element

serializeSignature :: Signature -> ByteString Source #

serialize a signature

from Type module

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 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 #