Re: [Haskell-cafe] ANNOUNCE: dbus-core 0.5 and dbus-client 0.1

The purpose behind the weird signature there is so that the
computations in DBus.Bus can be passed directly to mkClient. Because
of the design of dbus-client, you probably don't want to keep the
connection around separately.
-----
client <- mkClient getSessionBus
-----
Here's a quick-and-dirty skeleton for sending notifications:
-----
{-# LANGUAGE OverloadedStrings #-}
import DBus.Bus
import DBus.Client
import DBus.Types
-- Definition of notification object / interface
notifications = Proxy (RemoteObject
(mkBusName' "org.freedesktop.Notifications")
(mkObjectPath' "/org/freedesktop/Notifications"))
(mkInterfaceName' "org.freedesktop.Notifications")
-- Callbacks; in real systems, these would probably be more complex
onError x = putStrLn ("ERROR\n\n" ++ show x ++ "\n\n")
onReturn x = putStrLn ("RETURN\n\n" ++ show x ++ "\n\n")
-- A real library might accept additional parameters
-- by the way: signature of Notify() is "susssasa{sv}i"
notify c = call' params onError onReturn where
params = [{- build parameters for your library here -}]
call' = call client notifications (mkMemberName' "Notify") []
main = do
client <- mkClient getSessionBus
notify client
{- main loop / mvar / whatever your library uses -}
-----
On Tue, Nov 3, 2009 at 14:07, Max Rabkin
Hi John
I'm trying to implement a pure Haskell library for notifications (like libnotify). Unfortunately I don't know my way around dbus too well.
Is there a reason for
mkClient :: IO (Connection, BusName) -> IO Client
instead of
mkClient :: Connection -> IO Client
?
mkClient simply discards the bus name, so in the event that one doesn't have a bus name, one must create a fake one. Also, it executes the IO action right away, so there is no need for it to take an IO argument. All in all, this means I must write
getClient = mkClient (flip (,) undefined <$> getSessionConnection)
instead of
getClient = mkClient =<< getSessionConnection.
Perhaps you have a good reason for it?
Regards, Max
On Fri, Oct 30, 2009 at 11:44 PM, John Millikin
wrote: These are pure-Haskell client libraries for using the D-Bus protocol. D-Bus is heavily used for inter-application IPC on Free and open-source desktop platforms, such as Linux, OpenSolaris, and FreeBSD. These libraries allow applications written in Haskell to inter-operate with other components of recent GNOME, KDE, and XFCE desktops.
This is the first "real" release of these libraries; dbus-core has been published on Hackage for some time, but mostly just to make sure I got the Cabal bits right. I feel they are now stable / featureful enough for public use.
Both are available on Hackage:
http://hackage.haskell.org/package/dbus-core http://hackage.haskell.org/package/dbus-client
---------
"dbus-core" is an implementation of the D-Bus protocol, specifically the parts relevant to clients. Eventually, it will probably grow some functions useful for implementing a message bus as well. It includes type mapping / conversion, an implementation of the wire format (marshaling / unmarshaling), data types for the currently defined message types (METHOD_CALL, METHOD_RETURN, ERROR, and SIGNAL) and a basic parser / generator for introspection documents. It is roughly equivalent in purpose to libdbus.
By itself, a protocol implementation is somewhat cumbersome to use, so "dbus-client" is a high-level wrapper. It provides some abstractions like remote object proxies, exported object trees, synchronous method calls, signal reception, and name reservation. Messages are received and processed in separate IO threads, allowing asynchronous method call and signal handling.
The purpose between splitting the library into two packages is stability; "dbus-core", ideally, will change only rarely -- performance improvements, new message / data types, etc. It provides a base level of functionality which more specialised libraries may use. "dbus-client" is an example of what such a library could look like, though for now it's not very Haskell-y (IO everywhere, exceptions, explicit locking). By separating the protocol from the client libs, alternative client libs can safely depend on the protocol implementation.
---------
To see a sample of the library working, there's a clone of the "dbus-monitor" utility in
. Documentation is currently a bit lacking, so for now, the best documentation is the PDF of the source code itself, and the (rather barren) Haddock output: https://dl.getdropbox.com/u/1947532/dbus-core_0.5.pdf https://dl.getdropbox.com/u/1947532/dbus-core_0.5/index.html
https://dl.getdropbox.com/u/1947532/dbus-client_0.1.pdf https://dl.getdropbox.com/u/1947532/dbus-client_0.1/index.html
Once more people have used it without any major API issues, I'll write up a manual and populate the Haddock entries.
Please respond with any feedback, difficulties, or suggestions. I'm particularly interested in ways to improve the public API, since I would rather make any breaking changes *before* anything big depends on these libraries. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (1)
-
John Millikin