mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-05 06:31:54 -07:00
variable number of windows in master area
This commit is contained in:
11
Config.hs
11
Config.hs
@@ -111,6 +111,10 @@ modMask = mod1Mask
|
|||||||
defaultDelta :: Rational
|
defaultDelta :: Rational
|
||||||
defaultDelta = 3%100
|
defaultDelta = 3%100
|
||||||
|
|
||||||
|
-- The default number of windows in the master area
|
||||||
|
defaultWindowsInMaster :: Int
|
||||||
|
defaultWindowsInMaster = 1
|
||||||
|
|
||||||
-- numlock handling:
|
-- numlock handling:
|
||||||
--
|
--
|
||||||
-- The mask for the numlock key. You may need to change this on some systems.
|
-- The mask for the numlock key. You may need to change this on some systems.
|
||||||
@@ -135,7 +139,9 @@ borderWidth = 1
|
|||||||
|
|
||||||
-- The default set of Layouts:
|
-- The default set of Layouts:
|
||||||
defaultLayouts :: [Layout]
|
defaultLayouts :: [Layout]
|
||||||
defaultLayouts = [ full, tall defaultDelta (1%2), wide defaultDelta (1%2) ]
|
defaultLayouts = [ full,
|
||||||
|
tall defaultWindowsInMaster defaultDelta (1%2),
|
||||||
|
wide defaultWindowsInMaster defaultDelta (1%2) ]
|
||||||
|
|
||||||
--
|
--
|
||||||
-- The key bindings list.
|
-- The key bindings list.
|
||||||
@@ -157,6 +163,9 @@ keys = M.fromList $
|
|||||||
, ((modMask, xK_h ), sendMessage Shrink)
|
, ((modMask, xK_h ), sendMessage Shrink)
|
||||||
, ((modMask, xK_l ), sendMessage Expand)
|
, ((modMask, xK_l ), sendMessage Expand)
|
||||||
|
|
||||||
|
, ((modMask .|. shiftMask, xK_j ), sendMessage (IncMasterN 1))
|
||||||
|
, ((modMask .|. shiftMask, xK_k ), sendMessage (IncMasterN (-1)))
|
||||||
|
|
||||||
, ((modMask .|. shiftMask, xK_c ), kill)
|
, ((modMask .|. shiftMask, xK_c ), kill)
|
||||||
|
|
||||||
, ((modMask .|. shiftMask, xK_q ), io $ exitWith ExitSuccess)
|
, ((modMask .|. shiftMask, xK_q ), io $ exitWith ExitSuccess)
|
||||||
|
@@ -101,19 +101,22 @@ sendMessage a = layout $ \x@(l, ls) -> maybe x (flip (,) ls) (modifyLayout l (So
|
|||||||
data Resize = Shrink | Expand deriving Typeable
|
data Resize = Shrink | Expand deriving Typeable
|
||||||
instance Message Resize
|
instance Message Resize
|
||||||
|
|
||||||
|
data IncMasterN = IncMasterN Int deriving Typeable
|
||||||
|
instance Message IncMasterN
|
||||||
|
|
||||||
full :: Layout
|
full :: Layout
|
||||||
full = Layout { doLayout = \sc ws -> return [ (w,sc) | w <- ws ]
|
full = Layout { doLayout = \sc ws -> return [ (w,sc) | w <- ws ]
|
||||||
, modifyLayout = const Nothing } -- no changes
|
, modifyLayout = const Nothing } -- no changes
|
||||||
|
|
||||||
tall, wide :: Rational -> Rational -> Layout
|
tall, wide :: Int -> Rational -> Rational -> Layout
|
||||||
wide delta frac = mirrorLayout (tall delta frac)
|
wide nmaster delta frac = mirrorLayout (tall nmaster delta frac)
|
||||||
|
|
||||||
tall delta frac = Layout { doLayout = \r w -> return $ zip w $ tile frac r (length w)
|
tall nmaster delta frac = Layout { doLayout = \r w -> return $ zip w $ tile frac r nmaster (length w)
|
||||||
, modifyLayout = fmap handler . fromMessage }
|
, modifyLayout = \m -> fmap resize (fromMessage m) `mplus` fmap incmastern (fromMessage m) }
|
||||||
|
|
||||||
where handler s = tall delta $ (case s of
|
where resize Shrink = tall nmaster delta (frac-delta)
|
||||||
Shrink -> (-)
|
resize Expand = tall nmaster delta (frac+delta)
|
||||||
Expand -> (+)) frac delta
|
incmastern (IncMasterN d) = tall (max 1 (nmaster+d)) delta frac
|
||||||
|
|
||||||
-- | Mirror a rectangle
|
-- | Mirror a rectangle
|
||||||
mirrorRect :: Rectangle -> Rectangle
|
mirrorRect :: Rectangle -> Rectangle
|
||||||
@@ -131,9 +134,9 @@ mirrorLayout (Layout { doLayout = dl, modifyLayout = ml }) =
|
|||||||
-- * no windows overlap
|
-- * no windows overlap
|
||||||
-- * no gaps exist between windows.
|
-- * no gaps exist between windows.
|
||||||
--
|
--
|
||||||
tile :: Rational -> Rectangle -> Int -> [Rectangle]
|
tile :: Rational -> Rectangle -> Int -> Int -> [Rectangle]
|
||||||
tile _ d n | n < 2 = [d]
|
tile _ r nmaster n | n <= nmaster = splitVertically n r
|
||||||
tile f r n = r1 : splitVertically (n-1) r2
|
tile f r nmaster n = splitVertically nmaster r1 ++ splitVertically (n-nmaster) r2
|
||||||
where (r1,r2) = splitHorizontallyBy f r
|
where (r1,r2) = splitHorizontallyBy f r
|
||||||
|
|
||||||
splitVertically, splitHorizontally :: Int -> Rectangle -> [Rectangle]
|
splitVertically, splitHorizontally :: Int -> Rectangle -> [Rectangle]
|
||||||
|
@@ -265,10 +265,10 @@ prop_push_local (x :: T) i = not (member i x) ==> hidden x == hidden (push i x)
|
|||||||
-- some properties for layouts:
|
-- some properties for layouts:
|
||||||
|
|
||||||
-- 1 window should always be tiled fullscreen
|
-- 1 window should always be tiled fullscreen
|
||||||
prop_tile_fullscreen rect = tile pct rect 1 == [rect]
|
prop_tile_fullscreen rect = tile pct rect 1 1 == [rect]
|
||||||
|
|
||||||
-- multiple windows
|
-- multiple windows
|
||||||
prop_tile_non_overlap rect windows = noOverlaps (tile pct rect windows)
|
prop_tile_non_overlap rect windows nmaster = noOverlaps (tile pct rect nmaster windows)
|
||||||
where _ = rect :: Rectangle
|
where _ = rect :: Rectangle
|
||||||
|
|
||||||
pct = 3 % 100
|
pct = 3 % 100
|
||||||
|
Reference in New Issue
Block a user