:# Copyright (C) 2009 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 . \documentclass[12pt]{article} \usepackage{color} \usepackage{hyperref} \usepackage{noweb} :# Smaller margins \usepackage[left=1.5cm,top=2cm,right=1.5cm,nohead,nofoot]{geometry} :# Remove boxes from hyperlinks \hypersetup{ colorlinks, linkcolor=blue, } \makeindex \begin{document} \addcontentsline{toc}{section}{Contents} \tableofcontents \section{Introduction} This library provides a simplified, high-level interface for use by D-Bus clients. It implements async operations, remote object proxies, and local object exporting. The {\tt DBus.Client} module provides the public interface to this library. :f DBus/Client.hs |copyright| |language extensions| module DBus.Client ( |exports| ) where |imports| : {\tt DBus.Client} also re-exports some modules from the {\tt dbus-core} package. :d exports module DBus.Bus , module DBus.Types , module DBus.Message : :d imports import DBus.Bus import DBus.Types import DBus.Message import qualified DBus.Connection as C import qualified DBus.Constants as Const import qualified DBus.Introspection as I import qualified DBus.MatchRule as MR import qualified DBus.Message as M import qualified DBus.NameReservation as NR import qualified DBus.Types as T import qualified DBus.Wire as W : All source code is licensed under the terms of the GNU GPL v3 or later. :d copyright -- Copyright (C) 2009 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 language extensions {-# LANGUAGE OverloadedStrings #-} : \section{DBus Clients} The {\tt Client} type provides an opaque handle to internal client state, including callback registration and the open connection. :d imports import qualified Control.Concurrent.MVar as MV import qualified Data.Map as Map : :f DBus/Client.hs |apidoc Client| data Client = Client { clientConnection :: C.Connection , clientName :: T.BusName , clientCallbacks :: MV.MVar (Map.Map M.Serial MessageHandler) , clientObjects :: MV.MVar (Map.Map T.ObjectPath Object) , clientSignalHandlers :: MV.MVar [MessageHandler] } type MessageHandler = (M.ReceivedMessage -> DBus ()) : :d exports -- * Clients , Client , C.Connection , clientName : The signature of {\tt newClient} is a bit weird so it can be called with results from the {\tt DBus.Bus} family of computations, without having to unwrap or curry. :f DBus/Client.hs |apidoc newClient| newClient :: (C.Connection, T.BusName) -> IO Client newClient (c, name) = do callbacks <- MV.newMVar Map.empty objects <- MV.newMVar Map.empty signals <- MV.newMVar [] let client = Client c name callbacks objects signals |initialize client| return client : :d exports , newClient : \section{Monadic interface} Most of this module uses the {\tt DBus} monad, which wraps up the DBus connection into a more abstract form. :d imports import Control.Monad (liftM, ap, forever) import Control.Monad.IO.Class (liftIO) import qualified Control.Monad.IO.Class as MIO import qualified Control.Monad.Reader as R import qualified Control.Applicative as A : :f DBus/Client.hs newtype DBus a = DBus { unDBus :: R.ReaderT Client IO a } instance Monad DBus where return = DBus . return (>>=) (DBus m) f = DBus $ m >>= unDBus . f instance MIO.MonadIO DBus where liftIO = DBus . MIO.liftIO instance Functor DBus where fmap = liftM instance A.Applicative DBus where pure = return (<*>) = ap : The low-level DBus module prefers to return errors in the standard {\tt Either} type, to let clients explicitly handle errors. Most of the time, there's no reasonable way to handle such an error, so any errors encountered when running a DBus client are thrown as exceptions. :d language extensions {-# LANGUAGE DeriveDataTypeable #-} : :d imports import Data.Typeable (Typeable) import qualified Control.Exception as Exc : Errors marshaling and unmarshaling are supported. Additionally, uncaught errors from blocking method calls may be thrown from some computations. :f DBus/Client.hs data DBusException = MarshalFailed W.MarshalError | UnmarshalFailed W.UnmarshalError | MethodCallFailed M.Error | InvalidRequestNameReply M.MethodReturn | InvalidReleaseNameReply M.MethodReturn deriving (Show, Eq, Typeable) instance Exc.Exception DBusException : Having to run {\tt liftIO} everywhere is annoying, so {\tt MonadError} is instanced to let clients throw/catch more easily. :d language extensions {-# LANGUAGE TypeFamilies #-} : :d imports import qualified Control.Monad.Error as E : :f DBus/Client.hs instance E.MonadError DBus where type E.ErrorType DBus = DBusException throwError = MIO.liftIO . Exc.throwIO catchError dbus h = do c <- getClient liftIO $ Exc.catch (runDBus c dbus) (runDBus c . h) : Typical monad unwrapper, and some access computations. :f DBus/Client.hs |apidoc runDBus| runDBus :: Client -> DBus a -> IO a runDBus c (DBus m) = R.runReaderT m c getClient :: DBus Client getClient = DBus R.ask getConnection :: DBus C.Connection getConnection = fmap clientConnection getClient : :d exports , DBus , DBusException , runDBus , getClient : \subsection{Dispatching messages} Messages are read sequentially from the connection (typically in a central loop), and then processed according to the client's message handler maps. Unknown message types are ignored. :f DBus/Client.hs |apidoc processMessage| processMessage :: M.ReceivedMessage -> DBus () processMessage received = p received where p (M.ReceivedUnknown _ _ _) = return () |process messages| reply s = onReply s received : :d exports , processMessage : \subsection{Useful wrappers} Sending and receiving messages is common enough to use some small wrapper functions. :f DBus/Client.hs |apidoc send| send :: M.Message msg => (M.Serial -> DBus a) -> msg -> DBus a send onSerial msg = do c <- getConnection client <- getClient sent <- liftIO $ C.send c (runDBus client . onSerial) msg case sent of Left err -> E.throwError $ MarshalFailed err Right a -> return a |apidoc send_| send_ :: M.Message msg => msg -> DBus () send_ = send (const $ return ()) : :f DBus/Client.hs |apidoc receive| receive :: DBus M.ReceivedMessage receive = do c <- getConnection parsed <- liftIO $ C.receive c case parsed of Left err -> E.throwError $ UnmarshalFailed err Right msg -> return msg : :f DBus/Client.hs |apidoc mainLoop| mainLoop :: DBus () mainLoop = forever $ receive >>= processMessage : :d exports , send , send_ , receive , mainLoop : \section{Method calls} DBus is inherently asynchronous. Method calls are sent over the bus, and at some future point a response might be received. Because all messages are sent and received over a single connection, waiting for replies should be performed from a single thread. However, it's safe to send messages from any thread. \subsection{Asynchronous} :f DBus/Client.hs |apidoc call| call :: M.MethodCall -> (M.Error -> DBus ()) -> (M.MethodReturn -> DBus ()) -> DBus () call msg onError onReturn = send addCallback msg where cb (M.ReceivedError _ _ msg') = onError msg' cb (M.ReceivedMethodReturn _ _ msg') = onReturn msg' cb _ = return () addCallback s = do mvar <- fmap clientCallbacks getClient liftIO $ MV.modifyMVar_ mvar $ return . Map.insert s cb : :d exports , call : :d process messages p (M.ReceivedMethodReturn _ _ msg) = reply $ M.methodReturnSerial msg p (M.ReceivedError _ _ msg) = reply $ M.errorSerial msg : When a {\tt MethodReturn} or {\tt Error} message is received, DBus expects that its stored serial refers to a registered callback. Sometimes this isn't true -- for example, a client might have used {\tt send} to call a method and ignore its return value. In these cases, the return message should be ignored. :d imports import Data.Maybe (isJust) : :f DBus/Client.hs onReply :: M.Serial -> M.ReceivedMessage -> DBus () onReply serial msg = do mvar <- fmap clientCallbacks getClient maybeCB <- liftIO $ MV.modifyMVar mvar $ \callbacks -> let x = Map.lookup serial callbacks callbacks' = if isJust x then Map.delete serial callbacks else callbacks in return (callbacks', x) case maybeCB of Just cb -> cb msg Nothing -> return () : \subsection{Synchronous} Synchronous (or ``blocking'') operation is emulated using an {\tt MVar}. :f DBus/Client.hs |apidoc callBlocking| callBlocking :: M.MethodCall -> DBus (Either M.Error M.MethodReturn) callBlocking msg = do mvar <- liftIO $ MV.newEmptyMVar call msg (liftIO . MV.putMVar mvar . Left) (liftIO . MV.putMVar mvar . Right) liftIO $ MV.takeMVar mvar |apidoc callBlocking_| callBlocking_ :: M.MethodCall -> DBus M.MethodReturn callBlocking_ msg = do reply <- callBlocking msg case reply of Left err -> E.throwError $ MethodCallFailed err Right x -> return x : :d exports , callBlocking , callBlocking_ : \section{Handling signals} Before the bus forwards any signals to this client, the client must send a match rule to the bus. The rule is kept around so the correct callback can be found when the signal is received. :f DBus/Client.hs |apidoc onSignal| onSignal :: MR.MatchRule -> (T.BusName -> M.Signal -> DBus ()) -> DBus () onSignal rule h = addHandler where rule' = rule { MR.matchType = Just MR.Signal } handler msg@(M.ReceivedSignal _ (Just sender) signal) | MR.matches rule' msg = h sender signal handler _ = return () addHandler = do callBlocking_ $ MR.addMatch rule' mvar <- fmap clientSignalHandlers getClient liftIO $ MV.modifyMVar_ mvar $ return . (handler :) : :d process messages p (M.ReceivedSignal _ _ _) = do mvar <- fmap clientSignalHandlers getClient handlers <- liftIO $ MV.readMVar mvar mapM_ ($ received) handlers : :d exports -- * Handling signals , onSignal : \section{Name reservation} :d exports -- * Name reservation , NR.RequestNameFlag (..) , NR.RequestNameReply (..) , NR.ReleaseNameReply (..) , requestName , releaseName , requestName_ , releaseName_ : :f DBus/Client.hs requestName :: T.BusName -> [NR.RequestNameFlag] -> (M.Error -> DBus ()) -> (NR.RequestNameReply -> DBus ()) -> DBus () requestName name flags onError callback = call (NR.requestName name flags) onError $ \reply -> case NR.mkRequestNameReply reply of Nothing -> E.throwError $ InvalidRequestNameReply reply Just x -> callback x : :f DBus/Client.hs releaseName :: T.BusName -> (M.Error -> DBus ()) -> (NR.ReleaseNameReply -> DBus ()) -> DBus () releaseName name onError callback = call (NR.releaseName name) onError $ \reply -> case NR.mkReleaseNameReply reply of Nothing -> E.throwError $ InvalidReleaseNameReply reply Just x -> callback x : :f DBus/Client.hs requestName_ :: T.BusName -> [NR.RequestNameFlag] -> DBus NR.RequestNameReply requestName_ name flags = do reply <- callBlocking_ $ NR.requestName name flags case NR.mkRequestNameReply reply of Nothing -> E.throwError $ InvalidRequestNameReply reply Just x -> return x : :f DBus/Client.hs releaseName_ :: T.BusName -> DBus NR.ReleaseNameReply releaseName_ name = do reply <- callBlocking_ $ NR.releaseName name case NR.mkReleaseNameReply reply of Nothing -> E.throwError $ InvalidReleaseNameReply reply Just x -> return x : \section{Exporting local objects} DBus is an object-oriented design, and most languages with DBus libraries conform at least vaguely to object-oriented principles. Since Haskell is functional, it's somewhat difficult to make exporting local behavior as simple as it is in other languages. In DBus, the basic unit of behavior is a ``member''. Members may be either methods, which are called, or signals, which are emitted. A collection of members indexed by name is an ``interface''. A collection interfaces (also indexed by name) is an ``object''. A method has two signatures, one for inputs and another for outputs. DBus does not support in-out (aka ``reference'') parameters. Signals have only one signature, which is of their output. :f DBus/Client.hs newtype Object = Object (Map.Map T.InterfaceName Interface) newtype Interface = Interface (Map.Map T.MemberName Member) data Member = MemberMethod Method | MemberSignal T.Signature data Method = Method T.Signature T.Signature (MethodCtx -> DBus ()) : :d exports -- * Exporting local objects , Object (..) , Interface (..) , Member (..) , Method (..) : Exporting is mostly just a matter of adding the object and its path to the client's lookup map. However, note the call to {\tt addIntrospectable} -- DBus supports remote object introspection, and it's useful to generate a basic schema by default. :f DBus/Client.hs |apidoc export| export :: T.ObjectPath -> Object -> DBus () export path obj = do let obj' = addIntrospectable path obj mvar <- fmap clientObjects getClient liftIO $ MV.modifyMVar_ mvar $ return . Map.insert path obj' : :d exports , export : To simplify building objects from existing functions, some helper functions are defined. :f DBus/Client.hs object :: [(T.InterfaceName, Interface)] -> Object object = Object . Map.fromList interface :: [(T.MemberName, Member)] -> Interface interface = Interface . Map.fromList method :: T.Signature -- ^ Input signature -> T.Signature -- ^ Output signature -> (MethodCtx -> DBus ()) -- ^ Implementation -> Member method inSig outSig cb = MemberMethod $ Method inSig outSig cb : :d exports , object , interface , method : \subsection{Responding to method calls} When a method call message is received for a local object, relevant information for replying to the call is placed in a {\tt MethodCtx} value. :d imports import qualified Data.Set as Set : :f DBus/Client.hs data MethodCtx = MethodCtx { methodCtxObject :: Object , methodCtxMethod :: Method , methodCtxSerial :: M.Serial , methodCtxSender :: Maybe T.BusName , methodCtxFlags :: Set.Set M.Flag , methodCtxBody :: [T.Variant] } : {\tt replyReturn} and {\tt replyError} can be used by client code to send a response message to a method call. Using these is easier than constructing the reply manually. :f DBus/Client.hs |apidoc replyReturn| replyReturn :: MethodCtx -> [T.Variant] -> DBus () replyReturn call' body = if valid then sendReply else sendError where sendError = replyError call' Const.errorFailed [T.toVariant ("Method return didn't match signature." :: String)] sendReply = send_ $ M.MethodReturn (methodCtxSerial call') (methodCtxSender call') body (Method _ outSig _) = methodCtxMethod call' valid = listSig body == Just outSig : :f DBus/Client.hs replyError :: MethodCtx -> T.ErrorName -> [T.Variant] -> DBus () replyError call' name body = send_ $ M.Error name (methodCtxSerial call') (methodCtxSender call') body : :d exports -- ** Responding to method calls , MethodCtx (..) , replyReturn , replyError : \subsection{Dispatching method calls} Method calls are dispatched using the client's object map. If the specified method is not found, an error will be returned. :d process messages p (M.ReceivedMethodCall _ _ msg) = do mvar <- fmap clientObjects getClient objects <- liftIO $ MV.readMVar mvar case findMethod objects msg of Just (obj, m) -> onMethodCall obj m received Nothing -> unknownMethod received : :f DBus/Client.hs unknownMethod :: M.ReceivedMessage -> DBus () unknownMethod msg = send_ errorMsg where M.ReceivedMethodCall serial sender _ = msg errorMsg = M.Error Const.errorUnknownMethod serial sender [] : Technically method calls don't have to specify an interface if there's only one available in the destination object, but that'll never be the case here, so treat an unspecified interface as unknown. :f DBus/Client.hs findMethod :: Map.Map T.ObjectPath Object -> M.MethodCall -> Maybe (Object, Method) findMethod objects call' = do Object obj <- Map.lookup (M.methodCallPath call') objects ifaceName <- M.methodCallInterface call' Interface iface <- Map.lookup ifaceName obj member <- Map.lookup (M.methodCallMember call') iface case member of MemberMethod m -> return (Object obj, m) _ -> Nothing : If the method was found, it needs to have its parameter list validated before being sent on to the inner callback. This prevents DBus's dynamic typing from causing trouble in Haskell code. :f DBus/Client.hs onMethodCall :: Object -> Method -> M.ReceivedMessage -> DBus () onMethodCall obj method' received = runCall where M.ReceivedMethodCall serial sender msg = received sig = listSig $ M.methodCallBody msg Method inSig _ cb = method' call' = MethodCtx obj method' serial sender (M.methodCallFlags msg) (M.methodCallBody msg) runCall = if sig == Just inSig then cb call' else replyError call' Const.errorInvalidArgs [] : \subsection{Automatic introspection} Some basic introspection can be performed automatically, based on the contents of an {\tt Object}. This is only added to objects which do not already define the {\tt Introspectable} interface -- that way, clients can provide their own implementations if needed. :f DBus/Client.hs addIntrospectable :: T.ObjectPath -> Object -> Object addIntrospectable path (Object ifaces) = Object ifaces' where ifaces' = Map.insertWith (\_ x -> x) name iface ifaces name = Const.interfaceIntrospectable iface = interface [("Introspect", impl)] impl = method "" "s" $ \call' -> do let Just xml = I.toXML . introspect path . methodCtxObject $ call' replyReturn call' [T.toVariant xml] : :f DBus/Client.hs introspect :: T.ObjectPath -> Object -> I.Object introspect path obj = I.Object path interfaces [] where Object ifaceMap = obj interfaces = map introspectIface (Map.toList ifaceMap) introspectIface :: (T.InterfaceName, Interface) -> I.Interface introspectIface (name, iface) = I.Interface name methods signals [] where Interface memberMap = iface members = Map.toList memberMap methods = concatMap introspectMethod members signals = concatMap introspectSignal members introspectMethod :: (T.MemberName, Member) -> [I.Method] introspectMethod (name, (MemberMethod (Method inSig outSig _))) = [I.Method name (map introspectParam (T.signatureTypes inSig)) (map introspectParam (T.signatureTypes outSig))] introspectMethod _ = [] introspectSignal :: (T.MemberName, Member) -> [I.Signal] introspectSignal (name, (MemberSignal sig)) = [I.Signal name (map introspectParam (T.signatureTypes sig))] introspectSignal _ = [] introspectParam = I.Parameter "" . T.mkSignature_ . T.typeCode : \subsection{The root object} Every client exports a ``root'' object, which provides introspection for all exported objects. Although the DBus export list is hierarchical, this module models it as a flat map. :f DBus/Client.hs rootObject :: Object rootObject = object [(ifaceName, interface [(memberName, impl)])] where ifaceName = Const.interfaceIntrospectable memberName = "Introspect" methodXML = I.Method memberName [] [I.Parameter "xml" "s"] ifaceXML = I.Interface ifaceName [methodXML] [] [] impl = method "" "s" $ \call' -> do mvar <- fmap clientObjects getClient paths <- liftIO $ fmap Map.keys $ MV.readMVar mvar let paths' = filter (/= "/") paths let Just xml = I.toXML $ I.Object "/" [ifaceXML] [I.Object p [] [] | p <- paths'] replyReturn call' [T.toVariant xml] : :d initialize client liftIO $ MV.modifyMVar_ objects $ return . Map.insert "/" rootObject : \section{Remote object proxies} Most DBus libraries support the concept of an ``object proxy'', which behaves like a native object but runs its operations in another process. A {\tt Proxy} is an approximation of this model for Haskell. :f DBus/Client.hs data Proxy = Proxy { proxyName :: T.BusName , proxyObjectPath :: T.ObjectPath , proxyInterface :: T.InterfaceName } deriving (Show, Eq) : :f DBus/Client.hs |apidoc callProxy| callProxy :: Proxy -> T.MemberName -> [M.Flag] -> [T.Variant] -> (M.Error -> DBus ()) -> (M.MethodReturn -> DBus ()) -> DBus () callProxy proxy name flags body onError onReturn = let msg = buildMethodCall proxy name flags body in call msg onError onReturn : :f DBus/Client.hs |apidoc callProxyBlocking| callProxyBlocking :: Proxy -> T.MemberName -> [M.Flag] -> [T.Variant] -> DBus (Either M.Error M.MethodReturn) callProxyBlocking proxy name flags body = callBlocking $ buildMethodCall proxy name flags body : :f DBus/Client.hs |apidoc callProxyBlocking_| callProxyBlocking_ :: Proxy -> T.MemberName -> [M.Flag] -> [T.Variant] -> DBus M.MethodReturn callProxyBlocking_ proxy name flags body = callBlocking_ $ buildMethodCall proxy name flags body : :f DBus/Client.hs |apidoc onProxySignal| onProxySignal :: Proxy -> T.MemberName -> (M.Signal -> DBus ()) -> DBus () onProxySignal proxy member handler = onSignal rule handler' where Proxy dest path iface = proxy rule = MR.MatchRule { MR.matchType = Nothing , MR.matchSender = Just dest , MR.matchInterface = Just iface , MR.matchMember = Just member , MR.matchPath = Just path , MR.matchDestination = Nothing , MR.matchParameters = [] } handler' _ msg = handler msg : :d exports , Proxy (..) , callProxy , callProxyBlocking , callProxyBlocking_ , onProxySignal : :f DBus/Client.hs buildMethodCall :: Proxy -> T.MemberName -> [M.Flag] -> [T.Variant] -> M.MethodCall buildMethodCall proxy name flags body = msg where Proxy dest path iface = proxy msg = M.MethodCall path name (Just iface) (Just dest) (Set.fromList flags) body : \section{Utility functions} :d imports import Data.Monoid (mconcat) : :f DBus/Client.hs listSig :: [T.Variant] -> Maybe T.Signature listSig = T.mkSignature . mconcat . map (T.typeCode . T.variantType) : \section{Haddock API documentation} :d apidoc Client -- | 'Client's are opaque handles to an open connection and other internal -- state. : :d apidoc newClient -- | Create a new 'Client' from an open connection and bus name. The weird -- signature allows @newClient@ to use the computations in "DBus.Bus" -- directly, without unpacking: -- -- @ -- client <- newClient =<< 'getSessionBus' -- @ -- -- Only one client should be created for any given connection. Otherwise, -- they will compete to receive messages. : :d apidoc runDBus -- | Run a DBus computation with the given client callbacks. Errors -- encountered while running will be thrown as exceptions, using the -- 'DBusException' type. -- -- Use the 'E.MonadError' instance for 'DBus' to handle errors inside -- the computation. : :d apidoc processMessage -- | Run message handlers with the received message. If any method reply -- callbacks or signal handlers are found, they will be run in the current -- thread. : :d apidoc send -- | A wrapper around 'C.send'. : :d apidoc send_ -- | A wrapper around 'C.send', which does not allow the message serial -- to be recorded. This is a useful shortcut when sending messages which -- are not expected to receive a reply. : :d apidoc receive -- | A wrapper around 'C.receive'. : :d apidoc mainLoop -- | Run in a loop forever, processing messages. -- -- This is commonly run in a separate thread, ie -- -- > client <- newClient =<< getSessionBus -- > forkIO $ runDBus client mainLoop : :d apidoc call -- | Perform an asynchronous method call. One of the provided computations -- will be performed depending on what message type the destination sends -- back. : :d apidoc callBlocking -- | Sends a method call, and then blocks until a reply is received. Use -- this when the receive/process loop is running in a separate thread. : :d apidoc callBlocking_ -- | A variant of 'callBlocking', which throws an exception if the -- remote client returns 'M.Error'. : :d apidoc onSignal -- | Perform some computation every time this client receives a matching -- signal. : :d apidoc export -- | Export a set of interfaces on the bus. Whenever a method call is -- received which matches the object's path, interface, and member name, -- one of its members will be called. -- -- Exported objects automatically implement the -- @org.freedesktop.DBus.Introspectable@ interface. : :d apidoc replyReturn -- | Send a successful return reply for a method call. : :d apidoc replyError -- | Send an error reply for a method call. : :d apidoc callProxy -- | As 'call', except that the proxy's information is used to -- build the message. : :d apidoc callProxyBlocking -- | As 'callBlocking', except that the proxy's information is used -- to build the message. : :d apidoc callProxyBlocking_ -- | As 'callBlocking_', except that the proxy's information is used -- to build the message. : :d apidoc onProxySignal -- | As 'onSIgnal', except that the proxy's information is used -- to build the match rule. :