aboutsummaryrefslogtreecommitdiffstats
path: root/TwoPane.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-06-19 17:09:28 +0200
committerDavid Roundy <droundy@darcs.net>2007-06-19 17:09:28 +0200
commita48b6a3ed27808bf64d477e3a974a981ade7caba (patch)
tree94032d59192494d247bce9b3fae75bf451403aee /TwoPane.hs
parentafea637c68d30cf3bc5c2dc6db7a3f284e0b3f40 (diff)
downloadXMonadContrib-a48b6a3ed27808bf64d477e3a974a981ade7caba.tar.gz
XMonadContrib-a48b6a3ed27808bf64d477e3a974a981ade7caba.tar.xz
XMonadContrib-a48b6a3ed27808bf64d477e3a974a981ade7caba.zip
clean up TwoPane to work on Stacks as it ought.
darcs-hash:20070619150928-72aca-51028a2488f93cd4274f772206a508e90b608642.gz
Diffstat (limited to '')
-rw-r--r--TwoPane.hs23
1 files changed, 9 insertions, 14 deletions
diff --git a/TwoPane.hs b/TwoPane.hs
index 25bdc48..f5c9c92 100644
--- a/TwoPane.hs
+++ b/TwoPane.hs
@@ -21,10 +21,8 @@ module XMonadContrib.TwoPane (
) where
import XMonad
-import Operations
-import qualified StackSet as W
-import Control.Monad.State (gets)
-
+import Operations ( Resize(..), splitHorizontallyBy )
+import StackSet ( focus, up, down)
-- $usage
--
@@ -37,17 +35,14 @@ import Control.Monad.State (gets)
-- > twoPane defaultDelta (1%2)
twoPane :: Rational -> Rational -> Layout
-twoPane delta split = Layout { doLayout = \r -> arrange r . W.integrate, modifyLayout = message }
+twoPane delta split = Layout { doLayout = \r s -> return $ arrange r s, modifyLayout = message }
where
- arrange rect ws@(w:x:_) = do
- -- TODO this is buggy, it might peek another workspace
- (Just f) <- gets (W.peek . windowset) -- safe because of pattern match above
- let y = if f == w then x else f
- (left, right) = splitHorizontallyBy split rect
- mapM_ hide . filter (\a -> a /= w && a /= y) $ ws
- return [(w, left), (y, right)]
- -- there are one or zero windows
- arrange rect ws = return . map (\w -> (w, rect)) $ ws
+ arrange rect st = case reverse (up st) of
+ (master:_) -> [(master,left),(focus st,right)]
+ [] -> case down st of
+ (next:_) -> [(focus st,left),(next,right)]
+ [] -> [(focus st, rect)]
+ where (left, right) = splitHorizontallyBy split rect
message x = return $ case fromMessage x of
Just Shrink -> Just (twoPane delta (split - delta))