X.L.NoBorders: Fix float handling on multihead setups

Before c6cdb77e3b, handling of floats was
trivial (too trivial, and thus inefficient and flickery): any float
whose rectangle covered (RationalRect 0 0 1 1), regardless of what
screen or workspace it belonged to, got its borders hidden.

Then c6cdb77e3b added some nuance
(OnlyLayoutFloatBelow, OnlyLayoutFloat, OnlyScreenFloat) which requires
looking at floats in the context of individual screens. Unfortunately
the implementation only worked in singlehead setups, as it always used
only the active screen/workspace regardless of which screen/workspace
was currently being layouted. This resulted in the new functionality not
working correctly on inactive screens and also regressed the handling of
fullscreen floats on inactive screens.

The fix is conceptually easy: use the screen that is being layouted.

There is a catch, unfortunately: this code runs in redoLayout, but the
information we need is only available in modifyLayout and
modifyLayoutWithUpdate. I could store a screen id in the
ConfigurableBorder record in modifyLayoutWithUpdate and use it later in
redoLayout, but that'd be a massive hack, so what I do instead is to
find the relevant screen by searching for one that covers the `lr`
(layout/screen rectangle). In most setups, this should be reliable. If
it turns out it is not, we can fix this later.

Fixes: c6cdb77e3b ("'XMonad.Layout.NoBorders': various improvements:")
Fixes: https://github.com/xmonad/xmonad-contrib/issues/280
This commit is contained in:
Tomas Janousek
2021-01-01 23:21:40 +01:00
parent a98cc194ad
commit 9cff824a24
2 changed files with 20 additions and 7 deletions

View File

@@ -246,23 +246,31 @@ instance SetsAmbiguous Ambiguity where
$ W.screenDetail scr
]
-- Find the screen containing the workspace being layouted.
-- (This is a list only to avoid the need to specialcase when it
-- can't be found or when several contain @lr@. When that happens,
-- the result will probably be incorrect.)
thisScreen = [ scr | scr <- W.screens wset
, screenRect (W.screenDetail scr) `R.supersetOf` lr ]
-- This originally considered all floating windows across all
-- workspaces. It seems more efficient to have each layout manage
-- its own floating windows - and equally valid though untested
-- against a multihead setup. In some cases the previous code would
-- redundantly add then remove borders from already-borderless
-- windows.
-- workspaces. It seems more efficient to have each screen manage
-- its own floating windows - and necessary to support the
-- additional OnlyLayoutFloat* variants correctly in multihead
-- setups. In some cases the previous code would redundantly add
-- then remove borders from already-borderless windows.
floating = do
scr <- thisScreen
let wz :: Integer -> (Window,Rectangle)
-> (Integer,Window,Rectangle)
wz i (w,wr) = (i,w,wr)
-- For the following: in stacking order lowest -> highest.
ts = reverse . zipWith wz [-1,-2..] $ wrs
fs = zipWith wz [0..] $ do
w <- reverse . W.index $ wset
w <- reverse . W.integrate' . W.stack . W.workspace $ scr
Just wr <- [M.lookup w (W.floating wset)]
return (w,scaleRationalRect sr wr)
sr = screenRect . W.screenDetail . W.current $ wset
sr = screenRect . W.screenDetail $ scr
(i1,w1,wr1) <- fs
guard $ case amb of
OnlyLayoutFloatBelow ->