diff --git a/CHANGES.md b/CHANGES.md index 4aac841d72..342a169582 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -60,11 +60,10 @@ * `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. + - Preserve the window order of the modified layout, this lowers the risk of + interfering with the modified layout. + - Stop windows from overlapping when a window is exactly in the center along + an axis. * `XMonad.Layout.MultiColumns` diff --git a/XMonad/Layout/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs index a5258b13cd..0e34ad8db0 100644 --- a/XMonad/Layout/LayoutHints.hs +++ b/XMonad/Layout/LayoutHints.hs @@ -130,7 +130,7 @@ fitting rects = sum $ do r <- rects return $ length $ filter (touching r) rects -applyOrder :: Rectangle -> [((Window, Rectangle),t)] -> [[((Window, Rectangle),t)]] +applyOrder :: Rectangle -> [((a, Rectangle),t)] -> [[((a, Rectangle),t)]] applyOrder root wrs = do -- perhaps it would just be better to take all permutations, or apply the -- resizing multiple times @@ -148,7 +148,7 @@ 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)) + . changeOrder (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 @@ -158,7 +158,7 @@ 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 :: Eq a => W.Stack a -> Rectangle -> [((a, Rectangle),(D -> D))] -> [(a, Rectangle)] applyHints _ _ [] = [] applyHints s root (((w,lrect@(Rectangle a b c d)),adj):xs) = let (c',d') = adj (c,d) @@ -172,21 +172,12 @@ applyHints s root (((w,lrect@(Rectangle a b c d)),adj):xs) = in (w,redr):next growOther :: (Position, Position) -> Rectangle -> Set Direction2D -> Rectangle -> Rectangle -growOther ds lrect fds r - | dirs <- flipDir <$> Set.toList (Set.intersection adj fds) - , not $ any (uncurry opposite) $ cross dirs = - foldr (flip grow ds) r dirs - | otherwise = r +growOther ds lrect fds r = foldr (flip grow ds) r $ flipDir <$> Set.toList (Set.intersection adj fds) where adj = adjacent lrect r - cross xs = [ (a,b) | a <- xs, b <- xs ] - flipDir :: Direction2D -> Direction2D flipDir d = case d of { L -> R; U -> D; R -> L; D -> U } - opposite :: Direction2D -> Direction2D -> Bool - opposite x y = flipDir x == y - -- | Leave the opposite edges where they were grow :: Direction2D -> (Position,Position) -> Rectangle -> Rectangle 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) centerPlacement :: RealFrac r => Rectangle -> Rectangle -> (r, r) centerPlacement = centerPlacement' clamp where clamp n = case signum n of - 0 -> 0.5 1 -> 1 _ -> 0 @@ -244,11 +234,9 @@ freeDirs root = Set.fromList . uncurry (++) . (lr *** ud) . centerPlacement' signum root where lr 1 = [L] - lr (-1) = [R] - lr _ = [L,R] + lr _ = [R] ud 1 = [U] - ud (-1) = [D] - ud _ = [U,D] + ud _ = [D] centerPlacement' :: (Position -> r) -> Rectangle -> Rectangle -> (r, r) centerPlacement' cf root assigned