[Xmonad] turn any window into a statusbar or manage/unmage
windows 'remotely'
Andrea Rossato
mailing_list at istitutocolli.org
Wed Jul 11 05:13:24 EDT 2007
On Wed, Jul 11, 2007 at 09:19:45AM +0200, Robert Manea wrote:
> Hi,
>
> as the question:
>
> 'How can I make xmonad ignore application "foo" and have it appear on every workspace?'
>
> is kind of a FAQ in xmonad's IRC channel, i wrote a tiny application
> just for this purpose.
>
> Source is attached below, usage is trivial:
>
> - retreive the window ID of the application you want to
> unmanage/manage with 'xwininfo'
>
> - invoke the program below, like:
> * unmanage <windowid>
> * manage <windowid>
Ok, get this: does the same, in Haskell!
Requires the patch to X11-extras I've just sent.
It does not check if the windowID is correct, but who cares?
;-)
ciao
andrea
(Competition with Robert is so fun, but without his help I would not
be able to do anything like this.
So Thanks Robert for your great help!!!!!!)
-----------------------------------------------------------------------------
-- |
-- Module : XMobar
-- 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 (thanks to Robert Manea
-- for suggestions on how to get this stuff to work!)
--
-----------------------------------------------------------------------------
module Main where
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import System.Environment
usage :: String -> String
usage n = "Usage: " ++ n ++ "manage/unmanage windowID"
main :: IO ()
main = do
args <- getArgs
pn <- getProgName
let (win,ac) = case args of
[] -> error $ usage pn
w -> case (w !!0) of
"manage" -> (window, False)
"unmanage" -> (window, True)
_ -> error $ usage pn
where window = case (w !! 1) of
[] -> error $ usage pn
w -> read w :: Window
dpy <- openDisplay ""
unmapWindow dpy win
sync dpy False
allocaSetWindowAttributes $
\attributes -> do
set_override_redirect attributes ac
changeWindowAttributes dpy win cWOverrideRedirect attributes
mapWindow dpy win
sync dpy False
More information about the Xmonad
mailing list