aboutsummaryrefslogtreecommitdiffstats
path: root/EwmhDesktops.hs
diff options
context:
space:
mode:
authormail <mail@joachim-breitner.de>2007-10-06 00:25:40 +0200
committermail <mail@joachim-breitner.de>2007-10-06 00:25:40 +0200
commit96f570035d6353c421164329d3d022773ec894f1 (patch)
treee4c91a01eda2d990dfe3d7f24a6d41b105e6c847 /EwmhDesktops.hs
parent52c08c5c47a4025db21eef30282a88a377008a7e (diff)
downloadXMonadContrib-96f570035d6353c421164329d3d022773ec894f1.tar.gz
XMonadContrib-96f570035d6353c421164329d3d022773ec894f1.tar.xz
XMonadContrib-96f570035d6353c421164329d3d022773ec894f1.zip
EwmhDesktops initial patch
What works so far, quit hackerish: * Number of Workspaces * Active current workspace * Names of workspaces More to come.. darcs-hash:20071005222540-c9905-33f19902bbe804a7dc4eccba27fed43822f55dd1.gz
Diffstat (limited to 'EwmhDesktops.hs')
-rw-r--r--EwmhDesktops.hs42
1 files changed, 42 insertions, 0 deletions
diff --git a/EwmhDesktops.hs b/EwmhDesktops.hs
new file mode 100644
index 0000000..d6684ac
--- /dev/null
+++ b/EwmhDesktops.hs
@@ -0,0 +1,42 @@
+module XMonadContrib.EwmhDesktops (ewmhDesktopsLogHook) where
+
+import Data.Maybe (listToMaybe,fromJust)
+import Data.List (elemIndex, sortBy)
+import Data.Ord ( comparing)
+
+import Control.Monad.Reader
+import XMonad
+import qualified StackSet as W
+import System.IO
+import Graphics.X11.Xlib
+import Graphics.X11.Xlib.Extras
+
+ewmhDesktopsLogHook :: X ()
+ewmhDesktopsLogHook = withDisplay $ \dpy -> withWindowSet $ \s -> do
+ -- Number of Workspaces
+ -- Bad hack because xmonad forgets the original order of things, it seems
+ let ws = sortBy (comparing W.tag) $ W.workspaces s
+
+ let n = fromIntegral (length ws)
+ a <- getAtom "_NET_NUMBER_OF_DESKTOPS"
+ c <- getAtom "CARDINAL"
+ r <- asks theRoot
+ io $ changeProperty32 dpy r a c propModeReplace [n]
+
+ -- Names thereof
+ a <- getAtom "_NET_DESKTOP_NAMES"
+ c <- getAtom "UTF8_STRING"
+ let names = map (fromIntegral.fromEnum) $
+ concatMap (("Workspace "++) . (++['\0']). W.tag) ws
+ io $ changeProperty8 dpy r a c propModeReplace names
+
+ -- Current desktop
+ a <- getAtom "_NET_CURRENT_DESKTOP"
+ c <- getAtom "CARDINAL"
+ let Just n = W.lookupWorkspace 0 s
+ let Just i = elemIndex n $ map W.tag ws
+ io $ changeProperty32 dpy r a c propModeReplace [fromIntegral i]
+
+ return ()
+
+