aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorAnders Engstrom <ankaan@gmail.com>2010-03-08 12:43:18 +0100
committerAnders Engstrom <ankaan@gmail.com>2010-03-08 12:43:18 +0100
commit0091a17372b0e639e3f0140b52251a3857e2a219 (patch)
tree60723ab8680d6069ce70649f5e71f28540bef17a /XMonad
parenta40b80d0d810733be0cd7553d11339217e5528ed (diff)
downloadXMonadContrib-0091a17372b0e639e3f0140b52251a3857e2a219.tar.gz
XMonadContrib-0091a17372b0e639e3f0140b52251a3857e2a219.tar.xz
XMonadContrib-0091a17372b0e639e3f0140b52251a3857e2a219.zip
X.L.LayoutScreens split current screen
Ignore-this: e7bd1ef63aee3f736e12e109cabb839 This patch will allow the user to split the currently focused screen instead of all screens together. This is usefull for multiscreen users who have functioning xinerama, but wish to split one of the screens. darcs-hash:20100308114318-8978f-5317cec870f83b4677d101cf490623be156c61a7.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Layout/LayoutScreens.hs17
1 files changed, 16 insertions, 1 deletions
diff --git a/XMonad/Layout/LayoutScreens.hs b/XMonad/Layout/LayoutScreens.hs
index aa8699c..25d44c9 100644
--- a/XMonad/Layout/LayoutScreens.hs
+++ b/XMonad/Layout/LayoutScreens.hs
@@ -16,7 +16,7 @@
module XMonad.Layout.LayoutScreens (
-- * Usage
-- $usage
- layoutScreens, fixedLayout
+ layoutScreens, layoutSplitScreen, fixedLayout
) where
import XMonad
@@ -55,6 +55,7 @@ import qualified XMonad.StackSet as W
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".
+-- | Modify all screens.
layoutScreens :: LayoutClass l Int => Int -> l Int -> X ()
layoutScreens nscr _ | nscr < 1 = trace $ "Can't layoutScreens with only " ++ show nscr ++ " screens."
layoutScreens nscr l =
@@ -67,6 +68,20 @@ layoutScreens nscr l =
, W.visible = zipWith3 W.Screen xs [1 ..] $ map SD ss
, W.hidden = ys }
+-- | Modify current screen.
+layoutSplitScreen :: LayoutClass l Int => Int -> l Int -> X ()
+layoutSplitScreen nscr _ | nscr < 1 = trace $ "Can't layoutSplitScreen with only " ++ show nscr ++ " screens."
+layoutSplitScreen nscr l =
+ do rect <- gets $ screenRect . W.screenDetail . W.current . windowset
+ (wss, _) <- runLayout (W.Workspace "" l (Just $ W.Stack { W.focus=1, W.up=[],W.down=[1..nscr-1] })) rect
+ windows $ \ws@(W.StackSet { W.current = c, W.visible = vs, W.hidden = hs }) ->
+ let (x:xs, ys) = splitAt nscr $ W.workspace c : hs
+ s:ss = map snd wss
+ in ws { W.current = W.Screen x (W.screen c) (SD s)
+ , W.visible = (zipWith3 W.Screen xs [(W.screen c+1) ..] $ map SD ss) ++
+ map (\v -> if W.screen v>W.screen c then v{W.screen = W.screen v + fromIntegral (nscr-1)} else v) vs
+ , W.hidden = ys }
+
getWindowRectangle :: Window -> X Rectangle
getWindowRectangle w = withDisplay $ \d ->
do a <- io $ getWindowAttributes d w