[Haskell-cafe] Using Haskell to write dbus <del>server</del> <ins>client exporting objects</ins>

John Millikin jmillikin at gmail.com
Tue Jan 5 13:56:06 EST 2010


Ah, the issue is one of terminology.

To me, "server" is the central bus, and "client" is any application
which connects to the bus. Clients may send or receive any support
message type.

D-Bus doesn't actually have any mechanism for "exporting" objects;
this is an abstraction, layered over the asynchronous message
protocol. Any client library can "export" objects. Here is an example
of using dbus-core and dbus-client to export some objects /hello and
/world on the "org.test.exporting" name. It includes name
registration, receiving method calls, sending replies, and sending
errors:

---------------------------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import DBus.Bus
import DBus.Client
import DBus.Types
import DBus.Constants
import qualified Data.Map as Map
import Control.Concurrent.MVar

a x = LocalObject $ Map.fromList
        [ (mkInterfaceName' "test.iface_1", Interface $ Map.fromList
                [ (mkMemberName' "Foo", onFoo "a" x)
                , (mkMemberName' "Bar", onBar "a" x)
                ])
        ]

onFoo :: String -> String -> Member
onFoo x y = Method (mkSignature' "") (mkSignature' "s") $ \call -> do
        putStrLn $ "Foo " ++ x ++ " " ++ y
        replyReturn call [toVariant $ "Foo " ++ x ++ " " ++ y]

onBar :: String -> String -> Member
onBar x y = Method (mkSignature' "") (mkSignature' "s") $ \call -> do
        putStrLn $ "Bar " ++ x ++ " " ++ y
        replyError call errorFailed [toVariant $ "Bar " ++ x ++ " " ++ y]

main = do
        client <- mkClient =<< getSessionBus

        requestName client (mkBusName' "org.test.exporting") []

        export client (mkObjectPath' "/hello") (a "hello")
        export client (mkObjectPath' "/world") (a "world")
        mvar <- newEmptyMVar
        takeMVar mvar
---------------------------------------------------------------------------------------------------


On Tue, Jan 5, 2010 at 10:43, Maciej Piechotka <uzytkownik2 at gmail.com> wrote:
> On Tue, 2010-01-05 at 10:27 -0800, John Millikin wrote:
>> There's already three client libraries:
>>
>> http://hackage.haskell.org/package/dbus-client
>> http://hackage.haskell.org/package/network-dbus
>> http://hackage.haskell.org/package/DBus
>>
>> Perhaps there is some confusion? The D-Bus server, or "bus", is a
>> service which allows many-to-many communication between clients. You
>> do not need an implementation of the server in Haskell to use D-Bus in
>> Haskell applications, and (to my knowledge) there is no API for the
>> reference server.
>
> Hmm. Yes. By server I mean client server not the dbus daemon. I.e. the
> side which exports the objects.
>
> I.e. for me (my terminology is network-oriented[1]):
> - dbus server: something exporting objects. Eg. devkit, hal, nm
> - dbus client: something connecting to server/listining for signals etc.
> - dbus daemon: something running in background started
> by /etc/init.d/dbus start & with session
> - dbus bus: namespace in which servers and clients operates. Most
> popular as system and session buses (now I know there is one-to-one
> correspondence with daemons)
>
> I belive that last time I read dbus-client documentation was
> 'client'-oriented.
>
> Regards
> PS. I hope no ASCII ribbonner will kill me for using HTML in subject
>
> [1] Especially that there is xinetd daemon which runs ssh/ftp/...
> servers
>


More information about the Haskell-Cafe mailing list