:# Copyright (C) 2009-2010 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 . \section{Introspection} D-Bus objects may be ``introspected'' to determine which methods, signals, etc they support. Intospection data is sent over the bus in {\sc xml}, in a mostly standardised but undocumented format. An XML introspection document looks like this: \begin{verbatim} \end{verbatim} \subsection*{Data types} :d DBus.Introspection data Object = Object T.ObjectPath [Interface] [Object] deriving (Show, Eq) data Interface = Interface T.InterfaceName [Method] [Signal] [Property] deriving (Show, Eq) data Method = Method T.MemberName [Parameter] [Parameter] deriving (Show, Eq) data Signal = Signal T.MemberName [Parameter] deriving (Show, Eq) data Parameter = Parameter Text T.Signature deriving (Show, Eq) data Property = Property Text T.Signature [PropertyAccess] deriving (Show, Eq) data PropertyAccess = Read | Write deriving (Show, Eq) : \subsection*{Parsing XML} If parsing fails, {\tt fromXML} will return {\tt Nothing}. Aside from the elements directly accessed by the parser, no effort is made to check the document's validity because there is no DTD as of yet. :d DBus.Introspection fromXML :: T.ObjectPath -> Text -> Maybe Object fromXML path text = do root <- parseElement text parseRoot path root : LibXML's event-based parsing is used to convert the input into a list of events. DBus's introspection format doesn't use any character data, so only the element attributes and nesting are preserved. :d DBus.Introspection parseElement :: Text -> Maybe X.Element parseElement text = 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 text) SAX.parseComplete p stack <- ST.readSTRef stackRef return $ case stack of [] -> Nothing (_, children'):_ -> Just $ head children' : The root {\tt node} is special, in that it's the only {\tt node} which is not required to have a {\tt name} attribute. If the root has no {\tt name}, its path will default to the path of the introspected object. Even though the root object's {\tt name} is optional, if present, it must still be a valid object path. :d DBus.Introspection parseRoot :: T.ObjectPath -> X.Element -> Maybe Object parseRoot defaultPath e = do path <- case X.attributeText "name" e of Nothing -> Just defaultPath Just x -> T.objectPath x parseObject path e : Child {\tt nodes} have ``relative'' paths -- that is, their {\tt name} attribute is not a valid object path, but should be valid when appended to the root object's path. :d DBus.Introspection parseChild :: T.ObjectPath -> X.Element -> Maybe Object parseChild parentPath e = do let parentPath' = case T.objectPathText parentPath of "/" -> "/" x -> Data.Text.append x "/" pathSegment <- X.attributeText "name" e path <- T.objectPath $ Data.Text.append parentPath' pathSegment parseObject path e : Other than the name, both root and non-root {\tt nodes} have identical contents. They may contain interface definitions, and child {\tt node}s. :d DBus.Introspection 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 : Interfaces may contain methods, signals, and properties. :d DBus.Introspection parseInterface :: X.Element -> Maybe Interface parseInterface e = do name <- T.interfaceName =<< X.attributeText "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 : Methods contain a list of parameters, which default to ``in'' parameters if no direction is specified. :d DBus.Introspection parseMethod :: X.Element -> Maybe Method parseMethod e = do name <- T.memberName =<< X.attributeText "name" e paramsIn <- children parseParameter (isParam ["in", ""]) e paramsOut <- children parseParameter (isParam ["out"]) e return $ Method name paramsIn paramsOut : Signals are similar to methods, except they have no ``in'' parameters. :d DBus.Introspection parseSignal :: X.Element -> Maybe Signal parseSignal e = do name <- T.memberName =<< X.attributeText "name" e params <- children parseParameter (isParam ["out", ""]) e return $ Signal name params : A parameter has a free-form name, and a single valid type. :d DBus.Introspection parseType :: X.Element -> Maybe T.Signature parseType e = X.attributeText "type" e >>= T.signature parseParameter :: X.Element -> Maybe Parameter parseParameter e = do let name = getattr "name" e sig <- parseType e case T.signatureTypes sig of [_] -> Just (Parameter name sig) _ -> Nothing : Properties are used by the {\tt org.freedesktop.DBus.Properties} interface. Each property may be read, written, or both, and has an associated type. :d DBus.Introspection parseProperty :: X.Element -> Maybe Property parseProperty e = do let name = getattr "name" e sig <- parseType e access <- case getattr "access" e of "" -> Just [] "read" -> Just [Read] "write" -> Just [Write] "readwrite" -> Just [Read, Write] _ -> Nothing return $ Property name sig access : :d DBus.Introspection getattr :: X.Name -> X.Element -> Text getattr = (fromMaybe "" .) . X.attributeText isParam :: [Text] -> X.Element -> [X.Element] isParam dirs = X.isNamed "arg" >=> checkDir where checkDir e = [e | getattr "direction" e `elem` dirs] children :: Monad m => (X.Element -> m b) -> (X.Element -> [X.Element]) -> X.Element -> m [b] children f p = mapM f . concatMap p . X.elementChildren : \subsection*{Generating XML} Generating XML can fail; if a child object's path is not a sub-path of the parent, {\tt toXML} will return {\tt Nothing}. To simplify XML serialization, a variant of {\tt Writer} is used to combine text fragments with optional failure. This would be {\tt WriterT Text Maybe}, except I didn't want to drag in a dependency on {\tt transformers} for such a little thing. :d DBus.Introspection newtype XmlWriter a = XmlWriter { runXmlWriter :: Maybe (a, Text) } instance Monad XmlWriter where return a = XmlWriter $ Just (a, Data.Text.empty) m >>= f = XmlWriter $ do (a, w) <- runXmlWriter m (b, w') <- runXmlWriter (f a) return (b, Data.Text.append w w') : :d DBus.Introspection tell :: Text -> XmlWriter () tell t = XmlWriter $ Just ((), t) : :d DBus.Introspection toXML :: Object -> Maybe Text toXML obj = do (_, text) <- runXmlWriter (writeRoot obj) return text : :d DBus.Introspection writeRoot :: Object -> XmlWriter () writeRoot obj@(Object path _ _) = do tell "\n" writeObject (T.objectPathText path) obj : :d DBus.Introspection writeChild :: T.ObjectPath -> Object -> XmlWriter () writeChild parentPath obj@(Object path _ _) = write where path' = T.objectPathText path parent' = T.objectPathText parentPath relpathM = if Data.Text.isPrefixOf parent' path' then Just $ if parent' == "/" then Data.Text.drop 1 path' else Data.Text.drop (Data.Text.length parent' + 1) path' else Nothing write = case relpathM of Just relpath -> writeObject relpath obj Nothing -> XmlWriter Nothing : :d DBus.Introspection writeObject :: Text -> Object -> XmlWriter () writeObject path (Object fullPath interfaces children') = writeElement "node" [("name", path)] $ do mapM_ writeInterface interfaces mapM_ (writeChild fullPath) children' : :d DBus.Introspection writeInterface :: Interface -> XmlWriter () writeInterface (Interface name methods signals properties) = writeElement "interface" [("name", T.interfaceNameText name)] $ do mapM_ writeMethod methods mapM_ writeSignal signals mapM_ writeProperty properties : :d DBus.Introspection writeMethod :: Method -> XmlWriter () writeMethod (Method name inParams outParams) = writeElement "method" [("name", T.memberNameText name)] $ do mapM_ (writeParameter "in") inParams mapM_ (writeParameter "out") outParams : :d DBus.Introspection writeSignal :: Signal -> XmlWriter () writeSignal (Signal name params) = writeElement "signal" [("name", T.memberNameText name)] $ do mapM_ (writeParameter "out") params : :d DBus.Introspection writeParameter :: Text -> Parameter -> XmlWriter () writeParameter direction (Parameter name sig) = writeEmptyElement "arg" [ ("name", name) , ("type", T.signatureText sig) , ("direction", direction) ] : :d DBus.Introspection writeProperty :: Property -> XmlWriter () writeProperty (Property name sig access) = writeEmptyElement "property" [ ("name", name) , ("type", T.signatureText sig) , ("access", strAccess access) ] : :d DBus.Introspection strAccess :: [PropertyAccess] -> Text strAccess access = Data.Text.append readS writeS where readS = if elem Read access then "read" else "" writeS = if elem Write access then "write" else "" : :d DBus.Introspection writeElement :: Text -> [(Text, Text)] -> XmlWriter () -> XmlWriter () writeElement name attrs content = do tell "<" tell name mapM_ writeAttribute attrs tell ">" content tell "" : :d DBus.Introspection writeEmptyElement :: Text -> [(Text, Text)] -> XmlWriter () writeEmptyElement name attrs = do tell "<" tell name mapM_ writeAttribute attrs tell "/>" : :d DBus.Introspection writeAttribute :: (Text, Text) -> XmlWriter () writeAttribute (name, content) = do tell " " tell name tell "='" tell (escape content) tell "'" : :d DBus.Introspection escape :: Text -> Text escape = Data.Text.concatMap escapeChar where escapeChar c = case c of '&' -> "&" '<' -> "<" '>' -> ">" '"' -> """ '\'' -> "'" _ -> Data.Text.singleton c :