aboutsummaryrefslogtreecommitdiffstats
path: root/ThreeColumns.hs
diff options
context:
space:
mode:
authorKai Grossjohann <kai@emptydomain.de>2007-07-21 16:46:54 +0200
committerKai Grossjohann <kai@emptydomain.de>2007-07-21 16:46:54 +0200
commit97b136fcde7597c5ae6c81e405d46cd70d1358ae (patch)
tree3227d30ac633ba355a61e740573c969c0289a89e /ThreeColumns.hs
parent5e0331117db3430beafafabe76f7a96f31ef2bf5 (diff)
downloadXMonadContrib-97b136fcde7597c5ae6c81e405d46cd70d1358ae.tar.gz
XMonadContrib-97b136fcde7597c5ae6c81e405d46cd70d1358ae.tar.xz
XMonadContrib-97b136fcde7597c5ae6c81e405d46cd70d1358ae.zip
Three column layout
This layout is similar to tall, but has three columns. The first column is the master column. darcs-hash:20070721144654-07ca0-eb6800fc98415741739e2a5eca5b0feae7587d05.gz
Diffstat (limited to 'ThreeColumns.hs')
-rw-r--r--ThreeColumns.hs70
1 files changed, 70 insertions, 0 deletions
diff --git a/ThreeColumns.hs b/ThreeColumns.hs
new file mode 100644
index 0000000..6d74cb9
--- /dev/null
+++ b/ThreeColumns.hs
@@ -0,0 +1,70 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonadContrib.ThreeColumns
+-- Copyright : (c) Kai Grossjohann <kai@emptydomain.de>
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : ?
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A layout similar to tall but with three columns.
+--
+-----------------------------------------------------------------------------
+
+module XMonadContrib.ThreeColumns (
+ -- * Usage
+ -- $usage
+ threeCol
+ ) where
+
+import XMonad
+import qualified StackSet as W
+import Operations ( Resize(..), IncMasterN(..), splitVertically, tall )
+
+import Data.Ratio
+
+--import Control.Monad.State
+import Control.Monad.Reader
+
+import Graphics.X11.Xlib
+
+-- $usage
+--
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonadContrib.ThreeColumns
+--
+-- and add, to the list of layouts:
+--
+-- > threeCol
+
+threeCol :: Int -> Rational -> Rational -> Layout a
+threeCol nmaster delta frac =
+ Layout { doLayout = \r -> return . (\x->(x,Nothing)) .
+ ap zip (tile3 frac r nmaster . length) . W.integrate
+ , modifyLayout = \m -> return $ msum [fmap resize (fromMessage m)
+ ,fmap incmastern (fromMessage m)] }
+
+ where resize Shrink = tall nmaster delta (max 0 $ frac-delta)
+ resize Expand = tall nmaster delta (min 1 $ frac+delta)
+ incmastern (IncMasterN d) = tall (max 0 (nmaster+d)) delta frac
+
+-- | tile3. Compute window positions using 3 panes
+tile3 :: Rational -> Rectangle -> Int -> Int -> [Rectangle]
+tile3 f r nmaster n = if n <= nmaster || nmaster == 0
+ then splitVertically n r
+ else splitVertically nmaster r1 ++ splitVertically nmid r2 ++ splitVertically nright r3
+ where (r1, r2, r3) = split3HorizontallyBy f r
+ nslave = (n - nmaster)
+ nmid = floor (nslave % 2)
+ nright = (n - nmaster - nmid)
+
+split3HorizontallyBy :: Rational -> Rectangle -> (Rectangle, Rectangle, Rectangle)
+split3HorizontallyBy f (Rectangle sx sy sw sh) =
+ ( Rectangle sx sy leftw sh
+ , Rectangle (sx + fromIntegral leftw) sy midw sh
+ , Rectangle (sx + fromIntegral leftw + fromIntegral midw) sy rightw sh )
+ where leftw = floor $ fromIntegral sw * (2/3) * f
+ midw = floor ( (sw - leftw) % 2 )
+ rightw = sw - leftw - midw