Skip to content

Commit 506fe04

Browse files
liskinTheMC47
authored andcommitted
X.H.EwmhDesktops: Clean up "handle"
Whitespace and refactoring before other changes.
1 parent fe97cfb commit 506fe04

File tree

1 file changed

+33
-35
lines changed

1 file changed

+33
-35
lines changed

XMonad/Hooks/EwmhDesktops.hs

Lines changed: 33 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE DeriveDataTypeable #-}
2+
{-# LANGUAGE MultiWayIf #-}
23

34
-----------------------------------------------------------------------------
45
-- |
@@ -204,6 +205,8 @@ ewmhDesktopsLogHookCustom f = withWindowSet $ \s -> do
204205
-- * _NET_WM_DESKTOP (move windows to other desktops)
205206
--
206207
-- * _NET_ACTIVE_WINDOW (activate another window, changing workspace if needed)
208+
--
209+
-- * _NET_CLOSE_WINDOW (close window)
207210
ewmhDesktopsEventHook :: Event -> X All
208211
ewmhDesktopsEventHook = ewmhDesktopsEventHookCustom id
209212

@@ -248,41 +251,36 @@ activateLogHook mh = XS.get >>= maybe (return ()) go . netActivated
248251
windows (appEndo f)
249252

250253
handle :: ([WindowSpace] -> [WindowSpace]) -> Event -> X ()
251-
handle f (ClientMessageEvent {
252-
ev_window = w,
253-
ev_message_type = mt,
254-
ev_data = d
255-
}) = withWindowSet $ \s -> do
256-
sort' <- getSortByIndex
257-
let ws = f $ sort' $ W.workspaces s
258-
259-
a_cd <- getAtom "_NET_CURRENT_DESKTOP"
260-
a_d <- getAtom "_NET_WM_DESKTOP"
261-
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
262-
a_cw <- getAtom "_NET_CLOSE_WINDOW"
263-
a_ignore <- mapM getAtom ["XMONAD_TIMER"]
264-
if mt == a_cd then do
265-
let n = head d
266-
if 0 <= n && fi n < length ws then
267-
windows $ W.view (W.tag (ws !! fi n))
268-
else trace $ "Bad _NET_CURRENT_DESKTOP with data[0]="++show n
269-
else if mt == a_d then do
270-
let n = head d
271-
if 0 <= n && fi n < length ws then
272-
windows $ W.shiftWin (W.tag (ws !! fi n)) w
273-
else trace $ "Bad _NET_DESKTOP with data[0]="++show n
274-
else if mt == a_aw then do
275-
lh <- asks (logHook . config)
276-
XS.put (NetActivated (Just w))
277-
lh
278-
else if mt == a_cw then
279-
killWindow w
280-
else if mt `elem` a_ignore then
281-
return ()
282-
else
283-
-- The Message is unknown to us, but that is ok, not all are meant
284-
-- to be handled by the window manager
285-
return ()
254+
handle f (ClientMessageEvent {ev_window = w, ev_message_type = mt, ev_data = d}) =
255+
withWindowSet $ \s -> do
256+
sort' <- getSortByIndex
257+
let ws = f $ sort' $ W.workspaces s
258+
259+
a_cd <- getAtom "_NET_CURRENT_DESKTOP"
260+
a_d <- getAtom "_NET_WM_DESKTOP"
261+
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
262+
a_cw <- getAtom "_NET_CLOSE_WINDOW"
263+
264+
if | mt == a_cd ->
265+
case d of
266+
(n:_) | 0 <= n && fi n < length ws -> windows $ W.view (W.tag (ws !! fi n))
267+
| otherwise -> trace $ "Bad _NET_CURRENT_DESKTOP with data[0]="++show n
268+
_ -> trace $ "Bad _NET_CURRENT_DESKTOP with data="++show d
269+
| mt == a_d ->
270+
case d of
271+
(n:_) | 0 <= n && fi n < length ws -> windows $ W.shiftWin (W.tag (ws !! fi n)) w
272+
| otherwise -> trace $ "Bad _NET_DESKTOP with data[0]="++show n
273+
_ -> trace $ "Bad _NET_DESKTOP with data="++show d
274+
| mt == a_aw -> do
275+
lh <- asks (logHook . config)
276+
XS.put (NetActivated (Just w))
277+
lh
278+
| mt == a_cw ->
279+
killWindow w
280+
| otherwise ->
281+
-- The Message is unknown to us, but that is ok, not all are meant
282+
-- to be handled by the window manager
283+
return ()
286284
handle _ _ = return ()
287285

288286
-- | Add EWMH fullscreen functionality to the given config.

0 commit comments

Comments
 (0)