Skip to content

Commit 700507f

Browse files
authored
Merge pull request #886 from liskin/steam-fixes
Fixes/workarounds for Steam client menus/flickering
2 parents 8efff53 + ca5e70f commit 700507f

File tree

5 files changed

+162
-10
lines changed

5 files changed

+162
-10
lines changed

Diff for: CHANGES.md

+23-7
Original file line numberDiff line numberDiff line change
@@ -7,11 +7,11 @@
77
* `XMonad.Hooks.StatusBars`
88

99
- Move status bar functions from the `IO` to the `X` monad to
10-
allow them to look up information from `X`, like the screen
11-
width. Existing configurations may need to use `io` from
12-
`XMonad.Core` or `liftIO` from `Control.Monad.IO.Class` in
13-
order to lift any existing `IO StatusBarConfig` values into
14-
`X StatusBarConfig` values.
10+
allow them to look up information from `X`, like the screen
11+
width. Existing configurations may need to use `io` from
12+
`XMonad.Core` or `liftIO` from `Control.Monad.IO.Class` in
13+
order to lift any existing `IO StatusBarConfig` values into
14+
`X StatusBarConfig` values.
1515

1616
* `XMonad.Prompt`
1717

@@ -22,10 +22,17 @@
2222

2323
### New Modules
2424

25-
* `XMonad.Actions.Profiles`.
25+
* `XMonad.Actions.Profiles`
2626

2727
- Group workspaces by similarity. Useful when one has lots
28-
of workspaces and uses only a couple per unit of work.
28+
of workspaces and uses only a couple per unit of work.
29+
30+
* `XMonad.Hooks.FloatConfigureReq`
31+
32+
- Customize handling of floating windows' move/resize/restack requests
33+
(ConfigureRequest). Useful as a workaround for some misbehaving client
34+
applications (Steam, rxvt-unicode, anything that tries to restore
35+
absolute position of floats).
2936

3037
### Bug Fixes and Minor Changes
3138

@@ -49,6 +56,15 @@
4956
- The history file is not extraneously read and written anymore if
5057
the `historySize` is set to 0.
5158

59+
* `XMonad.Hooks.EwmhDesktops`
60+
61+
- Requests for unmanaged windows no longer cause a refresh. This avoids
62+
flicker and also fixes disappearing menus in the Steam client and
63+
possibly a few other client applications.
64+
65+
(See also `XMonad.Hooks.FloatConfigureReq` and/or `XMonad.Util.Hacks`
66+
for additional Steam client workarounds.)
67+
5268
### Other changes
5369

5470
## 0.18.0 (February 3, 2024)

Diff for: XMonad/Hooks/EwmhDesktops.hs

+8-3
Original file line numberDiff line numberDiff line change
@@ -459,7 +459,14 @@ ewmhDesktopsEventHook'
459459
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
460460
a_cw <- getAtom "_NET_CLOSE_WINDOW"
461461

462-
if | mt == a_cd, n : _ <- d, Just ww <- ws !? fi n ->
462+
if | mt == a_cw ->
463+
killWindow w
464+
| not (w `W.member` s) ->
465+
-- do nothing for unmanaged windows; it'd be just a useless
466+
-- refresh which breaks menus/popups of misbehaving apps that
467+
-- send _NET_ACTIVE_WINDOW requests for override-redirect wins
468+
mempty
469+
| mt == a_cd, n : _ <- d, Just ww <- ws !? fi n ->
463470
if W.currentTag s == W.tag ww then mempty else windows $ W.view (W.tag ww)
464471
| mt == a_cd ->
465472
trace $ "Bad _NET_CURRENT_DESKTOP with data=" ++ show d
@@ -473,8 +480,6 @@ ewmhDesktopsEventHook'
473480
if W.peek s == Just w then mempty else windows $ W.focusWindow w
474481
| mt == a_aw -> do
475482
if W.peek s == Just w then mempty else windows . appEndo =<< runQuery activateHook w
476-
| mt == a_cw ->
477-
killWindow w
478483
| otherwise ->
479484
-- The Message is unknown to us, but that is ok, not all are meant
480485
-- to be handled by the window manager

Diff for: XMonad/Hooks/FloatConfigureReq.hs

+126
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,126 @@
1+
{-# LANGUAGE LambdaCase #-}
2+
-- |
3+
-- Module : XMonad.Hooks.FloatConfigureReq
4+
-- Description : Customize handling of floating windows' move\/resize\/restack requests (ConfigureRequest).
5+
-- Copyright : (c) 2024 Tomáš Janoušek <[email protected]>
6+
-- License : BSD3
7+
-- Maintainer : Tomáš Janoušek <[email protected]>
8+
--
9+
-- xmonad normally honours those requests by doing exactly what the client
10+
-- application asked, and refreshing. There are some misbehaving clients,
11+
-- however, that:
12+
--
13+
-- * try to move their window to the last known absolute position regardless
14+
-- of the current xrandr/xinerama layout
15+
--
16+
-- * move their window to 0, 0 for no particular reason (e.g. rxvt-unicode)
17+
--
18+
-- * issue lots of no-op requests causing flickering (e.g. Steam)
19+
--
20+
-- This module provides a replacement handler for 'ConfigureRequestEvent' to
21+
-- work around such misbehaviours.
22+
--
23+
module XMonad.Hooks.FloatConfigureReq (
24+
-- * Usage
25+
-- $usage
26+
MaybeMaybeManageHook,
27+
floatConfReqHook,
28+
29+
-- * Known workarounds
30+
fixSteamFlicker,
31+
fixSteamFlickerMMMH,
32+
) where
33+
34+
import qualified Data.Map.Strict as M
35+
import XMonad
36+
import XMonad.Hooks.ManageHelpers
37+
import XMonad.Prelude
38+
import qualified XMonad.StackSet as W
39+
40+
-- $usage
41+
-- To use this, include the following in your @xmonad.hs@:
42+
--
43+
-- > import XMonad.Hooks.FloatConfigureReq
44+
-- > import XMonad.Hooks.ManageHelpers
45+
--
46+
-- > myFloatConfReqHook :: MaybeMaybeManageHook
47+
-- > myFloatConfReqHook = composeAll
48+
-- > [ … ]
49+
--
50+
-- > myEventHook :: Event -> X All
51+
-- > myEventHook = mconcat
52+
-- > [ …
53+
-- > , floatConfReqHook myFloatConfReqHook
54+
-- > , … ]
55+
--
56+
-- > main = xmonad $ …
57+
-- > $ def{ handleEventHook = myEventHook
58+
-- > , … }
59+
--
60+
-- Then fill the @myFloatConfReqHook@ with whatever custom rules you need.
61+
--
62+
-- As an example, the following will prevent rxvt-unicode from moving its
63+
-- (floating) window to 0, 0 after a font change but still ensure its size
64+
-- increment hints are respected:
65+
--
66+
-- > className =? "URxvt" -?> pure <$> doFloat
67+
--
68+
-- Another example that avoids flickering and xmonad slowdowns caused by the
69+
-- Steam client (completely ignore all its requests, none of which are
70+
-- meaningful in the context of a tiling WM):
71+
--
72+
-- > map toLower `fmap` className =? "steam" -?> mempty
73+
--
74+
-- (this example is also available as 'fixSteamFlickerMMMH' to be added to
75+
-- one's @myFloatConfReqHook@ and also 'fixSteamFlicker' to be added directly
76+
-- to one's 'handleEventHook')
77+
78+
-- | A variant of 'MaybeManageHook' that additionally may or may not make
79+
-- changes to the 'WindowSet'.
80+
type MaybeMaybeManageHook = Query (Maybe (Maybe (Endo WindowSet)))
81+
82+
-- | Customizable handler for a 'ConfigureRequestEvent'. If the event's
83+
-- 'ev_window' is a managed floating window, the provided
84+
-- 'MaybeMaybeManageHook' is consulted and its result interpreted as follows:
85+
--
86+
-- * @Nothing@ - no match, fall back to the default handler
87+
--
88+
-- * @Just Nothing@ - match but ignore, no refresh, just send ConfigureNotify
89+
--
90+
-- * @Just (Just a)@ - match, modify 'WindowSet', refresh, send ConfigureNotify
91+
floatConfReqHook :: MaybeMaybeManageHook -> Event -> X All
92+
floatConfReqHook mh ConfigureRequestEvent{ev_window = w} =
93+
runQuery (join <$> (isFloatQ -?> mh)) w >>= \case
94+
Nothing -> mempty
95+
Just e -> do
96+
whenJust e (windows . appEndo)
97+
sendConfEvent
98+
pure (All False)
99+
where
100+
sendConfEvent = withDisplay $ \dpy ->
101+
withWindowAttributes dpy w $ \wa -> do
102+
io . allocaXEvent $ \ev -> do
103+
-- We may have made no changes to the window size/position
104+
-- and thus the X server didn't emit any ConfigureNotify,
105+
-- so we need to send the ConfigureNotify ourselves to make
106+
-- sure there is a reply to this ConfigureRequestEvent and the
107+
-- window knows we (possibly) ignored its request.
108+
setEventType ev configureNotify
109+
setConfigureEvent ev w w
110+
(wa_x wa) (wa_y wa) (wa_width wa)
111+
(wa_height wa) (wa_border_width wa) none (wa_override_redirect wa)
112+
sendEvent dpy w False 0 ev
113+
floatConfReqHook _ _ = mempty
114+
115+
-- | A 'Query' to determine if a window is floating.
116+
isFloatQ :: Query Bool
117+
isFloatQ = ask >>= \w -> liftX . gets $ M.member w . W.floating . windowset
118+
119+
-- | A pre-packaged 'floatConfReqHook' that fixes flickering of the Steam client by ignoring 'ConfigureRequestEvent's on any of its floating windows.
120+
--
121+
-- To use this, add 'fixSteamFlicker' to your 'handleEventHook'.
122+
fixSteamFlicker :: Event -> X All
123+
fixSteamFlicker = floatConfReqHook fixSteamFlickerMMMH
124+
125+
fixSteamFlickerMMMH :: MaybeMaybeManageHook
126+
fixSteamFlickerMMMH = map toLower `fmap` className =? "steam" -?> mempty

Diff for: XMonad/Util/Hacks.hs

+4
Original file line numberDiff line numberDiff line change
@@ -40,10 +40,14 @@ module XMonad.Util.Hacks (
4040
trayerPaddingXmobarEventHook,
4141
trayPaddingXmobarEventHook,
4242
trayPaddingEventHook,
43+
44+
-- * Steam flickering fix
45+
fixSteamFlicker,
4346
) where
4447

4548

4649
import XMonad
50+
import XMonad.Hooks.FloatConfigureReq (fixSteamFlicker)
4751
import XMonad.Hooks.StatusBar (xmonadPropLog')
4852
import XMonad.Prelude (All (All), fi, filterM, when)
4953
import System.Posix.Env (putEnv)

Diff for: xmonad-contrib.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -192,6 +192,7 @@ library
192192
XMonad.Hooks.EwmhDesktops
193193
XMonad.Hooks.FadeInactive
194194
XMonad.Hooks.FadeWindows
195+
XMonad.Hooks.FloatConfigureReq
195196
XMonad.Hooks.FloatNext
196197
XMonad.Hooks.Focus
197198
XMonad.Hooks.InsertPosition

0 commit comments

Comments
 (0)