@@ -25,7 +25,7 @@ module XMonad.Layout.LayoutHints
2525 ) where
2626
2727import XMonad (LayoutClass (runLayout ), mkAdjust , Window ,
28- Dimension , Position , Rectangle (Rectangle ), D ,
28+ Dimension , Position , Rectangle (.. ), D ,
2929 X , refresh , Event (.. ), propertyNotify , wM_NORMAL_HINTS ,
3030 (<&&>) , io , applySizeHints , whenX , isClient , withDisplay ,
3131 getWindowAttributes , getWMNormalHints , WindowAttributes (.. ))
@@ -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 )]]
134134applyOrder 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,41 +158,36 @@ 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 )]
162162applyHints _ _ [] = []
163163applyHints s root (((w,lrect@ (Rectangle a b c d)),adj): xs) =
164164 let (c',d') = adj (c,d)
165165 redr = placeRectangle (centerPlacement root lrect :: (Double ,Double )) lrect
166166 $ if isInStack s w then Rectangle a b c' d' else lrect
167167
168- ds = (fromIntegral c - fromIntegral c',fromIntegral d - fromIntegral d')
168+ ds = ( fromIntegral a + fromIntegral c - fromIntegral (rect_x redr) - fromIntegral (rect_width redr)
169+ , fromIntegral b + fromIntegral d - fromIntegral (rect_y redr) - fromIntegral (rect_height redr)
170+ , fromIntegral (rect_x redr) - fromIntegral a
171+ , fromIntegral (rect_y redr) - fromIntegral b
172+ )
169173 growOther' r = growOther ds lrect (freeDirs root lrect) r
170174 mapSnd f = map (first $ second f)
171175 next = applyHints s root $ mapSnd growOther' xs
172176 in (w,redr): next
173177
174- 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
178+ growOther :: (Position , Position , Position , Position ) -> Rectangle -> Set Direction2D -> Rectangle -> Rectangle
179+ growOther ds lrect fds r = foldr (flip grow ds) r $ flipDir <$> Set. toList (Set. intersection adj fds)
180180 where
181181 adj = adjacent lrect r
182- cross xs = [ (a,b) | a <- xs, b <- xs ]
183-
184182 flipDir :: Direction2D -> Direction2D
185183 flipDir d = case d of { L -> R ; U -> D ; R -> L ; D -> U }
186184
187- opposite :: Direction2D -> Direction2D -> Bool
188- opposite x y = flipDir x == y
189-
190185-- | Leave the opposite edges where they were
191- grow :: Direction2D -> (Position ,Position ) -> Rectangle -> Rectangle
192- grow L (px ,_ ) (Rectangle x y w h) = Rectangle (x- px ) y (w+ fromIntegral px ) h
193- grow U (_ ,py ) (Rectangle x y w h) = Rectangle x (y- py ) w (h+ fromIntegral py )
194- grow R (px ,_ ) (Rectangle x y w h) = Rectangle x y (w+ fromIntegral px ) h
195- grow D (_ ,py ) (Rectangle x y w h) = Rectangle x y w (h+ fromIntegral py )
186+ grow :: Direction2D -> (Position ,Position , Position , Position ) -> Rectangle -> Rectangle
187+ grow L (pl ,_ ,_ ,_ ) (Rectangle x y w h) = Rectangle (x- pl ) y (w+ fromIntegral pl ) h
188+ grow U (_ ,pu,_ ,_ ) (Rectangle x y w h) = Rectangle x (y- pu ) w (h+ fromIntegral pu )
189+ grow R (_ ,_ ,pr,_ ) (Rectangle x y w h) = Rectangle x y (w+ fromIntegral pr ) h
190+ grow D (_ ,_ ,_ ,pd ) (Rectangle x y w h) = Rectangle x y w (h+ fromIntegral pd )
196191
197192comparingEdges :: ([Position ] -> [Position ] -> Bool ) -> Rectangle -> Rectangle -> Set Direction2D
198193comparingEdges surrounds r1 r2 = Set. fromList $ map fst $ filter snd [ (\ k -> (dir,k)) $
@@ -208,8 +203,6 @@ comparingEdges surrounds r1 r2 = Set.fromList $ map fst $ filter snd [ (\k -> (d
208203
209204-- | in what direction is the second window from the first that can expand if the
210205-- first is shrunk, assuming that the root window is fully covered:
211- -- one direction for a common edge
212- -- two directions for a common corner
213206adjacent :: Rectangle -> Rectangle -> Set Direction2D
214207adjacent = comparingEdges (all . onClosedInterval)
215208
0 commit comments