Skip to content

Commit c5032a4

Browse files
authored
Merge pull request #911 from liskin/rescreen
X.H.Rescreen, X.A.PhysicalScreens: Add facilities to avoid (some) workspace reshuffling
2 parents 1c5261d + 61f8b4a commit c5032a4

File tree

3 files changed

+120
-22
lines changed

3 files changed

+120
-22
lines changed

CHANGES.md

+21-12
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,19 @@
1111
would be deleted when switching to a dynamic project.
1212
- Improved documentation on how to close a project.
1313

14+
* `XMonad.Hooks.Rescreen`
15+
16+
- Allow overriding the `rescreen` operation itself. Additionally, the
17+
`XMonad.Actions.PhysicalScreens` module now provides an alternative
18+
implementation of `rescreen` that avoids reshuffling the workspaces if
19+
the number of screens doesn't change and only their locations do (which
20+
is especially common if one uses `xrandr --setmonitor` to split an
21+
ultra-wide display in two).
22+
23+
- Added an optional delay when waiting for events to settle. This may be
24+
used to avoid flicker and unnecessary workspace reshuffling if multiple
25+
`xrandr` commands are used to reconfigure the display layout.
26+
1427
## 0.18.1 (August 20, 2024)
1528

1629
### Breaking Changes
@@ -430,7 +443,8 @@
430443
* `XMonad.Config.{Arossato,Dmwit,Droundy,Monad,Prime,Saegesser,Sjanssen}`
431444

432445
- Deprecated all of these modules. The user-specific configuration
433-
modules may still be found [on the website].
446+
modules may still be found [on the
447+
website](https://xmonad.org/configurations.html)
434448

435449
* `XMonad.Util.NamedScratchpad`
436450

@@ -451,8 +465,6 @@
451465
- Deprecated `urgencyConfig`; use `def` from the new `Default`
452466
instance of `UrgencyConfig` instead.
453467

454-
[on the website]: https://xmonad.org/configurations.html
455-
456468
### New Modules
457469

458470
* `XMonad.Actions.PerLayoutKeys`
@@ -527,7 +539,8 @@
527539
`todo +d 12 02 2024` work.
528540

529541
- Added the ability to specify alphabetic (`#A`, `#B`, and `#C`)
530-
[priorities] at the end of the input note.
542+
[priorities](https://orgmode.org/manual/Priorities.html) at the end of
543+
the input note.
531544

532545
* `XMonad.Prompt.Unicode`
533546

@@ -621,7 +634,8 @@
621634

622635
- Modified `mkAbsolutePath` to support a leading environment variable, so
623636
things like `$HOME/NOTES` work. If you want more general environment
624-
variable support, comment on [this PR].
637+
variable support, comment on [this
638+
PR](https://github.com/xmonad/xmonad-contrib/pull/744)
625639

626640
* `XMonad.Util.XUtils`
627641

@@ -660,9 +674,6 @@
660674

661675
- Added a `Default` instance for `UrgencyConfig` and `DzenUrgencyHook`.
662676

663-
[this PR]: https://github.com/xmonad/xmonad-contrib/pull/744
664-
[priorities]: https://orgmode.org/manual/Priorities.html
665-
666677
### Other changes
667678

668679
* Migrated the sample build scripts from the deprecated `xmonad-testing` repo to
@@ -2188,8 +2199,8 @@
21882199

21892200
* `XMonad.Prompt.Pass`
21902201

2191-
This module provides 3 `XMonad.Prompt`s to ease passwords
2192-
manipulation (generate, read, remove) via [pass][].
2202+
This module provides 3 `XMonad.Prompt`s to ease passwords manipulation
2203+
(generate, read, remove) via [pass](http://www.passwordstore.org/).
21932204

21942205
* `XMonad.Util.RemoteWindows`
21952206

@@ -2265,5 +2276,3 @@
22652276
## See Also
22662277

22672278
<https://wiki.haskell.org/Xmonad/Notable_changes_since_0.8>
2268-
2269-
[pass]: http://www.passwordstore.org/

XMonad/Actions/PhysicalScreens.hs

+57-2
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
11
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2+
{-# LANGUAGE LambdaCase #-}
3+
{-# LANGUAGE ParallelListComp #-}
24
-----------------------------------------------------------------------------
35
-- |
46
-- Module : XMonad.Actions.PhysicalScreens
@@ -28,10 +30,13 @@ module XMonad.Actions.PhysicalScreens (
2830
, getScreenIdAndRectangle
2931
, screenComparatorById
3032
, screenComparatorByRectangle
33+
, rescreen
3134
) where
3235

33-
import XMonad
34-
import XMonad.Prelude (elemIndex, fromMaybe, on, sortBy)
36+
import Data.List.NonEmpty (nonEmpty)
37+
import XMonad hiding (rescreen)
38+
import XMonad.Prelude (elemIndex, fromMaybe, on, sortBy, NonEmpty((:|)))
39+
import qualified Data.List.NonEmpty as NE
3540
import qualified XMonad.StackSet as W
3641

3742
{- $usage
@@ -146,3 +151,53 @@ onNextNeighbour sc = neighbourWindows sc 1
146151
-- | Apply operation on a WindowSet with the WorkspaceId of the previous screen in the physical order as parameter.
147152
onPrevNeighbour :: ScreenComparator -> (WorkspaceId -> WindowSet -> WindowSet) -> X ()
148153
onPrevNeighbour sc = neighbourWindows sc (-1)
154+
155+
-- | An alternative to 'XMonad.Operations.rescreen' that avoids reshuffling
156+
-- the workspaces if the number of screens doesn't change and only their
157+
-- locations do. Useful for users of @xrandr --setmonitor@.
158+
--
159+
-- See 'XMonad.Hooks.Rescreen.setRescreenWorkspacesHook', which lets you
160+
-- replace the builtin rescreen handler.
161+
rescreen :: ScreenComparator -> X ()
162+
rescreen (ScreenComparator cmpScreen) = withDisplay (fmap nonEmpty . getCleanedScreenInfo) >>= \case
163+
Nothing -> trace "getCleanedScreenInfo returned []"
164+
Just xinescs -> windows $ rescreen' xinescs
165+
where
166+
rescreen' :: NonEmpty Rectangle -> WindowSet -> WindowSet
167+
rescreen' xinescs ws
168+
| NE.length xinescs == length (W.visible ws) + 1 = rescreenSameLength xinescs ws
169+
| otherwise = rescreenCore xinescs ws
170+
171+
-- the 'XMonad.Operations.rescreen' implementation from core as a fallback
172+
rescreenCore :: NonEmpty Rectangle -> WindowSet -> WindowSet
173+
rescreenCore (xinesc :| xinescs) ws@W.StackSet{ W.current = v, W.visible = vs, W.hidden = hs } =
174+
let (xs, ys) = splitAt (length xinescs) (map W.workspace vs ++ hs)
175+
a = W.Screen (W.workspace v) 0 (SD xinesc)
176+
as = zipWith3 W.Screen xs [1..] $ map SD xinescs
177+
in ws{ W.current = a
178+
, W.visible = as
179+
, W.hidden = ys }
180+
181+
-- sort both existing screens and the screens we just got from xinerama
182+
-- using cmpScreen, and then replace the rectangles in the WindowSet,
183+
-- keeping the order of current/visible workspaces intact
184+
rescreenSameLength :: NonEmpty Rectangle -> WindowSet -> WindowSet
185+
rescreenSameLength xinescs ws =
186+
ws{ W.current = (W.current ws){ W.screenDetail = SD newCurrentRect }
187+
, W.visible = [ w{ W.screenDetail = SD r } | w <- W.visible ws | r <- newVisibleRects ]
188+
}
189+
where
190+
undoSort =
191+
NE.map fst $
192+
NE.sortBy (cmpScreen `on` (getScreenIdAndRectangle . snd)) $
193+
NE.zip ((0 :: Int) :| [1..]) $ -- add indices to undo the sort later
194+
W.current ws :| W.visible ws
195+
newCurrentRect :| newVisibleRects =
196+
NE.map snd $ NE.sortWith fst $ NE.zip undoSort $ -- sort back into current:visible order
197+
NE.map snd $ NE.sortBy cmpScreen $ NE.zip (0 :| [1..]) xinescs
198+
199+
-- TODO:
200+
-- If number of screens before and after isn't the same, we might still
201+
-- try to match locations and avoid changing the workspace for those that
202+
-- didn't move, while making sure that the current workspace is still
203+
-- visible somewhere.

XMonad/Hooks/Rescreen.hs

+42-8
Original file line numberDiff line numberDiff line change
@@ -15,10 +15,13 @@ module XMonad.Hooks.Rescreen (
1515
-- $usage
1616
addAfterRescreenHook,
1717
addRandrChangeHook,
18+
setRescreenWorkspacesHook,
19+
setRescreenDelay,
1820
RescreenConfig(..),
1921
rescreenHook,
2022
) where
2123

24+
import Control.Concurrent (threadDelay)
2225
import Graphics.X11.Xrandr
2326
import XMonad
2427
import XMonad.Prelude
@@ -59,16 +62,21 @@ import qualified XMonad.Util.ExtensibleConf as XC
5962
data RescreenConfig = RescreenConfig
6063
{ afterRescreenHook :: X () -- ^ hook to invoke after 'rescreen'
6164
, randrChangeHook :: X () -- ^ hook for other randr changes, e.g. (dis)connects
65+
, rescreenWorkspacesHook :: Last (X ()) -- ^ hook to invoke instead of 'rescreen'
66+
, rescreenDelay :: Last Int -- ^ delay (in microseconds) to wait for events to settle
6267
}
6368

6469
instance Default RescreenConfig where
6570
def = RescreenConfig
6671
{ afterRescreenHook = mempty
6772
, randrChangeHook = mempty
73+
, rescreenWorkspacesHook = mempty
74+
, rescreenDelay = mempty
6875
}
6976

7077
instance Semigroup RescreenConfig where
71-
RescreenConfig arh rch <> RescreenConfig arh' rch' = RescreenConfig (arh <> arh') (rch <> rch')
78+
RescreenConfig arh rch rwh rd <> RescreenConfig arh' rch' rwh' rd' =
79+
RescreenConfig (arh <> arh') (rch <> rch') (rwh <> rwh') (rd <> rd')
7280

7381
instance Monoid RescreenConfig where
7482
mempty = def
@@ -89,20 +97,45 @@ instance Monoid RescreenConfig where
8997
-- 'randrChangeHook' may be used to automatically trigger xrandr (or perhaps
9098
-- autorandr) when outputs are (dis)connected.
9199
--
100+
-- 'rescreenWorkspacesHook' allows tweaking the 'rescreen' implementation,
101+
-- to change the order workspaces are assigned to physical screens for
102+
-- example.
103+
--
104+
-- 'rescreenDelay' makes xmonad wait a bit for events to settle (after the
105+
-- first event is received) — useful when multiple @xrandr@ invocations are
106+
-- being used to change the screen layout.
107+
--
92108
-- Note that 'rescreenHook' is safe to use several times, 'rescreen' is still
93-
-- done just once and hooks are invoked in sequence, also just once.
109+
-- done just once and hooks are invoked in sequence (except
110+
-- 'rescreenWorkspacesHook', which has a replace rather than sequence
111+
-- semantics), also just once.
94112
rescreenHook :: RescreenConfig -> XConfig l -> XConfig l
95-
rescreenHook = XC.once $ \c -> c
96-
{ startupHook = startupHook c <> rescreenStartupHook
97-
, handleEventHook = handleEventHook c <> rescreenEventHook }
113+
rescreenHook = XC.once hook . catchUserCode
114+
where
115+
hook c = c
116+
{ startupHook = startupHook c <> rescreenStartupHook
117+
, handleEventHook = handleEventHook c <> rescreenEventHook }
118+
catchUserCode rc@RescreenConfig{..} = rc
119+
{ afterRescreenHook = userCodeDef () afterRescreenHook
120+
, randrChangeHook = userCodeDef () randrChangeHook
121+
, rescreenWorkspacesHook = flip catchX rescreen <$> rescreenWorkspacesHook
122+
}
98123

99124
-- | Shortcut for 'rescreenHook'.
100125
addAfterRescreenHook :: X () -> XConfig l -> XConfig l
101-
addAfterRescreenHook h = rescreenHook def{ afterRescreenHook = userCodeDef () h }
126+
addAfterRescreenHook h = rescreenHook def{ afterRescreenHook = h }
102127

103128
-- | Shortcut for 'rescreenHook'.
104129
addRandrChangeHook :: X () -> XConfig l -> XConfig l
105-
addRandrChangeHook h = rescreenHook def{ randrChangeHook = userCodeDef () h }
130+
addRandrChangeHook h = rescreenHook def{ randrChangeHook = h }
131+
132+
-- | Shortcut for 'rescreenHook'.
133+
setRescreenWorkspacesHook :: X () -> XConfig l -> XConfig l
134+
setRescreenWorkspacesHook h = rescreenHook def{ rescreenWorkspacesHook = pure h }
135+
136+
-- | Shortcut for 'rescreenHook'.
137+
setRescreenDelay :: Int -> XConfig l -> XConfig l
138+
setRescreenDelay d = rescreenHook def{ rescreenDelay = pure d }
106139

107140
-- | Startup hook to listen for @RRScreenChangeNotify@ events.
108141
rescreenStartupHook :: X ()
@@ -126,13 +159,14 @@ handleEvent :: Event -> X ()
126159
handleEvent e = XC.with $ \RescreenConfig{..} -> do
127160
-- Xorg emits several events after every change, clear them to prevent
128161
-- triggering the hook multiple times.
162+
whenJust (getLast rescreenDelay) (io . threadDelay)
129163
moreConfigureEvents <- clearTypedWindowEvents (ev_window e) configureNotify
130164
_ <- clearTypedWindowRREvents (ev_window e) rrScreenChangeNotify
131165
-- If there were any ConfigureEvents, this is an actual screen
132166
-- configuration change, so rescreen and fire rescreenHook. Otherwise,
133167
-- this is just a connect/disconnect, fire randrChangeHook.
134168
if ev_event_type e == configureNotify || moreConfigureEvents
135-
then rescreen >> afterRescreenHook
169+
then fromMaybe rescreen (getLast rescreenWorkspacesHook) >> afterRescreenHook
136170
else randrChangeHook
137171

138172
-- | Remove all X events of a given window and type from the event queue,

0 commit comments

Comments
 (0)