Skip to content

Commit

Permalink
Merge pull request #186 from ankaan/multicolumns-layouthints-windowor…
Browse files Browse the repository at this point in the history
…derfix

Fix render order of LayoutHints and MultiColumns
  • Loading branch information
pjones authored May 24, 2017
2 parents ade890a + cff3343 commit 12227d3
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 3 deletions.
13 changes: 13 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,19 @@

### Bug Fixes and Minor Changes

* `XMonad.Layout.LayoutHints`

Preserve the window order of the modified layout, except for the focused
window that is placed on top. This fixes an issue where the border of the
focused window in certain situations could be rendered below borders of
unfocused windows. It also has a lower risk of interfering with the
modified layout.

* `XMonad.Layout.MultiColumns`

The focused window is placed above the other windows if they would be made to
overlap due to a layout modifier. (As long as it preserves the window order.)

* `XMonad.Actions.GridSelect`

- The vertical centring of text in each cell has been improved.
Expand Down
6 changes: 6 additions & 0 deletions XMonad/Layout/LayoutHints.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ import Data.Monoid(All(..))

import Data.Set (Set)
import qualified Data.Set as Set
import Data.Maybe(fromJust)

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

changeOrder :: [Window] -> [(Window, Rectangle)] -> [(Window, Rectangle)]
changeOrder w wr = zip w' $ map (fromJust . flip lookup wr) w'
where w' = filter (`elem` map fst wr) w

-- apply hints to first, grow adjacent windows
applyHints :: W.Stack Window -> Rectangle -> [((Window, Rectangle),(D -> D))] -> [(Window, Rectangle)]
applyHints _ _ [] = []
Expand Down
10 changes: 7 additions & 3 deletions XMonad/Layout/MultiColumns.hs
Original file line number Diff line number Diff line change
Expand Up @@ -77,10 +77,9 @@ data MultiCol a = MultiCol
} deriving (Show,Read,Eq)

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

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

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

0 comments on commit 12227d3

Please sign in to comment.