aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorJoachim Breitner <mail@joachim-breitner.de>2008-03-19 20:57:36 +0100
committerJoachim Breitner <mail@joachim-breitner.de>2008-03-19 20:57:36 +0100
commit908c727cedf28356a6d26c716cf57f066f3e122f (patch)
tree9a8d972af3b51ec55ccb712a5620f5a73aa9ad26 /XMonad
parent36802edd28c37100c0782563a78ba497388be772 (diff)
downloadXMonadContrib-908c727cedf28356a6d26c716cf57f066f3e122f.tar.gz
XMonadContrib-908c727cedf28356a6d26c716cf57f066f3e122f.tar.xz
XMonadContrib-908c727cedf28356a6d26c716cf57f066f3e122f.zip
add ewmhDesktopsLayout for EWMH interaction
This is based on Andrea’s EventHook thingy. Note that I could not merge this with some of my earlier EWHM interaction patches (darcs was failing on me), so I copied some code. Do not try to merge it with those patches either. Note that the docs are saying what should work. There are still some bugs to be resolved, but it works sometimes and should work similar to what we have. darcs-hash:20080319195736-23c07-78be594f4352055d21d921eecab4312905124cf9.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Hooks/EwmhDesktops.hs62
1 files changed, 58 insertions, 4 deletions
diff --git a/XMonad/Hooks/EwmhDesktops.hs b/XMonad/Hooks/EwmhDesktops.hs
index 94c4b3d..4cf7432 100644
--- a/XMonad/Hooks/EwmhDesktops.hs
+++ b/XMonad/Hooks/EwmhDesktops.hs
@@ -1,7 +1,7 @@
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.EwmhDesktops
--- Copyright : (c) Joachim Breitner <mail@joachim-breitner.de>
+-- Copyright : (c) 2007, 2008 Joachim Breitner <mail@joachim-breitner.de>
-- License : BSD
--
-- Maintainer : Joachim Breitner <mail@joachim-breitner.de>
@@ -9,12 +9,14 @@
-- Portability : unportable
--
-- Makes xmonad use the EWMH hints to tell panel applications about its
--- workspaces and the windows therein.
+-- workspaces and the windows therein. It also allows the user to interact
+-- with xmonad by clicking on panels and window lists.
-----------------------------------------------------------------------------
module XMonad.Hooks.EwmhDesktops (
-- * Usage
-- $usage
- ewmhDesktopsLogHook
+ ewmhDesktopsLogHook,
+ ewmhDesktopsLayout
) where
import Data.List
@@ -26,6 +28,7 @@ import qualified XMonad.StackSet as W
import XMonad.Hooks.SetWMName
import XMonad.Util.WorkspaceCompare
+import XMonad.Hooks.EventHook
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -37,11 +40,17 @@ import XMonad.Util.WorkspaceCompare
-- > myLogHook = do ewmhDesktopsLogHook
-- > return ()
-- >
--- > main = xmonad defaultConfig { logHook = myLogHook }
+-- > layoutHook = ewmhDesktopsLayout $ avoidStruts $ simpleTabbed ||| Full ||| etc..
+-- >
+-- > main = xmonad defaultConfig { layoutHook = myLayouts, logHook = myLogHook }
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#The_log_hook_and_external_status_bars"
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
-- |
-- Notifies pagers and window lists, such as those in the gnome-panel
@@ -83,6 +92,51 @@ ewmhDesktopsLogHook = withWindowSet $ \s -> do
return ()
+-- |
+-- Intercepts messages from pagers and similar applications and reacts on them.
+-- Currently supports:
+--
+-- * _NET_CURRENT_DESKTOP (switching desktops)
+--
+-- * _NET_WM_DESKTOP (move windows to other desktops)
+--
+-- * _NET_ACTIVE_WINDOW (activate another window)
+--
+ewmhDesktopsLayout :: layout a -> HandleEvent EwmhDesktopsHook layout a
+ewmhDesktopsLayout = eventHook EwmhDesktopsHook
+
+data EwmhDesktopsHook = EwmhDesktopsHook deriving ( Show, Read )
+instance EventHook EwmhDesktopsHook where
+ handleEvent _ e@ClientMessageEvent {} = do handle e
+ handleEvent _ _ = return ()
+
+handle :: Event -> X ()
+handle ClientMessageEvent {
+ ev_window = w,
+ ev_message_type = mt,
+ ev_data = d
+ } = withWindowSet $ \s -> do
+ sort' <- getSortByIndex
+ let ws = sort' $ W.workspaces s
+
+ a_cd <- getAtom "_NET_CURRENT_DESKTOP"
+ a_d <- getAtom "_NET_WM_DESKTOP"
+ a_aw <- getAtom "_NET_ACTIVE_WINDOW"
+ if mt == a_cd then do
+ let n = fromIntegral (head d)
+ if 0 <= n && n < length ws then
+ windows $ W.view (W.tag (ws !! n))
+ else trace $ "Bad _NET_CURRENT_DESKTOP with data[0]="++show n
+ else if mt == a_d then do
+ let n = fromIntegral (head d)
+ if 0 <= n && n < length ws then
+ windows $ W.shiftWin (W.tag (ws !! n)) w
+ else trace $ "Bad _NET_DESKTOP with data[0]="++show n
+ else if mt == a_aw then do
+ windows $ W.focusWindow w
+ else trace $ "Unknown ClientMessageEvent " ++ show mt
+handle _ = undefined -- does not happen, as otherwise ewmhDesktopsHook would not match
+
setNumberOfDesktops :: (Integral a) => a -> X ()
setNumberOfDesktops n = withDisplay $ \dpy -> do