Skip to content

Commit 1040853

Browse files
liskinTheMC47
authored andcommitted
X.H.EwmhDesktops: (wip) activation via activateHook
TODO: documentation in X.H.EwmhDesktops TODO: changelog TODO: adapt X.H.Focus Related: xmonad#396 Related: xmonad#110
1 parent 0adb7c4 commit 1040853

File tree

5 files changed

+21
-82
lines changed

5 files changed

+21
-82
lines changed

CHANGES.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,8 @@
4545
`activateLogHook` to your `logHook`. Also, module `X.H.Focus` provides
4646
additional combinators.
4747

48+
TODO: refactor and update and make it not a breaking change
49+
4850
* All modules still exporting a `defaultFoo` constructor
4951

5052
- All of these were now removed. You can use the re-exported `def` from

XMonad/Config/Desktop.hs

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,6 @@ import XMonad
5858
import XMonad.Hooks.ManageDocks
5959
import XMonad.Hooks.EwmhDesktops
6060
import XMonad.Util.Cursor
61-
import qualified XMonad.StackSet as W
6261

6362
import qualified Data.Map as M
6463

@@ -168,16 +167,9 @@ import qualified Data.Map as M
168167
desktopConfig = docks $ ewmh def
169168
{ startupHook = setDefaultCursor xC_left_ptr <+> startupHook def
170169
, layoutHook = desktopLayoutModifiers $ layoutHook def
171-
, logHook = desktopLogHook <+> logHook def
172170
, keys = desktopKeys <+> keys def }
173171

174172
desktopKeys (XConfig {modMask = modm}) = M.fromList $
175173
[ ((modm, xK_b), sendMessage ToggleStruts) ]
176174

177175
desktopLayoutModifiers layout = avoidStruts layout
178-
179-
-- | 'logHook' preserving old 'ewmh' behavior to switch workspace and focus to
180-
-- activated window.
181-
desktopLogHook :: X ()
182-
desktopLogHook = activateLogHook (reader W.focusWindow >>= doF)
183-

XMonad/Hooks/EwmhDesktops.hs

Lines changed: 7 additions & 70 deletions
Original file line numberDiff line numberDiff line change
@@ -27,9 +27,6 @@ module XMonad.Hooks.EwmhDesktops (
2727
ewmhDesktopsLogHook',
2828
ewmhDesktopsLogHook,
2929
ewmhDesktopsLogHookCustom,
30-
NetActivated (..),
31-
activated,
32-
activateLogHook,
3330
ewmhDesktopsEventHook',
3431
ewmhDesktopsEventHook,
3532
ewmhDesktopsEventHookCustom,
@@ -49,12 +46,12 @@ import XMonad
4946
import Control.Monad
5047
import qualified XMonad.StackSet as W
5148

49+
import XMonad.Hooks.ManageHelpers
5250
import XMonad.Hooks.SetWMName
5351
import qualified XMonad.Util.ExtensibleState as E
5452
import XMonad.Util.XUtils (fi)
5553
import XMonad.Util.WorkspaceCompare
5654
import XMonad.Util.WindowProperties (getProp32)
57-
import qualified XMonad.Util.ExtensibleState as XS
5855

5956
-- $usage
6057
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -70,42 +67,19 @@ import qualified XMonad.Util.ExtensibleState as XS
7067
--
7168
-- You may also be interested in 'docks' from "XMonad.Hooks.ManageDocks".
7269
--
73-
-- __/NOTE:/__ 'ewmh' function will call 'logHook' for handling activated
74-
-- window.
75-
--
76-
-- And now by default window activation will do nothing: neither switch
77-
-- workspace, nor focus. You can use regular 'ManageHook' combinators for
78-
-- changing window activation behavior and then add resulting 'ManageHook'
79-
-- using 'activateLogHook' to your 'logHook'. Also, you may be interested in
80-
-- "XMonad.Hooks.Focus", which provides additional predicates for using in
81-
-- 'ManageHook'.
82-
--
83-
-- To get back old 'ewmh' window activation behavior (switch workspace and
84-
-- focus to activated window) you may use:
85-
--
86-
-- > import XMonad
87-
-- >
88-
-- > import XMonad.Hooks.EwmhDesktops
89-
-- > import qualified XMonad.StackSet as W
90-
-- >
91-
-- > main :: IO ()
92-
-- > main = do
93-
-- > let acMh :: ManageHook
94-
-- > acMh = reader W.focusWindow >>= doF
95-
-- > xcf = ewmh $ def
96-
-- > { modMask = mod4Mask
97-
-- > , logHook = activateLogHook acMh <+> logHook def
98-
-- > }
99-
-- > xmonad xcf
70+
-- TODO: mention "XMonad.Hooks.UrgencyHook"
71+
-- TODO: mention "XMonad.Hooks.Focus"
10072

10173
-- | TODO
10274
data EwmhConfig = EwmhConfig
10375
{ workspaceListTransform :: [WindowSpace] -> [WindowSpace]
76+
, activateHook :: ManageHook
10477
}
10578

10679
instance Default EwmhConfig where
10780
def = EwmhConfig
10881
{ workspaceListTransform = id
82+
, activateHook = doFocus
10983
}
11084

11185
-- | 'ewmh'' with default 'EwmhConfig'.
@@ -238,40 +212,6 @@ ewmhDesktopsEventHook = ewmhDesktopsEventHook' def
238212
ewmhDesktopsEventHookCustom :: ([WindowSpace] -> [WindowSpace]) -> Event -> X All
239213
ewmhDesktopsEventHookCustom f = ewmhDesktopsEventHook' def{ workspaceListTransform = f }
240214

241-
-- | Whether new window _NET_ACTIVE_WINDOW activated or not. I should keep
242-
-- this value in global state, because i use 'logHook' for handling activated
243-
-- windows and i need a way to tell 'logHook' what window is activated.
244-
newtype NetActivated = NetActivated {netActivated :: Maybe Window}
245-
deriving (Show, Typeable)
246-
instance ExtensionClass NetActivated where
247-
initialValue = NetActivated Nothing
248-
249-
-- | Was new window @_NET_ACTIVE_WINDOW@ activated?
250-
activated :: Query Bool
251-
activated = fmap (isJust . netActivated) (liftX XS.get)
252-
253-
-- | Run supplied 'ManageHook' for activated windows /only/. If you want to
254-
-- run this 'ManageHook' for new windows too, add it to 'manageHook'.
255-
--
256-
-- __/NOTE:/__ 'activateLogHook' will work only _once_. I.e. if several
257-
-- 'activateLogHook'-s was used, only first one will actually run (because it
258-
-- resets 'NetActivated' at the end and others won't know, that window is
259-
-- activated).
260-
activateLogHook :: ManageHook -> X ()
261-
activateLogHook mh = XS.get >>= maybe (return ()) go . netActivated
262-
where
263-
go :: Window -> X ()
264-
go w = do
265-
f <- runQuery mh w
266-
-- I should reset 'NetActivated' here, because:
267-
-- * 'windows' calls 'logHook' and i shouldn't go here the second
268-
-- time for one window.
269-
-- * if i reset 'NetActivated' before running 'logHook' once,
270-
-- then 'activated' predicate won't match.
271-
-- Thus, here is the /only/ correct place.
272-
XS.put NetActivated{netActivated = Nothing}
273-
windows (appEndo f)
274-
275215
-- |
276216
-- Intercepts messages from pagers and similar applications and reacts on them.
277217
-- Currently supports:
@@ -284,7 +224,7 @@ activateLogHook mh = XS.get >>= maybe (return ()) go . netActivated
284224
--
285225
-- * _NET_CLOSE_WINDOW (close window)
286226
ewmhDesktopsEventHook' :: EwmhConfig -> Event -> X All
287-
ewmhDesktopsEventHook' EwmhConfig{ workspaceListTransform }
227+
ewmhDesktopsEventHook' EwmhConfig{ workspaceListTransform, activateHook }
288228
ClientMessageEvent{ev_window = w, ev_message_type = mt, ev_data = d}
289229
= withWindowSet $ \s -> do
290230
sort' <- getSortByIndex
@@ -310,10 +250,7 @@ ewmhDesktopsEventHook' EwmhConfig{ workspaceListTransform }
310250
-- when the request comes from a pager, honor it unconditionally
311251
-- https://specifications.freedesktop.org/wm-spec/wm-spec-1.3.html#sourceindication
312252
(2:_) -> windows $ W.focusWindow w
313-
_ -> do
314-
lh <- asks (logHook . config)
315-
XS.put (NetActivated (Just w))
316-
lh
253+
_ -> windows . appEndo =<< runQuery activateHook w
317254
| mt == a_cw ->
318255
killWindow w
319256
| otherwise ->

XMonad/Hooks/Focus.hs

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -56,9 +56,9 @@ module XMonad.Hooks.Focus
5656
-- * Example configurations.
5757
--
5858
-- $examples
59-
, activateSwitchWs
59+
{-, activateSwitchWs
6060
, activateOnCurrentWs
61-
, activateOnCurrentKeepFocus
61+
, activateOnCurrentKeepFocus-}
6262
)
6363
where
6464

@@ -73,7 +73,7 @@ import XMonad
7373
import qualified XMonad.StackSet as W
7474
import qualified XMonad.Util.ExtensibleState as XS
7575
import XMonad.Hooks.ManageHelpers (currentWs)
76-
import XMonad.Hooks.EwmhDesktops (activated)
76+
-- import XMonad.Hooks.EwmhDesktops (activated)
7777

7878

7979
-- $main
@@ -344,6 +344,8 @@ data Focus = Focus
344344
, currentWorkspace :: WorkspaceId
345345
}
346346
deriving (Show)
347+
348+
-- TODO: drop this
347349
instance Default Focus where
348350
def = Focus
349351
{ focusedWindow = Nothing
@@ -555,6 +557,7 @@ when' b mx
555557
-- Exmaple configurations.
556558
-- $examples
557559

560+
{-
558561
-- | Default EWMH window activation behavior: switch to workspace with
559562
-- activated window and switch focus to it.
560563
activateSwitchWs :: ManageHook
@@ -577,4 +580,4 @@ activateOnCurrentWs = manageFocus (liftQuery activated <&&> newOnCur --> switchF
577580
activateOnCurrentKeepFocus :: ManageHook
578581
activateOnCurrentKeepFocus = manageFocus (liftQuery activated <&&> newOnCur --> keepFocus)
579582
<+> activateOnCurrent'
580-
583+
-}

XMonad/Hooks/ManageHelpers.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ module XMonad.Hooks.ManageHelpers (
5555
doSink,
5656
doLower,
5757
doRaise,
58+
doFocus,
5859
Match,
5960
) where
6061

@@ -288,3 +289,7 @@ doLower = ask >>= \w -> liftX $ withDisplay $ \dpy -> io (lowerWindow dpy w) >>
288289
-- special windows that for some reason don't do it themselves.
289290
doRaise :: ManageHook
290291
doRaise = ask >>= \w -> liftX $ withDisplay $ \dpy -> io (raiseWindow dpy w) >> mempty
292+
293+
-- | Focus a window (useful in 'XMonad.Hooks.EwmhDesktops.activateHook')
294+
doFocus :: ManageHook
295+
doFocus = reader (Endo . W.focusWindow)

0 commit comments

Comments
 (0)