[Xmonad] Re: scripting xmonad externally?
Andrea Rossato
mailing_list at istitutocolli.org
Thu Jul 26 09:14:07 EDT 2007
On Mon, Jul 23, 2007 at 10:49:11PM -0700, Stefan O'Rear wrote:
> Actually, commands uses dmenu synchronously and parses the string
> in-process. While it would be nice to control xmonad using a socket
> model, ISTR sjanssen saying { -package X11 is nearly impossible to use
> with threads, and this is one of the main motivations for XHSB. }. You
> can kluge around it by adding a handler for root PropertyNotify events
> on XMONAD_COMMAND and dispatching accordingly, then use xprop to control
> it; thus embedding the control channel over X11. (Not a small task, but
> most of the details could be in a re-usable contrib module...)
I think the idea is cool, if I get it right. But I believe that it
would require a small modification to Main.handle.
by the way, attached you'll find just a proof of concept. SeverMode.hs
must be used as a contrib module:
- save it in XMonadContrib
- import it from Config.hs and add something like:
, ((modMask .|. controlMask, xK_s), startServer)
in the keymap settings.
be careful! when you start the server mode XMonad will be blocked and
the only way you can unblock it is by sending a "restart-wm" command!
then there's is the sendCommand utility:
- compile it with ghc --make sendCommand.hs -o sendCommand
To send a command, after you started the server mode, run:
sendCommand "command"
Remember to open an terminal with the focus before starting the server
mode.
As I said, this is just a joke to have some fun with.
I don't know if this is what you had in mind. Let me know please.
Ciao
Andrea
-------------- next part --------------
-----------------------------------------------------------------------------
-- |
-- Module : Main
-- Copyright : (c) Andrea Rossato
-- License : GPL2
--
-- Maintainer : Andrea Rossato <andrea.rossato at unibz.it>
-- Stability : unstable
-- Portability : unportable
--
-- Toggle override_redirect for an X window
--
-----------------------------------------------------------------------------
module Main where
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import System.Environment
import Control.Monad
usage :: String -> String
usage n = "Usage: " ++ n ++ " windowID command"
main :: IO ()
main = do
args <- getArgs
pn <- getProgName
let com = case args of
[] -> error $ usage pn
w -> (w !! 0)
dpy <- openDisplay ""
rootw <- rootWindow dpy $ defaultScreen dpy
(_,_, ws) <- queryTree dpy rootw
[win] <- filterM (\w -> do
s <- getClassHint dpy w
n <- maybe (resName s) id `fmap` (fetchName dpy w)
if n == "ServerWindow" then return True else return False) ws
setTextProperty dpy win com wM_COMMAND
allocaXEvent $ \e -> do
setEventType e propertyNotify
putStrLn $ show win
sendEvent dpy win False noEventMask e
sync dpy False
-------------- next part --------------
-----------------------------------------------------------------------------
-- |
-- Module : XMonadContrib.ServerMode
-- Copyright : (c) Andrea Rossato
-- License : BSD-style (see xmonad/LICENSE)
--
-- Maintainer : andrea.rossato#unibz.it
-- Stability : unstable
-- Portability : unportable
--
-- A server Mode for the Xmonad Window Manager
--
-----------------------------------------------------------------------------
module XMonadContrib.ServerMode
-- * Usage:
-- $usage
where
import Control.Monad.Reader
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import Data.Bits
import Data.Char
import Data.Maybe
import XMonad
import Operations
import qualified Data.Map as M
import System.Exit
-- $usage
-- You can use this module with the following in your configuration file:
--
startServer :: X ()
startServer = do
c <- ask
let dpy = display c
rootw = theRoot c
win <- io $ mkUnmanagedWindow dpy (defaultScreenOfDisplay dpy) rootw
0 0 1 1
io $ setTextProperty dpy win "ServerWindow" wM_NAME
io $ selectInput dpy win (propertyNotify .|. buttonPress .|. exposureMask)
io $ mapWindow dpy win
io $ sync dpy False
eventLoop dpy win
return ()
eventLoop :: Display -> Window -> X ()
eventLoop dpy win = do
c <- io $ allocaXEvent $ \e -> do
nextEvent dpy e
ev <- getEvent e
putStrLn $ eventName ev
pp <- getWindowProperty8 dpy wM_COMMAND win
let command = map (chr . fromIntegral) . fromMaybe [] $ pp
putStrLn command
return command
runCommand_ c
eventLoop dpy win
runCommand_ :: String -> X ()
runCommand_ c = do
fromMaybe (return ()) (M.lookup c commandMap_)
commandMap_ = M.fromList basicCommands_
basicCommands_ :: [(String, X ())]
basicCommands_ = [ ("restart-wm", restart Nothing True)
, ("restart-wm-no-resume", restart Nothing False)
, ("layout", switchLayout)
, ("xterm", spawn "xterm")
, ("run", spawn "exe=`dmenu_path | dmenu -b` && exec $exe")
, ("kill", kill)
, ("refresh", refresh)
, ("focus-up", focusUp)
, ("focus-down", focusDown)
, ("swap-up", swapUp)
, ("swap-down", swapDown)
, ("swap-master", swapMaster)
, ("sink", withFocused sink)
, ("quit-wm", io $ exitWith ExitSuccess)
]
-- | Creates a window with the attribute override_redirect set to True.
-- Windows Managers should not touch this kind of windows.
mkUnmanagedWindow :: Display
-> Screen
-> Window
-> Position
-> Position
-> Dimension
-> Dimension
-> IO Window
mkUnmanagedWindow dpy scr rw x y w h = do
let visual = defaultVisualOfScreen scr
attrmask = cWOverrideRedirect
win <- allocaSetWindowAttributes $
\attributes -> do
set_override_redirect attributes True
createWindow dpy rw x y w h 0 (defaultDepthOfScreen scr)
inputOutput visual attrmask attributes
return win
More information about the Xmonad
mailing list