Skip to content

Commit

Permalink
X.H.EwmhDesktops: Improve interface for hooking window activation
Browse files Browse the repository at this point in the history
TODO

Fixes: #396
Related: #110
Related: #192
Related: #128
  • Loading branch information
liskin committed Oct 19, 2021
1 parent 6ea9fbf commit de7217f
Show file tree
Hide file tree
Showing 6 changed files with 69 additions and 96 deletions.
12 changes: 5 additions & 7 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -47,13 +47,11 @@
`addEwmhWorkspaceRename` functions, or better still, use integrations
provided by modules such as `XMonad.Actions.WorkspaceNames`.

- `ewmh` function will use `logHook` for handling activated window. And now
by default window activation will do nothing.

You can use regular `ManageHook` combinators for changing window
activation behavior and then add resulting `ManageHook` using
`activateLogHook` to your `logHook`. Also, module `X.H.Focus` provides
additional combinators.
This interface now additionally allows customization of what happens
when clients request window activation. This can be used to ignore
activation of annoying applications, to mark windows as urgent instead
of focusing them, and more. There's also a new `XMonad.Hooks.Focus`
module extending the ManageHook EDSL with useful combinators.

- Ordering of windows that are set to `_NET_CLIENT_LIST` and `_NET_CLIENT_LIST_STACKING`
was changed to be closer to the spec. From now these two lists will have
Expand Down
7 changes: 0 additions & 7 deletions XMonad/Config/Desktop.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,6 @@ import XMonad.Hooks.ManageDocks
import XMonad.Hooks.EwmhDesktops
import XMonad.Layout.LayoutModifier (ModifiedLayout)
import XMonad.Util.Cursor
import qualified XMonad.StackSet as W

import qualified Data.Map as M

Expand Down Expand Up @@ -172,7 +171,6 @@ desktopConfig :: XConfig (ModifiedLayout AvoidStruts
desktopConfig = docks $ ewmh def
{ startupHook = setDefaultCursor xC_left_ptr <+> startupHook def
, layoutHook = desktopLayoutModifiers $ layoutHook def
, logHook = desktopLogHook <+> logHook def
, keys = desktopKeys <+> keys def }

desktopKeys :: XConfig l -> M.Map (KeyMask, KeySym) (X ())
Expand All @@ -181,8 +179,3 @@ desktopKeys XConfig{modMask = modm} = M.fromList

desktopLayoutModifiers :: LayoutClass l a => l a -> ModifiedLayout AvoidStruts l a
desktopLayoutModifiers = avoidStruts

-- | 'logHook' preserving old 'ewmh' behavior to switch workspace and focus to
-- activated window.
desktopLogHook :: X ()
desktopLogHook = activateLogHook (reader W.focusWindow >>= doF)
123 changes: 52 additions & 71 deletions XMonad/Hooks/EwmhDesktops.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,9 +27,7 @@ module XMonad.Hooks.EwmhDesktops (
-- $customization
addEwmhWorkspaceSort, setEwmhWorkspaceSort,
addEwmhWorkspaceRename, setEwmhWorkspaceRename,
NetActivated (..),
activated,
activateLogHook,
setEwmhActivateHook,

-- * Standalone hooks (to be deprecated)
ewmhDesktopsStartup,
Expand All @@ -49,6 +47,7 @@ import XMonad
import XMonad.Prelude
import qualified XMonad.StackSet as W

import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.SetWMName
import XMonad.Util.WorkspaceCompare
import XMonad.Util.WindowProperties (getProp32)
Expand All @@ -70,34 +69,6 @@ import qualified XMonad.Util.ExtensibleState as XS
-- You may also be interested in 'XMonad.Hooks.ManageDocks.docks' and
-- 'XMonad.Hooks.UrgencyHook.withUrgencyHook', which provide support for other
-- parts of the EWMH specification.
--
-- __/NOTE:/__ 'ewmh' function will call 'logHook' for handling activated
-- window.
--
-- And now by default window activation will do nothing: neither switch
-- workspace, nor focus. You can use regular 'ManageHook' combinators for
-- changing window activation behavior and then add resulting 'ManageHook'
-- using 'activateLogHook' to your 'logHook'. Also, you may be interested in
-- "XMonad.Hooks.Focus", which provides additional predicates for using in
-- 'ManageHook'.
--
-- To get back old 'ewmh' window activation behavior (switch workspace and
-- focus to activated window) you may use:
--
-- > import XMonad
-- >
-- > import XMonad.Hooks.EwmhDesktops
-- > import qualified XMonad.StackSet as W
-- >
-- > main :: IO ()
-- > main = do
-- > let acMh :: ManageHook
-- > acMh = reader W.focusWindow >>= doF
-- > xcf = ewmh $ def
-- > { modMask = mod4Mask
-- > , logHook = activateLogHook acMh <+> logHook def
-- > }
-- > xmonad xcf

-- | Add EWMH support for workspaces (virtual desktops) to the given
-- 'XConfig'. See above for an example.
Expand All @@ -116,6 +87,39 @@ ewmh c = c { startupHook = ewmhDesktopsStartup <+> startupHook c
-- == Renaming of workspaces
--
-- TODO
--
-- == Window activation
--
-- When a client sends a @_NET_ACTIVE_WINDOW@ request to activate a window, by
-- default that window is activated by invoking the 'doFocus' 'ManageHook'.
-- The EWMH specification suggests that a window manager may instead just mark
-- the window as urgent, and this can be achieved using the following:
--
-- > import XMonad.Hooks.UrgencyHook
-- >
-- > main = xmonad $ … . setEwmhActivateHook doAskUrgent . ewmh . … $ def{…}
--
-- One may also wish to ignore activation requests from certain applications
-- entirely:
--
-- > import XMonad.Hooks.ManageHelpers
-- >
-- > myActivateHook :: ManageHook
-- > myActivateHook =
-- > className /=? "Google-chrome" <&&> className /=? "google-chrome" --> doFocus
-- >
-- > main = xmonad $ … . setEwmhActivateHook myActivateHook . ewmh . … $ def{…}
--
-- Arbitrarily complex hooks can be used. This last example marks Chrome
-- windows as urgent and focuses everything else:
--
-- > myActivateHook :: ManageHook
-- > myActivateHook = composeOne
-- > [ className =? "Google-chrome" <||> className =? "google-chrome" -?> doAskUrgent
-- > , pure True -?> doFocus ]
--
-- See "XMonad.ManageHook", "XMonad.Hooks.ManageHelpers" and "XMonad.Hooks.Focus"
-- for functions that can be useful here.

-- | Customizable configuration for EwmhDesktops
data EwmhDesktopsConfig =
Expand All @@ -124,12 +128,15 @@ data EwmhDesktopsConfig =
-- ^ configurable workspace sorting/filtering
, workspaceRename :: X (String -> WindowSpace -> String)
-- ^ configurable workspace rename (see 'XMonad.Hooks.StatusBar.PP.ppRename')
, activateHook :: ManageHook
-- ^ configurable handling of window activation requests
}

instance Default EwmhDesktopsConfig where
def = EwmhDesktopsConfig
{ workspaceSort = getSortByIndex
, workspaceRename = pure pure
, activateHook = doFocus
}

-- | Add (compose after) an arbitrary user-specified function to sort/filter
Expand All @@ -155,6 +162,16 @@ addEwmhWorkspaceRename f = XC.modifyDef $ \c -> c{ workspaceRename = liftA2 (<=<
setEwmhWorkspaceRename :: X (String -> WindowSpace -> String) -> XConfig l -> XConfig l
setEwmhWorkspaceRename f = XC.modifyDef $ \c -> c{ workspaceRename = f }

-- | Set (replace) the hook which is invoked when a client sends a
-- @_NET_ACTIVE_WINDOW@ request to activate a window. The default is 'doFocus'
-- which focuses the window immediately, switching workspace if necessary.
-- 'XMonad.Hooks.UrgencyHook.doAskUrgent' is a less intrusive alternative.
--
-- More complex hooks can be constructed using combinators from
-- "XMonad.ManageHook", "XMonad.Hooks.ManageHelpers" and "XMonad.Hooks.Focus".
setEwmhActivateHook :: ManageHook -> XConfig l -> XConfig l
setEwmhActivateHook h = XC.modifyDef $ \c -> c{ activateHook = h }

-- | Initializes EwmhDesktops and advertises EWMH support to the X server
ewmhDesktopsStartup :: X ()
ewmhDesktopsStartup = setSupported
Expand Down Expand Up @@ -260,44 +277,10 @@ ewmhDesktopsLogHook' EwmhDesktopsConfig{workspaceSort, workspaceRename} = withWi
let activeWindow' = fromMaybe none (W.peek s)
whenChanged (ActiveWindow activeWindow') $ setActiveWindow activeWindow'

-- | Whether new window _NET_ACTIVE_WINDOW activated or not. I should keep
-- this value in global state, because i use 'logHook' for handling activated
-- windows and i need a way to tell 'logHook' what window is activated.
newtype NetActivated = NetActivated {netActivated :: Maybe Window}
deriving Show
instance ExtensionClass NetActivated where
initialValue = NetActivated Nothing

-- | Was new window @_NET_ACTIVE_WINDOW@ activated?
activated :: Query Bool
activated = fmap (isJust . netActivated) (liftX XS.get)

-- | Run supplied 'ManageHook' for activated windows /only/. If you want to
-- run this 'ManageHook' for new windows too, add it to 'manageHook'.
--
-- __/NOTE:/__ 'activateLogHook' will work only _once_. I.e. if several
-- 'activateLogHook'-s was used, only first one will actually run (because it
-- resets 'NetActivated' at the end and others won't know, that window is
-- activated).
activateLogHook :: ManageHook -> X ()
activateLogHook mh = XS.get >>= maybe (return ()) go . netActivated
where
go :: Window -> X ()
go w = do
f <- runQuery mh w
-- I should reset 'NetActivated' here, because:
-- * 'windows' calls 'logHook' and i shouldn't go here the second
-- time for one window.
-- * if i reset 'NetActivated' before running 'logHook' once,
-- then 'activated' predicate won't match.
-- Thus, here is the /only/ correct place.
XS.put NetActivated{netActivated = Nothing}
windows (appEndo f)

ewmhDesktopsEventHook' :: Event -> EwmhDesktopsConfig -> X All
ewmhDesktopsEventHook'
ClientMessageEvent{ev_window = w, ev_message_type = mt, ev_data = d}
EwmhDesktopsConfig{workspaceSort} =
EwmhDesktopsConfig{workspaceSort, activateHook} =
withWindowSet $ \s -> do
sort' <- workspaceSort
let ws = sort' $ W.workspaces s
Expand All @@ -318,11 +301,9 @@ ewmhDesktopsEventHook'
| mt == a_aw, 2 : _ <- d ->
-- when the request comes from a pager, honor it unconditionally
-- https://specifications.freedesktop.org/wm-spec/wm-spec-1.3.html#sourceindication
windows $ W.focusWindow w
| mt == a_aw, W.peek s /= Just w -> do
lh <- asks (logHook . config)
XS.put (NetActivated (Just w))
lh
if W.peek s == Just w then mempty else windows $ W.focusWindow w
| mt == a_aw -> do
if W.peek s == Just w then mempty else windows . appEndo =<< runQuery activateHook w
| mt == a_cw ->
killWindow w
| otherwise ->
Expand Down
12 changes: 4 additions & 8 deletions XMonad/Hooks/Focus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,6 @@ import XMonad.Prelude
import qualified XMonad.StackSet as W
import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Hooks.ManageHelpers (currentWs)
import XMonad.Hooks.EwmhDesktops (activated)


-- $main
Expand Down Expand Up @@ -555,22 +554,19 @@ when' b mx
-- | Default EWMH window activation behavior: switch to workspace with
-- activated window and switch focus to it.
activateSwitchWs :: ManageHook
activateSwitchWs = manageFocus (liftQuery activated -->
switchWorkspace <+> switchFocus)
activateSwitchWs = manageFocus (switchWorkspace <+> switchFocus)

-- | Move activated window to current workspace.
activateOnCurrent' :: ManageHook
activateOnCurrent' = activated --> currentWs >>= unlessFocusLock . doShift
activateOnCurrent' = currentWs >>= unlessFocusLock . doShift

-- | Move activated window to current workspace and switch focus to it. Note,
-- that i need to explicitly call 'switchFocus' here, because otherwise, when
-- activated window is /already/ on current workspace, focus won't be
-- switched.
activateOnCurrentWs :: ManageHook
activateOnCurrentWs = manageFocus (liftQuery activated <&&> newOnCur --> switchFocus)
<+> activateOnCurrent'
activateOnCurrentWs = manageFocus (newOnCur --> switchFocus) <+> activateOnCurrent'

-- | Move activated window to current workspace, but keep focus unchanged.
activateOnCurrentKeepFocus :: ManageHook
activateOnCurrentKeepFocus = manageFocus (liftQuery activated <&&> newOnCur --> keepFocus)
<+> activateOnCurrent'
activateOnCurrentKeepFocus = manageFocus (newOnCur --> keepFocus) <+> activateOnCurrent'
7 changes: 6 additions & 1 deletion XMonad/Hooks/ManageHelpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ module XMonad.Hooks.ManageHelpers (
doSink,
doLower,
doRaise,
doFocus,
Match,
) where

Expand Down Expand Up @@ -274,7 +275,7 @@ doHideIgnore = ask >>= \w -> liftX (hide w) >> doF (W.delete w)

-- | Sinks a window
doSink :: ManageHook
doSink = reader (Endo . W.sink)
doSink = doF . W.sink =<< ask

-- | Lower an unmanaged window. Useful together with 'doIgnore' to lower
-- special windows that for some reason don't do it themselves.
Expand All @@ -285,3 +286,7 @@ doLower = ask >>= \w -> liftX $ withDisplay $ \dpy -> io (lowerWindow dpy w) >>
-- special windows that for some reason don't do it themselves.
doRaise :: ManageHook
doRaise = ask >>= \w -> liftX $ withDisplay $ \dpy -> io (raiseWindow dpy w) >> mempty

-- | Focus a window (useful in 'XMonad.Hooks.EwmhDesktops.setActivateHook').
doFocus :: ManageHook
doFocus = doF . W.focusWindow =<< ask
4 changes: 2 additions & 2 deletions XMonad/Hooks/UrgencyHook.hs
Original file line number Diff line number Diff line change
Expand Up @@ -564,7 +564,7 @@ askUrgent w = withDisplay $ \dpy -> do

-- | Helper for 'ManageHook' that marks the window as urgent (unless
-- suppressed, see 'SuppressWhen'). Useful in
-- 'XMonad.Hooks.EwmhDesktops.activateLogHook' and also in combination with
-- "XMonad.Hooks.InsertPosition", "XMonad.Hooks.Focus".
-- 'XMonad.Hooks.EwmhDesktops.setEwmhActivateHook' and also in combination
-- with "XMonad.Hooks.InsertPosition", "XMonad.Hooks.Focus".
doAskUrgent :: ManageHook
doAskUrgent = ask >>= \w -> liftX (askUrgent w) >> mempty

0 comments on commit de7217f

Please sign in to comment.