aboutsummaryrefslogtreecommitdiffstats
path: root/TilePrime.hs
diff options
context:
space:
mode:
authorEric Mertens <emertens@galois.com>2007-10-17 22:51:53 +0200
committerEric Mertens <emertens@galois.com>2007-10-17 22:51:53 +0200
commitca073e31c40e2ef5b1495b4f968574287120a432 (patch)
tree6895c03aa414a0a0e115b62b92d2ac52c4b83aa2 /TilePrime.hs
parentca61dc383dfdb1e92c0fdc33730992e9a5589439 (diff)
downloadXMonadContrib-ca073e31c40e2ef5b1495b4f968574287120a432.tar.gz
XMonadContrib-ca073e31c40e2ef5b1495b4f968574287120a432.tar.xz
XMonadContrib-ca073e31c40e2ef5b1495b4f968574287120a432.zip
TilePrime.hs: Correct behavior when number of windows <
Additionally this patch does various clean-ups that should not affect functionality. darcs-hash:20071017205153-b49f3-d36953f5ba4684e62ac55e2d04ee93a2f1c6ec9a.gz
Diffstat (limited to 'TilePrime.hs')
-rw-r--r--TilePrime.hs32
1 files changed, 17 insertions, 15 deletions
diff --git a/TilePrime.hs b/TilePrime.hs
index d5ce6d9..8b1e693 100644
--- a/TilePrime.hs
+++ b/TilePrime.hs
@@ -21,7 +21,7 @@ module XMonadContrib.TilePrime (
) where
import Control.Monad (mplus)
-import Data.List (genericLength)
+import Data.List (mapAccumL)
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras (getWMNormalHints)
import Operations
@@ -59,30 +59,29 @@ instance LayoutClass TilePrime Window where
resize Expand = c { frac = min 1 $ frac c + delta c }
incmastern (IncMasterN d) = c { nmaster = max 0 $ nmaster c + d }
- doLayout c rect s = do
- let flp = flipped c
+ doLayout TilePrime { frac = f, nmaster = m, flipped = flp } rect s = do
let xs = W.integrate s
hints <- withDisplay $ \ disp -> io (mapM (getWMNormalHints disp) xs)
let xs' = zip xs hints
(leftRect, rightRect)
- | null (drop 1 xs) = (rect, Rectangle 0 0 0 0)
- | flp = splitVerticallyBy (frac c) rect
- | otherwise = splitHorizontallyBy (frac c) rect
- masters = fillWindows flp leftRect (take (nmaster c) xs')
- slaves = fillWindows flp rightRect (drop (nmaster c) xs')
+ | null (drop m xs) = (rect, Rectangle 0 0 0 0)
+ | flp = splitVerticallyBy f rect
+ | otherwise = splitHorizontallyBy f rect
+ (leftXs, rightXs) = splitAt m xs'
+ masters = fillWindows leftRect leftXs
+ slaves = fillWindows rightRect rightXs
return (masters ++ slaves, Nothing)
where
+ fillWindows r xs = snd $ mapAccumL aux (r,n) xs
+ where n = fromIntegral (length xs) :: Rational
- fillWindows _ _ [] = []
- fillWindows flp r ((x,hint):xs) = (x,r') : fillWindows flp rest xs
+ aux (r,n) (x,hint) = ((rest,n-1),(x,r'))
where
- n = 1 + genericLength xs :: Rational
+ (allocated, _) | flp = splitHorizontallyBy (recip n) r
+ | otherwise = splitVerticallyBy (recip n) r
- (alloca, _) | flp = splitHorizontallyBy (recip n) r
- | otherwise = splitVerticallyBy (recip n) r
-
- (w,h) = applySizeHints hint `underBorders` (rect_width alloca, rect_height alloca)
+ (w,h) = applySizeHints hint `underBorders` rect_D allocated
r' = r { rect_width = w, rect_height = h }
@@ -91,6 +90,9 @@ instance LayoutClass TilePrime Window where
| otherwise = r { rect_y = rect_y r + toEnum (fromEnum h)
, rect_height = rect_height r - h }
+rect_D :: Rectangle -> D
+rect_D Rectangle { rect_width = w, rect_height = h } = (w,h)
+
-- | Transform a function on dimensions into one without regard for borders
underBorders :: (D -> D) -> D -> D
underBorders f = adjBorders 1 . f . adjBorders (-1)