mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 20:21:51 -07:00
X.H.EwmhDesktops: Improve interface for hooking window activation
https://github.com/xmonad/xmonad-contrib/pull/192 introduced a breaking change: * `XMonad.Hooks.EwmhDesktops`   `ewmh` function will use `logHook` for handling activated window. And now  by default window activation will do nothing. This breaking change can be avoided if we designed that a bit differently. #192 changed `ewmhDesktopsEventHook` to invoke `logHook` instead of focusing the window that requested activation and now `logHook` is supposed to invoke a `ManageHook` through `activateLogHook` which consults a global `NetActivated` extensible state to tell if it's being invoked from `ewmhDesktopsEventHook`. This seems convoluted to me. A better design, in my opinion, is to invoke the `ManageHook` directly from `ewmhDesktopsEventHook`, and we just need a way to configure the hook. Luckily, we now have `X.U.ExtensibleConf` which makes this straightforward. So we now have a `setEwmhActivateHook`, and the activation hook defaults to focusing the window, undoing the breaking change. Fixes: https://github.com/xmonad/xmonad-contrib/issues/396 Related: https://github.com/xmonad/xmonad-contrib/pull/110 Related: https://github.com/xmonad/xmonad-contrib/pull/192 Related: https://github.com/xmonad/xmonad-contrib/pull/128
This commit is contained in:
@@ -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
|
||||
|
||||
@@ -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 ())
|
||||
@@ -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)
|
||||
|
Reference in New Issue
Block a user