dbus-0.10.13/benchmarks/0000755000000000000000000000000013073332436013120 5ustar0000000000000000dbus-0.10.13/examples/0000755000000000000000000000000013073332436012621 5ustar0000000000000000dbus-0.10.13/lib/0000755000000000000000000000000013073332436011551 5ustar0000000000000000dbus-0.10.13/lib/DBus/0000755000000000000000000000000013073332436012406 5ustar0000000000000000dbus-0.10.13/lib/DBus/Internal/0000755000000000000000000000000013073332436014162 5ustar0000000000000000dbus-0.10.13/tests/0000755000000000000000000000000013073332436012145 5ustar0000000000000000dbus-0.10.13/tests/DBusTests/0000755000000000000000000000000013073332436014025 5ustar0000000000000000dbus-0.10.13/lib/DBus.hs0000644000000000000000000002102313073332436012740 0ustar0000000000000000-- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . -- | Basic types, useful to every D-Bus application. -- -- Authors of client applications should import "DBus.Client", which provides -- an easy RPC-oriented interface to D-Bus methods and signals. module DBus ( -- * Messages Message -- ** Method calls , MethodCall , methodCall , methodCallPath , methodCallInterface , methodCallMember , methodCallSender , methodCallDestination , methodCallAutoStart , methodCallReplyExpected , methodCallBody -- ** Method returns , MethodReturn , methodReturn , methodReturnSerial , methodReturnSender , methodReturnDestination , methodReturnBody -- ** Method errors , MethodError , methodError , methodErrorName , methodErrorSerial , methodErrorSender , methodErrorDestination , methodErrorBody , methodErrorMessage -- ** Signals , Signal , signal , signalPath , signalMember , signalInterface , signalSender , signalDestination , signalBody -- ** Received messages , ReceivedMessage(ReceivedMethodCall, ReceivedMethodReturn, ReceivedMethodError, ReceivedSignal) , receivedMessageSerial , receivedMessageSender , receivedMessageBody -- * Variants , Variant , IsVariant(..) , variantType , IsAtom , IsValue , typeOf -- * Signatures , Signature , Type(..) , signature , signature_ , signatureTypes , formatSignature , parseSignature -- * Object paths , ObjectPath , objectPath_ , formatObjectPath , parseObjectPath -- * Names -- ** Interface names , InterfaceName , interfaceName_ , formatInterfaceName , parseInterfaceName -- ** Member names , MemberName , memberName_ , formatMemberName , parseMemberName -- ** Error names , ErrorName , errorName_ , formatErrorName , parseErrorName -- ** Bus names , BusName , busName_ , formatBusName , parseBusName -- * Non-native containers -- ** Structures , Structure , structureItems -- ** Arrays , Array , arrayItems -- ** Dictionaries , Dictionary , dictionaryItems -- * Addresses , Address , addressMethod , addressParameters , address , formatAddress , formatAddresses , parseAddress , parseAddresses , getSystemAddress , getSessionAddress , getStarterAddress -- * Message marshaling , Endianness (..) -- ** Marshal , marshal , MarshalError , marshalErrorMessage -- ** Unmarshal , unmarshal , UnmarshalError , unmarshalErrorMessage -- ** Message serials , Serial , serialValue , firstSerial , nextSerial -- * D-Bus UUIDs , UUID , formatUUID , randomUUID ) where import Control.Monad (replicateM) import qualified Data.ByteString.Char8 as Char8 import Data.Word (Word16) import System.Random (randomRIO) import Text.Printf (printf) import DBus.Internal.Address import DBus.Internal.Message import qualified DBus.Internal.Types import DBus.Internal.Types hiding (typeOf) import DBus.Internal.Wire -- | Get the D-Bus type corresponding to the given Haskell value. The value -- may be @undefined@. typeOf :: IsValue a => a -> Type typeOf = DBus.Internal.Types.typeOf -- | Construct a new 'MethodCall' for the given object, interface, and method. -- -- Use fields such as 'methodCallDestination' and 'methodCallBody' to populate -- a 'MethodCall'. -- -- @ --{-\# LANGUAGE OverloadedStrings \#-} -- --methodCall \"/\" \"org.example.Math\" \"Add\" -- { 'methodCallDestination' = Just \"org.example.Calculator\" -- , 'methodCallBody' = ['toVariant' (1 :: Int32), 'toVariant' (2 :: Int32)] -- } -- @ methodCall :: ObjectPath -> InterfaceName -> MemberName -> MethodCall methodCall path iface member = MethodCall path (Just iface) member Nothing Nothing True True [] -- | Construct a new 'MethodReturn', in reply to a method call with the given -- serial. -- -- Use fields such as 'methodReturnBody' to populate a 'MethodReturn'. methodReturn :: Serial -> MethodReturn methodReturn s = MethodReturn s Nothing Nothing [] -- | Construct a new 'MethodError', in reply to a method call with the given -- serial. -- -- Use fields such as 'methodErrorBody' to populate a 'MethodError'. methodError :: Serial -> ErrorName -> MethodError methodError s name = MethodError name s Nothing Nothing [] -- | Construct a new 'Signal' for the given object, interface, and signal name. -- -- Use fields such as 'signalBody' to populate a 'Signal'. signal :: ObjectPath -> InterfaceName -> MemberName -> Signal signal path iface member = Signal path iface member Nothing Nothing [] -- | No matter what sort of message was received, get its serial. receivedMessageSerial :: ReceivedMessage -> Serial receivedMessageSerial (ReceivedMethodCall s _) = s receivedMessageSerial (ReceivedMethodReturn s _) = s receivedMessageSerial (ReceivedMethodError s _) = s receivedMessageSerial (ReceivedSignal s _) = s receivedMessageSerial (ReceivedUnknown s _) = s -- | No matter what sort of message was received, get its sender (if provided). receivedMessageSender :: ReceivedMessage -> Maybe BusName receivedMessageSender (ReceivedMethodCall _ msg) = methodCallSender msg receivedMessageSender (ReceivedMethodReturn _ msg) = methodReturnSender msg receivedMessageSender (ReceivedMethodError _ msg) = methodErrorSender msg receivedMessageSender (ReceivedSignal _ msg) = signalSender msg receivedMessageSender (ReceivedUnknown _ msg) = unknownMessageSender msg -- | No matter what sort of message was received, get its body (if provided). receivedMessageBody :: ReceivedMessage -> [Variant] receivedMessageBody (ReceivedMethodCall _ msg) = methodCallBody msg receivedMessageBody (ReceivedMethodReturn _ msg) = methodReturnBody msg receivedMessageBody (ReceivedMethodError _ msg) = methodErrorBody msg receivedMessageBody (ReceivedSignal _ msg) = signalBody msg receivedMessageBody (ReceivedUnknown _ msg) = unknownMessageBody msg -- | Convert a 'Message' into a 'Char8.ByteString'. Although unusual, it is -- possible for marshaling to fail; if this occurs, an error will be -- returned instead. marshal :: Message msg => Endianness -> Serial -> msg -> Either MarshalError Char8.ByteString marshal = marshalMessage -- | Parse a 'Char8.ByteString' into a 'ReceivedMessage'. The result can be -- inspected to see what type of message was parsed. Unknown message types -- can still be parsed successfully, as long as they otherwise conform to -- the D-Bus standard. unmarshal :: Char8.ByteString -> Either UnmarshalError ReceivedMessage unmarshal = unmarshalMessage -- | A D-Bus UUID is 128 bits of data, usually randomly generated. They are -- used for identifying unique server instances to clients. -- -- Older versions of the D-Bus spec also called these values /GUIDs/. -- -- D-Bus UUIDs are not the same as the RFC-standardized UUIDs or GUIDs. newtype UUID = UUID Char8.ByteString deriving (Eq, Ord, Show) -- | Format a D-Bus UUID as hex-encoded ASCII. formatUUID :: UUID -> String formatUUID (UUID bytes) = Char8.unpack bytes -- | Generate a random D-Bus UUID. This value is suitable for use in a -- randomly-allocated address, or as a listener's socket address -- @\"guid\"@ parameter. randomUUID :: IO UUID randomUUID = do -- The version of System.Random bundled with ghc < 7.2 doesn't define -- instances for any of the fixed-length word types, so we imitate -- them using the instance for Int. -- -- 128 bits is 8 16-bit integers. We use chunks of 16 instead of 32 -- because Int is not guaranteed to be able to store a Word32. let hexInt16 i = printf "%04x" (i :: Int) int16s <- replicateM 8 (randomRIO (0, fromIntegral (maxBound :: Word16))) return (UUID (Char8.pack (concatMap hexInt16 int16s))) dbus-0.10.13/lib/DBus/Client.hs0000644000000000000000000010407713073332436014171 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverlappingInstances #-} {-# LANGUAGE OverloadedStrings #-} -- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . -- | D-Bus clients are an abstraction over the lower-level messaging -- system. When combined with an external daemon called the \"bus\", clients -- can perform remote procedure calls to other clients on the bus. -- -- Clients may also listen for or emit /signals/, which are asynchronous -- broadcast notifications. -- -- Example: connect to the session bus, and get a list of active names. -- -- @ --{-\# LANGUAGE OverloadedStrings \#-} -- --import Data.List (sort) --import DBus --import DBus.Client -- --main = do -- client <- 'connectSession' -- // -- \-- Request a list of connected clients from the bus -- reply <- 'call_' client ('methodCall' \"\/org\/freedesktop\/DBus\" \"org.freedesktop.DBus\" \"ListNames\") -- { 'methodCallDestination' = Just \"org.freedesktop.DBus\" -- } -- // -- \-- org.freedesktop.DBus.ListNames() returns a single value, which is -- \-- a list of names (here represented as [String]) -- let Just names = 'fromVariant' ('methodReturnBody' reply !! 0) -- // -- \-- Print each name on a line, sorted so reserved names are below -- \-- temporary names. -- mapM_ putStrLn (sort names) -- @ -- module DBus.Client ( -- * Clients Client -- * Connecting to a bus , connect , connectSystem , connectSession , connectStarter , disconnect -- * Sending method calls , call , call_ , callNoReply -- * Receiving method calls , export , unexport , Method , method , Reply , replyReturn , replyError , throwError -- ** Automatic method signatures , AutoMethod , autoMethod -- * Signals , SignalHandler , addMatch , removeMatch , emit , listen -- ** Match rules , MatchRule , formatMatchRule , matchAny , matchSender , matchDestination , matchPath , matchInterface , matchMember -- * Name reservation , requestName , releaseName , RequestNameFlag , nameAllowReplacement , nameReplaceExisting , nameDoNotQueue , RequestNameReply(NamePrimaryOwner, NameInQueue, NameExists, NameAlreadyOwner) , ReleaseNameReply(NameReleased, NameNonExistent, NameNotOwner) -- * Client errors , ClientError , clientError , clientErrorMessage , clientErrorFatal -- * Advanced connection options , ClientOptions , clientSocketOptions , clientThreadRunner , defaultClientOptions , connectWith ) where import Control.Concurrent import Control.Exception (SomeException, throwIO) import qualified Control.Exception import Control.Monad (forever, forM_, when) import Data.Bits ((.|.)) import Data.IORef import Data.List (foldl', intercalate) import qualified Data.Map import Data.Map (Map) import Data.Maybe (catMaybes, listToMaybe) import Data.Typeable (Typeable) import Data.Unique import Data.Word (Word32) import DBus import qualified DBus.Introspection as I import qualified DBus.Socket import DBus.Transport (TransportOpen, SocketTransport) data ClientError = ClientError { clientErrorMessage :: String , clientErrorFatal :: Bool } deriving (Eq, Show, Typeable) instance Control.Exception.Exception ClientError clientError :: String -> ClientError clientError msg = ClientError msg True -- | An active client session to a message bus. Clients may send or receive -- method calls, and listen for or emit signals. data Client = Client { clientSocket :: DBus.Socket.Socket , clientPendingCalls :: IORef (Map Serial (MVar (Either MethodError MethodReturn))) , clientSignalHandlers :: IORef (Map Unique SignalHandler) , clientObjects :: IORef (Map ObjectPath ObjectInfo) , clientThreadID :: ThreadId } data ClientOptions t = ClientOptions { -- | Options for the underlying socket, for advanced use cases. See -- the "DBus.Socket" module. clientSocketOptions :: DBus.Socket.SocketOptions t -- | A function to run the client thread. The provided IO computation -- should be called repeatedly; each time it is called, it will process -- one incoming message. -- -- The provided computation will throw a 'ClientError' if it fails to -- process an incoming message, or if the connection is lost. -- -- The default implementation is 'forever'. , clientThreadRunner :: IO () -> IO () } type Callback = (ReceivedMessage -> IO ()) type FormattedMatchRule = String data SignalHandler = SignalHandler Unique FormattedMatchRule (IORef Bool) (Signal -> IO ()) data Reply = ReplyReturn [Variant] | ReplyError ErrorName [Variant] -- | Reply to a method call with a successful return, containing the given body. replyReturn :: [Variant] -> Reply replyReturn = ReplyReturn -- | Reply to a method call with an error, containing the given error name and -- body. -- -- Typically, the first item of the error body is a string with a message -- describing the error. replyError :: ErrorName -> [Variant] -> Reply replyError = ReplyError data Method = Method InterfaceName MemberName Signature Signature (MethodCall -> IO Reply) type ObjectInfo = Map InterfaceName InterfaceInfo type InterfaceInfo = Map MemberName MethodInfo data MethodInfo = MethodInfo Signature Signature Callback -- | 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. connectSystem :: IO Client connectSystem = do env <- getSystemAddress case env of Nothing -> throwIO (clientError "connectSystem: DBUS_SYSTEM_BUS_ADDRESS is invalid.") Just addr -> connect addr -- | 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. connectSession :: IO Client connectSession = do env <- getSessionAddress case env of Nothing -> throwIO (clientError "connectSession: DBUS_SESSION_BUS_ADDRESS is missing or invalid.") Just addr -> connect addr -- | Connect to the bus specified in the environment variable -- @DBUS_STARTER_ADDRESS@, which must be set. -- -- Throws a 'ClientError' if @DBUS_STARTER_ADDRESS@ is unset, contains an -- invalid address, or if connecting to the bus failed. connectStarter :: IO Client connectStarter = do env <- getStarterAddress case env of Nothing -> throwIO (clientError "connectStarter: DBUS_STARTER_ADDRESS is missing or invalid.") Just addr -> connect addr -- | Connect to the bus at the specified address. -- -- Throws a 'ClientError' on failure. connect :: Address -> IO Client connect = connectWith defaultClientOptions -- | Connect to the bus at the specified address, with the given connection -- options. Most users should use 'connect' instead. -- -- Throws a 'ClientError' on failure. connectWith :: TransportOpen t => ClientOptions t -> Address -> IO Client connectWith opts addr = do sock <- DBus.Socket.openWith (clientSocketOptions opts) addr pendingCalls <- newIORef Data.Map.empty signalHandlers <- newIORef Data.Map.empty objects <- newIORef Data.Map.empty let threadRunner = clientThreadRunner opts clientMVar <- newEmptyMVar threadID <- forkIO $ do client <- readMVar clientMVar threadRunner (mainLoop client) let client = Client { clientSocket = sock , clientPendingCalls = pendingCalls , clientSignalHandlers = signalHandlers , clientObjects = objects , clientThreadID = threadID } putMVar clientMVar client export client "/" [introspectRoot client] callNoReply client (methodCall dbusPath dbusInterface "Hello") { methodCallDestination = Just dbusName } return client -- | Default client options. Uses the built-in Socket-based transport, which -- supports the @tcp:@ and @unix:@ methods. defaultClientOptions :: ClientOptions SocketTransport defaultClientOptions = ClientOptions { clientSocketOptions = DBus.Socket.defaultSocketOptions , clientThreadRunner = forever } -- | Stop a 'Client''s callback thread and close its underlying socket. disconnect :: Client -> IO () disconnect client = do killThread (clientThreadID client) disconnect' client disconnect' :: Client -> IO () disconnect' client = do pendingCalls <- atomicModifyIORef (clientPendingCalls client) (\p -> (Data.Map.empty, p)) forM_ (Data.Map.toList pendingCalls) $ \(k, v) -> do putMVar v (Left (methodError k errorDisconnected)) atomicWriteIORef (clientSignalHandlers client) Data.Map.empty atomicWriteIORef (clientObjects client) Data.Map.empty DBus.Socket.close (clientSocket client) mainLoop :: Client -> IO () mainLoop client = do let sock = clientSocket client received <- Control.Exception.try (DBus.Socket.receive sock) msg <- case received of Left err -> do disconnect' client throwIO (clientError (DBus.Socket.socketErrorMessage err)) Right msg -> return msg dispatch client msg dispatch :: Client -> ReceivedMessage -> IO () dispatch client = go where go (ReceivedMethodReturn _ msg) = dispatchReply (methodReturnSerial msg) (Right msg) go (ReceivedMethodError _ msg) = dispatchReply (methodErrorSerial msg) (Left msg) go (ReceivedSignal _ msg) = do handlers <- readIORef (clientSignalHandlers client) forM_ (Data.Map.toAscList handlers) (\(_, SignalHandler _ _ _ h) -> forkIO (h msg) >> return ()) go received@(ReceivedMethodCall serial msg) = do objects <- readIORef (clientObjects client) let sender = methodCallSender msg _ <- forkIO $ case findMethod objects msg of Right io -> io received Left errName -> send_ client (methodError serial errName) { methodErrorDestination = sender } (\_ -> return ()) return () go _ = return () dispatchReply serial result = do pending <- atomicModifyIORef (clientPendingCalls client) (\p -> case Data.Map.lookup serial p of Nothing -> (p, Nothing) Just mvar -> (Data.Map.delete serial p, Just mvar)) case pending of Just mvar -> putMVar mvar result Nothing -> return () data RequestNameFlag = AllowReplacement | ReplaceExisting | DoNotQueue deriving (Eq, Show) -- | Allow this client's reservation to be replaced, if another client -- requests it with the 'nameReplaceExisting' flag. -- -- If this client's reservation is replaced, this client will be added to the -- wait queue unless the request also included the 'nameDoNotQueue' flag. nameAllowReplacement :: RequestNameFlag nameAllowReplacement = AllowReplacement -- | If the name being requested is already reserved, attempt to replace it. -- This only works if the current owner provided the 'nameAllowReplacement' -- flag. nameReplaceExisting :: RequestNameFlag nameReplaceExisting = ReplaceExisting -- | If the name is already in use, do not add this client to the queue, just -- return an error. nameDoNotQueue :: RequestNameFlag nameDoNotQueue = DoNotQueue data RequestNameReply -- | This client is now the primary owner of the requested name. = NamePrimaryOwner -- | The name was already reserved by another client, and replacement -- was either not attempted or not successful. | NameInQueue -- | The name was already reserved by another client, 'DoNotQueue' -- was set, and replacement was either not attempted or not -- successful. | NameExists -- | This client is already the primary owner of the requested name. | NameAlreadyOwner -- | Not exported; exists to generate a compiler warning if users -- case on the reply and forget to include a default case. | UnknownRequestNameReply Word32 deriving (Eq, Show) data ReleaseNameReply -- | This client has released the provided name. = NameReleased -- | The provided name is not assigned to any client on the bus. | NameNonExistent -- | The provided name is not assigned to this client. | NameNotOwner -- | Not exported; exists to generate a compiler warning if users -- case on the reply and forget to include a default case. | UnknownReleaseNameReply Word32 deriving (Eq, Show) encodeFlags :: [RequestNameFlag] -> Word32 encodeFlags = foldr (.|.) 0 . map flagValue where flagValue AllowReplacement = 0x1 flagValue ReplaceExisting = 0x2 flagValue DoNotQueue = 0x4 -- | Asks the message bus to assign the given name to this client. The bus -- maintains a queue of possible owners, where the head of the queue is the -- current (\"primary\") owner. -- -- There are several uses for name reservation: -- -- * Clients which export methods reserve a name so users and applications -- can send them messages. For example, the GNOME Keyring reserves the name -- @\"org.gnome.keyring\"@ on the user's session bus, and NetworkManager -- reserves @\"org.freedesktop.NetworkManager\"@ on the system bus. -- -- * When there are multiple implementations of a particular service, the -- service standard will ususally include a generic bus name for the -- service. This allows other clients to avoid depending on any particular -- implementation's name. For example, both the GNOME Keyring and KDE -- KWallet services request the @\"org.freedesktop.secrets\"@ name on the -- user's session bus. -- -- * A process with \"single instance\" behavior can use name assignment to -- check whether the instance is already running, and invoke some method -- on it (e.g. opening a new window). -- -- Throws a 'ClientError' if the call failed. requestName :: Client -> BusName -> [RequestNameFlag] -> IO RequestNameReply requestName client name flags = do reply <- call_ client (methodCall dbusPath dbusInterface "RequestName") { methodCallDestination = Just dbusName , methodCallBody = [toVariant name, toVariant (encodeFlags flags)] } var <- case listToMaybe (methodReturnBody reply) of Just x -> return x Nothing -> throwIO (clientError "requestName: received empty response") { clientErrorFatal = False } code <- case fromVariant var of Just x -> return x Nothing -> throwIO (clientError ("requestName: received invalid response code " ++ showsPrec 11 var "")) { clientErrorFatal = False } return $ case code :: Word32 of 1 -> NamePrimaryOwner 2 -> NameInQueue 3 -> NameExists 4 -> NameAlreadyOwner _ -> UnknownRequestNameReply code -- | Release a name that this client previously requested. See 'requestName' -- for an explanation of name reservation. -- -- Throws a 'ClientError' if the call failed. releaseName :: Client -> BusName -> IO ReleaseNameReply releaseName client name = do reply <- call_ client (methodCall dbusPath dbusInterface "ReleaseName") { methodCallDestination = Just dbusName , methodCallBody = [toVariant name] } var <- case listToMaybe (methodReturnBody reply) of Just x -> return x Nothing -> throwIO (clientError "releaseName: received empty response") { clientErrorFatal = False } code <- case fromVariant var of Just x -> return x Nothing -> throwIO (clientError ("releaseName: received invalid response code " ++ showsPrec 11 var "")) { clientErrorFatal = False } return $ case code :: Word32 of 1 -> NameReleased 2 -> NameNonExistent 3 -> NameNotOwner _ -> UnknownReleaseNameReply code send_ :: Message msg => Client -> msg -> (Serial -> IO a) -> IO a send_ client msg io = do result <- Control.Exception.try (DBus.Socket.send (clientSocket client) msg io) case result of Right x -> return x Left err -> throwIO (clientError (DBus.Socket.socketErrorMessage err)) { clientErrorFatal = DBus.Socket.socketErrorFatal err } -- | Send a method call to the bus, and wait for the response. -- -- Throws a 'ClientError' if the method call couldn't be sent, or if the reply -- couldn't be parsed. call :: Client -> MethodCall -> IO (Either MethodError MethodReturn) call client msg = do -- If ReplyExpected is False, this function would block indefinitely -- if the remote side honors it. let safeMsg = msg { methodCallReplyExpected = True } mvar <- newEmptyMVar let ref = clientPendingCalls client serial <- send_ client safeMsg (\serial -> atomicModifyIORef ref (\p -> (Data.Map.insert serial mvar p, serial))) -- At this point, we wait for the reply to arrive. The user may cancel -- a pending call by sending this thread an exception via something -- like 'timeout'; in that case, we want to clean up the pending call. Control.Exception.onException (takeMVar mvar) (atomicModifyIORef_ ref (Data.Map.delete serial)) -- | Send a method call to the bus, and wait for the response. -- -- Unsets the 'noReplyExpected' message flag before sending. -- -- Throws a 'ClientError' if the method call couldn't sent, if the reply -- couldn't be parsed, or if the reply was a 'MethodError'. call_ :: Client -> MethodCall -> IO MethodReturn call_ client msg = do result <- call client msg case result of Left err -> throwIO (clientError ("Call failed: " ++ methodErrorMessage err)) { clientErrorFatal = methodErrorName err == errorDisconnected } Right ret -> return ret -- | Send a method call to the bus, and do not wait for a response. -- -- Sets the 'noReplyExpected' message flag before sending. -- -- Throws a 'ClientError' if the method call couldn't be sent. callNoReply :: Client -> MethodCall -> IO () callNoReply client msg = do -- Ensure that noReplyExpected is always set. let safeMsg = msg { methodCallReplyExpected = False } send_ client safeMsg (\_ -> return ()) -- | Request that the bus forward signals matching the given rule to this -- client, and process them in a callback. -- -- A received signal might be processed by more than one callback at a time. -- Callbacks each run in their own thread. -- -- The returned 'SignalHandler' can be passed to 'removeMatch' -- to stop handling this signal. -- -- Throws a 'ClientError' if the match rule couldn't be added to the bus. addMatch :: Client -> MatchRule -> (Signal -> IO ()) -> IO SignalHandler addMatch client rule io = do let formatted = case formatMatchRule rule of "" -> "type='signal'" x -> "type='signal'," ++ x handlerId <- newUnique registered <- newIORef True let handler = SignalHandler handlerId formatted registered (\msg -> when (checkMatchRule rule msg) (io msg)) atomicModifyIORef (clientSignalHandlers client) (\hs -> (Data.Map.insert handlerId handler hs, ())) _ <- call_ client (methodCall dbusPath dbusInterface "AddMatch") { methodCallDestination = Just dbusName , methodCallBody = [toVariant formatted] } return handler -- | Request that the bus stop forwarding signals for the given handler. -- -- Throws a 'ClientError' if the match rule couldn't be removed from the bus. removeMatch :: Client -> SignalHandler -> IO () removeMatch client (SignalHandler handlerId formatted registered _) = do shouldUnregister <- atomicModifyIORef registered (\wasRegistered -> (False, wasRegistered)) when shouldUnregister $ do atomicModifyIORef (clientSignalHandlers client) (\hs -> (Data.Map.delete handlerId hs, ())) _ <- call_ client (methodCall dbusPath dbusInterface "RemoveMatch") { methodCallDestination = Just dbusName , methodCallBody = [toVariant formatted] } return () -- | Equivalent to 'addMatch', but does not return the added 'SignalHandler'. listen :: Client -> MatchRule -> (Signal -> IO ()) -> IO () listen client rule io = addMatch client rule io >> return () {-# DEPRECATED listen "Prefer DBus.Client.addMatch in new code." #-} -- | Emit the signal on the bus. -- -- Throws a 'ClientError' if the signal message couldn't be sent. emit :: Client -> Signal -> IO () emit client msg = send_ client msg (\_ -> return ()) -- | A match rule describes which signals a particular callback is interested -- in. Use 'matchAny' to construct match rules. -- -- Example: a match rule which matches signals sent by the root object. -- -- @ --matchFromRoot :: MatchRule --matchFromRoot = 'matchAny' { 'matchPath' = Just \"/\" } -- @ data MatchRule = MatchRule { -- | If set, only receives signals sent from the given bus name. -- -- The standard D-Bus implementation from -- almost always sets signal senders to the unique name of the sending -- client. If 'matchSender' is a requested name like -- @\"com.example.Foo\"@, it will not match any signals. -- -- The exception is for signals sent by the bus itself, which always -- have a sender of @\"org.freedesktop.DBus\"@. matchSender :: Maybe BusName -- | If set, only receives signals sent to the given bus name. , matchDestination :: Maybe BusName -- | If set, only receives signals sent with the given path. , matchPath :: Maybe ObjectPath -- | If set, only receives signals sent with the given interface name. , matchInterface :: Maybe InterfaceName -- | If set, only receives signals sent with the given member name. , matchMember :: Maybe MemberName } instance Show MatchRule where showsPrec d rule = showParen (d > 10) (showString "MatchRule " . shows (formatMatchRule rule)) -- | Convert a match rule into the textual format accepted by the bus. formatMatchRule :: MatchRule -> String formatMatchRule rule = intercalate "," predicates where predicates = catMaybes [ f "sender" matchSender formatBusName , f "destination" matchDestination formatBusName , f "path" matchPath formatObjectPath , f "interface" matchInterface formatInterfaceName , f "member" matchMember formatMemberName ] f :: String -> (MatchRule -> Maybe a) -> (a -> String) -> Maybe String f key get text = do val <- fmap text (get rule) return (concat [key, "='", val, "'"]) -- | Match any signal. matchAny :: MatchRule matchAny = MatchRule Nothing Nothing Nothing Nothing Nothing checkMatchRule :: MatchRule -> Signal -> Bool checkMatchRule rule msg = and [ maybe True (\x -> signalSender msg == Just x) (matchSender rule) , maybe True (\x -> signalDestination msg == Just x) (matchDestination rule) , maybe True (== signalPath msg) (matchPath rule) , maybe True (== signalInterface msg) (matchInterface rule) , maybe True (== signalMember msg) (matchMember rule) ] data MethodExc = MethodExc ErrorName [Variant] deriving (Show, Eq, Typeable) instance Control.Exception.Exception MethodExc -- | Normally, any exceptions raised while executing a method will be -- given the generic @\"org.freedesktop.DBus.Error.Failed\"@ name. -- 'throwError' allows the programmer to specify an error name, and provide -- additional information to the remote application. You may use this instead -- of 'Control.Exception.throwIO' to abort a method call. throwError :: ErrorName -> String -- ^ Error message -> [Variant] -- ^ Additional items of the error body -> IO a throwError name message extra = Control.Exception.throwIO (MethodExc name (toVariant message : extra)) -- | Define a method handler, which will accept method calls with the given -- interface and member name. -- -- Note that the input and output parameter signatures are used for -- introspection, but are not checked when executing a method. -- -- See 'autoMethod' for an easier way to export functions with simple -- parameter and return types. method :: InterfaceName -> MemberName -> Signature -- ^ Input parameter signature -> Signature -- ^ Output parameter signature -> (MethodCall -> IO Reply) -> Method method iface name inSig outSig io = Method iface name inSig outSig (\msg -> Control.Exception.catch (Control.Exception.catch (io msg) (\(MethodExc name' vs') -> return (ReplyError name' vs'))) (\exc -> return (ReplyError errorFailed [toVariant (show (exc :: SomeException))]))) -- | Export the given functions under the given 'ObjectPath' and -- 'InterfaceName'. -- -- Use 'autoMethod' to construct a 'Method' from a function that accepts and -- returns simple types. -- -- Use 'method' to construct a 'Method' from a function that handles parameter -- conversion manually. -- -- @ --ping :: MethodCall -> IO 'Reply' --ping _ = replyReturn [] -- --sayHello :: String -> IO String --sayHello name = return (\"Hello \" ++ name ++ \"!\") -- --export client \"/hello_world\" -- [ 'method' \"com.example.HelloWorld\" \"Ping\" ping -- , 'autoMethod' \"com.example.HelloWorld\" \"Hello\" sayHello -- ] -- @ export :: Client -> ObjectPath -> [Method] -> IO () export client path methods = atomicModifyIORef (clientObjects client) addObject where addObject objs = (Data.Map.insert path info objs, ()) info = foldl' addMethod Data.Map.empty (defaultIntrospect : methods) addMethod m (Method iface name inSig outSig cb) = Data.Map.insertWith' Data.Map.union iface (Data.Map.fromList [(name, MethodInfo inSig outSig (wrapCB cb))]) m wrapCB cb (ReceivedMethodCall serial msg) = do reply <- cb msg let sender = methodCallSender msg case reply of ReplyReturn vs -> send_ client (methodReturn serial) { methodReturnDestination = sender , methodReturnBody = vs } (\_ -> return ()) ReplyError name vs -> send_ client (methodError serial name) { methodErrorDestination = sender , methodErrorBody = vs } (\_ -> return ()) wrapCB _ _ = return () defaultIntrospect = methodIntrospect $ do objects <- readIORef (clientObjects client) let Just obj = Data.Map.lookup path objects return (introspect path obj) -- | Revokes the export of the given 'ObjectPath'. This will remove all -- interfaces and methods associated with the path. unexport :: Client -> ObjectPath -> IO () unexport client path = atomicModifyIORef (clientObjects client) deleteObject where deleteObject objs = (Data.Map.delete path objs, ()) findMethod :: Map ObjectPath ObjectInfo -> MethodCall -> Either ErrorName Callback findMethod objects msg = case Data.Map.lookup (methodCallPath msg) objects of Nothing -> Left errorUnknownObject Just obj -> case methodCallInterface msg of Nothing -> let members = do iface <- Data.Map.elems obj case Data.Map.lookup (methodCallMember msg) iface of Just member -> [member] Nothing -> [] in case members of [MethodInfo _ _ io] -> Right io _ -> Left errorUnknownMethod Just ifaceName -> case Data.Map.lookup ifaceName obj of Nothing -> Left errorUnknownInterface Just iface -> case Data.Map.lookup (methodCallMember msg) iface of Just (MethodInfo _ _ io) -> Right io _ -> Left errorUnknownMethod introspectRoot :: Client -> Method introspectRoot client = methodIntrospect $ do objects <- readIORef (clientObjects client) let paths = filter (/= "/") (Data.Map.keys objects) return (I.object "/") { I.objectInterfaces = [ (I.interface interfaceIntrospectable) { I.interfaceMethods = [ (I.method "Introspect") { I.methodArgs = [ I.methodArg "" TypeString I.directionOut ] } ] } ] , I.objectChildren = [I.object p | p <- paths] } methodIntrospect :: IO I.Object -> Method methodIntrospect get = method interfaceIntrospectable "Introspect" "" "s" $ \msg -> case methodCallBody msg of [] -> do obj <- get let Just xml = I.formatXML obj return (replyReturn [toVariant xml]) _ -> return (replyError errorInvalidParameters []) introspect :: ObjectPath -> ObjectInfo -> I.Object introspect path obj = (I.object path) { I.objectInterfaces = interfaces } where interfaces = map introspectIface (Data.Map.toList obj) introspectIface (name, iface) = (I.interface name) { I.interfaceMethods = concatMap introspectMethod (Data.Map.toList iface) } args inSig outSig = map (introspectArg I.directionIn) (signatureTypes inSig) ++ map (introspectArg I.directionOut) (signatureTypes outSig) introspectMethod (name, MethodInfo inSig outSig _) = [ (I.method name) { I.methodArgs = args inSig outSig } ] introspectArg dir t = I.methodArg "" t dir -- | Used to automatically generate method signatures for introspection -- documents. To support automatic signatures, a method's parameters and -- return value must all be instances of 'IsValue'. -- -- This class maps Haskell idioms to D-Bus; it is therefore unable to -- generate some signatures. In particular, it does not support methods -- which accept/return a single structure, or single-element structures. -- It also cannot generate signatures for methods with parameters or return -- values which are only instances of 'IsVariant'. For these cases, please -- use 'DBus.Client.method'. -- -- To match common Haskell use, if the return value is a tuple, it will be -- converted to a list of return values. class AutoMethod a where funTypes :: a -> ([Type], [Type]) apply :: a -> [Variant] -> Maybe (IO [Variant]) instance AutoMethod (IO ()) where funTypes _ = ([], []) apply io [] = Just (io >> return []) apply _ _ = Nothing instance IsValue a => AutoMethod (IO a) where funTypes io = cased where cased = ([], case ioT io undefined of (_, t) -> case t of TypeStructure ts -> ts _ -> [t]) ioT :: IsValue a => IO a -> a -> (a, Type) ioT _ a = (a, typeOf a) apply io [] = Just (do var <- fmap toVariant io case fromVariant var of Just struct -> return (structureItems struct) Nothing -> return [var]) apply _ _ = Nothing instance (IsValue a, AutoMethod fn) => AutoMethod (a -> fn) where funTypes fn = cased where cased = case valueT undefined of (a, t) -> case funTypes (fn a) of (ts, ts') -> (t : ts, ts') valueT :: IsValue a => a -> (a, Type) valueT a = (a, typeOf a) apply _ [] = Nothing apply fn (v:vs) = case fromVariant v of Just v' -> apply (fn v') vs Nothing -> Nothing -- | Prepare a Haskell function for export, automatically detecting the -- function's type signature. -- -- See 'AutoMethod' for details on the limitations of this function. -- -- See 'method' for exporting functions with user-defined types. autoMethod :: (AutoMethod fn) => InterfaceName -> MemberName -> fn -> Method autoMethod iface name fun = DBus.Client.method iface name inSig outSig io where (typesIn, typesOut) = funTypes fun inSig = case signature typesIn of Just sig -> sig Nothing -> invalid "input" outSig = case signature typesOut of Just sig -> sig Nothing -> invalid "output" io msg = case apply fun (methodCallBody msg) of Nothing -> return (ReplyError errorInvalidParameters []) Just io' -> fmap ReplyReturn io' invalid label = error (concat [ "Method " , formatInterfaceName iface , "." , formatMemberName name , " has an invalid " , label , " signature."]) errorFailed :: ErrorName errorFailed = errorName_ "org.freedesktop.DBus.Error.Failed" errorDisconnected :: ErrorName errorDisconnected = errorName_ "org.freedesktop.DBus.Error.Disconnected" errorUnknownObject :: ErrorName errorUnknownObject = errorName_ "org.freedesktop.DBus.Error.UnknownObject" errorUnknownInterface :: ErrorName errorUnknownInterface = errorName_ "org.freedesktop.DBus.Error.UnknownInterface" errorUnknownMethod :: ErrorName errorUnknownMethod = errorName_ "org.freedesktop.DBus.Error.UnknownMethod" errorInvalidParameters :: ErrorName errorInvalidParameters = errorName_ "org.freedesktop.DBus.Error.InvalidParameters" dbusName :: BusName dbusName = busName_ "org.freedesktop.DBus" dbusPath :: ObjectPath dbusPath = objectPath_ "/org/freedesktop/DBus" dbusInterface :: InterfaceName dbusInterface = interfaceName_ "org.freedesktop.DBus" interfaceIntrospectable :: InterfaceName interfaceIntrospectable = interfaceName_ "org.freedesktop.DBus.Introspectable" atomicModifyIORef_ :: IORef a -> (a -> a) -> IO () atomicModifyIORef_ ref fn = atomicModifyIORef ref (\x -> (fn x, ())) #if !MIN_VERSION_base(4,6,0) atomicWriteIORef :: IORef a -> a -> IO () atomicWriteIORef ref x = atomicModifyIORef ref (\_ -> (x, ())) #endif dbus-0.10.13/lib/DBus/Introspection.hs0000644000000000000000000002764313073332436015616 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} -- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBus.Introspection ( -- * XML conversion parseXML , formatXML -- * Objects , Object , object , objectPath , objectInterfaces , objectChildren -- * Interfaces , Interface , interface , interfaceName , interfaceMethods , interfaceSignals , interfaceProperties -- * Methods , Method , method , methodName , methodArgs -- ** Method arguments , MethodArg , methodArg , methodArgName , methodArgType , methodArgDirection , Direction , directionIn , directionOut -- * Signals , Signal , signal , signalName , signalArgs -- ** Signal arguments , SignalArg , signalArg , signalArgName , signalArgType -- * Properties , Property , property , propertyName , propertyType , propertyRead , propertyWrite ) where import qualified Control.Applicative import Control.Monad ((>=>), ap, liftM) import Control.Monad.ST (runST) import Data.List (isPrefixOf) import qualified Data.STRef as ST import qualified Data.Text import Data.Text (Text) import qualified Data.Text.Encoding import qualified Data.XML.Types as X import qualified Text.XML.LibXML.SAX as SAX import qualified DBus as T data Object = Object { objectPath :: T.ObjectPath , objectInterfaces :: [Interface] , objectChildren :: [Object] } deriving (Show, Eq) object :: T.ObjectPath -> Object object path = Object path [] [] data Interface = Interface { interfaceName :: T.InterfaceName , interfaceMethods :: [Method] , interfaceSignals :: [Signal] , interfaceProperties :: [Property] } deriving (Show, Eq) interface :: T.InterfaceName -> Interface interface name = Interface name [] [] [] data Method = Method { methodName :: T.MemberName , methodArgs :: [MethodArg] } deriving (Show, Eq) method :: T.MemberName -> Method method name = Method name [] data MethodArg = MethodArg { methodArgName :: String , methodArgType :: T.Type , methodArgDirection :: Direction } deriving (Show, Eq) methodArg :: String -> T.Type -> Direction -> MethodArg methodArg = MethodArg data Direction = In | Out deriving (Show, Eq) directionIn :: Direction directionIn = In directionOut :: Direction directionOut = Out data Signal = Signal { signalName :: T.MemberName , signalArgs :: [SignalArg] } deriving (Show, Eq) signal :: T.MemberName -> Signal signal name = Signal name [] data SignalArg = SignalArg { signalArgName :: String , signalArgType :: T.Type } deriving (Show, Eq) signalArg :: String -> T.Type -> SignalArg signalArg = SignalArg data Property = Property { propertyName :: String , propertyType :: T.Type , propertyRead :: Bool , propertyWrite :: Bool } deriving (Show, Eq) property :: String -> T.Type -> Property property name t = Property name t False False parseXML :: T.ObjectPath -> String -> Maybe Object parseXML path xml = do root <- parseElement (Data.Text.pack xml) parseRoot path root parseElement :: Text -> Maybe X.Element parseElement xml = runST $ do stackRef <- ST.newSTRef [([], [])] let onError _ = do ST.writeSTRef stackRef [] return False let onBegin _ attrs = do ST.modifySTRef stackRef ((attrs, []):) return True let onEnd name = do stack <- ST.readSTRef stackRef let (attrs, children'):stack' = stack let e = X.Element name attrs (map X.NodeElement (reverse children')) let (pAttrs, pChildren):stack'' = stack' let parent = (pAttrs, e:pChildren) ST.writeSTRef stackRef (parent:stack'') return True p <- SAX.newParserST Nothing SAX.setCallback p SAX.parsedBeginElement onBegin SAX.setCallback p SAX.parsedEndElement onEnd SAX.setCallback p SAX.reportError onError SAX.parseBytes p (Data.Text.Encoding.encodeUtf8 xml) SAX.parseComplete p stack <- ST.readSTRef stackRef return $ case stack of [] -> Nothing (_, children'):_ -> Just (head children') parseRoot :: T.ObjectPath -> X.Element -> Maybe Object parseRoot defaultPath e = do path <- case X.attributeText "name" e of Nothing -> Just defaultPath Just x -> T.parseObjectPath (Data.Text.unpack x) parseObject path e parseChild :: T.ObjectPath -> X.Element -> Maybe Object parseChild parentPath e = do let parentPath' = case T.formatObjectPath parentPath of "/" -> "/" x -> x ++ "/" pathSegment <- X.attributeText "name" e path <- T.parseObjectPath (parentPath' ++ Data.Text.unpack pathSegment) parseObject path e parseObject :: T.ObjectPath -> X.Element -> Maybe Object parseObject path e | X.elementName e == "node" = do interfaces <- children parseInterface (X.isNamed "interface") e children' <- children (parseChild path) (X.isNamed "node") e return (Object path interfaces children') parseObject _ _ = Nothing parseInterface :: X.Element -> Maybe Interface parseInterface e = do name <- T.parseInterfaceName =<< attributeString "name" e methods <- children parseMethod (X.isNamed "method") e signals <- children parseSignal (X.isNamed "signal") e properties <- children parseProperty (X.isNamed "property") e return (Interface name methods signals properties) parseMethod :: X.Element -> Maybe Method parseMethod e = do name <- T.parseMemberName =<< attributeString "name" e args <- children parseMethodArg (isArg ["in", "out", ""]) e return (Method name args) parseSignal :: X.Element -> Maybe Signal parseSignal e = do name <- T.parseMemberName =<< attributeString "name" e args <- children parseSignalArg (isArg ["out", ""]) e return (Signal name args) parseType :: X.Element -> Maybe T.Type parseType e = do typeStr <- attributeString "type" e sig <- T.parseSignature typeStr case T.signatureTypes sig of [t] -> Just t _ -> Nothing parseMethodArg :: X.Element -> Maybe MethodArg parseMethodArg e = do t <- parseType e let dir = case getattr "direction" e of "out" -> Out _ -> In Just (MethodArg (getattr "name" e) t dir) parseSignalArg :: X.Element -> Maybe SignalArg parseSignalArg e = do t <- parseType e Just (SignalArg (getattr "name" e) t) isArg :: [String] -> X.Element -> [X.Element] isArg dirs = X.isNamed "arg" >=> checkDir where checkDir e = [e | getattr "direction" e `elem` dirs] parseProperty :: X.Element -> Maybe Property parseProperty e = do t <- parseType e (canRead, canWrite) <- case getattr "access" e of "" -> Just (False, False) "read" -> Just (True, False) "write" -> Just (False, True) "readwrite" -> Just (True, True) _ -> Nothing Just (Property (getattr "name" e) t canRead canWrite) getattr :: X.Name -> X.Element -> String getattr name e = maybe "" Data.Text.unpack (X.attributeText name e) children :: Monad m => (X.Element -> m b) -> (X.Element -> [X.Element]) -> X.Element -> m [b] children f p = mapM f . concatMap p . X.elementChildren newtype XmlWriter a = XmlWriter { runXmlWriter :: Maybe (a, String) } instance Functor XmlWriter where fmap = liftM instance Control.Applicative.Applicative XmlWriter where pure = return (<*>) = ap instance Monad XmlWriter where return a = XmlWriter $ Just (a, "") m >>= f = XmlWriter $ do (a, w) <- runXmlWriter m (b, w') <- runXmlWriter (f a) return (b, w ++ w') tell :: String -> XmlWriter () tell s = XmlWriter (Just ((), s)) formatXML :: Object -> Maybe String formatXML obj = do (_, xml) <- runXmlWriter (writeRoot obj) return xml writeRoot :: Object -> XmlWriter () writeRoot obj@(Object path _ _) = do tell "\n" writeObject (T.formatObjectPath path) obj writeChild :: T.ObjectPath -> Object -> XmlWriter () writeChild parentPath obj@(Object path _ _) = write where path' = T.formatObjectPath path parent' = T.formatObjectPath parentPath relpathM = if parent' `isPrefixOf` path' then Just $ if parent' == "/" then drop 1 path' else drop (length parent' + 1) path' else Nothing write = case relpathM of Just relpath -> writeObject relpath obj Nothing -> XmlWriter Nothing writeObject :: String -> Object -> XmlWriter () writeObject path (Object fullPath interfaces children') = writeElement "node" [("name", path)] $ do mapM_ writeInterface interfaces mapM_ (writeChild fullPath) children' writeInterface :: Interface -> XmlWriter () writeInterface (Interface name methods signals properties) = writeElement "interface" [("name", T.formatInterfaceName name)] $ do mapM_ writeMethod methods mapM_ writeSignal signals mapM_ writeProperty properties writeMethod :: Method -> XmlWriter () writeMethod (Method name args) = writeElement "method" [("name", T.formatMemberName name)] $ do mapM_ writeMethodArg args writeSignal :: Signal -> XmlWriter () writeSignal (Signal name args) = writeElement "signal" [("name", T.formatMemberName name)] $ do mapM_ writeSignalArg args formatType :: T.Type -> XmlWriter String formatType t = do sig <- case T.signature [t] of Just x -> return x Nothing -> XmlWriter Nothing return (T.formatSignature sig) writeMethodArg :: MethodArg -> XmlWriter () writeMethodArg (MethodArg name t dir) = do typeStr <- formatType t let dirAttr = case dir of In -> "in" Out -> "out" writeEmptyElement "arg" $ [ ("name", name) , ("type", typeStr) , ("direction", dirAttr) ] writeSignalArg :: SignalArg -> XmlWriter () writeSignalArg (SignalArg name t) = do typeStr <- formatType t writeEmptyElement "arg" $ [ ("name", name) , ("type", typeStr) ] writeProperty :: Property -> XmlWriter () writeProperty (Property name t canRead canWrite) = do typeStr <- formatType t let readS = if canRead then "read" else "" let writeS = if canWrite then "write" else "" writeEmptyElement "property" [ ("name", name) , ("type", typeStr) , ("access", readS ++ writeS) ] attributeString :: X.Name -> X.Element -> Maybe String attributeString name e = fmap Data.Text.unpack (X.attributeText name e) writeElement :: String -> [(String, String)] -> XmlWriter () -> XmlWriter () writeElement name attrs content = do tell "<" tell name mapM_ writeAttribute attrs tell ">" content tell "" writeEmptyElement :: String -> [(String, String)] -> XmlWriter () writeEmptyElement name attrs = do tell "<" tell name mapM_ writeAttribute attrs tell "/>" writeAttribute :: (String, String) -> XmlWriter () writeAttribute (name, content) = do tell " " tell name tell "='" tell (escape content) tell "'" escape :: String -> String escape = concatMap $ \c -> case c of '&' -> "&" '<' -> "<" '>' -> ">" '"' -> """ '\'' -> "'" _ -> [c] dbus-0.10.13/lib/DBus/Socket.hs0000644000000000000000000003375613073332436014210 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE TypeFamilies #-} -- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . -- | D-Bus sockets are used for communication between two peers. In this model, -- there is no \"bus\" or \"client\", simply two endpoints sending messages. -- -- Most users will want to use the "DBus.Client" module instead. module DBus.Socket ( -- * Sockets Socket , send , receive -- * Socket errors , SocketError , socketError , socketErrorMessage , socketErrorFatal , socketErrorAddress -- * Socket options , SocketOptions , socketAuthenticator , socketTransportOptions , defaultSocketOptions -- * Opening and closing sockets , open , openWith , close -- * Listening for connections , SocketListener , listen , listenWith , accept , closeListener , socketListenerAddress -- * Authentication , Authenticator , authenticator , authenticatorClient , authenticatorServer ) where import Prelude hiding (getLine) import Control.Concurrent import Control.Exception import Control.Monad (mplus) import qualified Data.ByteString import qualified Data.ByteString.Char8 as Char8 import Data.Char (ord) import Data.IORef import Data.List (isPrefixOf) import Data.Typeable (Typeable) import qualified System.Posix.User import Text.Printf (printf) import DBus import DBus.Transport import DBus.Internal.Wire (unmarshalMessageM) -- | Stores information about an error encountered while creating or using a -- 'Socket'. data SocketError = SocketError { socketErrorMessage :: String , socketErrorFatal :: Bool , socketErrorAddress :: Maybe Address } deriving (Eq, Show, Typeable) instance Exception SocketError socketError :: String -> SocketError socketError msg = SocketError msg True Nothing data SomeTransport = forall t. (Transport t) => SomeTransport t instance Transport SomeTransport where data TransportOptions SomeTransport = SomeTransportOptions transportDefaultOptions = SomeTransportOptions transportPut (SomeTransport t) = transportPut t transportGet (SomeTransport t) = transportGet t transportClose (SomeTransport t) = transportClose t -- | An open socket to another process. Messages can be sent to the remote -- peer using 'send', or received using 'receive'. data Socket = Socket { socketTransport :: SomeTransport , socketAddress :: Maybe Address , socketSerial :: IORef Serial , socketReadLock :: MVar () , socketWriteLock :: MVar () } -- | An Authenticator defines how the local peer (client) authenticates -- itself to the remote peer (server). data Authenticator t = Authenticator { -- | Defines the client-side half of an authenticator. authenticatorClient :: t -> IO Bool -- | Defines the server-side half of an authenticator. The UUID is -- allocated by the socket listener. , authenticatorServer :: t -> UUID -> IO Bool } -- | Used with 'openWith' and 'listenWith' to provide custom authenticators or -- transport options. data SocketOptions t = SocketOptions { -- | Used to perform authentication with the remote peer. After a -- transport has been opened, it will be passed to the authenticator. -- If the authenticator returns true, then the socket was -- authenticated. socketAuthenticator :: Authenticator t -- | Options for the underlying transport, to be used by custom transports -- for controlling how to connect to the remote peer. -- -- See "DBus.Transport" for details on defining custom transports , socketTransportOptions :: TransportOptions t } -- | Default 'SocketOptions', which uses the default Unix/TCP transport and -- authenticator. defaultSocketOptions :: SocketOptions SocketTransport defaultSocketOptions = SocketOptions { socketTransportOptions = transportDefaultOptions , socketAuthenticator = authExternal } -- | Open a socket to a remote peer listening at the given address. -- -- @ --open = 'openWith' 'defaultSocketOptions' -- @ -- -- Throws 'SocketError' on failure. open :: Address -> IO Socket open = openWith defaultSocketOptions -- | Open a socket to a remote peer listening at the given address. -- -- Most users should use 'open'. This function is for users who need to define -- custom authenticators or transports. -- -- Throws 'SocketError' on failure. openWith :: TransportOpen t => SocketOptions t -> Address -> IO Socket openWith opts addr = toSocketError (Just addr) $ bracketOnError (transportOpen (socketTransportOptions opts) addr) transportClose (\t -> do authed <- authenticatorClient (socketAuthenticator opts) t if not authed then throwIO (socketError "Authentication failed") { socketErrorAddress = Just addr } else do serial <- newIORef firstSerial readLock <- newMVar () writeLock <- newMVar () return (Socket (SomeTransport t) (Just addr) serial readLock writeLock)) data SocketListener = forall t. (TransportListen t) => SocketListener (TransportListener t) (Authenticator t) -- | Begin listening at the given address. -- -- Use 'accept' to create sockets from incoming connections. -- -- Use 'closeListener' to stop listening, and to free underlying transport -- resources such as file descriptors. -- -- Throws 'SocketError' on failure. listen :: Address -> IO SocketListener listen = listenWith defaultSocketOptions -- | Begin listening at the given address. -- -- Use 'accept' to create sockets from incoming connections. -- -- Use 'closeListener' to stop listening, and to free underlying transport -- resources such as file descriptors. -- -- This function is for users who need to define custom authenticators -- or transports. -- -- Throws 'SocketError' on failure. listenWith :: TransportListen t => SocketOptions t -> Address -> IO SocketListener listenWith opts addr = toSocketError (Just addr) $ bracketOnError (transportListen (socketTransportOptions opts) addr) transportListenerClose (\l -> return (SocketListener l (socketAuthenticator opts))) -- | Accept a new connection from a socket listener. -- -- Throws 'SocketError' on failure. accept :: SocketListener -> IO Socket accept (SocketListener l auth) = toSocketError Nothing $ bracketOnError (transportAccept l) transportClose (\t -> do let uuid = transportListenerUUID l authed <- authenticatorServer auth t uuid if not authed then throwIO (socketError "Authentication failed") else do serial <- newIORef firstSerial readLock <- newMVar () writeLock <- newMVar () return (Socket (SomeTransport t) Nothing serial readLock writeLock)) -- | Close an open 'Socket'. Once closed, the socket is no longer valid and -- must not be used. close :: Socket -> IO () close = transportClose . socketTransport -- | Close an open 'SocketListener'. Once closed, the listener is no longer -- valid and must not be used. closeListener :: SocketListener -> IO () closeListener (SocketListener l _) = transportListenerClose l -- | Get the address to use to connect to a listener. socketListenerAddress :: SocketListener -> Address socketListenerAddress (SocketListener l _) = transportListenerAddress l -- | Send a single message, with a generated 'Serial'. The second parameter -- exists to prevent race conditions when registering a reply handler; it -- receives the serial the message /will/ be sent with, before it's -- actually sent. -- -- Sockets are thread-safe. Only one message may be sent at a time; if -- multiple threads attempt to send messages concurrently, one will block -- until after the other has finished. -- -- Throws 'SocketError' on failure. send :: Message msg => Socket -> msg -> (Serial -> IO a) -> IO a send sock msg io = toSocketError (socketAddress sock) $ do serial <- nextSocketSerial sock case marshal LittleEndian serial msg of Right bytes -> do let t = socketTransport sock a <- io serial withMVar (socketWriteLock sock) (\_ -> transportPut t bytes) return a Left err -> throwIO (socketError ("Message cannot be sent: " ++ show err)) { socketErrorFatal = False } nextSocketSerial :: Socket -> IO Serial nextSocketSerial sock = atomicModifyIORef (socketSerial sock) (\x -> (nextSerial x, x)) -- | Receive the next message from the socket , blocking until one is available. -- -- Sockets are thread-safe. Only one message may be received at a time; if -- multiple threads attempt to receive messages concurrently, one will block -- until after the other has finished. -- -- Throws 'SocketError' on failure. receive :: Socket -> IO ReceivedMessage receive sock = toSocketError (socketAddress sock) $ do -- TODO: after reading the length, read all bytes from the -- handle, then return a closure to perform the parse -- outside of the lock. let t = socketTransport sock let get n = if n == 0 then return Data.ByteString.empty else transportGet t n received <- withMVar (socketReadLock sock) (\_ -> unmarshalMessageM get) case received of Left err -> throwIO (socketError ("Error reading message from socket: " ++ show err)) Right msg -> return msg toSocketError :: Maybe Address -> IO a -> IO a toSocketError addr io = catches io handlers where handlers = [ Handler catchTransportError , Handler updateSocketError , Handler catchIOException ] catchTransportError err = throwIO (socketError (transportErrorMessage err)) { socketErrorAddress = addr } updateSocketError err = throwIO err { socketErrorAddress = mplus (socketErrorAddress err) addr } catchIOException exc = throwIO (socketError (show (exc :: IOException))) { socketErrorAddress = addr } -- | An empty authenticator. Use 'authenticatorClient' or 'authenticatorServer' -- to control how the authentication is performed. -- -- @ --myAuthenticator :: Authenticator MyTransport --myAuthenticator = authenticator -- { 'authenticatorClient' = clientMyAuth -- , 'authenticatorServer' = serverMyAuth -- } -- --clientMyAuth :: MyTransport -> IO Bool --serverMyAuth :: MyTransport -> String -> IO Bool -- @ authenticator :: Authenticator t authenticator = Authenticator (\_ -> return False) (\_ _ -> return False) -- | Implements the D-Bus @EXTERNAL@ mechanism, which uses credential -- passing over a Unix socket. authExternal :: Authenticator SocketTransport authExternal = authenticator { authenticatorClient = clientAuthExternal , authenticatorServer = serverAuthExternal } clientAuthExternal :: SocketTransport -> IO Bool clientAuthExternal t = do transportPut t (Data.ByteString.pack [0]) uid <- System.Posix.User.getRealUserID let token = concatMap (printf "%02X" . ord) (show uid) transportPutLine t ("AUTH EXTERNAL " ++ token) resp <- transportGetLine t case splitPrefix "OK " resp of Just _ -> do transportPutLine t "BEGIN" return True Nothing -> return False serverAuthExternal :: SocketTransport -> UUID -> IO Bool serverAuthExternal t uuid = do let waitForBegin = do resp <- transportGetLine t if resp == "BEGIN" then return () else waitForBegin let checkToken token = do (_, uid, _) <- socketTransportCredentials t let wantToken = concatMap (printf "%02X" . ord) (show uid) if token == wantToken then do transportPutLine t ("OK " ++ formatUUID uuid) waitForBegin return True else return False c <- transportGet t 1 if c /= Char8.pack "\x00" then return False else do line <- transportGetLine t case splitPrefix "AUTH EXTERNAL " line of Just token -> checkToken token Nothing -> if line == "AUTH EXTERNAL" then do dataLine <- transportGetLine t case splitPrefix "DATA " dataLine of Just token -> checkToken token Nothing -> return False else return False transportPutLine :: Transport t => t -> String -> IO () transportPutLine t line = transportPut t (Char8.pack (line ++ "\r\n")) transportGetLine :: Transport t => t -> IO String transportGetLine t = do let getchr = Char8.head `fmap` transportGet t 1 raw <- readUntil "\r\n" getchr return (dropEnd 2 raw) -- | Drop /n/ items from the end of a list dropEnd :: Int -> [a] -> [a] dropEnd n xs = take (length xs - n) xs splitPrefix :: String -> String -> Maybe String splitPrefix prefix str = if isPrefixOf prefix str then Just (drop (length prefix) str) else Nothing -- | Read values from a monad until a guard value is read; return all -- values, including the guard. readUntil :: (Monad m, Eq a) => [a] -> m a -> m [a] readUntil guard getx = readUntil' [] where guard' = reverse guard step xs | isPrefixOf guard' xs = return (reverse xs) | otherwise = readUntil' xs readUntil' xs = do x <- getx step (x:xs) dbus-0.10.13/lib/DBus/Transport.hs0000644000000000000000000004173313073332436014746 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE TypeFamilies #-} -- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . -- | Support for defining custom transport mechanisms. Most users will not -- need to care about the types defined in this module. module DBus.Transport ( -- * Transports Transport(..) , TransportOpen(..) , TransportListen(..) -- * Transport errors , TransportError , transportError , transportErrorMessage , transportErrorAddress -- * Socket transport , SocketTransport , socketTransportOptionBacklog , socketTransportCredentials ) where import Control.Exception import qualified Data.ByteString import Data.ByteString (ByteString) import qualified Data.ByteString.Builder as Builder import qualified Data.ByteString.Lazy as Lazy import qualified Data.Map as Map import Data.Monoid import Data.Typeable (Typeable) import Foreign.C (CUInt) import Network.Socket hiding (recv) import Network.Socket.ByteString (sendAll, recv) import qualified System.Info import Prelude import DBus -- | Thrown from transport methods when an error occurs. data TransportError = TransportError { transportErrorMessage :: String , transportErrorAddress :: Maybe Address } deriving (Eq, Show, Typeable) instance Exception TransportError transportError :: String -> TransportError transportError msg = TransportError msg Nothing -- | A 'Transport' can exchange bytes with a remote peer. class Transport t where -- | Additional options that this transport type may use when establishing -- a connection. data TransportOptions t :: * -- | Default values for this transport's options. transportDefaultOptions :: TransportOptions t -- | Send a 'ByteString' over the transport. -- -- Throws a 'TransportError' if an error occurs. transportPut :: t -> ByteString -> IO () -- | Receive a 'ByteString' of the given size from the transport. The -- transport should block until sufficient bytes are available, and -- only return fewer than the requested amount if there will not be -- any more data. -- -- Throws a 'TransportError' if an error occurs. transportGet :: t -> Int -> IO ByteString -- | Close an open transport, and release any associated resources -- or handles. transportClose :: t -> IO () -- | A 'Transport' which can open a connection to a remote peer. class Transport t => TransportOpen t where -- | Open a connection to the given address, using the given options. -- -- Throws a 'TransportError' if the connection could not be -- established. transportOpen :: TransportOptions t -> Address -> IO t -- | A 'Transport' which can listen for and accept connections from remote -- peers. class Transport t => TransportListen t where -- | Used for transports that listen on a port or address. data TransportListener t :: * -- | Begin listening for connections on the given address, using the -- given options. -- -- Throws a 'TransportError' if it's not possible to listen at that -- address (for example, if the port is already in use). transportListen :: TransportOptions t -> Address -> IO (TransportListener t) -- | Accept a new connection. -- -- Throws a 'TransportError' if some error happens before the -- transport is ready to exchange bytes. transportAccept :: TransportListener t -> IO t -- | Close an open listener. transportListenerClose :: TransportListener t -> IO () -- | Get the address to use to connect to a listener. transportListenerAddress :: TransportListener t -> Address -- | Get the UUID allocated to this transport listener. -- -- See 'randomUUID'. transportListenerUUID :: TransportListener t -> UUID -- | Supports connecting over Unix or TCP sockets. -- -- Unix sockets are similar to pipes, but exist as special files in the -- filesystem. On Linux, /abstract sockets/ have a path-like address, but do -- not actually have entries in the filesystem. -- -- TCP sockets may use either IPv4 or IPv6. data SocketTransport = SocketTransport (Maybe Address) Socket instance Transport SocketTransport where data TransportOptions SocketTransport = SocketTransportOptions { -- | The maximum size of the connection queue for a listening -- socket. socketTransportOptionBacklog :: Int } transportDefaultOptions = SocketTransportOptions 30 transportPut (SocketTransport addr s) bytes = catchIOException addr (sendAll s bytes) transportGet (SocketTransport addr s) n = catchIOException addr (recvLoop s n) transportClose (SocketTransport addr s) = catchIOException addr (close s) recvLoop :: Socket -> Int -> IO ByteString recvLoop s = \n -> Lazy.toStrict `fmap` loop mempty n where chunkSize = 4096 loop acc n = if n > chunkSize then do chunk <- recv s chunkSize let builder = mappend acc (Builder.byteString chunk) loop builder (n - Data.ByteString.length chunk) else do chunk <- recv s n case Data.ByteString.length chunk of -- Unexpected end of connection; maybe the remote end went away. -- Return what we've got so far. 0 -> return (Builder.toLazyByteString acc) len -> do let builder = mappend acc (Builder.byteString chunk) if len == n then return (Builder.toLazyByteString builder) else loop builder (n - Data.ByteString.length chunk) instance TransportOpen SocketTransport where transportOpen _ a = case addressMethod a of "unix" -> openUnix a "tcp" -> openTcp a method -> throwIO (transportError ("Unknown address method: " ++ show method)) { transportErrorAddress = Just a } instance TransportListen SocketTransport where data TransportListener SocketTransport = SocketTransportListener Address UUID Socket transportListen opts a = do uuid <- randomUUID (a', sock) <- case addressMethod a of "unix" -> listenUnix uuid a opts "tcp" -> listenTcp uuid a opts method -> throwIO (transportError ("Unknown address method: " ++ show method)) { transportErrorAddress = Just a } return (SocketTransportListener a' uuid sock) transportAccept (SocketTransportListener a _ s) = catchIOException (Just a) $ do (s', _) <- accept s return (SocketTransport Nothing s') transportListenerClose (SocketTransportListener a _ s) = catchIOException (Just a) (close s) transportListenerAddress (SocketTransportListener a _ _) = a transportListenerUUID (SocketTransportListener _ uuid _) = uuid -- | Returns the processID, userID, and groupID of the socket's peer. -- -- See 'getPeerCred'. socketTransportCredentials :: SocketTransport -> IO (CUInt, CUInt, CUInt) socketTransportCredentials (SocketTransport a s) = catchIOException a (getPeerCred s) openUnix :: Address -> IO SocketTransport openUnix transportAddr = go where params = addressParameters transportAddr param key = Map.lookup key params tooMany = "Only one of 'path' or 'abstract' may be specified for the\ \ 'unix' transport." tooFew = "One of 'path' or 'abstract' must be specified for the\ \ 'unix' transport." path = case (param "path", param "abstract") of (Just x, Nothing) -> Right x (Nothing, Just x) -> Right ('\x00' : x) (Nothing, Nothing) -> Left tooFew _ -> Left tooMany go = case path of Left err -> throwIO (transportError err) { transportErrorAddress = Just transportAddr } Right p -> catchIOException (Just transportAddr) $ bracketOnError (socket AF_UNIX Stream defaultProtocol) close (\sock -> do connect sock (SockAddrUnix p) return (SocketTransport (Just transportAddr) sock)) tcpHostname :: Maybe String -> Either a Network.Socket.Family -> String tcpHostname (Just host) _ = host tcpHostname Nothing (Right AF_INET) = "127.0.0.1" tcpHostname Nothing (Right AF_INET6) = "::1" tcpHostname _ _ = "localhost" openTcp :: Address -> IO SocketTransport openTcp transportAddr = go where params = addressParameters transportAddr param key = Map.lookup key params hostname = tcpHostname (param "host") getFamily unknownFamily x = "Unknown socket family for TCP transport: " ++ show x getFamily = case param "family" of Just "ipv4" -> Right AF_INET Just "ipv6" -> Right AF_INET6 Nothing -> Right AF_UNSPEC Just x -> Left (unknownFamily x) missingPort = "TCP transport requires the `port' parameter." badPort x = "Invalid socket port for TCP transport: " ++ show x getPort = case param "port" of Nothing -> Left missingPort Just x -> case readPortNumber x of Just port -> Right port Nothing -> Left (badPort x) getAddresses family_ = getAddrInfo (Just (defaultHints { addrFlags = [AI_ADDRCONFIG] , addrFamily = family_ , addrSocketType = Stream })) (Just hostname) Nothing openSocket [] = throwIO (transportError "openTcp: no addresses") { transportErrorAddress = Just transportAddr } openSocket (addr:addrs) = do tried <- Control.Exception.try $ bracketOnError (socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr)) close (\sock -> do connect sock (addrAddress addr) return sock) case tried of Left err -> case addrs of [] -> throwIO (transportError (show (err :: IOException))) { transportErrorAddress = Just transportAddr } _ -> openSocket addrs Right sock -> return sock go = case getPort of Left err -> throwIO (transportError err) { transportErrorAddress = Just transportAddr } Right port -> case getFamily of Left err -> throwIO (transportError err) { transportErrorAddress = Just transportAddr } Right family_ -> catchIOException (Just transportAddr) $ do addrs <- getAddresses family_ sock <- openSocket (map (setPort port) addrs) return (SocketTransport (Just transportAddr) sock) listenUnix :: UUID -> Address -> TransportOptions SocketTransport -> IO (Address, Socket) listenUnix uuid origAddr opts = getPath >>= go where params = addressParameters origAddr param key = Map.lookup key params tooMany = "Only one of 'abstract', 'path', or 'tmpdir' may be\ \ specified for the 'unix' transport." tooFew = "One of 'abstract', 'path', or 'tmpdir' must be specified\ \ for the 'unix' transport." getPath = case (param "abstract", param "path", param "tmpdir") of (Just path, Nothing, Nothing) -> let addr = address_ "unix" [ ("abstract", path) , ("guid", formatUUID uuid) ] in return (Right (addr, '\x00' : path)) (Nothing, Just path, Nothing) -> let addr = address_ "unix" [ ("path", path) , ("guid", formatUUID uuid) ] in return (Right (addr, path)) (Nothing, Nothing, Just x) -> do let fileName = x ++ "/haskell-dbus-" ++ formatUUID uuid -- Abstract paths are supported on Linux, but not on -- other Unix-like systems. let (addrParams, path) = if System.Info.os == "linux" then ([("abstract", fileName)], '\x00' : fileName) else ([("path", fileName)], fileName) let addr = address_ "unix" (addrParams ++ [("guid", formatUUID uuid)]) return (Right (addr, path)) (Nothing, Nothing, Nothing) -> return (Left tooFew) _ -> return (Left tooMany) go path = case path of Left err -> throwIO (transportError err) { transportErrorAddress = Just origAddr } Right (addr, p) -> catchIOException (Just origAddr) $ bracketOnError (socket AF_UNIX Stream defaultProtocol) close (\sock -> do bind sock (SockAddrUnix p) Network.Socket.listen sock (socketTransportOptionBacklog opts) return (addr, sock)) listenTcp :: UUID -> Address -> TransportOptions SocketTransport -> IO (Address, Socket) listenTcp uuid origAddr opts = go where params = addressParameters origAddr param key = Map.lookup key params unknownFamily x = "Unknown socket family for TCP transport: " ++ show x getFamily = case param "family" of Just "ipv4" -> Right AF_INET Just "ipv6" -> Right AF_INET6 Nothing -> Right AF_UNSPEC Just x -> Left (unknownFamily x) badPort x = "Invalid socket port for TCP transport: " ++ show x getPort = case param "port" of Nothing -> Right 0 Just x -> case readPortNumber x of Just port -> Right port Nothing -> Left (badPort x) paramBind = case param "bind" of Just "*" -> Nothing Just x -> Just x Nothing -> Just (tcpHostname (param "host") getFamily) getAddresses family_ = getAddrInfo (Just (defaultHints { addrFlags = [AI_ADDRCONFIG, AI_PASSIVE] , addrFamily = family_ , addrSocketType = Stream })) paramBind Nothing bindAddrs _ [] = throwIO (transportError "listenTcp: no addresses") { transportErrorAddress = Just origAddr } bindAddrs sock (addr:addrs) = do tried <- Control.Exception.try (bind sock (addrAddress addr)) case tried of Left err -> case addrs of [] -> throwIO (transportError (show (err :: IOException))) { transportErrorAddress = Just origAddr } _ -> bindAddrs sock addrs Right _ -> return () sockAddr port = address_ "tcp" p where p = baseParams ++ hostParam ++ familyParam baseParams = [ ("port", show port) , ("guid", formatUUID uuid) ] hostParam = case param "host" of Just x -> [("host", x)] Nothing -> [] familyParam = case param "family" of Just x -> [("family", x)] Nothing -> [] go = case getPort of Left err -> throwIO (transportError err) { transportErrorAddress = Just origAddr } Right port -> case getFamily of Left err -> throwIO (transportError err) { transportErrorAddress = Just origAddr } Right family_ -> catchIOException (Just origAddr) $ do sockAddrs <- getAddresses family_ bracketOnError (socket family_ Stream defaultProtocol) close (\sock -> do setSocketOption sock ReuseAddr 1 bindAddrs sock (map (setPort port) sockAddrs) Network.Socket.listen sock (socketTransportOptionBacklog opts) sockPort <- socketPort sock return (sockAddr sockPort, sock)) catchIOException :: Maybe Address -> IO a -> IO a catchIOException addr io = do tried <- try io case tried of Right a -> return a Left err -> throwIO (transportError (show (err :: IOException))) { transportErrorAddress = addr } address_ :: String -> [(String, String)] -> Address address_ method params = addr where Just addr = address method (Map.fromList params) setPort :: PortNumber -> AddrInfo -> AddrInfo setPort port info = case addrAddress info of (SockAddrInet _ x) -> info { addrAddress = SockAddrInet port x } (SockAddrInet6 _ x y z) -> info { addrAddress = SockAddrInet6 port x y z } _ -> info readPortNumber :: String -> Maybe PortNumber readPortNumber s = do case dropWhile (\c -> c >= '0' && c <= '9') s of [] -> return () _ -> Nothing let word = read s :: Integer if word > 0 && word <= 65535 then Just (fromInteger word) else Nothing dbus-0.10.13/lib/DBus/Internal/Address.hs0000644000000000000000000001374013073332436016110 0ustar0000000000000000-- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBus.Internal.Address where import qualified Control.Exception import Data.Char (digitToInt, ord, chr) import Data.List (intercalate) import qualified Data.Map import Data.Map (Map) import qualified System.Environment import Text.Printf (printf) import Text.ParserCombinators.Parsec -- | When a D-Bus server must listen for connections, or a client must connect -- to a server, the listening socket's configuration is specified with an -- /address/. An address contains the /method/, which determines the -- protocol and transport mechanism, and /parameters/, which provide -- additional method-specific information about the address. data Address = Address String (Map String String) deriving (Eq) addressMethod :: Address -> String addressMethod (Address x _ ) = x addressParameters :: Address -> Map String String addressParameters (Address _ x) = x -- | Try to convert a method string and parameter map to an 'Address'. -- -- Returns 'Nothing' if the method or parameters are invalid. address :: String -> Map String String -> Maybe Address address method params = if validMethod method && validParams params then if null method && Data.Map.null params then Nothing else Just (Address method params) else Nothing validMethod :: String -> Bool validMethod = all validChar where validChar c = c /= ';' && c /= ':' validParams :: Map String String -> Bool validParams = all validItem . Data.Map.toList where validItem (k, v) = notNull k && notNull v && validKey k validKey = all validChar validChar c = c /= ';' && c /= ',' && c /= '=' notNull = not . null optionallyEncoded :: [Char] optionallyEncoded = concat [ ['0'..'9'] , ['a'..'z'] , ['A'..'Z'] , ['-', '_', '/', '\\', '*', '.'] ] -- | Convert an address to a string in the format expected by 'parseAddress'. formatAddress :: Address -> String formatAddress (Address method params) = concat [method, ":", csvParams] where csvParams = intercalate "," $ do (k, v) <- Data.Map.toList params let v' = concatMap escape v return (concat [k, "=", v']) escape c = if elem c optionallyEncoded then [c] else printf "%%%02X" (ord c) -- | Convert a list of addresses to a string in the format expected by -- 'parseAddresses'. formatAddresses :: [Address] -> String formatAddresses = intercalate ";" . map formatAddress instance Show Address where showsPrec d x = showParen (d > 10) $ showString "Address " . shows (formatAddress x) -- | Try to parse a string containing one valid address. -- -- An address string is in the format @method:key1=val1,key2=val2@. There -- are some limitations on the characters allowed within methods and -- parameters; see the D-Bus specification for full details. parseAddress :: String -> Maybe Address parseAddress = maybeParseString $ do addr <- parsecAddress eof return addr -- | Try to parse a string containing one or more valid addresses. -- -- Addresses are separated by semicolons. See 'parseAddress' for the format -- of addresses. parseAddresses :: String -> Maybe [Address] parseAddresses = maybeParseString $ do addrs <- sepEndBy parsecAddress (char ';') eof return addrs parsecAddress :: Parser Address parsecAddress = p where p = do method <- many (noneOf ":;") _ <- char ':' params <- sepEndBy param (char ',') return (Address method (Data.Map.fromList params)) param = do key <- many1 (noneOf "=;,") _ <- char '=' value <- many1 valueChar return (key, value) valueChar = encoded <|> unencoded encoded = do _ <- char '%' hex <- count 2 hexDigit return (chr (hexToInt hex)) unencoded = oneOf optionallyEncoded -- | Returns the address in the environment variable -- @DBUS_SYSTEM_BUS_ADDRESS@, or -- @unix:path=\/var\/run\/dbus\/system_bus_socket@ if @DBUS_SYSTEM_BUS_ADDRESS@ -- is not set. -- -- Returns 'Nothing' if @DBUS_SYSTEM_BUS_ADDRESS@ contains an invalid address. getSystemAddress :: IO (Maybe Address) getSystemAddress = do let system = "unix:path=/var/run/dbus/system_bus_socket" env <- getenv "DBUS_SYSTEM_BUS_ADDRESS" return (parseAddress (maybe system id env)) -- | Returns the address in the environment variable -- @DBUS_SESSION_BUS_ADDRESS@, which must be set. -- -- Returns 'Nothing' if @DBUS_SYSTEM_BUS_ADDRESS@ is unset or contains an -- invalid address. getSessionAddress :: IO (Maybe Address) getSessionAddress = do env <- getenv "DBUS_SESSION_BUS_ADDRESS" return (env >>= parseAddress) -- | Returns the address in the environment variable -- @DBUS_STARTER_ADDRESS@, which must be set. -- -- Returns 'Nothing' if @DBUS_STARTER_ADDRESS@ is unset or contains an -- invalid address. getStarterAddress :: IO (Maybe Address) getStarterAddress = do env <- getenv "DBUS_STARTER_ADDRESS" return (env >>= parseAddress) getenv :: String -> IO (Maybe String) getenv name = Control.Exception.catch (fmap Just (System.Environment.getEnv name)) (\(Control.Exception.SomeException _) -> return Nothing) hexToInt :: String -> Int hexToInt = foldl ((+) . (16 *)) 0 . map digitToInt maybeParseString :: Parser a -> String -> Maybe a maybeParseString p str = case runParser p () "" str of Left _ -> Nothing Right a -> Just a dbus-0.10.13/lib/DBus/Internal/Message.hs0000644000000000000000000002504113073332436016104 0ustar0000000000000000-- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBus.Internal.Message ( Message(..) , UnknownMessage(..) , MethodCall(..) , MethodReturn(..) , MethodError(..) , methodErrorMessage , Signal(..) , ReceivedMessage(..) -- for use in Wire , HeaderField(..) , setMethodCallFlags ) where import Data.Bits ((.|.), (.&.)) import Data.Maybe (fromMaybe, listToMaybe) import Data.Word (Word8, Word32) import DBus.Internal.Types class Message a where messageTypeCode :: a -> Word8 messageHeaderFields :: a -> [HeaderField] messageBody :: a -> [Variant] messageFlags :: a -> Word8 messageFlags _ = 0 maybe' :: (a -> b) -> Maybe a -> [b] maybe' f = maybe [] (\x' -> [f x']) data UnknownMessage = UnknownMessage { unknownMessageType :: Word8 , unknownMessageSender :: Maybe BusName , unknownMessageBody :: [Variant] } deriving (Show, Eq) data HeaderField = HeaderPath ObjectPath | HeaderInterface InterfaceName | HeaderMember MemberName | HeaderErrorName ErrorName | HeaderReplySerial Serial | HeaderDestination BusName | HeaderSender BusName | HeaderSignature Signature | HeaderUnixFds Word32 deriving (Show, Eq) -- | A method call is a request to run some procedure exported by the -- remote process. Procedures are identified by an (object_path, -- interface_name, method_name) tuple. data MethodCall = MethodCall { -- | The object path of the method call. Conceptually, object paths -- act like a procedural language's pointers. Each object referenced -- by a path is a collection of procedures. methodCallPath :: ObjectPath -- | The interface of the method call. Each object may implement any -- number of interfaces. Each method is part of at least one -- interface. -- -- In certain cases, this may be @Nothing@, but most users should set -- it to a value. , methodCallInterface :: Maybe InterfaceName -- | The method name of the method call. Method names are unique within -- an interface, but might not be unique within an object. , methodCallMember :: MemberName -- | The name of the application that sent this call. -- -- Most users will just leave this empty, because the bus overwrites -- the sender for security reasons. Setting the sender manually is -- used for peer-peer connections. -- -- Defaults to @Nothing@. , methodCallSender :: Maybe BusName -- | The name of the application to send the call to. -- -- Most users should set this. If a message with no destination is -- sent to the bus, the bus will behave as if the destination was -- set to @org.freedesktop.DBus@. For peer-peer connections, the -- destination can be empty because there is only one peer. -- -- Defaults to @Nothing@. , methodCallDestination :: Maybe BusName -- | Set whether a reply is expected. This can save network and cpu -- resources by inhibiting unnecessary replies. -- -- Defaults to @True@. , methodCallReplyExpected :: Bool -- | Set whether the bus should auto-start the remote -- -- Defaults to @True@. , methodCallAutoStart :: Bool -- | The arguments to the method call. See 'toVariant'. -- -- Defaults to @[]@. , methodCallBody :: [Variant] } deriving (Eq, Show) setMethodCallFlags :: MethodCall -> Word8 -> MethodCall setMethodCallFlags c w = c { methodCallReplyExpected = w .&. 0x1 == 0 , methodCallAutoStart = w .&. 0x2 == 0 } instance Message MethodCall where messageTypeCode _ = 1 messageFlags c = foldr (.|.) 0 [ if methodCallReplyExpected c then 0 else 0x1 , if methodCallAutoStart c then 0 else 0x2 ] messageBody = methodCallBody messageHeaderFields m = concat [ [ HeaderPath (methodCallPath m) , HeaderMember (methodCallMember m) ] , maybe' HeaderInterface (methodCallInterface m) , maybe' HeaderSender (methodCallSender m) , maybe' HeaderDestination (methodCallDestination m) ] -- | A method return is a reply to a method call, indicating that the call -- succeeded. data MethodReturn = MethodReturn { -- | The serial of the original method call. This lets the original -- caller match up this reply to the pending call. methodReturnSerial :: Serial -- | The name of the application that is returning from a call. -- -- Most users will just leave this empty, because the bus overwrites -- the sender for security reasons. Setting the sender manually is -- used for peer-peer connections. -- -- Defaults to @Nothing@. , methodReturnSender :: Maybe BusName -- | The name of the application that initiated the call. -- -- Most users should set this. If a message with no destination is -- sent to the bus, the bus will behave as if the destination was -- set to @org.freedesktop.DBus@. For peer-peer connections, the -- destination can be empty because there is only one peer. -- -- Defaults to @Nothing@. , methodReturnDestination :: Maybe BusName -- | Values returned from the method call. See 'toVariant'. -- -- Defaults to @[]@. , methodReturnBody :: [Variant] } deriving (Show, Eq) instance Message MethodReturn where messageTypeCode _ = 2 messageBody = methodReturnBody messageHeaderFields m = concat [ [ HeaderReplySerial (methodReturnSerial m) ] , maybe' HeaderSender (methodReturnSender m) , maybe' HeaderDestination (methodReturnDestination m) ] -- | A method error is a reply to a method call, indicating that the call -- received an error and did not succeed. data MethodError = MethodError { -- | The name of the error type. Names are used so clients can -- handle certain classes of error differently from others. methodErrorName :: ErrorName -- | The serial of the original method call. This lets the original -- caller match up this reply to the pending call. , methodErrorSerial :: Serial -- | The name of the application that is returning from a call. -- -- Most users will just leave this empty, because the bus overwrites -- the sender for security reasons. Setting the sender manually is -- used for peer-peer connections. -- -- Defaults to @Nothing@. , methodErrorSender :: Maybe BusName -- | The name of the application that initiated the call. -- -- Most users should set this. If a message with no destination is -- sent to the bus, the bus will behave as if the destination was -- set to @org.freedesktop.DBus@. For peer-peer connections, the -- destination can be empty because there is only one peer. -- -- Defaults to @Nothing@. , methodErrorDestination :: Maybe BusName -- | Additional information about the error. By convention, if -- the error body contains any items, the first item should be a -- string describing the error. , methodErrorBody :: [Variant] } deriving (Show, Eq) instance Message MethodError where messageTypeCode _ = 3 messageBody = methodErrorBody messageHeaderFields m = concat [ [ HeaderErrorName (methodErrorName m) , HeaderReplySerial (methodErrorSerial m) ] , maybe' HeaderSender (methodErrorSender m) , maybe' HeaderDestination (methodErrorDestination m) ] -- | Get a human-readable description of the error, by returning the first -- item in the error body if it's a string. methodErrorMessage :: MethodError -> String methodErrorMessage err = fromMaybe "(no error message)" $ do field <- listToMaybe (methodErrorBody err) msg <- fromVariant field if null msg then Nothing else return msg -- | Signals are broadcast by applications to notify other clients of some -- event. data Signal = Signal { -- | The path of the object that emitted this signal. signalPath :: ObjectPath -- | The interface that this signal belongs to. , signalInterface :: InterfaceName -- | The name of this signal. , signalMember :: MemberName -- | The name of the application that emitted this signal. -- -- Most users will just leave this empty, because the bus overwrites -- the sender for security reasons. Setting the sender manually is -- used for peer-peer connections. -- -- Defaults to @Nothing@. , signalSender :: Maybe BusName -- | The name of the application to emit the signal to. If @Nothing@, -- the signal is sent to any application that has registered an -- appropriate match rule. -- -- Defaults to @Nothing@. , signalDestination :: Maybe BusName -- | Additional information about the signal, such as the new value -- or the time. -- -- Defaults to @[]@. , signalBody :: [Variant] } deriving (Show, Eq) instance Message Signal where messageTypeCode _ = 4 messageBody = signalBody messageHeaderFields m = concat [ [ HeaderPath (signalPath m) , HeaderMember (signalMember m) , HeaderInterface (signalInterface m) ] , maybe' HeaderSender (signalSender m) , maybe' HeaderDestination (signalDestination m) ] -- | Not an actual message type, but a wrapper around messages received from -- the bus. Each value contains the message's 'Serial'. -- -- If casing against these constructors, always include a default case to -- handle messages of an unknown type. New message types may be added to the -- D-Bus specification, and applications should handle them gracefully by -- either ignoring or logging them. data ReceivedMessage = ReceivedMethodCall Serial MethodCall | ReceivedMethodReturn Serial MethodReturn | ReceivedMethodError Serial MethodError | ReceivedSignal Serial Signal | ReceivedUnknown Serial UnknownMessage deriving (Show, Eq) dbus-0.10.13/lib/DBus/Internal/Types.hs0000644000000000000000000015536513073332436015641 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE IncoherentInstances #-} -- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBus.Internal.Types where import Control.Monad (liftM, when, (>=>)) import Control.Exception (Exception, handle, throwIO) import Data.ByteString (ByteString) import qualified Data.ByteString import qualified Data.ByteString.Char8 as Char8 import qualified Data.ByteString.Lazy import qualified Data.ByteString.Unsafe import Data.Char (ord) import Data.Int import Data.List (intercalate) import qualified Data.Map import Data.Map (Map) import qualified Data.String import qualified Data.Text import Data.Text (Text) import qualified Data.Text.Lazy import Data.Typeable (Typeable) import qualified Data.Vector import Data.Vector (Vector) import Data.Word import qualified Foreign import System.IO.Unsafe (unsafePerformIO) import System.Posix.Types (Fd) import qualified Text.ParserCombinators.Parsec as Parsec import Text.ParserCombinators.Parsec ((<|>), oneOf) data Type = TypeBoolean | TypeWord8 | TypeWord16 | TypeWord32 | TypeWord64 | TypeInt16 | TypeInt32 | TypeInt64 | TypeDouble | TypeUnixFd | TypeString | TypeSignature | TypeObjectPath | TypeVariant | TypeArray Type | TypeDictionary Type Type | TypeStructure [Type] deriving (Eq, Ord) instance Show Type where showsPrec d = showString . showType (d > 10) showType :: Bool -> Type -> String showType paren t = case t of TypeBoolean -> "Bool" TypeWord8 -> "Word8" TypeWord16 -> "Word16" TypeWord32 -> "Word32" TypeWord64 -> "Word64" TypeInt16 -> "Int16" TypeInt32 -> "Int32" TypeInt64 -> "Int64" TypeDouble -> "Double" TypeUnixFd -> "UnixFd" TypeString -> "String" TypeSignature -> "Signature" TypeObjectPath -> "ObjectPath" TypeVariant -> "Variant" TypeArray t' -> concat ["[", show t', "]"] TypeDictionary kt vt -> showParen paren ( showString "Dict " . shows kt . showString " " . showsPrec 11 vt) "" TypeStructure ts -> concat ["(", intercalate ", " (map show ts), ")"] -- | A signature is a list of D-Bus types, obeying some basic rules of -- validity. -- -- The rules of signature validity are complex: see -- -- for details. newtype Signature = Signature [Type] deriving (Eq, Ord) -- | Get the list of types in a signature. The inverse of 'signature'. signatureTypes :: Signature -> [Type] signatureTypes (Signature types) = types instance Show Signature where showsPrec d sig = showParen (d > 10) $ showString "Signature " . shows (formatSignature sig) -- | Convert a signature into a signature string. The inverse of -- 'parseSignature'. formatSignature :: Signature -> String formatSignature = concatMap typeCode . signatureTypes typeCode :: Type -> String typeCode TypeBoolean = "b" typeCode TypeWord8 = "y" typeCode TypeWord16 = "q" typeCode TypeWord32 = "u" typeCode TypeWord64 = "t" typeCode TypeInt16 = "n" typeCode TypeInt32 = "i" typeCode TypeInt64 = "x" typeCode TypeDouble = "d" typeCode TypeUnixFd = "h" typeCode TypeString = "s" typeCode TypeSignature = "g" typeCode TypeObjectPath = "o" typeCode TypeVariant = "v" typeCode (TypeArray t) = 'a' : typeCode t typeCode (TypeDictionary kt vt) = concat [ "a{", typeCode kt , typeCode vt, "}"] typeCode (TypeStructure ts) = concat ["(", concatMap typeCode ts, ")"] instance Data.String.IsString Signature where fromString = forceParse "signature" parseSignature -- | Convert a list of types into a valid signature. -- -- Returns @Nothing@ if the given types are not a valid signature. signature :: [Type] -> Maybe Signature signature = check where check ts = if sumLen ts > 255 then Nothing else Just (Signature ts) sumLen :: [Type] -> Int sumLen = sum . map len len (TypeArray t) = 1 + len t len (TypeDictionary kt vt) | typeIsAtomic kt = 3 + len kt + len vt | otherwise = 256 len (TypeStructure []) = 256 len (TypeStructure ts) = 2 + sumLen ts len _ = 1 typeIsAtomic TypeVariant = False typeIsAtomic TypeArray{} = False typeIsAtomic TypeDictionary{} = False typeIsAtomic TypeStructure{} = False typeIsAtomic _ = True -- | Convert a list of types into a valid signature. -- -- Throws an exception if the given types are not a valid signature. signature_ :: [Type] -> Signature signature_ ts = case signature ts of Just sig -> sig Nothing -> error ("invalid signature: " ++ show ts) -- | Parse a signature string into a valid signature. -- -- Returns @Nothing@ if the given string is not a valid signature. parseSignature :: String -> Maybe Signature parseSignature s = do when (length s > 255) Nothing when (any (\c -> ord c > 0x7F) s) Nothing parseSignatureBytes (Char8.pack s) parseSignatureBytes :: ByteString -> Maybe Signature parseSignatureBytes bytes = case Data.ByteString.length bytes of 0 -> Just (Signature []) 1 -> parseSigFast bytes len | len <= 255 -> parseSigFull bytes _ -> Nothing parseSigFast :: ByteString -> Maybe Signature parseSigFast bytes = let byte = Data.ByteString.Unsafe.unsafeHead bytes in parseAtom (fromIntegral byte) (\t -> Just (Signature [t])) (case byte of 0x76 -> Just (Signature [TypeVariant]) _ -> Nothing) parseAtom :: Int -> (Type -> a) -> a -> a parseAtom byte yes no = case byte of 0x62 -> yes TypeBoolean 0x6E -> yes TypeInt16 0x69 -> yes TypeInt32 0x78 -> yes TypeInt64 0x79 -> yes TypeWord8 0x71 -> yes TypeWord16 0x75 -> yes TypeWord32 0x74 -> yes TypeWord64 0x64 -> yes TypeDouble 0x68 -> yes TypeUnixFd 0x73 -> yes TypeString 0x67 -> yes TypeSignature 0x6F -> yes TypeObjectPath _ -> no {-# INLINE parseAtom #-} data SigParseError = SigParseError deriving (Show, Typeable) instance Exception SigParseError peekWord8AsInt :: Foreign.Ptr Word8 -> Int -> IO Int peekWord8AsInt ptr off = do w <- Foreign.peekElemOff ptr off return (fromIntegral w) parseSigFull :: ByteString -> Maybe Signature parseSigFull bytes = unsafePerformIO io where io = handle (\SigParseError -> return Nothing) $ Data.ByteString.Unsafe.unsafeUseAsCStringLen bytes $ \(ptr, len) -> do ts <- parseSigBuf (Foreign.castPtr ptr, len) return (Just (Signature ts)) parseSigBuf (buf, len) = mainLoop [] 0 where mainLoop acc ii | ii >= len = return (reverse acc) mainLoop acc ii = do c <- peekWord8AsInt buf ii let next t = mainLoop (t : acc) (ii + 1) parseAtom c next $ case c of 0x76 -> next TypeVariant 0x28 -> do -- '(' (ii', t) <- structure (ii + 1) mainLoop (t : acc) ii' 0x61 -> do -- 'a' (ii', t) <- array (ii + 1) mainLoop (t : acc) ii' _ -> throwIO SigParseError structure :: Int -> IO (Int, Type) structure = loop [] where loop _ ii | ii >= len = throwIO SigParseError loop acc ii = do c <- peekWord8AsInt buf ii let next t = loop (t : acc) (ii + 1) parseAtom c next $ case c of 0x76 -> next TypeVariant 0x28 -> do -- '(' (ii', t) <- structure (ii + 1) loop (t : acc) ii' 0x61 -> do -- 'a' (ii', t) <- array (ii + 1) loop (t : acc) ii' -- ')' 0x29 -> case acc of [] -> throwIO SigParseError _ -> return (ii + 1, TypeStructure (reverse acc)) _ -> throwIO SigParseError array :: Int -> IO (Int, Type) array ii | ii >= len = throwIO SigParseError array ii = do c <- peekWord8AsInt buf ii let next t = return (ii + 1, TypeArray t) parseAtom c next $ case c of 0x76 -> next TypeVariant 0x7B -> dict (ii + 1) -- '{' 0x28 -> do -- '(' (ii', t) <- structure (ii + 1) return (ii', TypeArray t) 0x61 -> do -- 'a' (ii', t) <- array (ii + 1) return (ii', TypeArray t) _ -> throwIO SigParseError dict :: Int -> IO (Int, Type) dict ii | ii + 1 >= len = throwIO SigParseError dict ii = do c1 <- peekWord8AsInt buf ii c2 <- peekWord8AsInt buf (ii + 1) let next t = return (ii + 2, t) (ii', t2) <- parseAtom c2 next $ case c2 of 0x76 -> next TypeVariant 0x28 -> structure (ii + 2) -- '(' 0x61 -> array (ii + 2) -- 'a' _ -> throwIO SigParseError if ii' >= len then throwIO SigParseError else do c3 <- peekWord8AsInt buf ii' if c3 == 0x7D then do t1 <- parseAtom c1 return (throwIO SigParseError) return (ii' + 1, TypeDictionary t1 t2) else throwIO SigParseError class IsVariant a where toVariant :: a -> Variant fromVariant :: Variant -> Maybe a -- | Value types can be used as items in containers, such as lists or -- dictionaries. -- -- Users may not provide new instances of 'IsValue' because this could allow -- containers to be created with items of heterogenous types. class IsVariant a => IsValue a where typeOf :: a -> Type toValue :: a -> Value fromValue :: Value -> Maybe a -- | Atomic types can be used as keys to dictionaries. -- -- Users may not provide new instances of 'IsAtom' because this could allow -- dictionaries to be created with invalid keys. class IsValue a => IsAtom a where toAtom :: a -> Atom fromAtom :: Atom -> Maybe a -- | 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. newtype Variant = Variant Value deriving (Eq) data Value = ValueAtom Atom | ValueVariant Variant | ValueBytes ByteString | ValueVector Type (Vector Value) | ValueMap Type Type (Map Atom Value) | ValueStructure [Value] deriving (Show) data Atom = AtomBool Bool | AtomWord8 Word8 | AtomWord16 Word16 | AtomWord32 Word32 | AtomWord64 Word64 | AtomInt16 Int16 | AtomInt32 Int32 | AtomInt64 Int64 | AtomDouble Double | AtomUnixFd Fd | AtomText Text | AtomSignature Signature | AtomObjectPath ObjectPath deriving (Show, Eq, Ord) instance Eq Value where (==) (ValueBytes x) y = case y of ValueBytes y' -> x == y' ValueVector TypeWord8 y' -> x == vectorToBytes y' _ -> False (==) (ValueVector TypeWord8 x) y = case y of ValueBytes y' -> vectorToBytes x == y' ValueVector TypeWord8 y' -> x == y' _ -> False (==) (ValueAtom x) (ValueAtom y) = x == y (==) (ValueVariant x) (ValueVariant y) = x == y (==) (ValueVector tx x) (ValueVector ty y) = tx == ty && x == y (==) (ValueMap ktx vtx x) (ValueMap kty vty y) = ktx == kty && vtx == vty && x == y (==) (ValueStructure x) (ValueStructure y) = x == y (==) _ _ = False showAtom :: Bool -> Atom -> String showAtom _ (AtomBool x) = show x showAtom _ (AtomWord8 x) = show x showAtom _ (AtomWord16 x) = show x showAtom _ (AtomWord32 x) = show x showAtom _ (AtomWord64 x) = show x showAtom _ (AtomInt16 x) = show x showAtom _ (AtomInt32 x) = show x showAtom _ (AtomInt64 x) = show x showAtom _ (AtomDouble x) = show x showAtom p (AtomUnixFd x) = showParen p (showString "UnixFd " . shows x) "" showAtom _ (AtomText x) = show x showAtom p (AtomSignature x) = showsPrec (if p then 11 else 0) x "" showAtom p (AtomObjectPath x) = showsPrec (if p then 11 else 0) x "" showValue :: Bool -> Value -> String showValue p (ValueAtom x) = showAtom p x showValue p (ValueVariant x) = showsPrec (if p then 11 else 0) x "" showValue _ (ValueBytes xs) = 'b' : show xs showValue _ (ValueVector TypeWord8 xs) = 'b' : show (vectorToBytes xs) showValue _ (ValueVector _ xs) = showThings "[" (showValue False) "]" (Data.Vector.toList xs) showValue _ (ValueMap _ _ xs) = showThings "{" showPair "}" (Data.Map.toList xs) where showPair (k, v) = showAtom False k ++ ": " ++ showValue False v showValue _ (ValueStructure xs) = showThings "(" (showValue False) ")" xs showThings :: String -> (a -> String) -> String -> [a] -> String showThings a s z xs = a ++ intercalate ", " (map s xs) ++ z vectorToBytes :: Vector Value -> ByteString vectorToBytes = Data.ByteString.pack . Data.Vector.toList . Data.Vector.map (\(ValueAtom (AtomWord8 x)) -> x) instance Show Variant where showsPrec d (Variant x) = showParen (d > 10) $ showString "Variant " . showString (showValue True x) -- | Every variant is strongly-typed; that is, the type of its contained -- value is known at all times. This function retrieves that type, so that -- the correct cast can be used to retrieve the value. variantType :: Variant -> Type variantType (Variant val) = valueType val valueType :: Value -> Type valueType (ValueAtom x) = atomType x valueType (ValueVariant _) = TypeVariant valueType (ValueVector t _) = TypeArray t valueType (ValueBytes _) = TypeArray TypeWord8 valueType (ValueMap kt vt _) = TypeDictionary kt vt valueType (ValueStructure vs) = TypeStructure (map valueType vs) atomType :: Atom -> Type atomType (AtomBool _) = TypeBoolean atomType (AtomWord8 _) = TypeWord8 atomType (AtomWord16 _) = TypeWord16 atomType (AtomWord32 _) = TypeWord32 atomType (AtomWord64 _) = TypeWord64 atomType (AtomInt16 _) = TypeInt16 atomType (AtomInt32 _) = TypeInt32 atomType (AtomInt64 _) = TypeInt64 atomType (AtomDouble _) = TypeDouble atomType (AtomUnixFd _) = TypeUnixFd atomType (AtomText _) = TypeString atomType (AtomSignature _) = TypeSignature atomType (AtomObjectPath _) = TypeObjectPath #define IS_ATOM(HsType, AtomCons, TypeCons) \ instance IsAtom HsType where \ { toAtom = AtomCons \ ; fromAtom (AtomCons x) = Just x \ ; fromAtom _ = Nothing \ }; \ instance IsValue HsType where \ { typeOf _ = TypeCons \ ; toValue = ValueAtom . toAtom \ ; fromValue (ValueAtom x) = fromAtom x \ ; fromValue _ = Nothing \ }; \ instance IsVariant HsType where \ { toVariant = Variant . toValue \ ; fromVariant (Variant val) = fromValue val \ } IS_ATOM(Bool, AtomBool, TypeBoolean) IS_ATOM(Word8, AtomWord8, TypeWord8) IS_ATOM(Word16, AtomWord16, TypeWord16) IS_ATOM(Word32, AtomWord32, TypeWord32) IS_ATOM(Word64, AtomWord64, TypeWord64) IS_ATOM(Int16, AtomInt16, TypeInt16) IS_ATOM(Int32, AtomInt32, TypeInt32) IS_ATOM(Int64, AtomInt64, TypeInt64) IS_ATOM(Double, AtomDouble, TypeDouble) IS_ATOM(Fd, AtomUnixFd, TypeUnixFd) IS_ATOM(Text, AtomText, TypeString) IS_ATOM(Signature, AtomSignature, TypeSignature) IS_ATOM(ObjectPath, AtomObjectPath, TypeObjectPath) instance IsValue Variant where typeOf _ = TypeVariant toValue = ValueVariant fromValue (ValueVariant x) = Just x fromValue _ = Nothing instance IsVariant Variant where toVariant = Variant . toValue fromVariant (Variant val) = fromValue val instance IsAtom Data.Text.Lazy.Text where toAtom = toAtom . Data.Text.Lazy.toStrict fromAtom = fmap Data.Text.Lazy.fromStrict . fromAtom instance IsValue Data.Text.Lazy.Text where typeOf _ = TypeString toValue = ValueAtom . toAtom fromValue (ValueAtom x) = fromAtom x fromValue _ = Nothing instance IsVariant Data.Text.Lazy.Text where toVariant = Variant . toValue fromVariant (Variant val) = fromValue val instance IsAtom String where toAtom = toAtom . Data.Text.pack fromAtom = fmap Data.Text.unpack . fromAtom instance IsValue String where typeOf _ = TypeString toValue = ValueAtom . toAtom fromValue (ValueAtom x) = fromAtom x fromValue _ = Nothing instance IsVariant String where toVariant = Variant . toValue fromVariant (Variant val) = fromValue val instance IsValue a => IsValue (Vector a) where typeOf v = TypeArray (vectorItemType v) toValue v = ValueVector (vectorItemType v) (Data.Vector.map toValue v) fromValue (ValueVector _ v) = Data.Vector.mapM fromValue v fromValue _ = Nothing vectorItemType :: IsValue a => Vector a -> Type vectorItemType v = typeOf (undefined `asTypeOf` Data.Vector.head v) instance IsValue a => IsVariant (Vector a) where toVariant = Variant . toValue fromVariant (Variant val) = fromValue val instance IsValue a => IsValue [a] where typeOf v = TypeArray (typeOf (undefined `asTypeOf` head v)) toValue = toValue . Data.Vector.fromList fromValue = fmap Data.Vector.toList . fromValue instance IsValue a => IsVariant [a] where toVariant = toVariant . Data.Vector.fromList fromVariant = fmap Data.Vector.toList . fromVariant instance IsValue ByteString where typeOf _ = TypeArray TypeWord8 toValue = ValueBytes fromValue (ValueBytes bs) = Just bs fromValue (ValueVector TypeWord8 v) = Just (vectorToBytes v) fromValue _ = Nothing instance IsVariant ByteString where toVariant = Variant . toValue fromVariant (Variant val) = fromValue val instance IsValue Data.ByteString.Lazy.ByteString where typeOf _ = TypeArray TypeWord8 toValue = toValue . Data.ByteString.concat . Data.ByteString.Lazy.toChunks fromValue = fmap (\bs -> Data.ByteString.Lazy.fromChunks [bs]) . fromValue instance IsVariant Data.ByteString.Lazy.ByteString where toVariant = Variant . toValue fromVariant (Variant val) = fromValue val instance (Ord k, IsAtom k, IsValue v) => IsValue (Map k v) where typeOf m = TypeDictionary kt vt where (kt, vt) = mapItemType m toValue m = ValueMap kt vt (bimap box m) where (kt, vt) = mapItemType m box k v = (toAtom k, toValue v) fromValue (ValueMap _ _ m) = bimapM unbox m where unbox k v = do k' <- fromAtom k v' <- fromValue v return (k', v') fromValue _ = Nothing bimap :: Ord k' => (k -> v -> (k', v')) -> Map k v -> Map k' v' bimap f = Data.Map.fromList . map (\(k, v) -> f k v) . Data.Map.toList bimapM :: (Monad m, Ord k') => (k -> v -> m (k', v')) -> Map k v -> m (Map k' v') bimapM f = liftM Data.Map.fromList . mapM (\(k, v) -> f k v) . Data.Map.toList mapItemType :: (IsValue k, IsValue v) => Map k v -> (Type, Type) mapItemType m = (typeOf k, typeOf v) where mapItem :: Map k v -> (k, v) mapItem _ = (undefined, undefined) (k, v) = mapItem m instance (Ord k, IsAtom k, IsValue v) => IsVariant (Map k v) where toVariant = Variant . toValue fromVariant (Variant val) = fromValue val instance (IsValue a1, IsValue a2) => IsValue (a1, a2) where typeOf ~(a1, a2) = TypeStructure [typeOf a1, typeOf a2] toValue (a1, a2) = ValueStructure [toValue a1, toValue a2] fromValue (ValueStructure [a1, a2]) = do a1' <- fromValue a1 a2' <- fromValue a2 return (a1', a2') fromValue _ = Nothing instance (IsVariant a1, IsVariant a2) => IsVariant (a1, a2) where toVariant (a1, a2) = Variant (ValueStructure [varToVal a1, varToVal a2]) fromVariant (Variant (ValueStructure [a1, a2])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 return (a1', a2') fromVariant _ = Nothing varToVal :: IsVariant a => a -> Value varToVal a = case toVariant a of Variant val -> val -- | 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 -- -- for details. newtype ObjectPath = ObjectPath String deriving (Eq, Ord, Show) formatObjectPath :: ObjectPath -> String formatObjectPath (ObjectPath s) = s parseObjectPath :: String -> Maybe ObjectPath parseObjectPath s = do maybeParseString parserObjectPath s return (ObjectPath s) objectPath_ :: String -> ObjectPath objectPath_ = forceParse "object path" parseObjectPath instance Data.String.IsString ObjectPath where fromString = objectPath_ parserObjectPath :: Parsec.Parser () parserObjectPath = root <|> object where root = Parsec.try $ do slash Parsec.eof object = do slash skipSepBy1 element slash Parsec.eof element = Parsec.skipMany1 (oneOf chars) slash = Parsec.char '/' >> return () chars = concat [ ['a'..'z'] , ['A'..'Z'] , ['0'..'9'] , "_"] -- | Interfaces are used to group a set of methods and signals within an -- exported object. Interface names consist of alphanumeric characters -- separated by periods. -- -- See -- -- for details. newtype InterfaceName = InterfaceName String deriving (Eq, Ord, Show) formatInterfaceName :: InterfaceName -> String formatInterfaceName (InterfaceName s) = s parseInterfaceName :: String -> Maybe InterfaceName parseInterfaceName s = do when (length s > 255) Nothing maybeParseString parserInterfaceName s return (InterfaceName s) interfaceName_ :: String -> InterfaceName interfaceName_ = forceParse "interface name" parseInterfaceName instance Data.String.IsString InterfaceName where fromString = interfaceName_ instance IsVariant InterfaceName where toVariant = toVariant . formatInterfaceName fromVariant = fromVariant >=> parseInterfaceName parserInterfaceName :: Parsec.Parser () parserInterfaceName = name >> Parsec.eof where alpha = ['a'..'z'] ++ ['A'..'Z'] ++ "_" alphanum = alpha ++ ['0'..'9'] element = do _ <- oneOf alpha Parsec.skipMany (oneOf alphanum) name = do element _ <- Parsec.char '.' skipSepBy1 element (Parsec.char '.') -- | Member names are used to identify a single method or signal within an -- interface. Method names consist of alphanumeric characters. -- -- See -- -- for details. newtype MemberName = MemberName String deriving (Eq, Ord, Show) formatMemberName :: MemberName -> String formatMemberName (MemberName s) = s parseMemberName :: String -> Maybe MemberName parseMemberName s = do when (length s > 255) Nothing maybeParseString parserMemberName s return (MemberName s) memberName_ :: String -> MemberName memberName_ = forceParse "member name" parseMemberName instance Data.String.IsString MemberName where fromString = memberName_ instance IsVariant MemberName where toVariant = toVariant . formatMemberName fromVariant = fromVariant >=> parseMemberName parserMemberName :: Parsec.Parser () parserMemberName = name >> Parsec.eof where alpha = ['a'..'z'] ++ ['A'..'Z'] ++ "_" alphanum = alpha ++ ['0'..'9'] name = do _ <- oneOf alpha Parsec.skipMany (oneOf alphanum) -- | Error names are used to identify which type of error was returned from -- a method call. Error names consist of alphanumeric characters -- separated by periods. -- -- See -- -- for details. newtype ErrorName = ErrorName String deriving (Eq, Ord, Show) formatErrorName :: ErrorName -> String formatErrorName (ErrorName s) = s parseErrorName :: String -> Maybe ErrorName parseErrorName s = do when (length s > 255) Nothing maybeParseString parserInterfaceName s return (ErrorName s) errorName_ :: String -> ErrorName errorName_ = forceParse "error name" parseErrorName instance Data.String.IsString ErrorName where fromString = errorName_ instance IsVariant ErrorName where toVariant = toVariant . formatErrorName fromVariant = fromVariant >=> parseErrorName -- | 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 -- -- for details. newtype BusName = BusName String deriving (Eq, Ord, Show) formatBusName :: BusName -> String formatBusName (BusName s) = s parseBusName :: String -> Maybe BusName parseBusName s = do when (length s > 255) Nothing maybeParseString parserBusName s return (BusName s) busName_ :: String -> BusName busName_ = forceParse "bus name" parseBusName instance Data.String.IsString BusName where fromString = busName_ instance IsVariant BusName where toVariant = toVariant . formatBusName fromVariant = fromVariant >=> parseBusName parserBusName :: Parsec.Parser () parserBusName = name >> Parsec.eof where alpha = ['a'..'z'] ++ ['A'..'Z'] ++ "_-" alphanum = alpha ++ ['0'..'9'] name = unique <|> wellKnown unique = do _ <- Parsec.char ':' elements alphanum wellKnown = elements alpha elements :: [Char] -> Parsec.Parser () elements start = do element start Parsec.skipMany1 $ do _ <- Parsec.char '.' element start element :: [Char] -> Parsec.Parser () element start = do _ <- oneOf start Parsec.skipMany (oneOf alphanum) -- | A D-Bus Structure is a container type similar to Haskell tuples, storing -- values of any type that is convertable to 'IsVariant'. A Structure may -- contain up to 255 values. -- -- Most users can use the 'IsVariant' instance for tuples to extract the -- values of a structure. This type is for very large structures, which may -- be awkward to work with as tuples. newtype Structure = Structure [Value] deriving (Eq) instance Show Structure where show (Structure xs) = showValue True (ValueStructure xs) instance IsVariant Structure where toVariant (Structure xs) = Variant (ValueStructure xs) fromVariant (Variant (ValueStructure xs)) = Just (Structure xs) fromVariant _ = Nothing structureItems :: Structure -> [Variant] structureItems (Structure xs) = map Variant xs -- | A D-Bus Array is a container type similar to Haskell lists, storing -- zero or more values of a single D-Bus type. -- -- Most users can use the 'IsVariant' instance for lists or vectors to extract -- the values of an array. This type is for advanced use cases, where the user -- wants to convert array values to Haskell types that are not instances of -- 'IsValue'. data Array = Array Type (Vector Value) | ArrayBytes ByteString instance Show Array where show (Array t xs) = showValue True (ValueVector t xs) show (ArrayBytes xs) = showValue True (ValueBytes xs) instance Eq Array where x == y = norm x == norm y where norm (Array TypeWord8 xs) = Left (vectorToBytes xs) norm (Array t xs) = Right (t, xs) norm (ArrayBytes xs) = Left xs instance IsVariant Array where toVariant (Array t xs) = Variant (ValueVector t xs) toVariant (ArrayBytes bs) = Variant (ValueBytes bs) fromVariant (Variant (ValueVector t xs)) = Just (Array t xs) fromVariant (Variant (ValueBytes bs)) = Just (ArrayBytes bs) fromVariant _ = Nothing arrayItems :: Array -> [Variant] arrayItems (Array _ xs) = map Variant (Data.Vector.toList xs) arrayItems (ArrayBytes bs) = map toVariant (Data.ByteString.unpack bs) -- | A D-Bus Dictionary is a container type similar to Haskell maps, storing -- zero or more associations between keys and values. -- -- Most users can use the 'IsVariant' instance for maps to extract the values -- of a dictionary. This type is for advanced use cases, where the user -- wants to convert dictionary items to Haskell types that are not instances -- of 'IsValue'. data Dictionary = Dictionary Type Type (Map Atom Value) deriving (Eq) instance Show Dictionary where show (Dictionary kt vt xs) = showValue True (ValueMap kt vt xs) instance IsVariant Dictionary where toVariant (Dictionary kt vt xs) = Variant (ValueMap kt vt xs) fromVariant (Variant (ValueMap kt vt xs)) = Just (Dictionary kt vt xs) fromVariant _ = Nothing dictionaryItems :: Dictionary -> [(Variant, Variant)] dictionaryItems (Dictionary _ _ xs) = do (k, v) <- Data.Map.toList xs return (Variant (ValueAtom k), Variant v) instance (IsValue a1, IsValue a2, IsValue a3) => IsValue (a1, a2, a3) where typeOf ~(a1, a2, a3) = TypeStructure [typeOf a1, typeOf a2, typeOf a3] toValue (a1, a2, a3) = ValueStructure [toValue a1, toValue a2, toValue a3] fromValue (ValueStructure [a1, a2, a3]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 return (a1', a2', a3') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4) => IsValue (a1, a2, a3, a4) where typeOf ~(a1, a2, a3, a4) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4] toValue (a1, a2, a3, a4) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4] fromValue (ValueStructure [a1, a2, a3, a4]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 return (a1', a2', a3', a4') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5) => IsValue (a1, a2, a3, a4, a5) where typeOf ~(a1, a2, a3, a4, a5) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5] toValue (a1, a2, a3, a4, a5) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5] fromValue (ValueStructure [a1, a2, a3, a4, a5]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 return (a1', a2', a3', a4', a5') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6) => IsValue (a1, a2, a3, a4, a5, a6) where typeOf ~(a1, a2, a3, a4, a5, a6) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6] toValue (a1, a2, a3, a4, a5, a6) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 return (a1', a2', a3', a4', a5', a6') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7) => IsValue (a1, a2, a3, a4, a5, a6, a7) where typeOf ~(a1, a2, a3, a4, a5, a6, a7) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7] toValue (a1, a2, a3, a4, a5, a6, a7) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 return (a1', a2', a3', a4', a5', a6', a7') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8) where typeOf ~(a1, a2, a3, a4, a5, a6, a7, a8) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7, typeOf a8] toValue (a1, a2, a3, a4, a5, a6, a7, a8) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7, toValue a8] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 a8' <- fromValue a8 return (a1', a2', a3', a4', a5', a6', a7', a8') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9) where typeOf ~(a1, a2, a3, a4, a5, a6, a7, a8, a9) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7, typeOf a8, typeOf a9] toValue (a1, a2, a3, a4, a5, a6, a7, a8, a9) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7, toValue a8, toValue a9] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 a8' <- fromValue a8 a9' <- fromValue a9 return (a1', a2', a3', a4', a5', a6', a7', a8', a9') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) where typeOf ~(a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7, typeOf a8, typeOf a9, typeOf a10] toValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7, toValue a8, toValue a9, toValue a10] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 a8' <- fromValue a8 a9' <- fromValue a9 a10' <- fromValue a10 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) where typeOf ~(a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7, typeOf a8, typeOf a9, typeOf a10, typeOf a11] toValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7, toValue a8, toValue a9, toValue a10, toValue a11] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 a8' <- fromValue a8 a9' <- fromValue a9 a10' <- fromValue a10 a11' <- fromValue a11 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) where typeOf ~(a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7, typeOf a8, typeOf a9, typeOf a10, typeOf a11, typeOf a12] toValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7, toValue a8, toValue a9, toValue a10, toValue a11, toValue a12] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 a8' <- fromValue a8 a9' <- fromValue a9 a10' <- fromValue a10 a11' <- fromValue a11 a12' <- fromValue a12 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11', a12') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) where typeOf ~(a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7, typeOf a8, typeOf a9, typeOf a10, typeOf a11, typeOf a12, typeOf a13] toValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7, toValue a8, toValue a9, toValue a10, toValue a11, toValue a12, toValue a13] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 a8' <- fromValue a8 a9' <- fromValue a9 a10' <- fromValue a10 a11' <- fromValue a11 a12' <- fromValue a12 a13' <- fromValue a13 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11', a12', a13') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13, IsValue a14) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) where typeOf ~(a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7, typeOf a8, typeOf a9, typeOf a10, typeOf a11, typeOf a12, typeOf a13, typeOf a14] toValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7, toValue a8, toValue a9, toValue a10, toValue a11, toValue a12, toValue a13, toValue a14] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 a8' <- fromValue a8 a9' <- fromValue a9 a10' <- fromValue a10 a11' <- fromValue a11 a12' <- fromValue a12 a13' <- fromValue a13 a14' <- fromValue a14 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11', a12', a13', a14') fromValue _ = Nothing instance (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13, IsValue a14, IsValue a15) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) where typeOf ~(a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) = TypeStructure [typeOf a1, typeOf a2, typeOf a3, typeOf a4, typeOf a5, typeOf a6, typeOf a7, typeOf a8, typeOf a9, typeOf a10, typeOf a11, typeOf a12, typeOf a13, typeOf a14, typeOf a15] toValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) = ValueStructure [toValue a1, toValue a2, toValue a3, toValue a4, toValue a5, toValue a6, toValue a7, toValue a8, toValue a9, toValue a10, toValue a11, toValue a12, toValue a13, toValue a14, toValue a15] fromValue (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15]) = do a1' <- fromValue a1 a2' <- fromValue a2 a3' <- fromValue a3 a4' <- fromValue a4 a5' <- fromValue a5 a6' <- fromValue a6 a7' <- fromValue a7 a8' <- fromValue a8 a9' <- fromValue a9 a10' <- fromValue a10 a11' <- fromValue a11 a12' <- fromValue a12 a13' <- fromValue a13 a14' <- fromValue a14 a15' <- fromValue a15 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11', a12', a13', a14', a15') fromValue _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3) => IsVariant (a1, a2, a3) where toVariant (a1, a2, a3) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3]) fromVariant (Variant (ValueStructure [a1, a2, a3])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 return (a1', a2', a3') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4) => IsVariant (a1, a2, a3, a4) where toVariant (a1, a2, a3, a4) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 return (a1', a2', a3', a4') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5) => IsVariant (a1, a2, a3, a4, a5) where toVariant (a1, a2, a3, a4, a5) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 return (a1', a2', a3', a4', a5') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6) => IsVariant (a1, a2, a3, a4, a5, a6) where toVariant (a1, a2, a3, a4, a5, a6) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 return (a1', a2', a3', a4', a5', a6') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7) => IsVariant (a1, a2, a3, a4, a5, a6, a7) where toVariant (a1, a2, a3, a4, a5, a6, a7) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 return (a1', a2', a3', a4', a5', a6', a7') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8) where toVariant (a1, a2, a3, a4, a5, a6, a7, a8) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7, varToVal a8]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 a8' <- (fromVariant . Variant) a8 return (a1', a2', a3', a4', a5', a6', a7', a8') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9) where toVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7, varToVal a8, varToVal a9]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 a8' <- (fromVariant . Variant) a8 a9' <- (fromVariant . Variant) a9 return (a1', a2', a3', a4', a5', a6', a7', a8', a9') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) where toVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7, varToVal a8, varToVal a9, varToVal a10]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 a8' <- (fromVariant . Variant) a8 a9' <- (fromVariant . Variant) a9 a10' <- (fromVariant . Variant) a10 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) where toVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7, varToVal a8, varToVal a9, varToVal a10, varToVal a11]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 a8' <- (fromVariant . Variant) a8 a9' <- (fromVariant . Variant) a9 a10' <- (fromVariant . Variant) a10 a11' <- (fromVariant . Variant) a11 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) where toVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7, varToVal a8, varToVal a9, varToVal a10, varToVal a11, varToVal a12]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 a8' <- (fromVariant . Variant) a8 a9' <- (fromVariant . Variant) a9 a10' <- (fromVariant . Variant) a10 a11' <- (fromVariant . Variant) a11 a12' <- (fromVariant . Variant) a12 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11', a12') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) where toVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7, varToVal a8, varToVal a9, varToVal a10, varToVal a11, varToVal a12, varToVal a13]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 a8' <- (fromVariant . Variant) a8 a9' <- (fromVariant . Variant) a9 a10' <- (fromVariant . Variant) a10 a11' <- (fromVariant . Variant) a11 a12' <- (fromVariant . Variant) a12 a13' <- (fromVariant . Variant) a13 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11', a12', a13') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13, IsVariant a14) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) where toVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7, varToVal a8, varToVal a9, varToVal a10, varToVal a11, varToVal a12, varToVal a13, varToVal a14]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 a8' <- (fromVariant . Variant) a8 a9' <- (fromVariant . Variant) a9 a10' <- (fromVariant . Variant) a10 a11' <- (fromVariant . Variant) a11 a12' <- (fromVariant . Variant) a12 a13' <- (fromVariant . Variant) a13 a14' <- (fromVariant . Variant) a14 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11', a12', a13', a14') fromVariant _ = Nothing instance (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13, IsVariant a14, IsVariant a15) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) where toVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) = Variant (ValueStructure [varToVal a1, varToVal a2, varToVal a3, varToVal a4, varToVal a5, varToVal a6, varToVal a7, varToVal a8, varToVal a9, varToVal a10, varToVal a11, varToVal a12, varToVal a13, varToVal a14, varToVal a15]) fromVariant (Variant (ValueStructure [a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15])) = do a1' <- (fromVariant . Variant) a1 a2' <- (fromVariant . Variant) a2 a3' <- (fromVariant . Variant) a3 a4' <- (fromVariant . Variant) a4 a5' <- (fromVariant . Variant) a5 a6' <- (fromVariant . Variant) a6 a7' <- (fromVariant . Variant) a7 a8' <- (fromVariant . Variant) a8 a9' <- (fromVariant . Variant) a9 a10' <- (fromVariant . Variant) a10 a11' <- (fromVariant . Variant) a11 a12' <- (fromVariant . Variant) a12 a13' <- (fromVariant . Variant) a13 a14' <- (fromVariant . Variant) a14 a15' <- (fromVariant . Variant) a15 return (a1', a2', a3', a4', a5', a6', a7', a8', a9', a10', a11', a12', a13', a14', a15') fromVariant _ = Nothing -- | A value used to uniquely identify a particular message within a session. -- Serials are 32-bit unsigned integers, and eventually wrap. newtype Serial = Serial Word32 deriving (Eq, Ord, Show) instance IsVariant Serial where toVariant (Serial x) = toVariant x fromVariant = fmap Serial . fromVariant serialValue :: Serial -> Word32 serialValue (Serial x) = x -- | Get the first serial in the sequence. firstSerial :: Serial firstSerial = Serial 1 -- | Get the next serial in the sequence. This may wrap around to -- 'firstSerial'. nextSerial :: Serial -> Serial nextSerial (Serial x) = Serial (if x + 1 == 0 then 1 -- wrap to firstSerial else x + 1) skipSepBy1 :: Parsec.Parser a -> Parsec.Parser b -> Parsec.Parser () skipSepBy1 p sep = do _ <- p Parsec.skipMany (sep >> p) forceParse :: String -> (String -> Maybe a) -> String -> a forceParse label parse str = case parse str of Just x -> x Nothing -> error ("Invalid " ++ label ++ ": " ++ show str) maybeParseString :: Parsec.Parser a -> String -> Maybe a maybeParseString parser s = case Parsec.parse parser "" s of Left _ -> Nothing Right a -> Just a dbus-0.10.13/lib/DBus/Internal/Wire.hs0000644000000000000000000006641113073332436015434 0ustar0000000000000000-- Copyright (C) 2009-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBus.Internal.Wire ( Endianness(..) , MarshalError , marshalErrorMessage , UnmarshalError , unmarshalErrorMessage , marshalMessage , unmarshalMessage , unmarshalMessageM ) where import qualified Control.Applicative import Control.Monad (ap, liftM, when, unless) import qualified Data.ByteString import Data.ByteString (ByteString) import qualified Data.ByteString.Builder as Builder import qualified Data.ByteString.Char8 import qualified Data.ByteString.Lazy as Lazy import Data.Int (Int16, Int32, Int64) import qualified Data.Map import Data.Map (Map) import Data.Maybe (fromJust, listToMaybe, fromMaybe) import Data.Monoid import Data.Text (Text) import qualified Data.Text.Encoding import qualified Data.Vector import Data.Vector (Vector) import Data.Word (Word8, Word16, Word32, Word64) import Foreign.C.Types (CInt) import System.Posix.Types (Fd(..)) import Prelude import qualified Data.Serialize.Get as Get import Data.Serialize.IEEE754 (getFloat64be, getFloat64le, putFloat64be, putFloat64le) import Data.Serialize.Put (runPut) import DBus.Internal.Message import DBus.Internal.Types data Endianness = LittleEndian | BigEndian deriving (Show, Eq) encodeEndianness :: Endianness -> Word8 encodeEndianness LittleEndian = 0x6C encodeEndianness BigEndian = 0x42 decodeEndianness :: Word8 -> Maybe Endianness decodeEndianness 0x6C = Just LittleEndian decodeEndianness 0x42 = Just BigEndian decodeEndianness _ = Nothing alignment :: Type -> Word8 alignment TypeBoolean = 4 alignment TypeWord8 = 1 alignment TypeWord16 = 2 alignment TypeWord32 = 4 alignment TypeWord64 = 8 alignment TypeInt16 = 2 alignment TypeInt32 = 4 alignment TypeInt64 = 8 alignment TypeDouble = 8 alignment TypeUnixFd = 4 alignment TypeString = 4 alignment TypeObjectPath = 4 alignment TypeSignature = 1 alignment (TypeArray _) = 4 alignment (TypeDictionary _ _) = 4 alignment (TypeStructure _) = 8 alignment TypeVariant = 1 {-# INLINE padding #-} padding :: Word64 -> Word8 -> Word64 padding current count = required where count' = fromIntegral count missing = mod current count' required = if missing > 0 then count' - missing else 0 data WireR s a = WireRL String | WireRR a !s newtype Wire s a = Wire { unWire :: Endianness -> s -> WireR s a } instance Functor (Wire s) where {-# INLINE fmap #-} fmap = liftM instance Control.Applicative.Applicative (Wire s) where {-# INLINE pure #-} pure = return {-# INLINE (<*>) #-} (<*>) = ap instance Monad (Wire s) where {-# INLINE return #-} return a = Wire (\_ s -> WireRR a s) {-# INLINE (>>=) #-} m >>= k = Wire $ \e s -> case unWire m e s of WireRL err -> WireRL err WireRR a s' -> unWire (k a) e s' {-# INLINE (>>) #-} m >> k = Wire $ \e s -> case unWire m e s of WireRL err -> WireRL err WireRR _ s' -> unWire k e s' throwError :: String -> Wire s a throwError err = Wire (\_ _ -> WireRL err) {-# INLINE getState #-} getState :: Wire s s getState = Wire (\_ s -> WireRR s s) {-# INLINE putState #-} putState :: s -> Wire s () putState s = Wire (\_ _ -> WireRR () s) {-# INLINE chooseEndian #-} chooseEndian :: a -> a -> Wire s a chooseEndian big little = Wire (\e s -> case e of BigEndian -> WireRR big s LittleEndian -> WireRR little s) type Marshal = Wire MarshalState newtype MarshalError = MarshalError String deriving (Show, Eq) marshalErrorMessage :: MarshalError -> String marshalErrorMessage (MarshalError s) = s data MarshalState = MarshalState !Builder.Builder {-# UNPACK #-} !Word64 marshal :: Value -> Marshal () marshal (ValueAtom x) = marshalAtom x marshal (ValueBytes xs) = marshalStrictBytes xs marshal (ValueVector t xs) = marshalVector t xs marshal (ValueMap kt vt xs) = marshalMap kt vt xs marshal (ValueStructure xs) = marshalStructure xs marshal (ValueVariant x) = marshalVariant x marshalAtom :: Atom -> Marshal () marshalAtom (AtomWord8 x) = marshalWord8 x marshalAtom (AtomWord16 x) = marshalWord16 x marshalAtom (AtomWord32 x) = marshalWord32 x marshalAtom (AtomWord64 x) = marshalWord64 x marshalAtom (AtomInt16 x) = marshalInt16 x marshalAtom (AtomInt32 x) = marshalInt32 x marshalAtom (AtomInt64 x) = marshalInt64 x marshalAtom (AtomDouble x) = marshalDouble x marshalAtom (AtomUnixFd x) = marshalUnixFd x marshalAtom (AtomBool x) = marshalBool x marshalAtom (AtomText x) = marshalText x marshalAtom (AtomObjectPath x) = marshalObjectPath x marshalAtom (AtomSignature x) = marshalSignature x appendB :: Word64 -> Builder.Builder -> Marshal () appendB size bytes = Wire (\_ (MarshalState builder count) -> let builder' = mappend builder bytes count' = count + size in WireRR () (MarshalState builder' count')) appendS :: ByteString -> Marshal () appendS bytes = appendB (fromIntegral (Data.ByteString.length bytes)) (Builder.byteString bytes) appendL :: Lazy.ByteString -> Marshal () appendL bytes = appendB (fromIntegral (Lazy.length bytes)) (Builder.lazyByteString bytes) pad :: Word8 -> Marshal () pad count = do (MarshalState _ existing) <- getState let padding' = fromIntegral (padding existing count) appendS (Data.ByteString.replicate padding' 0) marshalBuilder :: Word8 -> (a -> Builder.Builder) -> (a -> Builder.Builder) -> a -> Marshal () marshalBuilder size be le x = do builder <- chooseEndian (be x) (le x) pad size appendB (fromIntegral size) builder type Unmarshal = Wire UnmarshalState newtype UnmarshalError = UnmarshalError String deriving (Show, Eq) unmarshalErrorMessage :: UnmarshalError -> String unmarshalErrorMessage (UnmarshalError s) = s data UnmarshalState = UnmarshalState {-# UNPACK #-} !ByteString {-# UNPACK #-} !Word64 unmarshal :: Type -> Unmarshal Value unmarshal TypeWord8 = liftM toValue unmarshalWord8 unmarshal TypeWord16 = liftM toValue unmarshalWord16 unmarshal TypeWord32 = liftM toValue unmarshalWord32 unmarshal TypeWord64 = liftM toValue unmarshalWord64 unmarshal TypeInt16 = liftM toValue unmarshalInt16 unmarshal TypeInt32 = liftM toValue unmarshalInt32 unmarshal TypeInt64 = liftM toValue unmarshalInt64 unmarshal TypeDouble = liftM toValue unmarshalDouble unmarshal TypeUnixFd = liftM toValue unmarshalUnixFd unmarshal TypeBoolean = liftM toValue unmarshalBool unmarshal TypeString = liftM toValue unmarshalText unmarshal TypeObjectPath = liftM toValue unmarshalObjectPath unmarshal TypeSignature = liftM toValue unmarshalSignature unmarshal (TypeArray TypeWord8) = liftM toValue unmarshalByteArray unmarshal (TypeArray t) = liftM (ValueVector t) (unmarshalArray t) unmarshal (TypeDictionary kt vt) = unmarshalDictionary kt vt unmarshal (TypeStructure ts) = unmarshalStructure ts unmarshal TypeVariant = unmarshalVariant {-# INLINE consume #-} consume :: Word64 -> Unmarshal ByteString consume count = do (UnmarshalState bytes offset) <- getState let count' = fromIntegral count let (x, bytes') = Data.ByteString.splitAt count' bytes let lenConsumed = Data.ByteString.length x if lenConsumed == count' then do putState (UnmarshalState bytes' (offset + count)) return x else throwError ("Unexpected EOF at offset " ++ show (offset + fromIntegral lenConsumed)) skipPadding :: Word8 -> Unmarshal () skipPadding count = do (UnmarshalState _ offset) <- getState bytes <- consume (padding offset count) unless (Data.ByteString.all (== 0) bytes) (throwError ("Value padding " ++ show bytes ++ " contains invalid bytes.")) skipTerminator :: Unmarshal () skipTerminator = do byte <- unmarshalWord8 when (byte /= 0) (throwError "Textual value is not NUL-terminated.") fromMaybeU :: Show a => String -> (a -> Maybe b) -> a -> Unmarshal b fromMaybeU label f x = case f x of Just x' -> return x' Nothing -> throwError ("Invalid " ++ label ++ ": " ++ show x) unmarshalGet :: Word8 -> Get.Get a -> Get.Get a -> Unmarshal a unmarshalGet count be le = do skipPadding count bytes <- consume (fromIntegral count) get <- chooseEndian be le let Right ret = Get.runGet get bytes return ret marshalWord8 :: Word8 -> Marshal () marshalWord8 x = appendB 1 (Builder.word8 x) unmarshalWord8 :: Unmarshal Word8 unmarshalWord8 = liftM Data.ByteString.head (consume 1) marshalWord16 :: Word16 -> Marshal () marshalWord16 = marshalBuilder 2 Builder.word16BE Builder.word16LE marshalWord32 :: Word32 -> Marshal () marshalWord32 = marshalBuilder 4 Builder.word32BE Builder.word32LE marshalWord64 :: Word64 -> Marshal () marshalWord64 = marshalBuilder 8 Builder.word64BE Builder.word64LE marshalInt16 :: Int16 -> Marshal () marshalInt16 = marshalWord16 . fromIntegral marshalInt32 :: Int32 -> Marshal () marshalInt32 = marshalWord32 . fromIntegral marshalInt64 :: Int64 -> Marshal () marshalInt64 = marshalWord64 . fromIntegral unmarshalWord16 :: Unmarshal Word16 unmarshalWord16 = unmarshalGet 2 Get.getWord16be Get.getWord16le unmarshalWord32 :: Unmarshal Word32 unmarshalWord32 = unmarshalGet 4 Get.getWord32be Get.getWord32le unmarshalWord64 :: Unmarshal Word64 unmarshalWord64 = unmarshalGet 8 Get.getWord64be Get.getWord64le unmarshalInt16 :: Unmarshal Int16 unmarshalInt16 = liftM fromIntegral unmarshalWord16 unmarshalInt32 :: Unmarshal Int32 unmarshalInt32 = liftM fromIntegral unmarshalWord32 unmarshalInt64 :: Unmarshal Int64 unmarshalInt64 = liftM fromIntegral unmarshalWord64 marshalDouble :: Double -> Marshal () marshalDouble x = do put <- chooseEndian putFloat64be putFloat64le pad 8 appendS (runPut (put x)) unmarshalDouble :: Unmarshal Double unmarshalDouble = unmarshalGet 8 getFloat64be getFloat64le marshalUnixFd :: Fd -> Marshal () marshalUnixFd (Fd x) | x < 0 = throwError ("Invalid file descriptor: " ++ show x) | toInteger x > toInteger (maxBound :: Word32) = throwError ("D-Bus forbids file descriptors exceeding UINT32_MAX: " ++ show x) | otherwise = marshalWord32 (fromIntegral x) unmarshalUnixFd :: Unmarshal Fd unmarshalUnixFd = do x <- unmarshalWord32 when (toInteger x > toInteger (maxBound :: CInt)) (throwError ("Invalid file descriptor: " ++ show x)) return (Fd (fromIntegral x)) marshalBool :: Bool -> Marshal () marshalBool False = marshalWord32 0 marshalBool True = marshalWord32 1 unmarshalBool :: Unmarshal Bool unmarshalBool = do word <- unmarshalWord32 case word of 0 -> return False 1 -> return True _ -> throwError ("Invalid boolean: " ++ show word) marshalText :: Text -> Marshal () marshalText text = do let bytes = Data.Text.Encoding.encodeUtf8 text when (Data.ByteString.any (== 0) bytes) (throwError ("String " ++ show text ++ " contained forbidden character: '\\x00'")) marshalWord32 (fromIntegral (Data.ByteString.length bytes)) appendS bytes marshalWord8 0 unmarshalText :: Unmarshal Text unmarshalText = do byteCount <- unmarshalWord32 bytes <- consume (fromIntegral byteCount) skipTerminator fromMaybeU "text" maybeDecodeUtf8 bytes maybeDecodeUtf8 :: ByteString -> Maybe Text maybeDecodeUtf8 bs = case Data.Text.Encoding.decodeUtf8' bs of Right text -> Just text _ -> Nothing marshalObjectPath :: ObjectPath -> Marshal () marshalObjectPath p = do let bytes = Data.ByteString.Char8.pack (formatObjectPath p) marshalWord32 (fromIntegral (Data.ByteString.length bytes)) appendS bytes marshalWord8 0 unmarshalObjectPath :: Unmarshal ObjectPath unmarshalObjectPath = do byteCount <- unmarshalWord32 bytes <- consume (fromIntegral byteCount) skipTerminator fromMaybeU "object path" parseObjectPath (Data.ByteString.Char8.unpack bytes) signatureBytes :: Signature -> ByteString signatureBytes (Signature ts) = Data.ByteString.Char8.pack (concatMap typeCode ts) marshalSignature :: Signature -> Marshal () marshalSignature x = do let bytes = signatureBytes x marshalWord8 (fromIntegral (Data.ByteString.length bytes)) appendS bytes marshalWord8 0 unmarshalSignature :: Unmarshal Signature unmarshalSignature = do byteCount <- unmarshalWord8 bytes <- consume (fromIntegral byteCount) skipTerminator fromMaybeU "signature" parseSignatureBytes bytes arrayMaximumLength :: Int64 arrayMaximumLength = 67108864 marshalVector :: Type -> Vector Value -> Marshal () marshalVector t x = do (arrayPadding, arrayBytes) <- getArrayBytes t x let arrayLen = Lazy.length arrayBytes when (arrayLen > arrayMaximumLength) (throwError ("Marshaled array size (" ++ show arrayLen ++ " bytes) exceeds maximum limit of (" ++ show arrayMaximumLength ++ " bytes).")) marshalWord32 (fromIntegral arrayLen) appendS (Data.ByteString.replicate arrayPadding 0) appendL arrayBytes marshalStrictBytes :: ByteString -> Marshal () marshalStrictBytes bytes = do let arrayLen = Lazy.length (Lazy.fromStrict bytes) when (fromIntegral arrayLen > arrayMaximumLength) (throwError ("Marshaled array size (" ++ show arrayLen ++ " bytes) exceeds maximum limit of (" ++ show arrayMaximumLength ++ " bytes).")) marshalWord32 (fromIntegral arrayLen) appendS bytes getArrayBytes :: Type -> Vector Value -> Marshal (Int, Lazy.ByteString) getArrayBytes itemType vs = do s <- getState (MarshalState _ afterLength) <- marshalWord32 0 >> getState (MarshalState _ afterPadding) <- pad (alignment itemType) >> getState putState (MarshalState mempty afterPadding) (MarshalState itemBuilder _) <- Data.Vector.mapM_ marshal vs >> getState let itemBytes = Builder.toLazyByteString itemBuilder paddingSize = fromIntegral (afterPadding - afterLength) putState s return (paddingSize, itemBytes) unmarshalByteArray :: Unmarshal ByteString unmarshalByteArray = do byteCount <- unmarshalWord32 consume (fromIntegral byteCount) unmarshalArray :: Type -> Unmarshal (Vector Value) unmarshalArray itemType = do let getOffset = do (UnmarshalState _ o) <- getState return o byteCount <- unmarshalWord32 skipPadding (alignment itemType) start <- getOffset let end = start + fromIntegral byteCount vs <- untilM (liftM (>= end) getOffset) (unmarshal itemType) end' <- getOffset when (end' > end) (throwError ("Array data size exeeds array size of " ++ show end)) return (Data.Vector.fromList vs) dictionaryToArray :: Map Atom Value -> Vector Value dictionaryToArray = Data.Vector.fromList . map step . Data.Map.toList where step (k, v) = ValueStructure [ValueAtom k, v] arrayToDictionary :: Vector Value -> Map Atom Value arrayToDictionary = Data.Map.fromList . map step . Data.Vector.toList where step (ValueStructure [ValueAtom k, v]) = (k, v) step _ = error "arrayToDictionary: internal error" marshalMap :: Type -> Type -> Map Atom Value -> Marshal () marshalMap kt vt x = let structType = TypeStructure [kt, vt] array = dictionaryToArray x in marshalVector structType array unmarshalDictionary :: Type -> Type -> Unmarshal Value unmarshalDictionary kt vt = do let pairType = TypeStructure [kt, vt] array <- unmarshalArray pairType return (ValueMap kt vt (arrayToDictionary array)) marshalStructure :: [Value] -> Marshal () marshalStructure vs = do pad 8 mapM_ marshal vs unmarshalStructure :: [Type] -> Unmarshal Value unmarshalStructure ts = do skipPadding 8 liftM ValueStructure (mapM unmarshal ts) marshalVariant :: Variant -> Marshal () marshalVariant var@(Variant val) = do sig <- case signature [valueType val] of Just x' -> return x' Nothing -> throwError ("Signature " ++ show (typeCode (valueType val)) ++ " for variant " ++ show var ++ " is malformed or too large.") marshalSignature sig marshal val unmarshalVariant :: Unmarshal Value unmarshalVariant = do let getType sig = case signatureTypes sig of [t] -> Just t _ -> Nothing t <- fromMaybeU "variant signature" getType =<< unmarshalSignature (toValue . Variant) `liftM` unmarshal t protocolVersion :: Word8 protocolVersion = 1 messageMaximumLength :: Integer messageMaximumLength = 134217728 encodeField :: HeaderField -> Value encodeField (HeaderPath x) = encodeField' 1 x encodeField (HeaderInterface x) = encodeField' 2 x encodeField (HeaderMember x) = encodeField' 3 x encodeField (HeaderErrorName x) = encodeField' 4 x encodeField (HeaderReplySerial x) = encodeField' 5 x encodeField (HeaderDestination x) = encodeField' 6 x encodeField (HeaderSender x) = encodeField' 7 x encodeField (HeaderSignature x) = encodeField' 8 x encodeField (HeaderUnixFds x) = encodeField' 9 x encodeField' :: IsVariant a => Word8 -> a -> Value encodeField' code x = toValue (code, toVariant x) decodeField :: (Word8, Variant) -> ErrorM UnmarshalError [HeaderField] decodeField struct = case struct of (1, x) -> decodeField' x HeaderPath "path" (2, x) -> decodeField' x HeaderInterface "interface" (3, x) -> decodeField' x HeaderMember "member" (4, x) -> decodeField' x HeaderErrorName "error name" (5, x) -> decodeField' x HeaderReplySerial "reply serial" (6, x) -> decodeField' x HeaderDestination "destination" (7, x) -> decodeField' x HeaderSender "sender" (8, x) -> decodeField' x HeaderSignature "signature" (9, x) -> decodeField' x HeaderUnixFds "unix fds" _ -> return [] decodeField' :: IsVariant a => Variant -> (a -> b) -> String -> ErrorM UnmarshalError [b] decodeField' x f label = case fromVariant x of Just x' -> return [f x'] Nothing -> throwErrorM (UnmarshalError ("Header field " ++ show label ++ " contains invalid value " ++ show x)) marshalMessage :: Message a => Endianness -> Serial -> a -> Either MarshalError ByteString marshalMessage e serial msg = runMarshal where body = messageBody msg marshaler = do sig <- checkBodySig body empty <- getState mapM_ (marshal . (\(Variant x) -> x)) body (MarshalState bodyBytesB _) <- getState putState empty marshal (toValue (encodeEndianness e)) let bodyBytes = Builder.toLazyByteString bodyBytesB marshalHeader msg serial sig (fromIntegral (Lazy.length bodyBytes)) pad 8 appendL bodyBytes checkMaximumSize emptyState = MarshalState mempty 0 runMarshal = case unWire marshaler e emptyState of WireRL err -> Left (MarshalError err) WireRR _ (MarshalState builder _) -> Right (Lazy.toStrict (Builder.toLazyByteString builder)) checkBodySig :: [Variant] -> Marshal Signature checkBodySig vs = case signature (map variantType vs) of Just x -> return x Nothing -> throwError ("Message body " ++ show vs ++ " has too many items") marshalHeader :: Message a => a -> Serial -> Signature -> Word32 -> Marshal () marshalHeader msg serial bodySig bodyLength = do let fields = HeaderSignature bodySig : messageHeaderFields msg marshalWord8 (messageTypeCode msg) marshalWord8 (messageFlags msg) marshalWord8 protocolVersion marshalWord32 bodyLength marshalWord32 (serialValue serial) let fieldType = TypeStructure [TypeWord8, TypeVariant] marshalVector fieldType (Data.Vector.fromList (map encodeField fields)) checkMaximumSize :: Marshal () checkMaximumSize = do (MarshalState _ messageLength) <- getState when (toInteger messageLength > messageMaximumLength) (throwError ("Marshaled message size (" ++ show messageLength ++ " bytes) exeeds maximum limit of (" ++ show messageMaximumLength ++ " bytes).")) unmarshalMessageM :: Monad m => (Int -> m ByteString) -> m (Either UnmarshalError ReceivedMessage) unmarshalMessageM getBytes' = runErrorT $ do let getBytes count = do bytes <- ErrorT (liftM Right (getBytes' count)) if Data.ByteString.length bytes < count then throwErrorT (UnmarshalError "Unexpected end of input while parsing message header.") else return bytes let Just fixedSig = parseSignature "yyyyuuu" fixedBytes <- getBytes 16 let messageVersion = Data.ByteString.index fixedBytes 3 when (messageVersion /= protocolVersion) (throwErrorT (UnmarshalError ("Unsupported protocol version: " ++ show messageVersion))) let eByte = Data.ByteString.index fixedBytes 0 endianness <- case decodeEndianness eByte of Just x' -> return x' Nothing -> throwErrorT (UnmarshalError ("Invalid endianness: " ++ show eByte)) let unmarshalSig = mapM unmarshal . signatureTypes let unmarshal' x bytes = case unWire (unmarshalSig x) endianness (UnmarshalState bytes 0) of WireRR x' _ -> return x' WireRL err -> throwErrorT (UnmarshalError err) fixed <- unmarshal' fixedSig fixedBytes let messageType = fromJust (fromValue (fixed !! 1)) let flags = fromJust (fromValue (fixed !! 2)) let bodyLength = fromJust (fromValue (fixed !! 4)) :: Word32 let serial = fromJust (fromVariant (Variant (fixed !! 5))) let fieldByteCount = fromJust (fromValue (fixed !! 6)) :: Word32 let bodyPadding = padding (fromIntegral fieldByteCount + 16) 8 -- Forbid messages larger than 'messageMaximumLength' let messageLength = 16 + toInteger fieldByteCount + toInteger bodyPadding + toInteger bodyLength when (messageLength > messageMaximumLength) $ throwErrorT (UnmarshalError ("Message size " ++ show messageLength ++ " exceeds limit of " ++ show messageMaximumLength)) let Just headerSig = parseSignature "yyyyuua(yv)" fieldBytes <- getBytes (fromIntegral fieldByteCount) let headerBytes = Data.ByteString.append fixedBytes fieldBytes header <- unmarshal' headerSig headerBytes let fieldArray = Data.Vector.toList (fromJust (fromValue (header !! 6))) fields <- case runErrorM $ concat `liftM` mapM decodeField fieldArray of Left err -> throwErrorT err Right x -> return x _ <- getBytes (fromIntegral bodyPadding) let bodySig = findBodySignature fields bodyBytes <- getBytes (fromIntegral bodyLength) body <- unmarshal' bodySig bodyBytes y <- case runErrorM (buildReceivedMessage messageType fields) of Right x -> return x Left err -> throwErrorT (UnmarshalError ("Header field " ++ show err ++ " is required, but missing")) return (y serial flags (map Variant body)) findBodySignature :: [HeaderField] -> Signature findBodySignature fields = fromMaybe (signature_ []) (listToMaybe [x | HeaderSignature x <- fields]) buildReceivedMessage :: Word8 -> [HeaderField] -> ErrorM String (Serial -> Word8 -> [Variant] -> ReceivedMessage) buildReceivedMessage 1 fields = do path <- require "path" [x | HeaderPath x <- fields] member <- require "member name" [x | HeaderMember x <- fields] return $ \serial flags body -> let iface = listToMaybe [x | HeaderInterface x <- fields] dest = listToMaybe [x | HeaderDestination x <- fields] sender = listToMaybe [x | HeaderSender x <- fields] msg = MethodCall path iface member sender dest True True body in ReceivedMethodCall serial (setMethodCallFlags msg flags) buildReceivedMessage 2 fields = do replySerial <- require "reply serial" [x | HeaderReplySerial x <- fields] return $ \serial _ body -> let dest = listToMaybe [x | HeaderDestination x <- fields] sender = listToMaybe [x | HeaderSender x <- fields] msg = MethodReturn replySerial sender dest body in ReceivedMethodReturn serial msg buildReceivedMessage 3 fields = do name <- require "error name" [x | HeaderErrorName x <- fields] replySerial <- require "reply serial" [x | HeaderReplySerial x <- fields] return $ \serial _ body -> let dest = listToMaybe [x | HeaderDestination x <- fields] sender = listToMaybe [x | HeaderSender x <- fields] msg = MethodError name replySerial sender dest body in ReceivedMethodError serial msg buildReceivedMessage 4 fields = do path <- require "path" [x | HeaderPath x <- fields] member <- require "member name" [x | HeaderMember x <- fields] iface <- require "interface" [x | HeaderInterface x <- fields] return $ \serial _ body -> let dest = listToMaybe [x | HeaderDestination x <- fields] sender = listToMaybe [x | HeaderSender x <- fields] msg = Signal path iface member sender dest body in ReceivedSignal serial msg buildReceivedMessage messageType fields = return $ \serial _ body -> let sender = listToMaybe [x | HeaderSender x <- fields] msg = UnknownMessage messageType sender body in ReceivedUnknown serial msg require :: String -> [a] -> ErrorM String a require _ (x:_) = return x require label _ = throwErrorM label unmarshalMessage :: ByteString -> Either UnmarshalError ReceivedMessage unmarshalMessage bytes = checkError (Get.runGet get bytes) where get = unmarshalMessageM getBytes -- wrap getByteString, so it will behave like transportGet and return -- a truncated result on EOF instead of throwing an exception. getBytes count = do remaining <- Get.remaining Get.getByteString (min remaining count) checkError (Left err) = Left (UnmarshalError err) checkError (Right x) = x untilM :: Monad m => m Bool -> m a -> m [a] untilM test comp = do done <- test if done then return [] else do x <- comp xs <- untilM test comp return (x:xs) ------------------------------------------------------------------------------- -- local ErrorT and MonadError, which don't have the silly Error => dependency -- found in the "transformers" package. ------------------------------------------------------------------------------- newtype ErrorM e a = ErrorM { runErrorM :: Either e a } instance Functor (ErrorM e) where fmap f m = ErrorM $ case runErrorM m of Left err -> Left err Right x -> Right (f x) instance Control.Applicative.Applicative (ErrorM e) where pure = return (<*>) = ap instance Monad (ErrorM e) where return = ErrorM . Right (>>=) m k = case runErrorM m of Left err -> ErrorM (Left err) Right x -> k x throwErrorM :: e -> ErrorM e a throwErrorM = ErrorM . Left newtype ErrorT e m a = ErrorT { runErrorT :: m (Either e a) } instance Monad m => Functor (ErrorT e m) where fmap = liftM instance Monad m => Control.Applicative.Applicative (ErrorT e m) where pure = return (<*>) = ap instance Monad m => Monad (ErrorT e m) where return = ErrorT . return . Right (>>=) m k = ErrorT $ do x <- runErrorT m case x of Left l -> return (Left l) Right r -> runErrorT (k r) throwErrorT :: Monad m => e -> ErrorT e m a throwErrorT = ErrorT . return . Left dbus-0.10.13/tests/DBusTests.hs0000644000000000000000000000417213073332436014365 0ustar0000000000000000-- Copyright (C) 2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module Main ( tests , main ) where import Test.Chell import DBusTests.Address import DBusTests.BusName import DBusTests.Client import DBusTests.ErrorName import DBusTests.Integration import DBusTests.InterfaceName import DBusTests.Introspection import DBusTests.MemberName import DBusTests.Message import DBusTests.ObjectPath import DBusTests.Serialization import DBusTests.Socket import DBusTests.Signature import DBusTests.Transport import DBusTests.Variant import DBusTests.Wire -- import all dbus modules here to ensure they show up in the coverage report, -- even if not tested. import DBus () import DBus.Client () import DBus.Internal.Address () import DBus.Internal.Message () import DBus.Internal.Types () import DBus.Internal.Wire () import DBus.Introspection () import DBus.Socket () tests :: [Suite] tests = [ test_Address , test_BusName , test_Client , test_ErrorName , test_Integration , test_InterfaceName , test_Introspection , test_MemberName , test_Message , test_ObjectPath , test_Serialization , test_Signature , test_Socket , test_Transport , test_Variant , test_Wire ] main :: IO () main = Test.Chell.defaultMain tests dbus-0.10.13/tests/DBusTests/Address.hs0000644000000000000000000001605413073332436015754 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Address (test_Address) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding (property) import Data.Char (ord) import Data.List (intercalate) import Data.Map (Map) import qualified Data.Map import Text.Printf (printf) import DBus import DBusTests.Util (smallListOf, smallListOf1, withEnv) test_Address :: Suite test_Address = suite "Address" [ test_BuildAddress , test_ParseAddress , test_ParseAddresses , test_ParseInvalid , test_FormatAddress , test_FormatAddresses , test_GetSystemAddress , test_GetSessionAddress , test_GetStarterAddress ] test_BuildAddress :: Test test_BuildAddress = property "address" prop where prop = forAll gen_Address check check (method, params) = case address method params of Nothing -> False Just addr -> and [ addressMethod addr == method , addressParameters addr == params ] test_ParseAddress :: Test test_ParseAddress = property "parseAddress" prop where prop = forAll gen_AddressBytes check check (bytes, method, params) = case parseAddress bytes of Nothing -> False Just addr -> and [ addressMethod addr == method , addressParameters addr == params ] test_ParseAddresses :: Test test_ParseAddresses = property "parseAddresses" prop where prop = forAll gen_AddressesBytes checkMany checkMany (bytes, expectedAddrs) = case parseAddresses bytes of Nothing -> False Just addrs -> and [ length addrs == length expectedAddrs , and (map checkOne (zip addrs expectedAddrs)) ] checkOne (addr, (method, params)) = and [ addressMethod addr == method , addressParameters addr == params ] test_ParseInvalid :: Test test_ParseInvalid = assertions "parse-invalid" $ do -- empty $expect (nothing (address "" Data.Map.empty)) $expect (nothing (parseAddress "")) -- no colon $expect (nothing (parseAddress "a")) -- no equals sign $expect (nothing (parseAddress "a:b")) -- no parameter -- TODO: should this be OK? what about the trailing comma rule? $expect (nothing (parseAddress "a:,")) -- no key $expect (nothing (address "" (Data.Map.fromList [("", "c")]))) $expect (nothing (parseAddress "a:=c")) -- no value $expect (nothing (address "" (Data.Map.fromList [("b", "")]))) $expect (nothing (parseAddress "a:b=")) test_FormatAddress :: Test test_FormatAddress = property "formatAddress" prop where prop = forAll gen_Address check where check (method, params) = let Just addr = address method params bytes = formatAddress addr parsed = parseAddress bytes shown = show addr in and [ parsed == Just addr , shown == "Address " ++ show bytes ] test_FormatAddresses :: Test test_FormatAddresses = property "formatAddresses" prop where prop = forAll (smallListOf1 gen_Address) check where check pairs = let addrs = do (method, params) <- pairs let Just addr = address method params return addr bytes = formatAddresses addrs parsed = parseAddresses bytes in parsed == Just addrs test_GetSystemAddress :: Test test_GetSystemAddress = assertions "getSystemAddress" $ do do addr <- withEnv "DBUS_SYSTEM_BUS_ADDRESS" Nothing getSystemAddress $expect (just addr) $assert (equal addr (address "unix" (Data.Map.fromList [("path", "/var/run/dbus/system_bus_socket")]))) do addr <- withEnv "DBUS_SYSTEM_BUS_ADDRESS" (Just "a:b=c") getSystemAddress $expect (just addr) $assert (equal addr (address "a" (Data.Map.fromList [("b", "c")]))) test_GetSessionAddress :: Test test_GetSessionAddress = assertions "getSessionAddress" $ do addr <- withEnv "DBUS_SESSION_BUS_ADDRESS" (Just "a:b=c") getSessionAddress $expect (just addr) $assert (equal addr (address "a" (Data.Map.fromList [("b", "c")]))) test_GetStarterAddress :: Test test_GetStarterAddress = assertions "getStarterAddress" $ do addr <- withEnv "DBUS_STARTER_ADDRESS" (Just "a:b=c") getStarterAddress $expect (just addr) $assert (equal addr (address "a" (Data.Map.fromList [("b", "c")]))) gen_Address :: Gen (String, Map String String) gen_Address = gen where methodChars = filter (`notElem` ":;") ['!'..'~'] keyChars = filter (`notElem` "=;,") ['!'..'~'] param = do key <- smallListOf1 (elements keyChars) value <- smallListOf1 (elements ['\x00'..'\xFF']) return (key, value) gen = do params <- smallListOf param method <- if null params then smallListOf1 (elements methodChars) else smallListOf (elements methodChars) return (method, Data.Map.fromList params) gen_AddressBytes :: Gen (String, String, Map String String) gen_AddressBytes = gen where methodChars = filter (`notElem` ":;") ['!'..'~'] keyChars = filter (`notElem` "=;,") ['!'..'~'] plainChars = concat [ ['0'..'9'] , ['a'..'z'] , ['A'..'Z'] , "-_/\\*." ] encodedChars = [(printf "%%%02X" (ord x), x) | x <- ['\x00'..'\xFF']] plainChar = do x <- elements plainChars return ([x], x) encodedChar = elements encodedChars param = do key <- smallListOf1 (elements keyChars) value <- smallListOf1 (oneof [plainChar, encodedChar]) let (valueChunks, valueChars) = unzip value let str = key ++ "=" ++ concat (valueChunks) return (str, key, valueChars) gen = do params <- smallListOf param method <- if null params then smallListOf1 (elements methodChars) else smallListOf (elements methodChars) let paramStrs = [s | (s, _, _) <- params] let mapItems = [(k, v) | (_, k, v) <- params] let str = method ++ ":" ++ (intercalate "," paramStrs) return (str, method, Data.Map.fromList mapItems) gen_AddressesBytes :: Gen (String, [(String, Map String String)]) gen_AddressesBytes = do addrs <- smallListOf1 gen_AddressBytes let bytes = [b | (b, _, _) <- addrs] let expected = [(m, p) | (_, m, p) <- addrs] return (intercalate ";" bytes, expected) dbus-0.10.13/tests/DBusTests/BusName.hs0000644000000000000000000000544113073332436015717 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.BusName (test_BusName) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding (property) import Data.List (intercalate) import DBus import DBusTests.Util test_BusName :: Suite test_BusName = suite "BusName" [ test_Parse , test_ParseInvalid , test_IsVariant ] test_Parse :: Test test_Parse = property "parse" prop where prop = forAll gen_BusName check check x = case parseBusName x of Nothing -> False Just parsed -> formatBusName parsed == x test_ParseInvalid :: Test test_ParseInvalid = assertions "parse-invalid" $ do -- empty $expect (nothing (parseBusName "")) -- well-known starting with a digit $expect (nothing (parseBusName "foo.0bar")) -- well-known with one element $expect (nothing (parseBusName "foo")) -- unique with one element $expect (nothing (parseBusName ":foo")) -- trailing characters $expect (nothing (parseBusName "foo.bar!")) -- at most 255 characters $expect (just (parseBusName (":0." ++ replicate 251 'y'))) $expect (just (parseBusName (":0." ++ replicate 252 'y'))) $expect (nothing (parseBusName (":0." ++ replicate 253 'y'))) test_IsVariant :: Test test_IsVariant = assertions "IsVariant" $ do assertVariant TypeString (busName_ "foo.bar") gen_BusName :: Gen String gen_BusName = oneof [unique, wellKnown] where alpha = ['a'..'z'] ++ ['A'..'Z'] ++ "_-" alphanum = alpha ++ ['0'..'9'] unique = trim $ do x <- chunks alphanum return (":" ++ x) wellKnown = trim (chunks alpha) trim gen = do x <- gen if length x > 255 then return (dropWhileEnd (== '.') (take 255 x)) else return x chunks start = do x <- chunk start xs <- listOf1 (chunk start) return (intercalate "." (x:xs)) chunk start = do x <- elements start xs <- listOf (elements alphanum) return (x:xs) instance Arbitrary BusName where arbitrary = fmap busName_ gen_BusName dbus-0.10.13/tests/DBusTests/Client.hs0000644000000000000000000004477713073332436015622 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Client (test_Client) where import Control.Concurrent import Control.Exception (try) import Control.Monad.IO.Class (liftIO) import qualified Data.Map as Map import Data.Word import Test.Chell import DBus import qualified DBus.Client import qualified DBus.Socket import DBusTests.Util (forkVar, withEnv) test_Client :: Suite test_Client = suite "Client" $ [ test_RequestName , test_ReleaseName , test_Call , test_CallNoReply , test_AddMatch , test_AutoMethod , test_ExportIntrospection ] ++ suiteTests suite_Connect test_Connect :: String -> (Address -> IO DBus.Client.Client) -> Test test_Connect name connect = assertions name $ do (addr, sockVar) <- startDummyBus clientVar <- forkVar (connect addr) -- TODO: verify that 'hello' contains expected data, and -- send a properly formatted reply. sock <- liftIO (readMVar sockVar) receivedHello <- liftIO (DBus.Socket.receive sock) let (ReceivedMethodCall helloSerial _) = receivedHello liftIO (DBus.Socket.send sock (methodReturn helloSerial) (\_ -> return ())) client <- liftIO (readMVar clientVar) liftIO (DBus.Client.disconnect client) suite_Connect :: Suite suite_Connect = suite "connect" [ test_ConnectSystem , test_ConnectSystem_NoAddress , test_ConnectSession , test_ConnectSession_NoAddress , test_ConnectStarter , test_ConnectStarter_NoAddress ] test_ConnectSystem :: Test test_ConnectSystem = test_Connect "connectSystem" $ \addr -> do withEnv "DBUS_SYSTEM_BUS_ADDRESS" (Just (formatAddress addr)) DBus.Client.connectSystem test_ConnectSystem_NoAddress :: Test test_ConnectSystem_NoAddress = assertions "connectSystem-no-address" $ do $expect $ throwsEq (DBus.Client.clientError "connectSystem: DBUS_SYSTEM_BUS_ADDRESS is invalid.") (withEnv "DBUS_SYSTEM_BUS_ADDRESS" (Just "invalid") DBus.Client.connectSystem) test_ConnectSession :: Test test_ConnectSession = test_Connect "connectSession" $ \addr -> do withEnv "DBUS_SESSION_BUS_ADDRESS" (Just (formatAddress addr)) DBus.Client.connectSession test_ConnectSession_NoAddress :: Test test_ConnectSession_NoAddress = assertions "connectSession-no-address" $ do $expect $ throwsEq (DBus.Client.clientError "connectSession: DBUS_SESSION_BUS_ADDRESS is missing or invalid.") (withEnv "DBUS_SESSION_BUS_ADDRESS" (Just "invalid") DBus.Client.connectSession) test_ConnectStarter :: Test test_ConnectStarter = test_Connect "connectStarter" $ \addr -> do withEnv "DBUS_STARTER_ADDRESS" (Just (formatAddress addr)) DBus.Client.connectStarter test_ConnectStarter_NoAddress :: Test test_ConnectStarter_NoAddress = assertions "connectStarter-no-address" $ do $expect $ throwsEq (DBus.Client.clientError "connectStarter: DBUS_STARTER_ADDRESS is missing or invalid.") (withEnv "DBUS_STARTER_ADDRESS" (Just "invalid") DBus.Client.connectStarter) test_RequestName :: Test test_RequestName = assertions "requestName" $ do (sock, client) <- startConnectedClient let allFlags = [ DBus.Client.nameAllowReplacement , DBus.Client.nameReplaceExisting , DBus.Client.nameDoNotQueue ] let requestCall = (dbusCall "RequestName") { methodCallDestination = Just (busName_ "org.freedesktop.DBus") , methodCallBody = [toVariant "com.example.Foo", toVariant (7 :: Word32)] } let requestReply body serial = (methodReturn serial) { methodReturnBody = body } -- NamePrimaryOwner do reply <- stubMethodCall sock (DBus.Client.requestName client (busName_ "com.example.Foo") allFlags) requestCall (requestReply [toVariant (1 :: Word32)]) $expect (equal reply DBus.Client.NamePrimaryOwner) -- NameInQueue do reply <- stubMethodCall sock (DBus.Client.requestName client (busName_ "com.example.Foo") allFlags) requestCall (requestReply [toVariant (2 :: Word32)]) $expect (equal reply DBus.Client.NameInQueue) -- NameExists do reply <- stubMethodCall sock (DBus.Client.requestName client (busName_ "com.example.Foo") allFlags) requestCall (requestReply [toVariant (3 :: Word32)]) $expect (equal reply DBus.Client.NameExists) -- NameAlreadyOwner do reply <- stubMethodCall sock (DBus.Client.requestName client (busName_ "com.example.Foo") allFlags) requestCall (requestReply [toVariant (4 :: Word32)]) $expect (equal reply DBus.Client.NameAlreadyOwner) -- response with empty body do tried <- stubMethodCall sock (try (DBus.Client.requestName client (busName_ "com.example.Foo") allFlags)) requestCall (requestReply []) err <- $requireLeft tried $expect (equal err (DBus.Client.clientError "requestName: received empty response") { DBus.Client.clientErrorFatal = False }) -- response with invalid body do tried <- stubMethodCall sock (try (DBus.Client.requestName client (busName_ "com.example.Foo") allFlags)) requestCall (requestReply [toVariant ""]) err <- $requireLeft tried $expect (equal err (DBus.Client.clientError "requestName: received invalid response code (Variant \"\")") { DBus.Client.clientErrorFatal = False }) -- response with unknown result code do reply <- stubMethodCall sock (DBus.Client.requestName client (busName_ "com.example.Foo") allFlags) requestCall (requestReply [toVariant (5 :: Word32)]) $expect (equal (show reply) ("UnknownRequestNameReply 5")) test_ReleaseName :: Test test_ReleaseName = assertions "releaseName" $ do (sock, client) <- startConnectedClient let requestCall = (dbusCall "ReleaseName") { methodCallDestination = Just (busName_ "org.freedesktop.DBus") , methodCallBody = [toVariant "com.example.Foo"] } let requestReply body serial = (methodReturn serial) { methodReturnBody = body } -- NameReleased do reply <- stubMethodCall sock (DBus.Client.releaseName client (busName_ "com.example.Foo")) requestCall (requestReply [toVariant (1 :: Word32)]) $expect (equal reply DBus.Client.NameReleased) -- NameNonExistent do reply <- stubMethodCall sock (DBus.Client.releaseName client (busName_ "com.example.Foo")) requestCall (requestReply [toVariant (2 :: Word32)]) $expect (equal reply DBus.Client.NameNonExistent) -- NameNotOwner do reply <- stubMethodCall sock (DBus.Client.releaseName client (busName_ "com.example.Foo")) requestCall (requestReply [toVariant (3 :: Word32)]) $expect (equal reply DBus.Client.NameNotOwner) -- response with empty body do tried <- stubMethodCall sock (try (DBus.Client.releaseName client (busName_ "com.example.Foo"))) requestCall (requestReply []) err <- $requireLeft tried $expect (equal err (DBus.Client.clientError "releaseName: received empty response") { DBus.Client.clientErrorFatal = False }) -- response with invalid body do tried <- stubMethodCall sock (try (DBus.Client.releaseName client (busName_ "com.example.Foo"))) requestCall (requestReply [toVariant ""]) err <- $requireLeft tried $expect (equal err (DBus.Client.clientError "releaseName: received invalid response code (Variant \"\")") { DBus.Client.clientErrorFatal = False }) -- response with unknown result code do reply <- stubMethodCall sock (DBus.Client.releaseName client (busName_ "com.example.Foo")) requestCall (requestReply [toVariant (5 :: Word32)]) $expect (equal (show reply) ("UnknownReleaseNameReply 5")) test_Call :: Test test_Call = assertions "call" $ do (sock, client) <- startConnectedClient let requestCall = (dbusCall "Hello") { methodCallSender = Just (busName_ "com.example.Foo") , methodCallDestination = Just (busName_ "org.freedesktop.DBus") , methodCallReplyExpected = False , methodCallAutoStart = False , methodCallBody = [toVariant "com.example.Foo"] } -- methodCallReplyExpected is forced to True do response <- stubMethodCall sock (DBus.Client.call client requestCall) (requestCall { methodCallReplyExpected = True }) methodReturn reply <- $requireRight response $expect (equal reply (methodReturn (methodReturnSerial reply))) test_CallNoReply :: Test test_CallNoReply = assertions "callNoReply" $ do (sock, client) <- startConnectedClient let requestCall = (dbusCall "Hello") { methodCallSender = Just (busName_ "com.example.Foo") , methodCallDestination = Just (busName_ "org.freedesktop.DBus") , methodCallReplyExpected = True , methodCallAutoStart = False , methodCallBody = [toVariant "com.example.Foo"] } -- methodCallReplyExpected is forced to False do stubMethodCall sock (DBus.Client.callNoReply client requestCall) (requestCall { methodCallReplyExpected = False }) methodReturn test_AddMatch :: Test test_AddMatch = assertions "addMatch" $ do (sock, client) <- startConnectedClient let matchRule = DBus.Client.matchAny { DBus.Client.matchSender = Just (busName_ "com.example.Foo") , DBus.Client.matchDestination = Just (busName_ "com.example.Bar") , DBus.Client.matchPath = Just (objectPath_ "/") , DBus.Client.matchInterface = Just (interfaceName_ "com.example.Baz") , DBus.Client.matchMember = Just (memberName_ "Qux") } -- might as well test this while we're at it $expect (equal (show matchRule) "MatchRule \"sender='com.example.Foo',destination='com.example.Bar',path='/',interface='com.example.Baz',member='Qux'\"") let requestCall = (dbusCall "AddMatch") { methodCallDestination = Just (busName_ "org.freedesktop.DBus") , methodCallBody = [toVariant "type='signal',sender='com.example.Foo',destination='com.example.Bar',path='/',interface='com.example.Baz',member='Qux'"] } signalVar <- liftIO newEmptyMVar -- add a listener for the given signal stubMethodCall sock (DBus.Client.addMatch client matchRule (putMVar signalVar)) requestCall methodReturn -- ignored signal liftIO (DBus.Socket.send sock (signal (objectPath_ "/") (interfaceName_ "com.example.Baz") (memberName_ "Qux")) (\_ -> return ())) $assert (isEmptyMVar signalVar) -- matched signal let matchedSignal = (signal (objectPath_ "/") (interfaceName_ "com.example.Baz") (memberName_ "Qux")) { signalSender = Just (busName_ "com.example.Foo") , signalDestination = Just (busName_ "com.example.Bar") } liftIO (DBus.Socket.send sock matchedSignal (\_ -> return ())) received <- liftIO (takeMVar signalVar) $expect (equal received matchedSignal) test_AutoMethod :: Test test_AutoMethod = assertions "autoMethod" $ do (sock, client) <- startConnectedClient let methodMax = (\x y -> return (max x y)) :: Word32 -> Word32 -> IO Word32 let methodPair = (\x y -> return (x, y)) :: String -> String -> IO (String, String) liftIO (DBus.Client.export client (objectPath_ "/") [ DBus.Client.autoMethod (interfaceName_ "com.example.Foo") (memberName_ "Max") methodMax , DBus.Client.autoMethod (interfaceName_ "com.example.Foo") (memberName_ "Pair") methodPair ]) -- valid call to com.example.Foo.Max do (serial, response) <- callClientMethod sock "/" "com.example.Foo" "Max" [toVariant (2 :: Word32), toVariant (1 :: Word32)] $expect (equal response (Right (methodReturn serial) { methodReturnBody = [toVariant (2 :: Word32)] })) -- valid call to com.example.Foo.Pair do (serial, response) <- callClientMethod sock "/" "com.example.Foo" "Pair" [toVariant "x", toVariant "y"] $expect (equal response (Right (methodReturn serial) { methodReturnBody = [toVariant "x", toVariant "y"] })) -- invalid call to com.example.Foo.Max do (serial, response) <- callClientMethod sock "/" "com.example.Foo" "Max" [toVariant "x", toVariant "y"] $expect (equal response (Left (methodError serial (errorName_ "org.freedesktop.DBus.Error.InvalidParameters")))) test_ExportIntrospection :: Test test_ExportIntrospection = assertions "exportIntrospection" $ do (sock, client) <- startConnectedClient liftIO (DBus.Client.export client (objectPath_ "/foo") [ DBus.Client.autoMethod (interfaceName_ "com.example.Foo") (memberName_ "Method1") (undefined :: String -> IO ()) , DBus.Client.autoMethod (interfaceName_ "com.example.Foo") (memberName_ "Method2") (undefined :: String -> IO String) , DBus.Client.autoMethod (interfaceName_ "com.example.Foo") (memberName_ "Method3") (undefined :: String -> IO (String, String)) ]) let introspect path = do (_, response) <- callClientMethod sock path "org.freedesktop.DBus.Introspectable" "Introspect" [] ret <- $requireRight response let body = methodReturnBody ret $assert (equal (length body) 1) let Just xml = fromVariant (head body) return xml root <- introspect "/" $expect (equalLines root "\n\ \\ \\ \\ \\ \\ \\ \\ \") foo <- introspect "/foo" $expect (equalLines foo "\n\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \\ \") startDummyBus :: Assertions (Address, MVar DBus.Socket.Socket) startDummyBus = do uuid <- liftIO randomUUID let Just addr = address "unix" (Map.fromList [("abstract", formatUUID uuid)]) listener <- liftIO (DBus.Socket.listen addr) sockVar <- forkVar (DBus.Socket.accept listener) return (DBus.Socket.socketListenerAddress listener, sockVar) startConnectedClient :: Assertions (DBus.Socket.Socket, DBus.Client.Client) startConnectedClient = do (addr, sockVar) <- startDummyBus clientVar <- forkVar (DBus.Client.connect addr) -- TODO: verify that 'hello' contains expected data, and -- send a properly formatted reply. sock <- liftIO (readMVar sockVar) receivedHello <- liftIO (DBus.Socket.receive sock) let (ReceivedMethodCall helloSerial _) = receivedHello liftIO (DBus.Socket.send sock (methodReturn helloSerial) (\_ -> return ())) client <- liftIO (readMVar clientVar) afterTest (DBus.Client.disconnect client) return (sock, client) stubMethodCall :: DBus.Socket.Socket -> IO a -> MethodCall -> (Serial -> MethodReturn) -> Assertions a stubMethodCall sock io expectedCall respond = do var <- forkVar io receivedCall <- liftIO (DBus.Socket.receive sock) let ReceivedMethodCall callSerial call = receivedCall $expect (equal expectedCall call) liftIO (DBus.Socket.send sock (respond callSerial) (\_ -> return ())) liftIO (takeMVar var) callClientMethod :: DBus.Socket.Socket -> String -> String -> String -> [Variant] -> Assertions (Serial, Either MethodError MethodReturn) callClientMethod sock path iface name body = do let call = (methodCall (objectPath_ path) (interfaceName_ iface) (memberName_ name)) { methodCallBody = body } serial <- liftIO (DBus.Socket.send sock call return) resp <- liftIO (DBus.Socket.receive sock) case resp of ReceivedMethodReturn _ ret -> return (serial, Right ret) ReceivedMethodError _ err -> return (serial, Left err) _ -> $die "callClientMethod: unexpected response to method call" dbusCall :: String -> MethodCall dbusCall member = methodCall (objectPath_ "/org/freedesktop/DBus") (interfaceName_ "org.freedesktop.DBus") (memberName_ member) dbus-0.10.13/tests/DBusTests/ErrorName.hs0000644000000000000000000000511513073332436016255 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.ErrorName (test_ErrorName) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding (property) import Data.List (intercalate) import DBus import DBusTests.Util test_ErrorName :: Suite test_ErrorName = suite "ErrorName" [ test_Parse , test_ParseInvalid , test_IsVariant ] test_Parse :: Test test_Parse = property "parse" prop where prop = forAll gen_ErrorName check check x = case parseErrorName x of Nothing -> False Just parsed -> formatErrorName parsed == x test_ParseInvalid :: Test test_ParseInvalid = assertions "parse-invalid" $ do -- empty $expect (nothing (parseErrorName "")) -- one element $expect (nothing (parseErrorName "foo")) -- element starting with a digit $expect (nothing (parseErrorName "foo.0bar")) -- trailing characters $expect (nothing (parseErrorName "foo.bar!")) -- at most 255 characters $expect (just (parseErrorName ("f." ++ replicate 252 'y'))) $expect (just (parseErrorName ("f." ++ replicate 253 'y'))) $expect (nothing (parseErrorName ("f." ++ replicate 254 'y'))) test_IsVariant :: Test test_IsVariant = assertions "IsVariant" $ do assertVariant TypeString (errorName_ "foo.bar") gen_ErrorName :: Gen String gen_ErrorName = trim chunks where alpha = ['a'..'z'] ++ ['A'..'Z'] ++ "_" alphanum = alpha ++ ['0'..'9'] trim gen = do x <- gen if length x > 255 then return (dropWhileEnd (== '.') (take 255 x)) else return x chunks = do x <- chunk xs <- listOf1 chunk return (intercalate "." (x:xs)) chunk = do x <- elements alpha xs <- listOf (elements alphanum) return (x:xs) instance Arbitrary ErrorName where arbitrary = fmap errorName_ gen_ErrorName dbus-0.10.13/tests/DBusTests/Integration.hs0000644000000000000000000001205413073332436016646 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Integration (test_Integration) where import Test.Chell import Control.Exception (finally) import Control.Monad.IO.Class (liftIO) import System.Directory (removeFile) import System.Exit import System.IO (hGetLine, writeFile) import System.Process import DBus import DBus.Socket import DBus.Client import DBusTests.Util (getTempPath) test_Integration :: Suite test_Integration = suite "integration" [ test_Socket , test_Client ] test_Socket :: Test test_Socket = withDaemon "socket" $ \addr -> do let hello = (methodCall "/org/freedesktop/DBus" "org.freedesktop.DBus" "Hello") { methodCallDestination = Just "org.freedesktop.DBus" } sock <- liftIO (open addr) serial <- liftIO (send sock hello return) $expect (greaterEqual (serialValue serial) 1) received <- liftIO (receive sock) let ReceivedMethodReturn _ ret = received $expect (equal (methodReturnSerial ret) serial) $expect (equal (methodReturnSender ret) (Just "org.freedesktop.DBus")) liftIO (close sock) test_Client :: Test test_Client = withDaemon "client" $ \addr -> do clientA <- liftIO (connect addr) clientB <- liftIO (connect addr) liftIO (export clientA "/" [ method "com.example.Echo" "Echo" (signature_ [TypeString]) (signature_ []) ( \msg -> if map variantType (methodCallBody msg) == [TypeString] then return (replyReturn (methodCallBody msg)) else return (replyError "com.example.Error" [toVariant ("bad body: " ++ show (methodCallBody msg))])) ]) -- TODO: get bus address of clientA with a function let busAddrA = ":1.0" -- Successful call let bodyGood = [toVariant ("test" :: String)] retGood <- liftIO (call clientB (methodCall "/" "com.example.Echo" "Echo") { methodCallDestination = Just busAddrA , methodCallBody = bodyGood }) ret <- $requireRight retGood $expect (equal (methodReturnBody ret) bodyGood) -- Failed call let bodyBad = [toVariant True] retBad <- liftIO (call clientB (methodCall "/" "com.example.Echo" "Echo") { methodCallDestination = Just busAddrA , methodCallBody = bodyBad }) err <- $requireLeft retBad $expect (equal (methodErrorName err) "com.example.Error") $expect (equal (methodErrorBody err) [toVariant ("bad body: [Variant True]" :: String)]) liftIO (disconnect clientA) liftIO (disconnect clientB) configFileContent :: String configFileContent = "\ \\ \\ \ session\ \ \ \ unix:tmpdir=/tmp\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \" withDaemon :: String -> (Address -> Assertions ()) -> Test withDaemon name io = test name $ \opts -> do (versionExit, _, _) <- readProcessWithExitCode "dbus-daemon" ["--version"] "" case versionExit of ExitFailure _ -> return TestSkipped ExitSuccess -> do configFilePath <- liftIO getTempPath writeFile configFilePath configFileContent daemon <- createProcess (proc "dbus-daemon" ["--config-file=" ++ configFilePath, "--print-address"]) { std_out = CreatePipe , close_fds = True } let (_, Just daemonStdout, _, daemonProc) = daemon finally (do addrString <- hGetLine daemonStdout case parseAddress addrString of Nothing -> return (TestAborted [] ("dbus-daemon returned invalid address: " ++ show addrString)) Just addr -> runTest (assertions name (io addr)) opts) (do terminateProcess daemonProc _ <- waitForProcess daemonProc removeFile configFilePath return ()) dbus-0.10.13/tests/DBusTests/InterfaceName.hs0000644000000000000000000000524113073332436017064 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.InterfaceName (test_InterfaceName) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding (property) import Data.List (intercalate) import DBus import DBusTests.Util test_InterfaceName :: Suite test_InterfaceName = suite "InterfaceName" [ test_Parse , test_ParseInvalid , test_IsVariant ] test_Parse :: Test test_Parse = property "parse" prop where prop = forAll gen_InterfaceName check check x = case parseInterfaceName x of Nothing -> False Just parsed -> formatInterfaceName parsed == x test_ParseInvalid :: Test test_ParseInvalid = assertions "parse-invalid" $ do -- empty $expect (nothing (parseInterfaceName "")) -- one element $expect (nothing (parseInterfaceName "foo")) -- element starting with a digit $expect (nothing (parseInterfaceName "foo.0bar")) -- trailing characters $expect (nothing (parseInterfaceName "foo.bar!")) -- at most 255 characters $expect (just (parseInterfaceName ("f." ++ replicate 252 'y'))) $expect (just (parseInterfaceName ("f." ++ replicate 253 'y'))) $expect (nothing (parseInterfaceName ("f." ++ replicate 254 'y'))) test_IsVariant :: Test test_IsVariant = assertions "IsVariant" $ do assertVariant TypeString (interfaceName_ "foo.bar") gen_InterfaceName :: Gen String gen_InterfaceName = trim chunks where alpha = ['a'..'z'] ++ ['A'..'Z'] ++ "_" alphanum = alpha ++ ['0'..'9'] trim gen = do x <- gen if length x > 255 then return (dropWhileEnd (== '.') (take 255 x)) else return x chunks = do x <- chunk xs <- listOf1 chunk return (intercalate "." (x:xs)) chunk = do x <- elements alpha xs <- listOf (elements alphanum) return (x:xs) instance Arbitrary InterfaceName where arbitrary = fmap interfaceName_ gen_InterfaceName dbus-0.10.13/tests/DBusTests/Introspection.hs0000644000000000000000000001517613073332436017233 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Introspection (test_Introspection) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding (property) import Control.Applicative ((<$>), (<*>)) import Control.Monad (liftM, liftM2) import DBus import qualified DBus.Introspection as Introspection import DBusTests.InterfaceName () import DBusTests.MemberName () import DBusTests.ObjectPath () import DBusTests.Signature () import DBusTests.Util (halfSized) test_Introspection :: Suite test_Introspection = suite "Introspection" [ test_XmlPassthrough , test_XmlParse , test_XmlParseFailed , test_XmlWriteFailed ] test_XmlPassthrough :: Test test_XmlPassthrough = property "xml-passthrough" $ \obj -> let path = Introspection.objectPath obj Just xml = Introspection.formatXML obj in Introspection.parseXML path xml == Just obj test_XmlParse :: Test test_XmlParse = assertions "xml-parse" $ do -- root object path can be inferred $expect (equal (Introspection.parseXML (objectPath_ "/") "") (Just (Introspection.object (objectPath_ "/")) { Introspection.objectChildren = [ Introspection.object (objectPath_ "/foo") ] } )) test_XmlParseFailed :: Test test_XmlParseFailed = assertions "xml-parse-failed" $ do $expect (nothing (Introspection.parseXML (objectPath_ "/") "")) $expect (nothing (Introspection.parseXML (objectPath_ "/") "")) -- invalid property access $expect (nothing (Introspection.parseXML (objectPath_ "/") "\ \ \ \ \ \ \ \ \ \")) -- invalid parameter type $expect (nothing (Introspection.parseXML (objectPath_ "/") "\ \ \ \ \ \ \ \ \ \ \ \")) test_XmlWriteFailed :: Test test_XmlWriteFailed = assertions "xml-write-failed" $ do -- child's object path isn't under parent's $expect (nothing (Introspection.formatXML (Introspection.object (objectPath_ "/foo")) { Introspection.objectChildren = [ Introspection.object (objectPath_ "/bar") ] })) -- invalid type $expect (nothing (Introspection.formatXML (Introspection.object (objectPath_ "/foo")) { Introspection.objectInterfaces = [ (Introspection.interface (interfaceName_ "/bar")) { Introspection.interfaceProperties = [ Introspection.property "prop" (TypeDictionary TypeVariant TypeVariant) ] } ] })) instance Arbitrary Type where arbitrary = oneof [atom, container] where atom = elements [ TypeBoolean , TypeWord8 , TypeWord16 , TypeWord32 , TypeWord64 , TypeInt16 , TypeInt32 , TypeInt64 , TypeDouble , TypeString , TypeObjectPath , TypeSignature ] container = oneof [ return TypeVariant , liftM TypeArray arbitrary , liftM2 TypeDictionary atom arbitrary , liftM TypeStructure (listOf1 (halfSized arbitrary)) ] instance Arbitrary Introspection.Object where arbitrary = arbitrary >>= subObject subObject :: ObjectPath -> Gen Introspection.Object subObject parentPath = sized $ \n -> resize (min n 4) $ do let nonRoot = do x <- resize 10 arbitrary case formatObjectPath x of "/" -> nonRoot x' -> return x' thisPath <- nonRoot let path' = case formatObjectPath parentPath of "/" -> thisPath x -> x ++ thisPath let path = objectPath_ path' ifaces <- arbitrary children <- halfSized (listOf (subObject path)) return (Introspection.object path) { Introspection.objectInterfaces = ifaces , Introspection.objectChildren = children } instance Arbitrary Introspection.Interface where arbitrary = do name <- arbitrary methods <- arbitrary signals <- arbitrary properties <- arbitrary return (Introspection.interface name) { Introspection.interfaceMethods = methods , Introspection.interfaceSignals = signals , Introspection.interfaceProperties = properties } instance Arbitrary Introspection.Method where arbitrary = do name <- arbitrary args <- arbitrary return (Introspection.method name) { Introspection.methodArgs = args } instance Arbitrary Introspection.Signal where arbitrary = do name <- arbitrary args <- arbitrary return (Introspection.signal name) { Introspection.signalArgs = args } instance Arbitrary Introspection.MethodArg where arbitrary = Introspection.methodArg <$> gen_Ascii <*> arbitrary <*> arbitrary instance Arbitrary Introspection.Direction where arbitrary = elements [Introspection.directionIn, Introspection.directionOut] instance Arbitrary Introspection.SignalArg where arbitrary = Introspection.signalArg <$> gen_Ascii <*> arbitrary instance Arbitrary Introspection.Property where arbitrary = do name <- gen_Ascii t <- arbitrary canRead <- arbitrary canWrite <- arbitrary return (Introspection.property name t) { Introspection.propertyRead = canRead , Introspection.propertyWrite = canWrite } gen_Ascii :: Gen String gen_Ascii = listOf (elements ['!'..'~']) dbus-0.10.13/tests/DBusTests/MemberName.hs0000644000000000000000000000427513073332436016401 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.MemberName (test_MemberName) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding (property) import DBus import DBusTests.Util test_MemberName :: Suite test_MemberName = suite "MemberName" [ test_Parse , test_ParseInvalid , test_IsVariant ] test_Parse :: Test test_Parse = property "parse" prop where prop = forAll gen_MemberName check check x = case parseMemberName x of Nothing -> False Just parsed -> formatMemberName parsed == x test_ParseInvalid :: Test test_ParseInvalid = assertions "parse-invalid" $ do -- empty $expect (nothing (parseMemberName "")) -- starts with a digit $expect (nothing (parseMemberName "@foo")) -- trailing chars $expect (nothing (parseMemberName "foo!")) -- at most 255 characters $expect (just (parseMemberName (replicate 254 'y'))) $expect (just (parseMemberName (replicate 255 'y'))) $expect (nothing (parseMemberName (replicate 256 'y'))) test_IsVariant :: Test test_IsVariant = assertions "IsVariant" $ do assertVariant TypeString (memberName_ "foo") gen_MemberName :: Gen String gen_MemberName = gen where alpha = ['a'..'z'] ++ ['A'..'Z'] ++ "_" alphanum = alpha ++ ['0'..'9'] gen = do x <- elements alpha xs <- listOf (elements alphanum) return (x:xs) instance Arbitrary MemberName where arbitrary = fmap memberName_ gen_MemberName dbus-0.10.13/tests/DBusTests/Message.hs0000644000000000000000000000321113073332436015742 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Message (test_Message) where import Test.Chell import DBus test_Message :: Suite test_Message = suite "Message" [ test_MethodErrorMessage ] test_MethodErrorMessage :: Test test_MethodErrorMessage = assertions "methodErrorMessage" $ do let emptyError = methodError firstSerial (errorName_ "com.example.Error") $expect (equal "(no error message)" (methodErrorMessage emptyError { methodErrorBody = [] })) $expect (equal "(no error message)" (methodErrorMessage emptyError { methodErrorBody = [toVariant True] })) $expect (equal "(no error message)" (methodErrorMessage emptyError { methodErrorBody = [toVariant ""] })) $expect (equal "error" (methodErrorMessage emptyError { methodErrorBody = [toVariant "error"] })) dbus-0.10.13/tests/DBusTests/ObjectPath.hs0000644000000000000000000000374413073332436016414 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.ObjectPath (test_ObjectPath) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding (property) import Data.List (intercalate) import DBus test_ObjectPath :: Suite test_ObjectPath = suite "ObjectPath" [ test_Parse , test_ParseInvalid ] test_Parse :: Test test_Parse = property "parse" prop where prop = forAll gen_ObjectPath check check x = case parseObjectPath x of Nothing -> False Just parsed -> formatObjectPath parsed == x test_ParseInvalid :: Test test_ParseInvalid = assertions "parse-invalid" $ do -- empty $expect (nothing (parseObjectPath "")) -- bad char $expect (nothing (parseObjectPath "/f!oo")) -- ends with a slash $expect (nothing (parseObjectPath "/foo/")) -- empty element $expect (nothing (parseObjectPath "/foo//bar")) -- trailing chars $expect (nothing (parseObjectPath "/foo!")) gen_ObjectPath :: Gen String gen_ObjectPath = gen where chars = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ "_" gen = do xs <- listOf (listOf1 (elements chars)) return ("/" ++ intercalate "/" xs) instance Arbitrary ObjectPath where arbitrary = fmap objectPath_ gen_ObjectPath dbus-0.10.13/tests/DBusTests/Serialization.hs0000644000000000000000000001503013073332436017175 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Serialization (test_Serialization) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding ((.&.), property) import Data.ByteString (ByteString) import Data.Text (Text) import Data.Int (Int16, Int32, Int64) import Data.Word (Word8, Word16, Word32, Word64) import Data.Map (Map) import qualified Data.Map import qualified Data.Vector import Foreign.C.Types (CInt) import System.Posix.Types (Fd) import DBus import qualified DBus.Internal.Types import DBusTests.BusName () import DBusTests.ErrorName () import DBusTests.InterfaceName () import DBusTests.MemberName () import DBusTests.ObjectPath () import DBusTests.Signature () import DBusTests.Util (smallListOf) test_Serialization :: Suite test_Serialization = suite "Serialization" [ test_MethodCall , test_MethodReturn , test_MethodError , test_Signal ] test_MethodCall :: Test test_MethodCall = property "MethodCall" prop where prop = forAll gen_MethodCall check check msg endianness serial = let Right bytes = marshal endianness serial msg Right received = unmarshal bytes in ReceivedMethodCall serial msg == received test_MethodReturn :: Test test_MethodReturn = property "MethodReturn" prop where prop = forAll gen_MethodReturn check check msg endianness serial = let Right bytes = marshal endianness serial msg Right received = unmarshal bytes in ReceivedMethodReturn serial msg == received test_MethodError :: Test test_MethodError = property "MethodError" prop where prop = forAll gen_MethodError check check msg endianness serial = let Right bytes = marshal endianness serial msg Right received = unmarshal bytes in ReceivedMethodError serial msg == received test_Signal :: Test test_Signal = property "Signal" prop where prop = forAll gen_Signal check check msg endianness serial = let Right bytes = marshal endianness serial msg Right received = unmarshal bytes in ReceivedSignal serial msg == received gen_Atom :: Gen Variant gen_Atom = oneof [ fmap toVariant (arbitrary :: Gen Word8) , fmap toVariant (arbitrary :: Gen Word16) , fmap toVariant (arbitrary :: Gen Word32) , fmap toVariant (arbitrary :: Gen Word64) , fmap toVariant (arbitrary :: Gen Int16) , fmap toVariant (arbitrary :: Gen Int32) , fmap toVariant (arbitrary :: Gen Int64) , fmap toVariant (arbitrary :: Gen Bool) , fmap toVariant (arbitrary :: Gen Double) , fmap toVariant gen_UnixFd , fmap toVariant (arbitrary :: Gen Text) , fmap toVariant (arbitrary :: Gen ObjectPath) , fmap toVariant (arbitrary :: Gen Signature) ] gen_UnixFd :: Gen Fd gen_UnixFd = do let maxWord32 = toInteger (maxBound :: Word32) let maxCInt = toInteger (maxBound :: CInt) x <- choose (0, toInteger (min maxWord32 maxCInt)) return (fromInteger x) gen_Variant :: Gen Variant gen_Variant = oneof [ gen_Atom , fmap toVariant (arbitrary :: Gen ByteString) -- TODO: proper arbitrary vectors , elements [ toVariant (Data.Vector.fromList ([] :: [Word8])) , toVariant (Data.Vector.fromList ([0, 1, 2, 3, 4, 5] :: [Word8])) , toVariant (Data.Vector.fromList ([0, 1, 2, 3, 4, 5] :: [Word16])) , toVariant (Data.Vector.fromList ([0, 1, 2, 3, 4, 5] :: [Word32])) , toVariant (Data.Vector.fromList ([0, 1, 2, 3, 4, 5] :: [Word64])) , toVariant (Data.Vector.fromList (["foo", "bar", "baz"] :: [Text])) ] -- TODO: proper arbitrary maps , elements [ toVariant (Data.Map.fromList [] :: Map Text Text) , toVariant (Data.Map.fromList [("foo", "bar"), ("baz", "qux")] :: Map Text Text) ] -- TODO: proper arbitrary structures , elements [ toVariant (True, "foo" :: Text, ["bar" :: Text]) , toVariant (1 :: Word8, 1 :: Word16, 1 :: Word32, 1 :: Word64) ] , fmap toVariant gen_Variant ] gen_MethodCall :: Gen MethodCall gen_MethodCall = do path <- arbitrary iface <- arbitrary member <- arbitrary sender <- arbitrary dest <- arbitrary flagReplyExpected <- arbitrary flagAutoStart <- arbitrary body <- smallListOf gen_Variant return (methodCall path "com.example.ignored" member) { methodCallInterface = iface , methodCallSender = sender , methodCallDestination = dest , methodCallReplyExpected = flagReplyExpected , methodCallAutoStart = flagAutoStart , methodCallBody = body } gen_MethodReturn :: Gen MethodReturn gen_MethodReturn = do serial <- arbitrary sender <- arbitrary dest <- arbitrary body <- smallListOf gen_Variant return (methodReturn serial) { methodReturnSender = sender , methodReturnDestination = dest , methodReturnBody = body } gen_MethodError :: Gen MethodError gen_MethodError = do serial <- arbitrary name <- arbitrary sender <- arbitrary dest <- arbitrary body <- smallListOf gen_Variant return (methodError serial name) { methodErrorSender = sender , methodErrorDestination = dest , methodErrorBody = body } gen_Signal :: Gen Signal gen_Signal = do path <- arbitrary iface <- arbitrary member <- arbitrary sender <- arbitrary dest <- arbitrary body <- smallListOf gen_Variant return (signal path iface member) { signalSender = sender , signalDestination = dest , signalBody = body } instance Arbitrary Endianness where arbitrary = elements [BigEndian, LittleEndian] instance Arbitrary Serial where arbitrary = fmap DBus.Internal.Types.Serial arbitrary dbus-0.10.13/tests/DBusTests/Signature.hs0000644000000000000000000001244013073332436016323 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Signature (test_Signature) where import Test.Chell import Test.Chell.QuickCheck import Test.QuickCheck hiding ((.&.), property) import DBus import DBusTests.Util test_Signature :: Suite test_Signature = suite "Signature" [ test_BuildSignature , test_ParseSignature , test_ParseInvalid , test_FormatSignature , test_IsAtom , test_ShowType ] test_BuildSignature :: Test test_BuildSignature = property "signature" prop where prop = forAll gen_SignatureTypes check check types = case signature types of Nothing -> False Just sig -> signatureTypes sig == types test_ParseSignature :: Test test_ParseSignature = property "parseSignature" prop where prop = forAll gen_SignatureString check check (s, types) = case parseSignature s of Nothing -> False Just sig -> signatureTypes sig == types test_ParseInvalid :: Test test_ParseInvalid = assertions "parse-invalid" $ do -- at most 255 characters $expect (just (parseSignature (replicate 254 'y'))) $expect (just (parseSignature (replicate 255 'y'))) $expect (nothing (parseSignature (replicate 256 'y'))) -- length also enforced by 'signature' $expect (just (signature (replicate 255 TypeWord8))) $expect (nothing (signature (replicate 256 TypeWord8))) -- struct code $expect (nothing (parseSignature "r")) -- empty struct $expect (nothing (parseSignature "()")) $expect (nothing (signature [TypeStructure []])) -- dict code $expect (nothing (parseSignature "e")) -- non-atomic dict key $expect (nothing (parseSignature "a{vy}")) $expect (nothing (signature [TypeDictionary TypeVariant TypeVariant])) test_FormatSignature :: Test test_FormatSignature = property "formatSignature" prop where prop = forAll gen_SignatureString check check (s, _) = let Just sig = parseSignature s in formatSignature sig == s test_IsAtom :: Test test_IsAtom = assertions "IsAtom" $ do let Just sig = signature [] assertAtom TypeSignature sig test_ShowType :: Test test_ShowType = assertions "show-type" $ do $expect (equal "Bool" (show TypeBoolean)) $expect (equal "Bool" (show TypeBoolean)) $expect (equal "Word8" (show TypeWord8)) $expect (equal "Word16" (show TypeWord16)) $expect (equal "Word32" (show TypeWord32)) $expect (equal "Word64" (show TypeWord64)) $expect (equal "Int16" (show TypeInt16)) $expect (equal "Int32" (show TypeInt32)) $expect (equal "Int64" (show TypeInt64)) $expect (equal "Double" (show TypeDouble)) $expect (equal "UnixFd" (show TypeUnixFd)) $expect (equal "String" (show TypeString)) $expect (equal "Signature" (show TypeSignature)) $expect (equal "ObjectPath" (show TypeObjectPath)) $expect (equal "Variant" (show TypeVariant)) $expect (equal "[Word8]" (show (TypeArray TypeWord8))) $expect (equal "Dict Word8 (Dict Word8 Word8)" (show (TypeDictionary TypeWord8 (TypeDictionary TypeWord8 TypeWord8)))) $expect (equal "(Word8, Word16)" (show (TypeStructure [TypeWord8, TypeWord16]))) gen_SignatureTypes :: Gen [Type] gen_SignatureTypes = do (_, ts) <- gen_SignatureString return ts gen_SignatureString :: Gen (String, [Type]) gen_SignatureString = gen where anyType = oneof [atom, container] atom = elements [ ("b", TypeBoolean) , ("y", TypeWord8) , ("q", TypeWord16) , ("u", TypeWord32) , ("t", TypeWord64) , ("n", TypeInt16) , ("i", TypeInt32) , ("x", TypeInt64) , ("d", TypeDouble) , ("h", TypeUnixFd) , ("s", TypeString) , ("o", TypeObjectPath) , ("g", TypeSignature) ] container = oneof [ return ("v", TypeVariant) , array , dict , struct ] array = do (tCode, tEnum) <- anyType return ('a':tCode, TypeArray tEnum) dict = do (kCode, kEnum) <- atom (vCode, vEnum) <- anyType return (concat ["a{", kCode, vCode, "}"], TypeDictionary kEnum vEnum) struct = do ts <- listOf1 (halfSized anyType) let (codes, enums) = unzip ts return ("(" ++ concat codes ++ ")", TypeStructure enums) gen = do types <- listOf anyType let (codes, enums) = unzip types let chars = concat codes if length chars > 255 then halfSized gen else return (chars, enums) instance Arbitrary Signature where arbitrary = do ts <- gen_SignatureTypes let Just sig = signature ts return sig dbus-0.10.13/tests/DBusTests/Socket.hs0000644000000000000000000001106113073332436015610 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Socket (test_Socket) where import Test.Chell import Control.Concurrent import Control.Monad.IO.Class (MonadIO, liftIO) import qualified Data.Map as Map import DBus import DBus.Socket import DBus.Transport import DBusTests.Util (forkVar) test_Socket :: Suite test_Socket = suite "Socket" [ test_Listen , test_ListenWith_CustomAuth , test_SendReceive ] test_Listen :: Test test_Listen = assertions "listen" $ do uuid <- liftIO randomUUID let Just addr = address "unix" (Map.fromList [ ("abstract", formatUUID uuid) ]) listener <- liftIO (listen addr) afterTest (closeListener listener) acceptedVar <- forkVar (accept listener) openedVar <- forkVar (open addr) sock1 <- liftIO (takeMVar acceptedVar) afterTest (close sock1) sock2 <- liftIO (takeMVar openedVar) afterTest (close sock2) test_ListenWith_CustomAuth :: Test test_ListenWith_CustomAuth = assertions "listenWith-custom-auth" $ do uuid <- liftIO randomUUID let Just addr = address "unix" (Map.fromList [ ("abstract", formatUUID uuid) ]) listener <- liftIO (listenWith (defaultSocketOptions { socketAuthenticator = dummyAuth }) addr) afterTest (closeListener listener) acceptedVar <- forkVar (accept listener) openedVar <- forkVar (openWith (defaultSocketOptions { socketAuthenticator = dummyAuth }) addr) sock1 <- liftIO (takeMVar acceptedVar) afterTest (close sock1) sock2 <- liftIO (takeMVar openedVar) afterTest (close sock2) test_SendReceive :: Test test_SendReceive = assertions "send-receive" $ do uuid <- liftIO randomUUID let Just addr = address "unix" (Map.fromList [ ("abstract", formatUUID uuid) ]) let msg = (methodCall "/" "org.example.iface" "Foo") { methodCallSender = Just "org.example.src" , methodCallDestination = Just "org.example.dst" , methodCallAutoStart = False , methodCallReplyExpected = False , methodCallBody = [toVariant True] } listener <- liftIO (listen addr) afterTest (closeListener listener) acceptedVar <- forkVar (accept listener) openedVar <- forkVar (open addr) sock1 <- liftIO (takeMVar acceptedVar) afterTest (close sock1) sock2 <- liftIO (takeMVar openedVar) afterTest (close sock2) -- client -> server do serialVar <- liftIO newEmptyMVar sentVar <- forkVar (send sock2 msg (putMVar serialVar)) receivedVar <- forkVar (receive sock1) serial <- liftIO (takeMVar serialVar) sent <- liftIO (takeMVar sentVar) received <- liftIO (takeMVar receivedVar) $assert (equal sent ()) $assert (equal received (ReceivedMethodCall serial msg)) -- server -> client do serialVar <- liftIO newEmptyMVar sentVar <- forkVar (send sock1 msg (putMVar serialVar)) receivedVar <- forkVar (receive sock2) serial <- liftIO (takeMVar serialVar) sent <- liftIO (takeMVar sentVar) received <- liftIO (takeMVar receivedVar) $assert (equal sent ()) $assert (equal received (ReceivedMethodCall serial msg)) dummyAuth :: Transport t => Authenticator t dummyAuth = authenticator { authenticatorClient = dummyAuthClient , authenticatorServer = dummyAuthServer } dummyAuthClient :: Transport t => t -> IO Bool dummyAuthClient t = do transportPut t "\x00" resp <- transportGet t 4 return (resp == "OK\r\n") dummyAuthServer :: Transport t => t -> UUID -> IO Bool dummyAuthServer t _ = do c <- transportGet t 1 if c == "\x00" then do transportPut t "OK\r\n" return True else return False dbus-0.10.13/tests/DBusTests/Transport.hs0000644000000000000000000004353613073332436016370 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Transport (test_Transport) where import Test.Chell import Control.Concurrent import Control.Monad.IO.Class (MonadIO, liftIO) import qualified Data.ByteString import Data.Function (fix) import Data.List (isPrefixOf) import qualified Data.Map as Map import qualified Network as N import qualified Network.Socket as NS import Network.Socket.ByteString (sendAll, recv) import System.Directory (getTemporaryDirectory, removeFile) import DBus import DBus.Transport import DBusTests.Util test_Transport :: Suite test_Transport = suite "Transport" $ suiteTests suite_TransportOpen ++ suiteTests suite_TransportListen ++ suiteTests suite_TransportAccept ++ [ test_TransportSendReceive , test_HandleLostConnection ] suite_TransportOpen :: Suite suite_TransportOpen = suite "transportOpen" $ [ test_OpenUnknown ] ++ suiteTests suite_OpenUnix ++ suiteTests suite_OpenTcp suite_TransportListen :: Suite suite_TransportListen = suite "transportListen" $ [ test_ListenUnknown ] ++ suiteTests suite_ListenUnix ++ suiteTests suite_ListenTcp suite_TransportAccept :: Suite suite_TransportAccept = suite "transportAccept" [ test_AcceptSocket , test_AcceptSocketClosed ] test_OpenUnknown :: Test test_OpenUnknown = assertions "unknown" $ do let Just addr = address "noexist" Map.empty $assert $ throwsEq ((transportError "Unknown address method: \"noexist\"") { transportErrorAddress = Just addr }) (transportOpen socketTransportOptions addr) suite_OpenUnix :: Suite suite_OpenUnix = suite "unix" [ test_OpenUnix_Path , test_OpenUnix_Abstract , test_OpenUnix_TooFew , test_OpenUnix_TooMany , test_OpenUnix_NotListening ] test_OpenUnix_Path :: Test test_OpenUnix_Path = assertions "path" $ do (addr, networkSocket) <- listenRandomUnixPath afterTest (N.sClose networkSocket) fdcountBefore <- countFileDescriptors t <- liftIO (transportOpen socketTransportOptions addr) liftIO (transportClose t) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenUnix_Abstract :: Test test_OpenUnix_Abstract = assertions "abstract" $ do (addr, networkSocket) <- listenRandomUnixAbstract afterTest (N.sClose networkSocket) fdcountBefore <- countFileDescriptors t <- liftIO (transportOpen socketTransportOptions addr) liftIO (transportClose t) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenUnix_TooFew :: Test test_OpenUnix_TooFew = assertions "too-few" $ do fdcountBefore <- countFileDescriptors let Just addr = address "unix" Map.empty $assert $ throwsEq ((transportError "One of 'path' or 'abstract' must be specified for the 'unix' transport.") { transportErrorAddress = Just addr }) (transportOpen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenUnix_TooMany :: Test test_OpenUnix_TooMany = assertions "too-many" $ do fdcountBefore <- countFileDescriptors let Just addr = address "unix" (Map.fromList [ ("path", "foo") , ("abstract", "bar") ]) $assert $ throwsEq ((transportError "Only one of 'path' or 'abstract' may be specified for the 'unix' transport.") { transportErrorAddress = Just addr }) (transportOpen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenUnix_NotListening :: Test test_OpenUnix_NotListening = assertions "not-listening" $ do fdcountBefore <- countFileDescriptors (addr, networkSocket) <- listenRandomUnixAbstract liftIO (NS.sClose networkSocket) $assert $ throwsEq ((transportError "connect: does not exist (Connection refused)") { transportErrorAddress = Just addr }) (transportOpen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) suite_OpenTcp :: Suite suite_OpenTcp = suite "tcp" [ test_OpenTcp_IPv4 , skipWhen noIPv6 test_OpenTcp_IPv6 , test_OpenTcp_Unknown , test_OpenTcp_NoPort , test_OpenTcp_InvalidPort , test_OpenTcp_NoUsableAddresses , test_OpenTcp_NotListening ] test_OpenTcp_IPv4 :: Test test_OpenTcp_IPv4 = assertions "ipv4" $ do (addr, networkSocket) <- listenRandomIPv4 afterTest (N.sClose networkSocket) fdcountBefore <- countFileDescriptors t <- liftIO (transportOpen socketTransportOptions addr) liftIO (transportClose t) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenTcp_IPv6 :: Test test_OpenTcp_IPv6 = assertions "ipv6" $ do (addr, networkSocket) <- listenRandomIPv6 afterTest (N.sClose networkSocket) fdcountBefore <- countFileDescriptors t <- liftIO (transportOpen socketTransportOptions addr) liftIO (transportClose t) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenTcp_Unknown :: Test test_OpenTcp_Unknown = assertions "unknown-family" $ do fdcountBefore <- countFileDescriptors let Just addr = address "tcp" (Map.fromList [ ("family", "noexist") , ("port", "1234") ]) $assert $ throwsEq ((transportError "Unknown socket family for TCP transport: \"noexist\"") { transportErrorAddress = Just addr }) (transportOpen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenTcp_NoPort :: Test test_OpenTcp_NoPort = assertions "no-port" $ do fdcountBefore <- countFileDescriptors let Just addr = address "tcp" (Map.fromList [ ("family", "ipv4") ]) $assert $ throwsEq ((transportError "TCP transport requires the `port' parameter.") { transportErrorAddress = Just addr }) (transportOpen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenTcp_InvalidPort :: Test test_OpenTcp_InvalidPort = assertions "invalid-port" $ do fdcountBefore <- countFileDescriptors let Just addr = address "tcp" (Map.fromList [ ("family", "ipv4") , ("port", "123456") ]) $assert $ throwsEq ((transportError "Invalid socket port for TCP transport: \"123456\"") { transportErrorAddress = Just addr }) (transportOpen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenTcp_NoUsableAddresses :: Test test_OpenTcp_NoUsableAddresses = assertions "no-usable-addresses" $ do fdcountBefore <- countFileDescriptors let Just addr = address "tcp" (Map.fromList [ ("family", "ipv4") , ("port", "1234") , ("host", "256.256.256.256") ]) $assert $ throws (\err -> and [ "getAddrInfo: does not exist" `isPrefixOf` transportErrorMessage err , transportErrorAddress err == Just addr ]) (transportOpen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_OpenTcp_NotListening :: Test test_OpenTcp_NotListening = assertions "too-many" $ do fdcountBefore <- countFileDescriptors (addr, networkSocket) <- listenRandomIPv4 liftIO (NS.sClose networkSocket) $assert $ throwsEq ((transportError "connect: does not exist (Connection refused)") { transportErrorAddress = Just addr }) (transportOpen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_TransportSendReceive :: Test test_TransportSendReceive = assertions "send-receive" $ do (addr, networkSocket) <- listenRandomIPv4 afterTest (N.sClose networkSocket) -- a simple echo server, which sends back anything it receives. _ <- liftIO $ forkIO $ do (s, _) <- NS.accept networkSocket fix $ \loop -> do bytes <- recv s 50 if Data.ByteString.null bytes then NS.sClose s else do sendAll s bytes loop t <- liftIO (transportOpen socketTransportOptions addr) afterTest (transportClose t) -- small chunks of data are combined do var <- forkVar (transportGet t 3) liftIO (transportPut t "1") liftIO (transportPut t "2") liftIO (transportPut t "3") bytes <- liftIO (readMVar var) $assert (equal bytes "123") -- large chunks of data are read in full do let sentBytes = Data.ByteString.replicate (4096 * 100) 0 var <- forkVar (transportGet t (4096 * 100)) liftIO (transportPut t sentBytes) bytes <- liftIO (readMVar var) $assert (equal bytes sentBytes) test_HandleLostConnection :: Test test_HandleLostConnection = assertions "handle-lost-connection" $ do (addr, networkSocket) <- listenRandomIPv4 afterTest (N.sClose networkSocket) _ <- liftIO $ forkIO $ do (s, _) <- NS.accept networkSocket sendAll s "123" NS.sClose s t <- liftIO (transportOpen socketTransportOptions addr) afterTest (transportClose t) bytes <- liftIO (transportGet t 4) $assert (equal bytes "123") test_ListenUnknown :: Test test_ListenUnknown = assertions "unknown" $ do let Just addr = address "noexist" Map.empty $assert $ throwsEq ((transportError "Unknown address method: \"noexist\"") { transportErrorAddress = Just addr }) (transportListen socketTransportOptions addr) suite_ListenUnix :: Suite suite_ListenUnix = suite "unix" [ test_ListenUnix_Path , test_ListenUnix_Abstract , test_ListenUnix_Tmpdir , test_ListenUnix_TooFew , test_ListenUnix_TooMany , test_ListenUnix_InvalidBind ] test_ListenUnix_Path :: Test test_ListenUnix_Path = assertions "path" $ do path <- liftIO getTempPath let Just addr = address "unix" (Map.fromList [ ("path", path) ]) l <- liftIO (transportListen socketTransportOptions addr) afterTest (transportListenerClose l) afterTest (removeFile path) -- listener address is random, so it can't be checked directly. let addrParams = addressParameters (transportListenerAddress l) $expect (sameItems (Map.keys addrParams) ["path", "guid"]) $expect (equal (Map.lookup "path" addrParams) (Just path)) test_ListenUnix_Abstract :: Test test_ListenUnix_Abstract = assertions "abstract" $ do path <- liftIO getTempPath let Just addr = address "unix" (Map.fromList [ ("abstract", path) ]) l <- liftIO (transportListen socketTransportOptions addr) afterTest (transportListenerClose l) -- listener address is random, so it can't be checked directly. let addrParams = addressParameters (transportListenerAddress l) $expect (sameItems (Map.keys addrParams) ["abstract", "guid"]) $expect (equal (Map.lookup "abstract" addrParams) (Just path)) test_ListenUnix_Tmpdir :: Test test_ListenUnix_Tmpdir = assertions "tmpdir" $ do tmpdir <- liftIO getTemporaryDirectory let Just addr = address "unix" (Map.fromList [ ("tmpdir", tmpdir) ]) l <- liftIO (transportListen socketTransportOptions addr) afterTest (transportListenerClose l) -- listener address is random, so it can't be checked directly. let addrKeys = Map.keys (addressParameters (transportListenerAddress l)) $expect ("path" `elem` addrKeys || "abstract" `elem` addrKeys) test_ListenUnix_TooFew :: Test test_ListenUnix_TooFew = assertions "too-few" $ do let Just addr = address "unix" Map.empty $assert $ throwsEq ((transportError "One of 'abstract', 'path', or 'tmpdir' must be specified for the 'unix' transport.") { transportErrorAddress = Just addr }) (transportListen socketTransportOptions addr) test_ListenUnix_TooMany :: Test test_ListenUnix_TooMany = assertions "too-many" $ do let Just addr = address "unix" (Map.fromList [ ("path", "foo") , ("abstract", "bar") ]) $assert $ throwsEq ((transportError "Only one of 'abstract', 'path', or 'tmpdir' may be specified for the 'unix' transport.") { transportErrorAddress = Just addr }) (transportListen socketTransportOptions addr) test_ListenUnix_InvalidBind :: Test test_ListenUnix_InvalidBind = assertions "invalid-bind" $ do fdcountBefore <- countFileDescriptors let Just addr = address "unix" (Map.fromList [ ("path", "/") ]) $assert $ throwsEq ((transportError "bind: resource busy (Address already in use)") { transportErrorAddress = Just addr }) (transportListen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) suite_ListenTcp :: Suite suite_ListenTcp = suite "tcp" [ test_ListenTcp_IPv4 , skipWhen noIPv6 test_ListenTcp_IPv6 , test_ListenTcp_Unknown , test_ListenTcp_InvalidPort , test_ListenTcp_InvalidBind ] test_ListenTcp_IPv4 :: Test test_ListenTcp_IPv4 = assertions "ipv4" $ do let Just addr = address "tcp" (Map.fromList [ ("family", "ipv4") ]) l <- liftIO (transportListen socketTransportOptions addr) afterTest (transportListenerClose l) let params = addressParameters (transportListenerAddress l) $expect (equal (Map.lookup "family" params) (Just "ipv4")) $expect ("port" `elem` Map.keys params) test_ListenTcp_IPv6 :: Test test_ListenTcp_IPv6 = assertions "ipv6" $ do let Just addr = address "tcp" (Map.fromList [ ("family", "ipv6") ]) l <- liftIO (transportListen socketTransportOptions addr) afterTest (transportListenerClose l) let params = addressParameters (transportListenerAddress l) $expect (equal (Map.lookup "family" params) (Just "ipv6")) $expect ("port" `elem` Map.keys params) test_ListenTcp_Unknown :: Test test_ListenTcp_Unknown = assertions "unknown-family" $ do let Just addr = address "tcp" (Map.fromList [ ("family", "noexist") , ("port", "1234") ]) $assert $ throwsEq ((transportError "Unknown socket family for TCP transport: \"noexist\"") { transportErrorAddress = Just addr }) (transportListen socketTransportOptions addr) test_ListenTcp_InvalidPort :: Test test_ListenTcp_InvalidPort = assertions "invalid-port" $ do let Just addr = address "tcp" (Map.fromList [ ("family", "ipv4") , ("port", "123456") ]) $assert $ throwsEq ((transportError "Invalid socket port for TCP transport: \"123456\"") { transportErrorAddress = Just addr }) (transportListen socketTransportOptions addr) test_ListenTcp_InvalidBind :: Test test_ListenTcp_InvalidBind = assertions "invalid-bind" $ do fdcountBefore <- countFileDescriptors let Just addr = address "tcp" (Map.fromList [ ("family", "ipv4") , ("port", "1") ]) $assert $ throwsEq ((transportError "bind: permission denied (Permission denied)") { transportErrorAddress = Just addr }) (transportListen socketTransportOptions addr) fdcountAfter <- countFileDescriptors $assert (equal fdcountBefore fdcountAfter) test_AcceptSocket :: Test test_AcceptSocket = assertions "socket" $ do path <- liftIO getTempPath let Just addr = address "unix" (Map.fromList [ ("abstract", path) ]) listener <- liftIO (transportListen socketTransportOptions addr) afterTest (transportListenerClose listener) acceptedVar <- forkVar (transportAccept listener) openedVar <- forkVar (transportOpen socketTransportOptions addr) accepted <- liftIO (readMVar acceptedVar) opened <- liftIO (readMVar openedVar) afterTest (transportClose accepted) afterTest (transportClose opened) liftIO (transportPut opened "testing") bytes <- liftIO (transportGet accepted 7) $expect (equal bytes "testing") test_AcceptSocketClosed :: Test test_AcceptSocketClosed = assertions "socket-closed" $ do path <- liftIO getTempPath let Just addr = address "unix" (Map.fromList [ ("abstract", path) ]) listener <- liftIO (transportListen socketTransportOptions addr) let listeningAddr = transportListenerAddress listener liftIO (transportListenerClose listener) $assert $ throwsEq ((transportError "user error (accept: can't perform accept on socket ((AF_UNIX,Stream,0)) in status Closed)") { transportErrorAddress = Just listeningAddr }) (transportAccept listener) socketTransportOptions :: TransportOptions SocketTransport socketTransportOptions = transportDefaultOptions dbus-0.10.13/tests/DBusTests/Util.hs0000644000000000000000000002057113073332436015303 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Util ( assertVariant , assertValue , assertAtom , getTempPath , listenRandomUnixPath , listenRandomUnixAbstract , listenRandomIPv4 , listenRandomIPv6 , noIPv6 , forkVar , withEnv , countFileDescriptors , dropWhileEnd , halfSized , clampedSize , smallListOf , smallListOf1 ) where import Control.Concurrent import Control.Exception (IOException, try, bracket, bracket_) import Control.Monad.IO.Class (MonadIO, liftIO) import Data.Bits ((.&.)) import qualified Data.ByteString import qualified Data.ByteString.Lazy import Data.Char (chr) import qualified Data.Map as Map import qualified Data.Set import qualified Data.Text as T import qualified Network as N import qualified Network.Socket as NS import System.Directory (getTemporaryDirectory, removeFile) import qualified System.Posix as Posix import System.FilePath (()) import Test.Chell import Test.QuickCheck hiding ((.&.)) import DBus import DBus.Internal.Types assertVariant :: (Eq a, Show a, IsVariant a) => Type -> a -> Assertions () assertVariant t a = do $expect $ equal t (variantType (toVariant a)) $expect $ equal (fromVariant (toVariant a)) (Just a) $expect $ equal (toVariant a) (toVariant a) $([d||]) assertValue :: (Eq a, Show a, IsValue a) => Type -> a -> Assertions () assertValue t a = do $expect $ equal t (DBus.typeOf a) $expect $ equal t (DBus.Internal.Types.typeOf a) $expect $ equal t (valueType (toValue a)) $expect $ equal (fromValue (toValue a)) (Just a) $expect $ equal (toValue a) (toValue a) assertVariant t a $([d||]) assertAtom :: (Eq a, Show a, IsAtom a) => Type -> a -> Assertions () assertAtom t a = do $expect $ equal t (atomType (toAtom a)) $expect $ equal (fromAtom (toAtom a)) (Just a) $expect $ equal (toAtom a) (toAtom a) assertValue t a getTempPath :: IO String getTempPath = do tmp <- getTemporaryDirectory uuid <- randomUUID return (tmp formatUUID uuid) listenRandomUnixPath :: Assertions (Address, N.Socket) listenRandomUnixPath = do path <- liftIO getTempPath let sockAddr = NS.SockAddrUnix path sock <- liftIO (NS.socket NS.AF_UNIX NS.Stream NS.defaultProtocol) liftIO (NS.bindSocket sock sockAddr) liftIO (NS.listen sock 1) afterTest (removeFile path) let Just addr = address "unix" (Map.fromList [ ("path", path) ]) return (addr, sock) listenRandomUnixAbstract :: MonadIO m => m (Address, N.Socket) listenRandomUnixAbstract = liftIO $ do uuid <- liftIO randomUUID let sockAddr = NS.SockAddrUnix ('\x00' : formatUUID uuid) sock <- NS.socket NS.AF_UNIX NS.Stream NS.defaultProtocol NS.bindSocket sock sockAddr NS.listen sock 1 let Just addr = address "unix" (Map.fromList [ ("abstract", formatUUID uuid) ]) return (addr, sock) listenRandomIPv4 :: MonadIO m => m (Address, N.Socket) listenRandomIPv4 = liftIO $ do hostAddr <- NS.inet_addr "127.0.0.1" let sockAddr = NS.SockAddrInet 0 hostAddr sock <- NS.socket NS.AF_INET NS.Stream NS.defaultProtocol NS.bindSocket sock sockAddr NS.listen sock 1 sockPort <- NS.socketPort sock let Just addr = address "tcp" (Map.fromList [ ("family", "ipv4") , ("host", "localhost") , ("port", show (toInteger sockPort)) ]) return (addr, sock) listenRandomIPv6 :: MonadIO m => m (Address, N.Socket) listenRandomIPv6 = liftIO $ do addrs <- NS.getAddrInfo Nothing (Just "::1") Nothing let sockAddr = case addrs of [] -> error "listenRandomIPv6: no address for localhost?" a:_ -> NS.addrAddress a sock <- NS.socket NS.AF_INET6 NS.Stream NS.defaultProtocol NS.bindSocket sock sockAddr NS.listen sock 1 sockPort <- NS.socketPort sock let Just addr = address "tcp" (Map.fromList [ ("family", "ipv6") , ("host", "::1") , ("port", show (toInteger sockPort)) ]) return (addr, sock) noIPv6 :: IO Bool noIPv6 = do tried <- try (NS.getAddrInfo Nothing (Just "::1") Nothing) case (tried :: Either IOException [NS.AddrInfo]) of Left _ -> return True Right addrs -> return (null addrs) forkVar :: MonadIO m => IO a -> m (MVar a) forkVar io = liftIO $ do var <- newEmptyMVar _ <- forkIO (io >>= putMVar var) return var withEnv :: MonadIO m => String -> Maybe String -> IO a -> m a withEnv name value io = liftIO $ do let set val = case val of Just x -> Posix.setEnv name x True Nothing -> Posix.unsetEnv name old <- Posix.getEnv name bracket_ (set value) (set old) io countFileDescriptors :: MonadIO m => m Int countFileDescriptors = liftIO io where io = do pid <- Posix.getProcessID let fdDir = "/proc/" ++ show pid ++ "/fd" bracket (Posix.openDirStream fdDir) Posix.closeDirStream countDirEntries countDirEntries dir = loop 0 where loop n = do name <- Posix.readDirStream dir if null name then return n else loop (n + 1) halfSized :: Gen a -> Gen a halfSized gen = sized (\n -> if n > 0 then resize (div n 2) gen else gen) smallListOf :: Gen a -> Gen [a] smallListOf gen = clampedSize 10 (listOf gen) smallListOf1 :: Gen a -> Gen [a] smallListOf1 gen = clampedSize 10 (listOf1 gen) clampedSize :: Int -> Gen a -> Gen a clampedSize maxN gen = sized (\n -> resize (min n maxN) gen) instance Arbitrary T.Text where arbitrary = fmap T.pack genUnicode genUnicode :: Gen [Char] genUnicode = string where string = sized $ \n -> do k <- choose (0,n) sequence [ char | _ <- [1..k] ] excluding :: [a -> Bool] -> Gen a -> Gen a excluding bad gen = loop where loop = do x <- gen if or (map ($ x) bad) then loop else return x reserved = [lowSurrogate, highSurrogate, noncharacter] lowSurrogate c = c >= 0xDC00 && c <= 0xDFFF highSurrogate c = c >= 0xD800 && c <= 0xDBFF noncharacter c = masked == 0xFFFE || masked == 0xFFFF where masked = c .&. 0xFFFF ascii = choose (0x20, 0x7F) plane0 = choose (0xF0, 0xFFFF) plane1 = oneof [ choose (0x10000, 0x10FFF) , choose (0x11000, 0x11FFF) , choose (0x12000, 0x12FFF) , choose (0x13000, 0x13FFF) , choose (0x1D000, 0x1DFFF) , choose (0x1F000, 0x1FFFF) ] plane2 = oneof [ choose (0x20000, 0x20FFF) , choose (0x21000, 0x21FFF) , choose (0x22000, 0x22FFF) , choose (0x23000, 0x23FFF) , choose (0x24000, 0x24FFF) , choose (0x25000, 0x25FFF) , choose (0x26000, 0x26FFF) , choose (0x27000, 0x27FFF) , choose (0x28000, 0x28FFF) , choose (0x29000, 0x29FFF) , choose (0x2A000, 0x2AFFF) , choose (0x2B000, 0x2BFFF) , choose (0x2F000, 0x2FFFF) ] plane14 = choose (0xE0000, 0xE0FFF) planes = [ascii, plane0, plane1, plane2, plane14] char = chr `fmap` excluding reserved (oneof planes) instance Arbitrary Data.ByteString.ByteString where arbitrary = fmap Data.ByteString.pack arbitrary instance Arbitrary Data.ByteString.Lazy.ByteString where arbitrary = fmap Data.ByteString.Lazy.fromChunks arbitrary dropWhileEnd :: (Char -> Bool) -> String -> String dropWhileEnd p = T.unpack . T.dropWhileEnd p . T.pack dbus-0.10.13/tests/DBusTests/Variant.hs0000644000000000000000000001576113073332436015777 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2010-2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Variant (test_Variant) where import Prelude hiding (fail) import Test.Chell import qualified Data.ByteString import qualified Data.ByteString.Lazy import qualified Data.Text as T import qualified Data.Text import qualified Data.Text.Lazy import Data.Word (Word8, Word16, Word32, Word64) import Data.Int (Int16, Int32, Int64) import qualified Data.Map import qualified Data.Vector import System.Posix.Types (Fd) import DBus import DBus.Internal.Types (toValue) import DBusTests.Util test_Variant :: Suite test_Variant = suite "Variant" [ test_IsAtom , test_IsValue , test_Show , test_ByteStorage ] test_IsAtom :: Test test_IsAtom = assertions "IsAtom" $ do assertAtom TypeBoolean True assertAtom TypeWord8 (0 :: Word8) assertAtom TypeWord16 (0 :: Word16) assertAtom TypeWord32 (0 :: Word32) assertAtom TypeWord64 (0 :: Word64) assertAtom TypeInt16 (0 :: Int16) assertAtom TypeInt32 (0 :: Int32) assertAtom TypeInt64 (0 :: Int64) assertAtom TypeDouble (0 :: Double) assertAtom TypeUnixFd (0 :: Fd) assertAtom TypeString (Data.Text.pack "") assertAtom TypeString (Data.Text.Lazy.pack "") assertAtom TypeString ("" :: String) assertAtom TypeObjectPath (objectPath_ "/") assertAtom TypeSignature (signature_ []) test_IsValue :: Test test_IsValue = assertions "IsValue" $ do assertValue TypeVariant (toVariant True) assertValue (TypeArray TypeBoolean) [True] assertValue (TypeArray TypeBoolean) (Data.Vector.fromList [True]) assertValue (TypeArray TypeWord8) Data.ByteString.empty assertValue (TypeArray TypeWord8) Data.ByteString.Lazy.empty assertValue (TypeDictionary TypeBoolean TypeBoolean) (Data.Map.fromList [(True, True)]) assertValue (TypeStructure (replicate 2 TypeBoolean)) (True, True) assertValue (TypeStructure (replicate 3 TypeBoolean)) (True, True, True) assertValue (TypeStructure (replicate 4 TypeBoolean)) (True, True, True, True) assertValue (TypeStructure (replicate 5 TypeBoolean)) (True, True, True, True, True) assertValue (TypeStructure (replicate 6 TypeBoolean)) (True, True, True, True, True, True) assertValue (TypeStructure (replicate 7 TypeBoolean)) (True, True, True, True, True, True, True) assertValue (TypeStructure (replicate 8 TypeBoolean)) (True, True, True, True, True, True, True, True) assertValue (TypeStructure (replicate 9 TypeBoolean)) (True, True, True, True, True, True, True, True, True) assertValue (TypeStructure (replicate 10 TypeBoolean)) (True, True, True, True, True, True, True, True, True, True) assertValue (TypeStructure (replicate 11 TypeBoolean)) (True, True, True, True, True, True, True, True, True, True, True) assertValue (TypeStructure (replicate 12 TypeBoolean)) (True, True, True, True, True, True, True, True, True, True, True, True) assertValue (TypeStructure (replicate 13 TypeBoolean)) (True, True, True, True, True, True, True, True, True, True, True, True, True) assertValue (TypeStructure (replicate 14 TypeBoolean)) (True, True, True, True, True, True, True, True, True, True, True, True, True, True) assertValue (TypeStructure (replicate 15 TypeBoolean)) (True, True, True, True, True, True, True, True, True, True, True, True, True, True, True) test_Show :: Test test_Show = assertions "show" $ do $expect $ equal "Variant True" (show (toVariant True)) $expect $ equal "Variant 0" (show (toVariant (0 :: Word8))) $expect $ equal "Variant 0" (show (toVariant (0 :: Word16))) $expect $ equal "Variant 0" (show (toVariant (0 :: Word32))) $expect $ equal "Variant 0" (show (toVariant (0 :: Word64))) $expect $ equal "Variant 0" (show (toVariant (0 :: Int16))) $expect $ equal "Variant 0" (show (toVariant (0 :: Int32))) $expect $ equal "Variant 0" (show (toVariant (0 :: Int64))) $expect $ equal "Variant 0.1" (show (toVariant (0.1 :: Double))) $expect $ equal "Variant (UnixFd 1)" (show (toVariant (1 :: Fd))) $expect $ equal "Variant \"\"" (show (toVariant (T.pack ""))) $expect $ equal "Variant (ObjectPath \"/\")" (show (toVariant (objectPath_ "/"))) $expect $ equal "Variant (Signature \"\")" (show (toVariant (signature_ []))) $expect $ equal "Variant (Variant True)" (show (toVariant (toVariant True))) $expect $ equal "Variant [True, False]" (show (toVariant [True, False])) $expect $ equal "Variant b\"\"" (show (toVariant Data.ByteString.empty)) $expect $ equal "Variant b\"\"" (show (toVariant Data.ByteString.Lazy.empty)) $expect $ equal "Variant b\"\"" (show (toVariant ([] :: [Word8]))) $expect $ equal "(Variant {False: True, True: False})" (showsPrec 11 (toVariant (Data.Map.fromList [(True, False), (False, True)])) "") $expect $ equal "(Variant (True, False))" (showsPrec 11 (toVariant (True, False)) "") test_ByteStorage :: Test test_ByteStorage = assertions "byte-storage" $ do -- Vector Word8 -> Vector Word8 $assert $ equal (toValue (Data.Vector.fromList [0 :: Word8])) (toValue (Data.Vector.fromList [0 :: Word8])) -- Vector Word8 -> ByteString $assert $ equal (toValue (Data.Vector.fromList [0 :: Word8])) (toValue (Data.ByteString.pack [0])) -- Vector Word8 -> Lazy.ByteString $assert $ equal (toValue (Data.Vector.fromList [0 :: Word8])) (toValue (Data.ByteString.Lazy.pack [0])) -- ByteString -> Vector Word8 $assert $ equal (toValue (Data.ByteString.pack [0])) (toValue (Data.Vector.fromList [0 :: Word8])) -- ByteString -> ByteString $assert $ equal (toValue (Data.ByteString.pack [0])) (toValue (Data.ByteString.pack [0])) -- ByteString -> Lazy.ByteString $assert $ equal (toValue (Data.ByteString.pack [0])) (toValue (Data.ByteString.Lazy.pack [0])) -- Lazy.ByteString -> Vector Word8 $assert $ equal (toValue (Data.ByteString.Lazy.pack [0])) (toValue (Data.Vector.fromList [0 :: Word8])) -- Lazy.ByteString -> ByteString $assert $ equal (toValue (Data.ByteString.Lazy.pack [0])) (toValue (Data.ByteString.pack [0])) -- Lazy.ByteString -> Lazy.ByteString $assert $ equal (toValue (Data.ByteString.Lazy.pack [0])) (toValue (Data.ByteString.Lazy.pack [0])) dbus-0.10.13/tests/DBusTests/Wire.hs0000644000000000000000000000256213073332436015274 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} -- Copyright (C) 2012 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module DBusTests.Wire (test_Wire) where import Test.Chell import qualified Data.ByteString.Char8 () import DBus test_Wire :: Suite test_Wire = suite "Wire" $ suiteTests test_Unmarshal test_Unmarshal :: Suite test_Unmarshal = suite "unmarshal" [ test_UnmarshalUnexpectedEof ] test_UnmarshalUnexpectedEof :: Test test_UnmarshalUnexpectedEof = assertions "unexpected-eof" $ do let unmarshaled = unmarshal "0" $assert (left unmarshaled) let Left err = unmarshaled $assert (equal (unmarshalErrorMessage err) "Unexpected end of input while parsing message header.") dbus-0.10.13/benchmarks/DBusBenchmarks.hs0000644000000000000000000000765113073332436016320 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} -- Copyright (C) 2010-2011 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module Main (benchmarks, main) where import Control.DeepSeq import Criterion.Types import Criterion.Config import qualified Criterion.Main import Data.Word (Word32) import Unsafe.Coerce (unsafeCoerce) import DBus config :: Config config = defaultConfig { cfgPerformGC = ljust True } serial :: Word32 -> Serial serial = unsafeCoerce -- FIXME: should the Serial constructor be exposed to -- clients? instance NFData Type instance NFData Signature where rnf = rnf . signatureTypes instance NFData ObjectPath instance NFData InterfaceName instance NFData MemberName instance NFData ErrorName instance NFData BusName empty_MethodCall :: MethodCall empty_MethodCall = methodCall "/" "org.i" "m" empty_MethodReturn :: MethodReturn empty_MethodReturn = methodReturn (serial 0) benchMarshal :: Message msg => String -> msg -> Benchmark benchMarshal name msg = bench name (whnf (marshal LittleEndian (serial 0)) msg) benchUnmarshal :: Message msg => String -> msg -> Benchmark benchUnmarshal name msg = bench name (whnf unmarshal bytes) where Right bytes = marshal LittleEndian (serial 0) msg benchmarks :: [Benchmark] benchmarks = [ bgroup "Types" [ bgroup "Signature" [ bench "parseSignature/small" (nf parseSignature "y") , bench "parseSignature/medium" (nf parseSignature "yyyyuua(yv)") , bench "parseSignature/large" (nf parseSignature "a{s(asiiiiasa(siiia{s(iiiiv)}))}") ] , bgroup "ObjectPath" [ bench "objectPath_/small" (nf objectPath_ "/") , bench "objectPath_/medium" (nf objectPath_ "/foo/bar") , bench "objectPath_/large" (nf objectPath_ "/f0OO/b4R/baz_qux/blahblahblah") ] , bgroup "InterfaceName" [ bench "interfaceName_/small" (nf interfaceName_ "f.b") , bench "interfaceName_/medium" (nf interfaceName_ "foo.bar.baz") , bench "interfaceName_/large" (nf interfaceName_ "f0OOO.b4R.baz_qux.blahblahblah") ] , bgroup "MemberName" [ bench "memberName_/small" (nf memberName_ "f") , bench "memberName_/medium" (nf memberName_ "FooBar") , bench "memberName_/large" (nf memberName_ "f0OOOb4RBazQuxBlahBlahBlah") ] , bgroup "ErrorName" [ bench "errorName_/small" (nf errorName_ "f.b") , bench "errorName_/medium" (nf errorName_ "foo.bar.baz") , bench "errorName_/large" (nf errorName_ "f0OOO.b4R.baz_qux.blahblahblah") ] , bgroup "BusName" [ bench "busName_/small" (nf busName_ "f.b") , bench "busName_/medium" (nf busName_ "foo.bar.baz") , bench "busName_/large" (nf busName_ "f0OOO.b4R.baz-qux.blahblahblah") ] ] , bgroup "Marshal" [ benchMarshal "MethodCall/empty" empty_MethodCall , benchMarshal "MethodReturn/empty" empty_MethodReturn ] , bgroup "Unmarshal" [ benchUnmarshal "MethodCall/empty" empty_MethodCall , benchUnmarshal "MethodReturn/empty" empty_MethodReturn ] ] main :: IO () main = Criterion.Main.defaultMainWith config (return ()) benchmarks dbus-0.10.13/license.txt0000644000000000000000000010451313054375603013174 0ustar0000000000000000 GNU GENERAL PUBLIC LICENSE Version 3, 29 June 2007 Copyright (C) 2007 Free Software Foundation, Inc. Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The GNU General Public License is a free, copyleft license for software and other kinds of works. The licenses for most software and other practical works are designed to take away your freedom to share and change the works. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change all versions of a program--to make sure it remains free software for all its users. We, the Free Software Foundation, use the GNU General Public License for most of our software; it applies also to any other work released this way by its authors. You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for them if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs, and that you know you can do these things. To protect your rights, we need to prevent others from denying you these rights or asking you to surrender the rights. Therefore, you have certain responsibilities if you distribute copies of the software, or if you modify it: responsibilities to respect the freedom of others. For example, if you distribute copies of such a program, whether gratis or for a fee, you must pass on to the recipients the same freedoms that you received. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. Developers that use the GNU GPL protect your rights with two steps: (1) assert copyright on the software, and (2) offer you this License giving you legal permission to copy, distribute and/or modify it. For the developers' and authors' protection, the GPL clearly explains that there is no warranty for this free software. For both users' and authors' sake, the GPL requires that modified versions be marked as changed, so that their problems will not be attributed erroneously to authors of previous versions. Some devices are designed to deny users access to install or run modified versions of the software inside them, although the manufacturer can do so. This is fundamentally incompatible with the aim of protecting users' freedom to change the software. The systematic pattern of such abuse occurs in the area of products for individuals to use, which is precisely where it is most unacceptable. Therefore, we have designed this version of the GPL to prohibit the practice for those products. If such problems arise substantially in other domains, we stand ready to extend this provision to those domains in future versions of the GPL, as needed to protect the freedom of users. Finally, every program is threatened constantly by software patents. States should not allow patents to restrict development and use of software on general-purpose computers, but in those that do, we wish to avoid the special danger that patents applied to a free program could make it effectively proprietary. To prevent this, the GPL assures that patents cannot be used to render the program non-free. The precise terms and conditions for copying, distribution and modification follow. TERMS AND CONDITIONS 0. Definitions. "This License" refers to version 3 of the GNU General Public License. "Copyright" also means copyright-like laws that apply to other kinds of works, such as semiconductor masks. "The Program" refers to any copyrightable work licensed under this License. Each licensee is addressed as "you". "Licensees" and "recipients" may be individuals or organizations. To "modify" a work means to copy from or adapt all or part of the work in a fashion requiring copyright permission, other than the making of an exact copy. The resulting work is called a "modified version" of the earlier work or a work "based on" the earlier work. A "covered work" means either the unmodified Program or a work based on the Program. To "propagate" a work means to do anything with it that, without permission, would make you directly or secondarily liable for infringement under applicable copyright law, except executing it on a computer or modifying a private copy. Propagation includes copying, distribution (with or without modification), making available to the public, and in some countries other activities as well. To "convey" a work means any kind of propagation that enables other parties to make or receive copies. Mere interaction with a user through a computer network, with no transfer of a copy, is not conveying. An interactive user interface displays "Appropriate Legal Notices" to the extent that it includes a convenient and prominently visible feature that (1) displays an appropriate copyright notice, and (2) tells the user that there is no warranty for the work (except to the extent that warranties are provided), that licensees may convey the work under this License, and how to view a copy of this License. If the interface presents a list of user commands or options, such as a menu, a prominent item in the list meets this criterion. 1. Source Code. The "source code" for a work means the preferred form of the work for making modifications to it. "Object code" means any non-source form of a work. A "Standard Interface" means an interface that either is an official standard defined by a recognized standards body, or, in the case of interfaces specified for a particular programming language, one that is widely used among developers working in that language. The "System Libraries" of an executable work include anything, other than the work as a whole, that (a) is included in the normal form of packaging a Major Component, but which is not part of that Major Component, and (b) serves only to enable use of the work with that Major Component, or to implement a Standard Interface for which an implementation is available to the public in source code form. A "Major Component", in this context, means a major essential component (kernel, window system, and so on) of the specific operating system (if any) on which the executable work runs, or a compiler used to produce the work, or an object code interpreter used to run it. The "Corresponding Source" for a work in object code form means all the source code needed to generate, install, and (for an executable work) run the object code and to modify the work, including scripts to control those activities. However, it does not include the work's System Libraries, or general-purpose tools or generally available free programs which are used unmodified in performing those activities but which are not part of the work. For example, Corresponding Source includes interface definition files associated with source files for the work, and the source code for shared libraries and dynamically linked subprograms that the work is specifically designed to require, such as by intimate data communication or control flow between those subprograms and other parts of the work. The Corresponding Source need not include anything that users can regenerate automatically from other parts of the Corresponding Source. The Corresponding Source for a work in source code form is that same work. 2. Basic Permissions. All rights granted under this License are granted for the term of copyright on the Program, and are irrevocable provided the stated conditions are met. This License explicitly affirms your unlimited permission to run the unmodified Program. The output from running a covered work is covered by this License only if the output, given its content, constitutes a covered work. This License acknowledges your rights of fair use or other equivalent, as provided by copyright law. You may make, run and propagate covered works that you do not convey, without conditions so long as your license otherwise remains in force. You may convey covered works to others for the sole purpose of having them make modifications exclusively for you, or provide you with facilities for running those works, provided that you comply with the terms of this License in conveying all material for which you do not control copyright. Those thus making or running the covered works for you must do so exclusively on your behalf, under your direction and control, on terms that prohibit them from making any copies of your copyrighted material outside their relationship with you. Conveying under any other circumstances is permitted solely under the conditions stated below. Sublicensing is not allowed; section 10 makes it unnecessary. 3. Protecting Users' Legal Rights From Anti-Circumvention Law. No covered work shall be deemed part of an effective technological measure under any applicable law fulfilling obligations under article 11 of the WIPO copyright treaty adopted on 20 December 1996, or similar laws prohibiting or restricting circumvention of such measures. When you convey a covered work, you waive any legal power to forbid circumvention of technological measures to the extent such circumvention is effected by exercising rights under this License with respect to the covered work, and you disclaim any intention to limit operation or modification of the work as a means of enforcing, against the work's users, your or third parties' legal rights to forbid circumvention of technological measures. 4. Conveying Verbatim Copies. You may convey verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice; keep intact all notices stating that this License and any non-permissive terms added in accord with section 7 apply to the code; keep intact all notices of the absence of any warranty; and give all recipients a copy of this License along with the Program. You may charge any price or no price for each copy that you convey, and you may offer support or warranty protection for a fee. 5. Conveying Modified Source Versions. You may convey a work based on the Program, or the modifications to produce it from the Program, in the form of source code under the terms of section 4, provided that you also meet all of these conditions: a) The work must carry prominent notices stating that you modified it, and giving a relevant date. b) The work must carry prominent notices stating that it is released under this License and any conditions added under section 7. This requirement modifies the requirement in section 4 to "keep intact all notices". c) You must license the entire work, as a whole, under this License to anyone who comes into possession of a copy. This License will therefore apply, along with any applicable section 7 additional terms, to the whole of the work, and all its parts, regardless of how they are packaged. This License gives no permission to license the work in any other way, but it does not invalidate such permission if you have separately received it. d) If the work has interactive user interfaces, each must display Appropriate Legal Notices; however, if the Program has interactive interfaces that do not display Appropriate Legal Notices, your work need not make them do so. A compilation of a covered work with other separate and independent works, which are not by their nature extensions of the covered work, and which are not combined with it such as to form a larger program, in or on a volume of a storage or distribution medium, is called an "aggregate" if the compilation and its resulting copyright are not used to limit the access or legal rights of the compilation's users beyond what the individual works permit. Inclusion of a covered work in an aggregate does not cause this License to apply to the other parts of the aggregate. 6. Conveying Non-Source Forms. You may convey a covered work in object code form under the terms of sections 4 and 5, provided that you also convey the machine-readable Corresponding Source under the terms of this License, in one of these ways: a) Convey the object code in, or embodied in, a physical product (including a physical distribution medium), accompanied by the Corresponding Source fixed on a durable physical medium customarily used for software interchange. b) Convey the object code in, or embodied in, a physical product (including a physical distribution medium), accompanied by a written offer, valid for at least three years and valid for as long as you offer spare parts or customer support for that product model, to give anyone who possesses the object code either (1) a copy of the Corresponding Source for all the software in the product that is covered by this License, on a durable physical medium customarily used for software interchange, for a price no more than your reasonable cost of physically performing this conveying of source, or (2) access to copy the Corresponding Source from a network server at no charge. c) Convey individual copies of the object code with a copy of the written offer to provide the Corresponding Source. This alternative is allowed only occasionally and noncommercially, and only if you received the object code with such an offer, in accord with subsection 6b. d) Convey the object code by offering access from a designated place (gratis or for a charge), and offer equivalent access to the Corresponding Source in the same way through the same place at no further charge. You need not require recipients to copy the Corresponding Source along with the object code. If the place to copy the object code is a network server, the Corresponding Source may be on a different server (operated by you or a third party) that supports equivalent copying facilities, provided you maintain clear directions next to the object code saying where to find the Corresponding Source. Regardless of what server hosts the Corresponding Source, you remain obligated to ensure that it is available for as long as needed to satisfy these requirements. e) Convey the object code using peer-to-peer transmission, provided you inform other peers where the object code and Corresponding Source of the work are being offered to the general public at no charge under subsection 6d. A separable portion of the object code, whose source code is excluded from the Corresponding Source as a System Library, need not be included in conveying the object code work. A "User Product" is either (1) a "consumer product", which means any tangible personal property which is normally used for personal, family, or household purposes, or (2) anything designed or sold for incorporation into a dwelling. In determining whether a product is a consumer product, doubtful cases shall be resolved in favor of coverage. For a particular product received by a particular user, "normally used" refers to a typical or common use of that class of product, regardless of the status of the particular user or of the way in which the particular user actually uses, or expects or is expected to use, the product. A product is a consumer product regardless of whether the product has substantial commercial, industrial or non-consumer uses, unless such uses represent the only significant mode of use of the product. "Installation Information" for a User Product means any methods, procedures, authorization keys, or other information required to install and execute modified versions of a covered work in that User Product from a modified version of its Corresponding Source. The information must suffice to ensure that the continued functioning of the modified object code is in no case prevented or interfered with solely because modification has been made. If you convey an object code work under this section in, or with, or specifically for use in, a User Product, and the conveying occurs as part of a transaction in which the right of possession and use of the User Product is transferred to the recipient in perpetuity or for a fixed term (regardless of how the transaction is characterized), the Corresponding Source conveyed under this section must be accompanied by the Installation Information. But this requirement does not apply if neither you nor any third party retains the ability to install modified object code on the User Product (for example, the work has been installed in ROM). The requirement to provide Installation Information does not include a requirement to continue to provide support service, warranty, or updates for a work that has been modified or installed by the recipient, or for the User Product in which it has been modified or installed. Access to a network may be denied when the modification itself materially and adversely affects the operation of the network or violates the rules and protocols for communication across the network. Corresponding Source conveyed, and Installation Information provided, in accord with this section must be in a format that is publicly documented (and with an implementation available to the public in source code form), and must require no special password or key for unpacking, reading or copying. 7. Additional Terms. "Additional permissions" are terms that supplement the terms of this License by making exceptions from one or more of its conditions. Additional permissions that are applicable to the entire Program shall be treated as though they were included in this License, to the extent that they are valid under applicable law. If additional permissions apply only to part of the Program, that part may be used separately under those permissions, but the entire Program remains governed by this License without regard to the additional permissions. When you convey a copy of a covered work, you may at your option remove any additional permissions from that copy, or from any part of it. (Additional permissions may be written to require their own removal in certain cases when you modify the work.) You may place additional permissions on material, added by you to a covered work, for which you have or can give appropriate copyright permission. Notwithstanding any other provision of this License, for material you add to a covered work, you may (if authorized by the copyright holders of that material) supplement the terms of this License with terms: a) Disclaiming warranty or limiting liability differently from the terms of sections 15 and 16 of this License; or b) Requiring preservation of specified reasonable legal notices or author attributions in that material or in the Appropriate Legal Notices displayed by works containing it; or c) Prohibiting misrepresentation of the origin of that material, or requiring that modified versions of such material be marked in reasonable ways as different from the original version; or d) Limiting the use for publicity purposes of names of licensors or authors of the material; or e) Declining to grant rights under trademark law for use of some trade names, trademarks, or service marks; or f) Requiring indemnification of licensors and authors of that material by anyone who conveys the material (or modified versions of it) with contractual assumptions of liability to the recipient, for any liability that these contractual assumptions directly impose on those licensors and authors. All other non-permissive additional terms are considered "further restrictions" within the meaning of section 10. If the Program as you received it, or any part of it, contains a notice stating that it is governed by this License along with a term that is a further restriction, you may remove that term. If a license document contains a further restriction but permits relicensing or conveying under this License, you may add to a covered work material governed by the terms of that license document, provided that the further restriction does not survive such relicensing or conveying. If you add terms to a covered work in accord with this section, you must place, in the relevant source files, a statement of the additional terms that apply to those files, or a notice indicating where to find the applicable terms. Additional terms, permissive or non-permissive, may be stated in the form of a separately written license, or stated as exceptions; the above requirements apply either way. 8. Termination. You may not propagate or modify a covered work except as expressly provided under this License. Any attempt otherwise to propagate or modify it is void, and will automatically terminate your rights under this License (including any patent licenses granted under the third paragraph of section 11). However, if you cease all violation of this License, then your license from a particular copyright holder is reinstated (a) provisionally, unless and until the copyright holder explicitly and finally terminates your license, and (b) permanently, if the copyright holder fails to notify you of the violation by some reasonable means prior to 60 days after the cessation. Moreover, your license from a particular copyright holder is reinstated permanently if the copyright holder notifies you of the violation by some reasonable means, this is the first time you have received notice of violation of this License (for any work) from that copyright holder, and you cure the violation prior to 30 days after your receipt of the notice. Termination of your rights under this section does not terminate the licenses of parties who have received copies or rights from you under this License. If your rights have been terminated and not permanently reinstated, you do not qualify to receive new licenses for the same material under section 10. 9. Acceptance Not Required for Having Copies. You are not required to accept this License in order to receive or run a copy of the Program. Ancillary propagation of a covered work occurring solely as a consequence of using peer-to-peer transmission to receive a copy likewise does not require acceptance. However, nothing other than this License grants you permission to propagate or modify any covered work. These actions infringe copyright if you do not accept this License. Therefore, by modifying or propagating a covered work, you indicate your acceptance of this License to do so. 10. Automatic Licensing of Downstream Recipients. Each time you convey a covered work, the recipient automatically receives a license from the original licensors, to run, modify and propagate that work, subject to this License. You are not responsible for enforcing compliance by third parties with this License. An "entity transaction" is a transaction transferring control of an organization, or substantially all assets of one, or subdividing an organization, or merging organizations. If propagation of a covered work results from an entity transaction, each party to that transaction who receives a copy of the work also receives whatever licenses to the work the party's predecessor in interest had or could give under the previous paragraph, plus a right to possession of the Corresponding Source of the work from the predecessor in interest, if the predecessor has it or can get it with reasonable efforts. You may not impose any further restrictions on the exercise of the rights granted or affirmed under this License. For example, you may not impose a license fee, royalty, or other charge for exercise of rights granted under this License, and you may not initiate litigation (including a cross-claim or counterclaim in a lawsuit) alleging that any patent claim is infringed by making, using, selling, offering for sale, or importing the Program or any portion of it. 11. Patents. A "contributor" is a copyright holder who authorizes use under this License of the Program or a work on which the Program is based. The work thus licensed is called the contributor's "contributor version". A contributor's "essential patent claims" are all patent claims owned or controlled by the contributor, whether already acquired or hereafter acquired, that would be infringed by some manner, permitted by this License, of making, using, or selling its contributor version, but do not include claims that would be infringed only as a consequence of further modification of the contributor version. For purposes of this definition, "control" includes the right to grant patent sublicenses in a manner consistent with the requirements of this License. Each contributor grants you a non-exclusive, worldwide, royalty-free patent license under the contributor's essential patent claims, to make, use, sell, offer for sale, import and otherwise run, modify and propagate the contents of its contributor version. In the following three paragraphs, a "patent license" is any express agreement or commitment, however denominated, not to enforce a patent (such as an express permission to practice a patent or covenant not to sue for patent infringement). To "grant" such a patent license to a party means to make such an agreement or commitment not to enforce a patent against the party. If you convey a covered work, knowingly relying on a patent license, and the Corresponding Source of the work is not available for anyone to copy, free of charge and under the terms of this License, through a publicly available network server or other readily accessible means, then you must either (1) cause the Corresponding Source to be so available, or (2) arrange to deprive yourself of the benefit of the patent license for this particular work, or (3) arrange, in a manner consistent with the requirements of this License, to extend the patent license to downstream recipients. "Knowingly relying" means you have actual knowledge that, but for the patent license, your conveying the covered work in a country, or your recipient's use of the covered work in a country, would infringe one or more identifiable patents in that country that you have reason to believe are valid. If, pursuant to or in connection with a single transaction or arrangement, you convey, or propagate by procuring conveyance of, a covered work, and grant a patent license to some of the parties receiving the covered work authorizing them to use, propagate, modify or convey a specific copy of the covered work, then the patent license you grant is automatically extended to all recipients of the covered work and works based on it. A patent license is "discriminatory" if it does not include within the scope of its coverage, prohibits the exercise of, or is conditioned on the non-exercise of one or more of the rights that are specifically granted under this License. You may not convey a covered work if you are a party to an arrangement with a third party that is in the business of distributing software, under which you make payment to the third party based on the extent of your activity of conveying the work, and under which the third party grants, to any of the parties who would receive the covered work from you, a discriminatory patent license (a) in connection with copies of the covered work conveyed by you (or copies made from those copies), or (b) primarily for and in connection with specific products or compilations that contain the covered work, unless you entered into that arrangement, or that patent license was granted, prior to 28 March 2007. Nothing in this License shall be construed as excluding or limiting any implied license or other defenses to infringement that may otherwise be available to you under applicable patent law. 12. No Surrender of Others' Freedom. If conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot convey a covered work so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not convey it at all. For example, if you agree to terms that obligate you to collect a royalty for further conveying from those to whom you convey the Program, the only way you could satisfy both those terms and this License would be to refrain entirely from conveying the Program. 13. Use with the GNU Affero General Public License. Notwithstanding any other provision of this License, you have permission to link or combine any covered work with a work licensed under version 3 of the GNU Affero General Public License into a single combined work, and to convey the resulting work. The terms of this License will continue to apply to the part which is the covered work, but the special requirements of the GNU Affero General Public License, section 13, concerning interaction through a network will apply to the combination as such. 14. Revised Versions of this License. The Free Software Foundation may publish revised and/or new versions of the GNU General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies that a certain numbered version of the GNU General Public License "or any later version" applies to it, you have the option of following the terms and conditions either of that numbered version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of the GNU General Public License, you may choose any version ever published by the Free Software Foundation. If the Program specifies that a proxy can decide which future versions of the GNU General Public License can be used, that proxy's public statement of acceptance of a version permanently authorizes you to choose that version for the Program. Later license versions may give you additional or different permissions. However, no additional obligations are imposed on any author or copyright holder as a result of your choosing to follow a later version. 15. Disclaimer of Warranty. THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 16. Limitation of Liability. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MODIFIES AND/OR CONVEYS THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. 17. Interpretation of Sections 15 and 16. If the disclaimer of warranty and limitation of liability provided above cannot be given local legal effect according to their terms, reviewing courts shall apply local law that most closely approximates an absolute waiver of all civil liability in connection with the Program, unless a warranty or assumption of liability accompanies a copy of the Program in return for a fee. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively state the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . Also add information on how to contact you by electronic and paper mail. If the program does terminal interaction, make it output a short notice like this when it starts in an interactive mode: Copyright (C) This program comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, your program's commands might be different; for a GUI interface, you would use an "about box". You should also get your employer (if you work as a programmer) or school, if any, to sign a "copyright disclaimer" for the program, if necessary. For more information on this, and how to apply and follow the GNU GPL, see . The GNU General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Lesser General Public License instead of this License. But first, please read . dbus-0.10.13/Setup.hs0000644000000000000000000000005613054400602012426 0ustar0000000000000000import Distribution.Simple main = defaultMain dbus-0.10.13/dbus.cabal0000644000000000000000000000737513073332436012740 0ustar0000000000000000name: dbus version: 0.10.13 license: GPL-3 license-file: license.txt author: John Millikin maintainer: Andrey Sverdlichenko , John Millikin build-type: Simple cabal-version: >= 1.8 category: Network, Desktop stability: experimental homepage: https://github.com/rblaze/haskell-dbus#readme synopsis: A client library for the D-Bus IPC system. description: D-Bus is a simple, message-based protocol for inter-process communication, which allows applications to interact with other parts of the machine and the user's session using remote procedure calls. . D-Bus is a essential part of the modern Linux desktop, where it replaces earlier protocols such as CORBA and DCOP. . This library is an implementation of the D-Bus protocol in Haskell. It can be used to add D-Bus support to Haskell applications, without the awkward interfaces common to foreign bindings. . Example: connect to the session bus, and get a list of active names. . @ {-\# LANGUAGE OverloadedStrings \#-} . import Data.List (sort) import DBus import DBus.Client . main = do client <- connectSession // \-- Request a list of connected clients from the bus reply <- call_ client (methodCall \"\/org\/freedesktop\/DBus\" \"org.freedesktop.DBus\" \"ListNames\") { methodCallDestination = Just \"org.freedesktop.DBus\" } // \-- org.freedesktop.DBus.ListNames() returns a single value, which is \-- a list of names (here represented as [String]) let Just names = fromVariant (methodReturnBody reply !! 0) // \-- Print each name on a line, sorted so reserved names are below \-- temporary names. mapM_ putStrLn (sort names) @ . >$ ghc --make list-names.hs >$ ./list-names >:1.0 >:1.1 >:1.10 >:1.106 >:1.109 >:1.110 >ca.desrt.dconf >org.freedesktop.DBus >org.freedesktop.Notifications >org.freedesktop.secrets >org.gnome.ScreenSaver extra-source-files: examples/dbus-monitor.hs examples/export.hs examples/introspect.hs examples/list-names.hs source-repository head type: git location: https://github.com/rblaze/haskell-dbus library ghc-options: -W -Wall hs-source-dirs: lib build-depends: base >=4 && <5 , bytestring , cereal , containers , libxml-sax , network , parsec , random , text , transformers , unix , vector , xml-types exposed-modules: DBus DBus.Client DBus.Introspection DBus.Socket DBus.Transport DBus.Internal.Address DBus.Internal.Message DBus.Internal.Types DBus.Internal.Wire test-suite dbus_tests type: exitcode-stdio-1.0 main-is: DBusTests.hs hs-source-dirs: tests build-depends: dbus , base , bytestring , cereal , chell , chell-quickcheck , containers , directory , filepath , libxml-sax , network , parsec , process , QuickCheck , random , text , transformers , unix , vector , xml-types other-modules: DBusTests.Address DBusTests.BusName DBusTests.Client DBusTests.ErrorName DBusTests.Integration DBusTests.InterfaceName DBusTests.Introspection DBusTests.MemberName DBusTests.Message DBusTests.ObjectPath DBusTests.Serialization DBusTests.Signature DBusTests.Socket DBusTests.Transport DBusTests.Util DBusTests.Variant DBusTests.Wire benchmark dbus_benchmarks type: exitcode-stdio-1.0 main-is: DBusBenchmarks.hs hs-source-dirs: benchmarks ghc-options: -Wall -fno-warn-orphans build-depends: dbus , base , criterion , deepseq dbus-0.10.13/examples/dbus-monitor.hs0000644000000000000000000002145213073332436015603 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} -- Copyright (C) 2009-2011 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module Main (main) where import Control.Monad import Data.List (intercalate) import Data.Int import Data.Word import System.Environment import System.Exit import System.IO import System.Console.GetOpt import DBus import DBus.Socket data Bus = Session | System deriving (Show) data Option = BusOption Bus | AddressOption String deriving (Show) optionInfo :: [OptDescr Option] optionInfo = [ Option [] ["session"] (NoArg (BusOption Session)) "Monitor the session message bus. (default)" , Option [] ["system"] (NoArg (BusOption System)) "Monitor the system message bus." , Option [] ["address"] (ReqArg AddressOption "ADDRESS") "Connect to a particular bus address." ] usage :: String -> String usage name = "Usage: " ++ name ++ " [OPTION...]" findSocket :: [Option] -> IO Socket findSocket opts = getAddress opts >>= open where session = do got <- getSessionAddress case got of Just addr -> return addr Nothing -> error "DBUS_SESSION_BUS_ADDRESS is not a valid address" system = do got <- getSystemAddress case got of Just addr -> return addr Nothing -> error "DBUS_SYSTEM_BUS_ADDRESS is not a valid address" getAddress [] = session getAddress ((BusOption Session):_) = session getAddress ((BusOption System):_) = system getAddress ((AddressOption addr):_) = case parseAddress addr of Nothing -> error (show addr ++ " is not a valid address") Just parsed -> return parsed addMatch :: Socket -> String -> IO () addMatch sock match = send sock (methodCall "/org/freedesktop/DBus" "org.freedesktop.DBus" "AddMatch") { methodCallDestination = Just "org.freedesktop.DBus" , methodCallBody = [toVariant match] } (\_ -> return ()) defaultFilters :: [String] defaultFilters = [ "type='signal',eavesdrop=true" , "type='method_call',eavesdrop=true" , "type='method_return',eavesdrop=true" , "type='error',eavesdrop=true" ] main :: IO () main = do args <- getArgs let (options, userFilters, errors) = getOpt Permute optionInfo args unless (null errors) $ do name <- getProgName hPutStrLn stderr (concat errors) hPutStrLn stderr (usageInfo (usage name) optionInfo) exitFailure sock <- findSocket options send sock (methodCall "/org/freedesktop/DBus" "org.freedesktop.DBus" "Hello") { methodCallDestination = Just "org.freedesktop.DBus" } (\_ -> return ()) mapM_ (addMatch sock) (if null userFilters then defaultFilters else userFilters) forever $ do received <- receive sock putStrLn (formatMessage received ++ "\n") -- Message formatting is verbose and mostly uninteresting, except as an -- excersise in string manipulation. formatMessage :: ReceivedMessage -> String -- Method call formatMessage (ReceivedMethodCall serial msg) = concat [ "method call" , " sender=" , maybe "(null)" formatBusName (methodCallSender msg) , " -> dest=" , maybe "(null)" formatBusName (methodCallDestination msg) , " serial=" , show (serialValue serial) , " path=" , formatObjectPath (methodCallPath msg) , "; interface=" , maybe "(null)" formatInterfaceName (methodCallInterface msg) , "; member=" , formatMemberName (methodCallMember msg) , formatBody (methodCallBody msg) ] -- Method return formatMessage (ReceivedMethodReturn _ msg) = concat [ "method return" , " sender=" , maybe "(null)" formatBusName (methodReturnSender msg) , " -> dest=" , maybe "(null)" formatBusName (methodReturnDestination msg) , " reply_serial=" , show (serialValue (methodReturnSerial msg)) , formatBody (methodReturnBody msg) ] -- Method error formatMessage (ReceivedMethodError _ msg) = concat [ "error" , " sender=" , maybe "(null)" formatBusName (methodErrorSender msg) , " -> dest=" , maybe "(null)" formatBusName (methodErrorDestination msg) , " error_name=" , formatErrorName (methodErrorName msg) , " reply_serial=" , show (serialValue (methodErrorSerial msg)) , formatBody (methodErrorBody msg) ] -- Signal formatMessage (ReceivedSignal serial msg) = concat [ "signal" , " sender=" , maybe "(null)" formatBusName (signalSender msg) , " -> dest=" , maybe "(null)" formatBusName (signalDestination msg) , " serial=" , show (serialValue serial) , " path=" , formatObjectPath (signalPath msg) , "; interface=" , formatInterfaceName (signalInterface msg) , "; member=" , formatMemberName (signalMember msg) , formatBody (signalBody msg) ] formatMessage msg = concat [ "unknown" , " sender=" , maybe "(null)" formatBusName (receivedMessageSender msg) , " serial=" , show (serialValue (receivedMessageSerial msg)) , formatBody (receivedMessageBody msg) ] formatBody :: [Variant] -> String formatBody body = formatted where tree = Children (map formatVariant body) formatted = intercalate "\n" ("" : collapseTree 0 tree) -- A string tree allows easy indentation of nested structures data StringTree = Line String | MultiLine [StringTree] | Children [StringTree] deriving (Show) collapseTree :: Int -> StringTree -> [String] collapseTree d (Line x) = [replicate (d*3) ' ' ++ x] collapseTree d (MultiLine xs) = concatMap (collapseTree d) xs collapseTree d (Children xs) = concatMap (collapseTree (d + 1)) xs -- Formatting for various kinds of variants, keyed to their signature type. formatVariant :: Variant -> StringTree formatVariant x = case variantType x of TypeBoolean -> Line $ let Just x' = fromVariant x in "boolean " ++ if x' then "true" else "false" TypeWord8 -> Line $ let Just x' = fromVariant x in "byte " ++ show (x' :: Word8) TypeWord16 -> Line $ let Just x' = fromVariant x in "uint16 " ++ show (x' :: Word16) TypeWord32 -> Line $ let Just x' = fromVariant x in "uint32 " ++ show (x' :: Word32) TypeWord64 -> Line $ let Just x' = fromVariant x in "uint64 " ++ show (x' :: Word64) TypeInt16 -> Line $ let Just x' = fromVariant x in "int16 " ++ show (x' :: Int16) TypeInt32 -> Line $ let Just x' = fromVariant x in "int32 " ++ show (x' :: Int32) TypeInt64 -> Line $ let Just x' = fromVariant x in "int64 " ++ show (x' :: Int64) TypeDouble -> Line $ let Just x' = fromVariant x in "double " ++ show (x' :: Double) TypeString -> Line $ let Just x' = fromVariant x in "string " ++ show (x' :: String) TypeObjectPath -> Line $ let Just x' = fromVariant x in "object path " ++ show (formatObjectPath x') TypeSignature -> Line $ let Just x' = fromVariant x in "signature " ++ show (formatSignature x') TypeArray _ -> MultiLine $ let Just x' = fromVariant x items = arrayItems x' lines' = [ Line "array [" , Children (map formatVariant items) , Line "]" ] in lines' TypeDictionary _ _ -> MultiLine $ let Just x' = fromVariant x items = dictionaryItems x' lines' = [ Line "dictionary {" , Children (map formatItem items) , Line "}" ] formatItem (k, v) = MultiLine (firstLine : vTail) where Line k' = formatVariant k v' = collapseTree 0 (formatVariant v) vHead = head v' vTail = map Line (tail v') firstLine = Line (k' ++ " -> " ++ vHead) in lines' TypeStructure _ -> MultiLine $ let Just x' = fromVariant x items = structureItems x' lines' = [ Line "struct (" , Children (map formatVariant items) , Line ")" ] in lines' TypeVariant -> let Just x' = fromVariant x in MultiLine [Line "variant", Children [formatVariant x']] dbus-0.10.13/examples/export.hs0000644000000000000000000000375313073332436014506 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} -- Copyright (C) 2009-2011 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module Main (main) where import Control.Concurrent (threadDelay) import Control.Monad import System.Exit import DBus.Client onFoo :: String -> String -> IO (String, String) onFoo x y = do putStrLn ("Foo " ++ show x ++ " " ++ show y) return (x, y) onBar :: String -> String -> IO (String, String) onBar x y = do putStrLn ("Bar " ++ show x ++ " " ++ show y) throwError "com.example.ErrorBar" "Bar failed" [] main :: IO () main = do -- Connect to the bus client <- connectSession -- Request a unique name on the bus. requestResult <- requestName client "com.example.exporting" [] when (requestResult /= NamePrimaryOwner) $ do putStrLn "Another service owns the \"com.example.exporting\" bus name" exitFailure -- Export two example objects export client "/a" [ autoMethod "test.iface_1" "Foo" (onFoo "hello" "a") , autoMethod "test.iface_1" "Bar" (onBar "hello" "a") ] export client "/b" [ autoMethod "test.iface_1" "Foo" (onFoo "hello") , autoMethod "test.iface_1" "Bar" (onBar "hello") ] putStrLn "Exported objects /a and /b to bus name com.example.exporting" -- Wait forever for method calls forever (threadDelay 50000) dbus-0.10.13/examples/introspect.hs0000644000000000000000000000733413073332436015356 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} -- Copyright (C) 2009-2011 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module Main (main) where import Control.Monad (when) import Data.String (fromString) import System.Environment (getArgs, getProgName) import System.Exit (exitFailure) import System.IO (hPutStrLn, stderr) import DBus import DBus.Client import qualified DBus.Introspection as I main :: IO () main = do args <- getArgs (service, path) <- case args of a1:a2:_ -> return (fromString a1, fromString a2) _ -> do name <- getProgName hPutStrLn stderr ("Usage: " ++ name ++ " ") exitFailure client <- connectSession printObj (introspect client service) path introspect :: Client -> BusName -> ObjectPath -> IO I.Object introspect client service path = do reply <- call_ client (methodCall path "org.freedesktop.DBus.Introspectable" "Introspect") { methodCallDestination = Just service } let Just xml = fromVariant (methodReturnBody reply !! 0) case I.parseXML path xml of Just info -> return info Nothing -> error ("Invalid introspection XML: " ++ show xml) -- most of this stuff is just boring text formatting printObj :: (ObjectPath -> IO I.Object) -> ObjectPath -> IO () printObj get path = do obj <- get path putStrLn (formatObjectPath path) mapM_ printIface (I.objectInterfaces obj) putStrLn "" mapM_ (printObj get) [I.objectPath x | x <- I.objectChildren obj] printIface :: I.Interface -> IO () printIface iface = do putStr " " putStrLn (formatInterfaceName (I.interfaceName iface)) mapM_ printMethod (I.interfaceMethods iface) mapM_ printSignal (I.interfaceSignals iface) mapM_ printProperty (I.interfaceProperties iface) putStrLn "" printMethod :: I.Method -> IO () printMethod method = do putStr " method " putStrLn (formatMemberName (I.methodName method)) mapM_ printMethodArg (I.methodArgs method) printMethodArg :: I.MethodArg -> IO () printMethodArg arg = do let dir = case I.methodArgDirection arg of d | d == I.directionIn -> "IN " d | d == I.directionOut -> "OUT" _ -> " " putStr (" [" ++ dir ++ " ") putStr (show (formatSignature (signature_ [I.methodArgType arg])) ++ "] ") putStrLn (I.methodArgName arg) printSignal :: I.Signal -> IO () printSignal sig = do putStr " signal " putStrLn (formatMemberName (I.signalName sig)) mapM_ printSignalArg (I.signalArgs sig) printSignalArg :: I.SignalArg -> IO () printSignalArg arg = do putStr " [" putStr (show (formatSignature (signature_ [I.signalArgType arg])) ++ "] ") putStrLn (I.signalArgName arg) printProperty :: I.Property -> IO () printProperty prop = do putStr " property " putStr (show (formatSignature (signature_ [I.propertyType prop])) ++ " ") putStrLn (I.propertyName prop) putStr " " when (I.propertyRead prop) (putStr "Read") when (I.propertyWrite prop) (putStr "Write") putStrLn "" dbus-0.10.13/examples/list-names.hs0000644000000000000000000000264213073332436015235 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} -- Copyright (C) 2009-2011 John Millikin -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module Main (main) where import Data.List (sort) import DBus import DBus.Client main :: IO () main = do client <- connectSession -- Request a list of connected clients from the bus reply <- call_ client (methodCall "/org/freedesktop/DBus" "org.freedesktop.DBus" "ListNames") { methodCallDestination = Just "org.freedesktop.DBus" } -- org.freedesktop.DBus.ListNames returns a single value, which is -- a list of names (here represented as [String]) let Just names = fromVariant (methodReturnBody reply !! 0) -- Print each name on a line, sorted so reserved names are below -- temporary names. mapM_ putStrLn (sort names)