Skip to content

Commit

Permalink
X.H.EwmhDesktops: Clean up "handle"
Browse files Browse the repository at this point in the history
Related: #396
Related: #399
Related: #192
  • Loading branch information
liskin committed May 16, 2021
1 parent 6946bbc commit 82ecde8
Show file tree
Hide file tree
Showing 2 changed files with 34 additions and 37 deletions.
68 changes: 32 additions & 36 deletions XMonad/Hooks/EwmhDesktops.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE MultiWayIf #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -200,6 +201,8 @@ ewmhDesktopsLogHookCustom t = withWindowSet $ \s -> do
-- * _NET_WM_DESKTOP (move windows to other desktops)
--
-- * _NET_ACTIVE_WINDOW (activate another window, changing workspace if needed)
--
-- * _NET_CLOSE_WINDOW (close window)
ewmhDesktopsEventHook :: Event -> X All
ewmhDesktopsEventHook = ewmhDesktopsEventHookCustom id

Expand Down Expand Up @@ -244,41 +247,34 @@ activateLogHook mh = XS.get >>= maybe (return ()) go . netActivated
windows (appEndo f)

handle :: ([WindowSpace] -> [WindowSpace]) -> Event -> X ()
handle f (ClientMessageEvent {
ev_window = w,
ev_message_type = mt,
ev_data = d
}) = withWindowSet $ \s -> do
sort' <- getSortByIndex
let ws = f $ sort' $ W.workspaces s

a_cd <- getAtom "_NET_CURRENT_DESKTOP"
a_d <- getAtom "_NET_WM_DESKTOP"
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
a_cw <- getAtom "_NET_CLOSE_WINDOW"
a_ignore <- mapM getAtom ["XMONAD_TIMER"]
if mt == a_cd then do
let n = head d
if 0 <= n && fi n < length ws then
windows $ W.view (W.tag (ws !! fi n))
else trace $ "Bad _NET_CURRENT_DESKTOP with data[0]="++show n
else if mt == a_d then do
let n = head d
if 0 <= n && fi n < length ws then
windows $ W.shiftWin (W.tag (ws !! fi n)) w
else trace $ "Bad _NET_DESKTOP with data[0]="++show n
else if mt == a_aw then do
lh <- asks (logHook . config)
XS.put (NetActivated (Just w))
lh
else if mt == a_cw then
killWindow w
else if mt `elem` a_ignore then
return ()
else
-- The Message is unknown to us, but that is ok, not all are meant
-- to be handled by the window manager
return ()
handle f ClientMessageEvent{ev_window = w, ev_message_type = mt, ev_data = d} =
withWindowSet $ \s -> do
sort' <- getSortByIndex
let ws = f $ sort' $ W.workspaces s

a_cd <- getAtom "_NET_CURRENT_DESKTOP"
a_d <- getAtom "_NET_WM_DESKTOP"
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
a_cw <- getAtom "_NET_CLOSE_WINDOW"

if | mt == a_cd, n : _ <- d, Just ww <- ws !? fi n ->
windows $ W.view (W.tag ww)
| mt == a_cd ->
trace $ "Bad _NET_CURRENT_DESKTOP with data=" ++ show d
| mt == a_d, n : _ <- d, Just ww <- ws !? fi n ->
windows $ W.shiftWin (W.tag ww) w
| mt == a_d ->
trace $ "Bad _NET_WM_DESKTOP with data=" ++ show d
| mt == a_aw -> do
lh <- asks (logHook . config)
XS.put (NetActivated (Just w))
lh
| mt == a_cw ->
killWindow w
| otherwise ->
-- The Message is unknown to us, but that is ok, not all are meant
-- to be handled by the window manager
return ()
handle _ _ = return ()

-- | Add EWMH fullscreen functionality to the given config.
Expand Down
3 changes: 2 additions & 1 deletion XMonad/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,8 @@ chunksOf i xs = chunk : chunksOf i rest

-- | Safe version of '(!!)'.
(!?) :: [a] -> Int -> Maybe a
(!?) xs n = listToMaybe $ drop n xs
(!?) xs n | n < 0 = Nothing
| otherwise = listToMaybe $ drop n xs

-- | Multivariant composition.
--
Expand Down

0 comments on commit 82ecde8

Please sign in to comment.