[Xmonad] Remote Controlling XMonad: Cases and Materials [SOLVED]

Andrea Rossato andrea.rossato at unibz.it
Sun Feb 24 08:47:56 EST 2008


On Tue, Aug 07, 2007 at 11:47:07AM -0700, David Roundy wrote:
> On Tue, Aug 07, 2007 at 03:45:56PM +0200, Andrea Rossato wrote:
> > On Sun, Jul 29, 2007 at 01:22:32PM +0200, Andrea Rossato wrote:
> > > BTW, these patches require a vary small modification to XMonad itself.
> > > XMonad has just to wait for a propertyNotify event sent to the root
> > > window. If that happens a hook is called (I named that hook
> > > serverHook).
> >
> > Well, I build up such a case... typical of a lawyer I'd say...;-)
> >
> > Now I'm studying some of David's code, and LayoutHelpers, specifically.
> >
> > There's no need at all to modify XMonad, this is just a simple contrib
> > module I'm going to submit shortly.
> >
> > Unfortunately David did not document much his code, and some of it,
> > even if designed to help others, remains unused. I'll try to write
> > some documentation too. I'm sure David doesn't mind.
>
> I will greatly appreciate contributed documentation--or API improvements.
> LayoutHelpers was basically thrown together quickly to try to create *some*
> sort of working interface for a Layout transformer, but it isn't really
> something I can be proud of.  :(
>
> It's been continually a hack.  I have been thinking that we (I?) ought to
> define a layout monad L that basically would track the state of the layout
> (something like a state monad stacked on top of X) and return a value.
> Then we could write much prettier layout code.

Yes we could. Well, we can...

I didn't forget this thread... and I just pushed (in my repos) an
EventHook (based on the stuff I coded to answer to nomeata's
challenge): Hooks.ServerMode.

The code is well documented, with usage examples and all (see here):

http://gorgias.mine.nu/xmonad-docs/xmonad-contrib/XMonad-Hooks-ServerMode.html

Anyway:

 import XMonad.Hooks.ServerMode
 layoutHook = eventHook ServerMode $ avoidStruts $ simpleTabbed ||| Full ||| etc..
 main = xmonad defaultConfig { layoutHook = myLayouts }

Below the code for a client (sendMessage), which will send a command
number and xmonad will execute the relative command.

If you ask for a wrong command number or for 0 (sendCommand 0), xmonad
will print (in ~/.xsession-errors) the list of command numbers with
their relative command.

One of the nice things of an event hook implemented at the layout
level, is that you can have more event hooks (as it is documented
here:
http://gorgias.mine.nu/xmonad-docs/xmonad-contrib/XMonad-Hooks-EventHook.html

Cheers,
Andrea


module Main where

import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import System.Environment
import Data.Char

usage :: String -> String
usage n = "Usage: " ++ n ++ " command number\nSend a command number to a running instance of XMonad"

main :: IO ()
main = do
  args <- getArgs
  pn <- getProgName
  let com = case args of
              [] -> error $ usage pn
              w -> (w !! 0)
  sendCommand com

sendCommand :: String -> IO ()
sendCommand s = do
  d   <- openDisplay ""
  rw  <- rootWindow d $ defaultScreen d
  a <- internAtom d "XMONAD_COMMAND" False
  allocaXEvent $ \e -> do
                  setEventType e clientMessage
                  setClientMessageEvent e rw a 32 (fromIntegral (read s)) currentTime
                  sendEvent d rw False structureNotifyMask e
                  sync d False



More information about the xmonad mailing list