Skip to content

Commit a56a930

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 0d0964e commit a56a930

File tree

5 files changed

+21
-81
lines changed

5 files changed

+21
-81
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,
@@ -46,11 +43,11 @@ import XMonad
4643
import XMonad.Prelude
4744
import qualified XMonad.StackSet as W
4845

46+
import XMonad.Hooks.ManageHelpers
4947
import XMonad.Hooks.SetWMName
5048
import qualified XMonad.Util.ExtensibleState as E
5149
import XMonad.Util.WorkspaceCompare
5250
import XMonad.Util.WindowProperties (getProp32)
53-
import qualified XMonad.Util.ExtensibleState as XS
5451

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

9769
-- | TODO
9870
data EwmhConfig = EwmhConfig
9971
{ workspaceListTransform :: [WindowSpace] -> [WindowSpace]
72+
, activateHook :: ManageHook
10073
}
10174

10275
instance Default EwmhConfig where
10376
def = EwmhConfig
10477
{ workspaceListTransform = id
78+
, activateHook = doFocus
10579
}
10680

10781
-- | 'ewmh'' with default 'EwmhConfig'.
@@ -234,40 +208,6 @@ ewmhDesktopsEventHook = ewmhDesktopsEventHook' def
234208
ewmhDesktopsEventHookCustom :: ([WindowSpace] -> [WindowSpace]) -> Event -> X All
235209
ewmhDesktopsEventHookCustom f = ewmhDesktopsEventHook' def{ workspaceListTransform = f }
236210

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

XMonad/Hooks/Focus.hs

Lines changed: 7 additions & 3 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

@@ -70,7 +70,7 @@ import XMonad.Prelude
7070
import qualified XMonad.StackSet as W
7171
import qualified XMonad.Util.ExtensibleState as XS
7272
import XMonad.Hooks.ManageHelpers (currentWs)
73-
import XMonad.Hooks.EwmhDesktops (activated)
73+
-- import XMonad.Hooks.EwmhDesktops (activated)
7474

7575

7676
-- $main
@@ -341,6 +341,8 @@ data Focus = Focus
341341
, currentWorkspace :: WorkspaceId
342342
}
343343
deriving (Show)
344+
345+
-- TODO: drop this
344346
instance Default Focus where
345347
def = Focus
346348
{ focusedWindow = Nothing
@@ -552,6 +554,7 @@ when' b mx
552554
-- Exmaple configurations.
553555
-- $examples
554556

557+
{-
555558
-- | Default EWMH window activation behavior: switch to workspace with
556559
-- activated window and switch focus to it.
557560
activateSwitchWs :: ManageHook
@@ -574,3 +577,4 @@ activateOnCurrentWs = manageFocus (liftQuery activated <&&> newOnCur --> switchF
574577
activateOnCurrentKeepFocus :: ManageHook
575578
activateOnCurrentKeepFocus = manageFocus (liftQuery activated <&&> newOnCur --> keepFocus)
576579
<+> activateOnCurrent'
580+
-}

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

@@ -284,3 +285,7 @@ doLower = ask >>= \w -> liftX $ withDisplay $ \dpy -> io (lowerWindow dpy w) >>
284285
-- special windows that for some reason don't do it themselves.
285286
doRaise :: ManageHook
286287
doRaise = ask >>= \w -> liftX $ withDisplay $ \dpy -> io (raiseWindow dpy w) >> mempty
288+
289+
-- | Focus a window (useful in 'XMonad.Hooks.EwmhDesktops.activateHook')
290+
doFocus :: ManageHook
291+
doFocus = reader (Endo . W.focusWindow)

0 commit comments

Comments
 (0)