Skip to content

Commit 15f9e73

Browse files
committed
X.L.LayoutHints stop windows from overlapping
This is an improvement on the pull request "Fix render order of LayoutHints and MultiColumns" (#186) and addresses the actual underlying problem. It turned out that windows can sometimes overlap also. This happens when a window is exactly in the center along an axis. There was a special case in the code for this that was not handled properly. This change removes this special case and only shrinks at most in one direction on each axis. This is desirable since it gives us a better probability that the space will actually be used by another window, but is basically unnoticeable by the user. It also reduced the complexity slightly while adding code to actually handle the case would have increased the complexity. I removed the code that places the focused window on top since it is no longer required, but I still preserve the window order of the underlying layout. This interferes even less with the underlying layout. I also removed some code paths that were no longer necessary due to this change and generalized some types so that I could debug the code more easily.
1 parent 12227d3 commit 15f9e73

File tree

2 files changed

+10
-23
lines changed

2 files changed

+10
-23
lines changed

CHANGES.md

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -60,11 +60,10 @@
6060

6161
* `XMonad.Layout.LayoutHints`
6262

63-
Preserve the window order of the modified layout, except for the focused
64-
window that is placed on top. This fixes an issue where the border of the
65-
focused window in certain situations could be rendered below borders of
66-
unfocused windows. It also has a lower risk of interfering with the
67-
modified layout.
63+
- Preserve the window order of the modified layout, this lowers the risk of
64+
interfering with the modified layout.
65+
- Stop windows from overlapping when a window is exactly in the center along
66+
an axis.
6867

6968
* `XMonad.Layout.MultiColumns`
7069

XMonad/Layout/LayoutHints.hs

Lines changed: 6 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -130,7 +130,7 @@ fitting rects = sum $ do
130130
r <- rects
131131
return $ length $ filter (touching r) rects
132132

133-
applyOrder :: Rectangle -> [((Window, Rectangle),t)] -> [[((Window, Rectangle),t)]]
133+
applyOrder :: Rectangle -> [((a, Rectangle),t)] -> [[((a, Rectangle),t)]]
134134
applyOrder root wrs = do
135135
-- perhaps it would just be better to take all permutations, or apply the
136136
-- resizing multiple times
@@ -148,7 +148,7 @@ instance LayoutModifier LayoutHintsToCenter Window where
148148
modifyLayout _ ws@(W.Workspace _ _ (Just st)) r = do
149149
(arrs,ol) <- runLayout ws r
150150
flip (,) ol
151-
. changeOrder (W.focus st : (filter (/= W.focus st) $ map fst arrs))
151+
. changeOrder (map fst arrs)
152152
. head . reverse . sortBy (compare `on` (fitting . map snd))
153153
. map (applyHints st r) . applyOrder r
154154
<$> mapM (\x -> fmap ((,) x) $ mkAdjust (fst x)) arrs
@@ -158,7 +158,7 @@ changeOrder w wr = zip w' $ map (fromJust . flip lookup wr) w'
158158
where w' = filter (`elem` map fst wr) w
159159

160160
-- apply hints to first, grow adjacent windows
161-
applyHints :: W.Stack Window -> Rectangle -> [((Window, Rectangle),(D -> D))] -> [(Window, Rectangle)]
161+
applyHints :: Eq a => W.Stack a -> Rectangle -> [((a, Rectangle),(D -> D))] -> [(a, Rectangle)]
162162
applyHints _ _ [] = []
163163
applyHints s root (((w,lrect@(Rectangle a b c d)),adj):xs) =
164164
let (c',d') = adj (c,d)
@@ -172,21 +172,12 @@ applyHints s root (((w,lrect@(Rectangle a b c d)),adj):xs) =
172172
in (w,redr):next
173173

174174
growOther :: (Position, Position) -> Rectangle -> Set Direction2D -> Rectangle -> Rectangle
175-
growOther ds lrect fds r
176-
| dirs <- flipDir <$> Set.toList (Set.intersection adj fds)
177-
, not $ any (uncurry opposite) $ cross dirs =
178-
foldr (flip grow ds) r dirs
179-
| otherwise = r
175+
growOther ds lrect fds r = foldr (flip grow ds) r $ flipDir <$> Set.toList (Set.intersection adj fds)
180176
where
181177
adj = adjacent lrect r
182-
cross xs = [ (a,b) | a <- xs, b <- xs ]
183-
184178
flipDir :: Direction2D -> Direction2D
185179
flipDir d = case d of { L -> R; U -> D; R -> L; D -> U }
186180

187-
opposite :: Direction2D -> Direction2D -> Bool
188-
opposite x y = flipDir x == y
189-
190181
-- | Leave the opposite edges where they were
191182
grow :: Direction2D -> (Position,Position) -> Rectangle -> Rectangle
192183
grow L (px,_ ) (Rectangle x y w h) = Rectangle (x-px) y (w+fromIntegral px) h
@@ -235,7 +226,6 @@ center (Rectangle x y w h) = (avg x w, avg y h)
235226
centerPlacement :: RealFrac r => Rectangle -> Rectangle -> (r, r)
236227
centerPlacement = centerPlacement' clamp
237228
where clamp n = case signum n of
238-
0 -> 0.5
239229
1 -> 1
240230
_ -> 0
241231

@@ -244,11 +234,9 @@ freeDirs root = Set.fromList . uncurry (++) . (lr *** ud)
244234
. centerPlacement' signum root
245235
where
246236
lr 1 = [L]
247-
lr (-1) = [R]
248-
lr _ = [L,R]
237+
lr _ = [R]
249238
ud 1 = [U]
250-
ud (-1) = [D]
251-
ud _ = [U,D]
239+
ud _ = [D]
252240

253241
centerPlacement' :: (Position -> r) -> Rectangle -> Rectangle -> (r, r)
254242
centerPlacement' cf root assigned

0 commit comments

Comments
 (0)