Skip to content

Commit

Permalink
X.H.EwmhDesktops: (wip) activation via activateHook
Browse files Browse the repository at this point in the history
TODO: documentation in X.H.EwmhDesktops
TODO: adapt X.H.Focus
TODO: alternatively just set urgency?

Related: xmonad#396
Related: xmonad#110
  • Loading branch information
liskin committed Nov 5, 2020
1 parent bfdcf7a commit 107ebc5
Show file tree
Hide file tree
Showing 4 changed files with 16 additions and 82 deletions.
8 changes: 0 additions & 8 deletions XMonad/Config/Desktop.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,6 @@ import XMonad
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.EwmhDesktops
import XMonad.Util.Cursor
import qualified XMonad.StackSet as W

import qualified Data.Map as M

Expand Down Expand Up @@ -168,16 +167,9 @@ import qualified Data.Map as M
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 {modMask = modm}) = M.fromList $
[ ((modm, xK_b), sendMessage ToggleStruts) ]

desktopLayoutModifiers layout = avoidStruts layout

-- | 'logHook' preserving old 'ewmh' behavior to switch workspace and focus to
-- activated window.
desktopLogHook :: X ()
desktopLogHook = activateLogHook (reader W.focusWindow >>= doF)

76 changes: 6 additions & 70 deletions XMonad/Hooks/EwmhDesktops.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,9 +27,6 @@ module XMonad.Hooks.EwmhDesktops (
ewmhDesktopsLogHook',
ewmhDesktopsLogHook,
ewmhDesktopsLogHookCustom,
NetActivated (..),
activated,
activateLogHook,
ewmhDesktopsEventHook',
ewmhDesktopsEventHook,
ewmhDesktopsEventHookCustom,
Expand All @@ -48,12 +45,12 @@ import XMonad
import Control.Monad
import qualified XMonad.StackSet as W

import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.SetWMName
import qualified XMonad.Util.ExtensibleState as E
import XMonad.Util.XUtils (fi)
import XMonad.Util.WorkspaceCompare
import XMonad.Util.WindowProperties (getProp32)
import qualified XMonad.Util.ExtensibleState as XS

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
Expand All @@ -69,42 +66,18 @@ import qualified XMonad.Util.ExtensibleState as XS
--
-- You may also be interested in 'docks' from "XMonad.Hooks.ManageDocks".
--
-- __/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
-- TODO: mention "XMonad.Hooks.Focus"

-- | TODO
data EwmhConfig = EwmhConfig
{ workspaceListTransform :: [WindowSpace] -> [WindowSpace]
, activateHook :: ManageHook
}

instance Default EwmhConfig where
def = EwmhConfig
{ workspaceListTransform = id
, activateHook = doFocus
}

-- | 'ewmh'' with default 'EwmhConfig'.
Expand Down Expand Up @@ -237,40 +210,6 @@ ewmhDesktopsEventHook = ewmhDesktopsEventHook' def
ewmhDesktopsEventHookCustom :: ([WindowSpace] -> [WindowSpace]) -> Event -> X All
ewmhDesktopsEventHookCustom f = ewmhDesktopsEventHook' def{ workspaceListTransform = f }

-- | 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, Typeable)
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)

-- |
-- Intercepts messages from pagers and similar applications and reacts on them.
-- Currently supports:
Expand All @@ -283,7 +222,7 @@ activateLogHook mh = XS.get >>= maybe (return ()) go . netActivated
--
-- * _NET_CLOSE_WINDOW (close window)
ewmhDesktopsEventHook' :: EwmhConfig -> Event -> X All
ewmhDesktopsEventHook' EwmhConfig{ workspaceListTransform }
ewmhDesktopsEventHook' EwmhConfig{ workspaceListTransform, activateHook }
ClientMessageEvent{ev_window = w, ev_message_type = mt, ev_data = d}
= withWindowSet $ \s -> do
sort' <- getSortByIndex
Expand All @@ -309,10 +248,7 @@ ewmhDesktopsEventHook' EwmhConfig{ workspaceListTransform }
-- when the request comes from a pager, honor it unconditionally
-- https://specifications.freedesktop.org/wm-spec/wm-spec-1.3.html#sourceindication
(2:_) -> windows $ W.focusWindow w
_ -> do
lh <- asks (logHook . config)
XS.put (NetActivated (Just w))
lh
_ -> windows . appEndo =<< runQuery activateHook w
| mt == a_cw ->
killWindow w
| otherwise ->
Expand Down
9 changes: 5 additions & 4 deletions XMonad/Hooks/Focus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,9 +56,9 @@ module XMonad.Hooks.Focus
-- * Example configurations.
--
-- $examples
, activateSwitchWs
{-, activateSwitchWs
, activateOnCurrentWs
, activateOnCurrentKeepFocus
, activateOnCurrentKeepFocus-}
)
where

Expand All @@ -74,7 +74,7 @@ import XMonad
import qualified XMonad.StackSet as W
import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Hooks.ManageHelpers (currentWs)
import XMonad.Hooks.EwmhDesktops (activated, NetActivated(..))
-- import XMonad.Hooks.EwmhDesktops (activated, NetActivated(..))


-- $main
Expand Down Expand Up @@ -556,6 +556,7 @@ when' b mx
-- Exmaple configurations.
-- $examples

{-
-- | Default EWMH window activation behavior: switch to workspace with
-- activated window and switch focus to it.
activateSwitchWs :: ManageHook
Expand All @@ -578,4 +579,4 @@ activateOnCurrentWs = manageFocus (liftQuery activated <&&> newOnCur --> switchF
activateOnCurrentKeepFocus :: ManageHook
activateOnCurrentKeepFocus = manageFocus (liftQuery activated <&&> newOnCur --> keepFocus)
<+> activateOnCurrent'

-}
5 changes: 5 additions & 0 deletions XMonad/Hooks/ManageHelpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ module XMonad.Hooks.ManageHelpers (
doFloatDep,
doHideIgnore,
doSink,
doFocus,
Match,
) where

Expand Down Expand Up @@ -231,3 +232,7 @@ doHideIgnore = ask >>= \w -> liftX (hide w) >> doF (W.delete w)
-- | Sinks a window
doSink :: ManageHook
doSink = reader (Endo . W.sink)

-- | Focus a window (useful in 'XMonad.Hooks.EwmhDesktops.activateHook')
doFocus :: ManageHook
doFocus = reader (Endo . W.focusWindow)

0 comments on commit 107ebc5

Please sign in to comment.