mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-07 07:21:53 -07:00
X.H.EwmhDesktops: Clean up "handle"
Related: https://github.com/xmonad/xmonad-contrib/issues/396 Related: https://github.com/xmonad/xmonad-contrib/pull/399 Related: https://github.com/xmonad/xmonad-contrib/pull/192
This commit is contained in:
@@ -1,4 +1,5 @@
|
|||||||
{-# LANGUAGE DeriveDataTypeable #-}
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||||||
|
{-# LANGUAGE MultiWayIf #-}
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
@@ -200,6 +201,8 @@ ewmhDesktopsLogHookCustom t = withWindowSet $ \s -> do
|
|||||||
-- * _NET_WM_DESKTOP (move windows to other desktops)
|
-- * _NET_WM_DESKTOP (move windows to other desktops)
|
||||||
--
|
--
|
||||||
-- * _NET_ACTIVE_WINDOW (activate another window, changing workspace if needed)
|
-- * _NET_ACTIVE_WINDOW (activate another window, changing workspace if needed)
|
||||||
|
--
|
||||||
|
-- * _NET_CLOSE_WINDOW (close window)
|
||||||
ewmhDesktopsEventHook :: Event -> X All
|
ewmhDesktopsEventHook :: Event -> X All
|
||||||
ewmhDesktopsEventHook = ewmhDesktopsEventHookCustom id
|
ewmhDesktopsEventHook = ewmhDesktopsEventHookCustom id
|
||||||
|
|
||||||
@@ -244,41 +247,34 @@ activateLogHook mh = XS.get >>= maybe (return ()) go . netActivated
|
|||||||
windows (appEndo f)
|
windows (appEndo f)
|
||||||
|
|
||||||
handle :: ([WindowSpace] -> [WindowSpace]) -> Event -> X ()
|
handle :: ([WindowSpace] -> [WindowSpace]) -> Event -> X ()
|
||||||
handle f (ClientMessageEvent {
|
handle f ClientMessageEvent{ev_window = w, ev_message_type = mt, ev_data = d} =
|
||||||
ev_window = w,
|
withWindowSet $ \s -> do
|
||||||
ev_message_type = mt,
|
sort' <- getSortByIndex
|
||||||
ev_data = d
|
let ws = f $ sort' $ W.workspaces s
|
||||||
}) = withWindowSet $ \s -> do
|
|
||||||
sort' <- getSortByIndex
|
|
||||||
let ws = f $ sort' $ W.workspaces s
|
|
||||||
|
|
||||||
a_cd <- getAtom "_NET_CURRENT_DESKTOP"
|
a_cd <- getAtom "_NET_CURRENT_DESKTOP"
|
||||||
a_d <- getAtom "_NET_WM_DESKTOP"
|
a_d <- getAtom "_NET_WM_DESKTOP"
|
||||||
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
|
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
|
||||||
a_cw <- getAtom "_NET_CLOSE_WINDOW"
|
a_cw <- getAtom "_NET_CLOSE_WINDOW"
|
||||||
a_ignore <- mapM getAtom ["XMONAD_TIMER"]
|
|
||||||
if mt == a_cd then do
|
if | mt == a_cd, n : _ <- d, Just ww <- ws !? fi n ->
|
||||||
let n = head d
|
windows $ W.view (W.tag ww)
|
||||||
if 0 <= n && fi n < length ws then
|
| mt == a_cd ->
|
||||||
windows $ W.view (W.tag (ws !! fi n))
|
trace $ "Bad _NET_CURRENT_DESKTOP with data=" ++ show d
|
||||||
else trace $ "Bad _NET_CURRENT_DESKTOP with data[0]="++show n
|
| mt == a_d, n : _ <- d, Just ww <- ws !? fi n ->
|
||||||
else if mt == a_d then do
|
windows $ W.shiftWin (W.tag ww) w
|
||||||
let n = head d
|
| mt == a_d ->
|
||||||
if 0 <= n && fi n < length ws then
|
trace $ "Bad _NET_WM_DESKTOP with data=" ++ show d
|
||||||
windows $ W.shiftWin (W.tag (ws !! fi n)) w
|
| mt == a_aw -> do
|
||||||
else trace $ "Bad _NET_DESKTOP with data[0]="++show n
|
lh <- asks (logHook . config)
|
||||||
else if mt == a_aw then do
|
XS.put (NetActivated (Just w))
|
||||||
lh <- asks (logHook . config)
|
lh
|
||||||
XS.put (NetActivated (Just w))
|
| mt == a_cw ->
|
||||||
lh
|
killWindow w
|
||||||
else if mt == a_cw then
|
| otherwise ->
|
||||||
killWindow w
|
-- The Message is unknown to us, but that is ok, not all are meant
|
||||||
else if mt `elem` a_ignore then
|
-- to be handled by the window manager
|
||||||
return ()
|
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 _ _ = return ()
|
handle _ _ = return ()
|
||||||
|
|
||||||
-- | Add EWMH fullscreen functionality to the given config.
|
-- | Add EWMH fullscreen functionality to the given config.
|
||||||
|
@@ -46,7 +46,8 @@ chunksOf i xs = chunk : chunksOf i rest
|
|||||||
|
|
||||||
-- | Safe version of '(!!)'.
|
-- | Safe version of '(!!)'.
|
||||||
(!?) :: [a] -> Int -> Maybe a
|
(!?) :: [a] -> Int -> Maybe a
|
||||||
(!?) xs n = listToMaybe $ drop n xs
|
(!?) xs n | n < 0 = Nothing
|
||||||
|
| otherwise = listToMaybe $ drop n xs
|
||||||
|
|
||||||
-- | Multivariant composition.
|
-- | Multivariant composition.
|
||||||
--
|
--
|
||||||
|
Reference in New Issue
Block a user