Skip to content

Commit 12227d3

Browse files
authored
Merge pull request #186 from ankaan/multicolumns-layouthints-windoworderfix
Fix render order of LayoutHints and MultiColumns
2 parents ade890a + cff3343 commit 12227d3

File tree

3 files changed

+26
-3
lines changed

3 files changed

+26
-3
lines changed

CHANGES.md

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,19 @@
5858

5959
### Bug Fixes and Minor Changes
6060

61+
* `XMonad.Layout.LayoutHints`
62+
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.
68+
69+
* `XMonad.Layout.MultiColumns`
70+
71+
The focused window is placed above the other windows if they would be made to
72+
overlap due to a layout modifier. (As long as it preserves the window order.)
73+
6174
* `XMonad.Actions.GridSelect`
6275

6376
- The vertical centring of text in each cell has been improved.

XMonad/Layout/LayoutHints.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ import Data.Monoid(All(..))
4444

4545
import Data.Set (Set)
4646
import qualified Data.Set as Set
47+
import Data.Maybe(fromJust)
4748

4849
-- $usage
4950
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -147,10 +148,15 @@ instance LayoutModifier LayoutHintsToCenter Window where
147148
modifyLayout _ ws@(W.Workspace _ _ (Just st)) r = do
148149
(arrs,ol) <- runLayout ws r
149150
flip (,) ol
151+
. changeOrder (W.focus st : (filter (/= W.focus st) $ map fst arrs))
150152
. head . reverse . sortBy (compare `on` (fitting . map snd))
151153
. map (applyHints st r) . applyOrder r
152154
<$> mapM (\x -> fmap ((,) x) $ mkAdjust (fst x)) arrs
153155

156+
changeOrder :: [Window] -> [(Window, Rectangle)] -> [(Window, Rectangle)]
157+
changeOrder w wr = zip w' $ map (fromJust . flip lookup wr) w'
158+
where w' = filter (`elem` map fst wr) w
159+
154160
-- apply hints to first, grow adjacent windows
155161
applyHints :: W.Stack Window -> Rectangle -> [((Window, Rectangle),(D -> D))] -> [(Window, Rectangle)]
156162
applyHints _ _ [] = []

XMonad/Layout/MultiColumns.hs

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -77,10 +77,9 @@ data MultiCol a = MultiCol
7777
} deriving (Show,Read,Eq)
7878

7979
instance LayoutClass MultiCol a where
80-
doLayout l r s = return (zip w rlist, resl)
80+
doLayout l r s = return (combine s rlist, resl)
8181
where rlist = doL (multiColNWin l') (multiColSize l') r wlen
82-
w = W.integrate s
83-
wlen = length w
82+
wlen = length $ W.integrate s
8483
-- Make sure the list of columns is big enough and update active column
8584
nw = multiColNWin l ++ repeat (multiColDefWin l)
8685
l' = l { multiColNWin = take (max (length $ multiColNWin l) $ getCol (wlen-1) nw + 1) nw
@@ -90,6 +89,7 @@ instance LayoutClass MultiCol a where
9089
resl = if l'==l
9190
then Nothing
9291
else Just l'
92+
combine (W.Stack foc left right) rs = zip (foc : reverse left ++ right) $ raiseFocused (length left) rs
9393
handleMessage l m =
9494
return $ msum [fmap resize (fromMessage m)
9595
,fmap incmastern (fromMessage m)]
@@ -104,6 +104,10 @@ instance LayoutClass MultiCol a where
104104
a = multiColActive l
105105
description _ = "MultiCol"
106106

107+
raiseFocused :: Int -> [a] -> [a]
108+
raiseFocused n xs = actual ++ before ++ after
109+
where (before,rest) = splitAt n xs
110+
(actual,after) = splitAt 1 rest
107111

108112
-- | Get which column a window is in, starting at 0.
109113
getCol :: Int -> [Int] -> Int

0 commit comments

Comments
 (0)