aboutsummaryrefslogtreecommitdiffstats
path: root/TwoPane.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-05-17 21:56:18 +0200
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-05-17 21:56:18 +0200
commitb811e91781c67481a3163cb6b6d55996a82eb9d4 (patch)
treed2e801cf9d1bb05528ce64470357f771b53d0f13 /TwoPane.hs
parentb6c8cfcec548a0fc1c473ef8aeb691a1f3322c55 (diff)
downloadXMonadContrib-b811e91781c67481a3163cb6b6d55996a82eb9d4.tar.gz
XMonadContrib-b811e91781c67481a3163cb6b6d55996a82eb9d4.tar.xz
XMonadContrib-b811e91781c67481a3163cb6b6d55996a82eb9d4.zip
Add TwoPane
darcs-hash:20070517195618-a5988-a7bbe8e4fc12bb0f168cf519b0c52c914dda132d.gz
Diffstat (limited to 'TwoPane.hs')
-rw-r--r--TwoPane.hs25
1 files changed, 25 insertions, 0 deletions
diff --git a/TwoPane.hs b/TwoPane.hs
new file mode 100644
index 0000000..1dc4b14
--- /dev/null
+++ b/TwoPane.hs
@@ -0,0 +1,25 @@
+-- A layout that splits the screen horizontally and shows two windows. The
+-- left window is always the master window, and the right is either the
+-- currently focused window or the second window in layout order.
+
+module XMonadContrib.TwoPane where
+
+import XMonad
+import Operations
+import qualified StackSet as W
+import Control.Monad.State (gets)
+
+twoPane :: Rational -> Rational -> Layout
+twoPane delta split = Layout { doLayout = arrange, modifyLayout = message }
+ where
+ arrange rect (w:x:_) = do
+ (Just f) <- gets (W.peek . workspace) -- safe because of pattern match above
+ let (left, right) = splitHorizontallyBy split rect
+ return [(w, left), (if f == w then x else f, right)]
+ -- there are one or zero windows
+ arrange rect ws = return . map (\w -> (w, rect)) $ ws
+
+ message x = case fromMessage x of
+ Just Shrink -> Just (twoPane delta (split - delta))
+ Just Expand -> Just (twoPane delta (split + delta))
+ _ -> Nothing